Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
29 changes: 23 additions & 6 deletions src/Text/Parsec/ByteString.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE Safe #-}

-----------------------------------------------------------------------------
Expand All @@ -15,17 +16,36 @@
-----------------------------------------------------------------------------

module Text.Parsec.ByteString
( Parser, GenParser, parseFromFile
( Parser, ParserU, GenParser, parseFromFile, parseFromFile'
) where

#if __GLASGOW_HASKELL__ < 710
import Data.Functor((<$>))
#endif

import Text.Parsec.Error
import Text.Parsec.Prim

import qualified Data.ByteString.Char8 as C

type Parser = Parsec C.ByteString ()
type ParserU u = Parsec C.ByteString u
type Parser = ParserU ()
type GenParser t st = Parsec C.ByteString st


-- | @parseFromFile' p u filePath@ runs a strict bytestring parser @p@ on the
-- input read from @filePath@ using 'ByteString.Char8.readFile' with start state @u@.
-- Returns either a 'ParseError' ('Left') or a value of type @a@ ('Right').
--
-- > main = do{ result <- parseFromFile' numbers () "digits.txt"
-- > ; case result of
-- > Left err -> print err
-- > Right xs -> print (sum xs)
-- > }
parseFromFile' :: ParserU u a -> u -> FilePath -> IO (Either ParseError a)
parseFromFile' p u fname = runP p u fname <$> C.readFile fname


-- | @parseFromFile p filePath@ runs a strict bytestring parser @p@ on the
-- input read from @filePath@ using 'ByteString.Char8.readFile'. Returns either a 'ParseError'
-- ('Left') or a value of type @a@ ('Right').
Expand All @@ -35,8 +55,5 @@ type GenParser t st = Parsec C.ByteString st
-- > Left err -> print err
-- > Right xs -> print (sum xs)
-- > }

parseFromFile :: Parser a -> FilePath -> IO (Either ParseError a)
parseFromFile p fname
= do input <- C.readFile fname
return (runP p () fname input)
parseFromFile = (`parseFromFile'` ())
31 changes: 24 additions & 7 deletions src/Text/Parsec/ByteString/Lazy.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE Safe #-}

-----------------------------------------------------------------------------
Expand All @@ -15,18 +16,37 @@
-----------------------------------------------------------------------------

module Text.Parsec.ByteString.Lazy
( Parser, GenParser, parseFromFile
( Parser, ParserU, GenParser, parseFromFile, parseFromFile'
) where

#if __GLASGOW_HASKELL__ < 710
import Data.Functor((<$>))
#endif

import Text.Parsec.Error
import Text.Parsec.Prim

import qualified Data.ByteString.Lazy.Char8 as C

type Parser = Parsec C.ByteString ()
type ParserU u = Parsec C.ByteString u
type Parser = ParserU ()
type GenParser t st = Parsec C.ByteString st

-- | @parseFromFile p filePath@ runs a lazy bytestring parser @p@ on the

-- | @parseFromFile' p u filePath@ runs a strict bytestring parser @p@ on the
-- input read from @filePath@ using 'ByteString.Lazy.Char8.readFile' with start state @u@.
-- Returns either a 'ParseError' ('Left') or a value of type @a@ ('Right').
--
-- > main = do{ result <- parseFromFile' numbers () "digits.txt"
-- > ; case result of
-- > Left err -> print err
-- > Right xs -> print (sum xs)
-- > }
parseFromFile' :: ParserU u a -> u -> FilePath -> IO (Either ParseError a)
parseFromFile' p u fname = runP p u fname <$> C.readFile fname


-- | @parseFromFile p filePath@ runs a strict bytestring parser @p@ on the
-- input read from @filePath@ using 'ByteString.Lazy.Char8.readFile'. Returns either a 'ParseError'
-- ('Left') or a value of type @a@ ('Right').
--
Expand All @@ -35,8 +55,5 @@ type GenParser t st = Parsec C.ByteString st
-- > Left err -> print err
-- > Right xs -> print (sum xs)
-- > }

parseFromFile :: Parser a -> FilePath -> IO (Either ParseError a)
parseFromFile p fname
= do input <- C.readFile fname
return (runP p () fname input)
parseFromFile = (`parseFromFile'` ())
30 changes: 24 additions & 6 deletions src/Text/Parsec/String.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE Safe #-}

-----------------------------------------------------------------------------
Expand All @@ -15,16 +16,35 @@
-----------------------------------------------------------------------------

module Text.Parsec.String
( Parser, GenParser, parseFromFile
( Parser, ParserU, GenParser, parseFromFile, parseFromFile'
) where

#if __GLASGOW_HASKELL__ < 710
import Data.Functor((<$>))
#endif

import Text.Parsec.Error
import Text.Parsec.Prim

type Parser = Parsec String ()
type ParserU u = Parsec String u
type Parser = ParserU ()
type GenParser tok st = Parsec [tok] st

-- | @parseFromFile p filePath@ runs a string parser @p@ on the

-- | @parseFromFile' p u filePath@ runs a strict bytestring parser @p@ on the
-- input read from @filePath@ using 'Prelude.readFile' with start state @u@.
-- Returns either a 'ParseError' ('Left') or a value of type @a@ ('Right').
--
-- > main = do{ result <- parseFromFile' numbers () "digits.txt"
-- > ; case result of
-- > Left err -> print err
-- > Right xs -> print (sum xs)
-- > }
parseFromFile' :: ParserU u a -> u -> FilePath -> IO (Either ParseError a)
parseFromFile' p u fname = runP p u fname <$> readFile fname


-- | @parseFromFile p filePath@ runs a strict bytestring parser @p@ on the
-- input read from @filePath@ using 'Prelude.readFile'. Returns either a 'ParseError'
-- ('Left') or a value of type @a@ ('Right').
--
Expand All @@ -34,6 +54,4 @@ type GenParser tok st = Parsec [tok] st
-- > Right xs -> print (sum xs)
-- > }
parseFromFile :: Parser a -> FilePath -> IO (Either ParseError a)
parseFromFile p fname
= do input <- readFile fname
return (runP p () fname input)
parseFromFile = (`parseFromFile'` ())
33 changes: 24 additions & 9 deletions src/Text/Parsec/Text.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE Safe #-}

-----------------------------------------------------------------------------
Expand All @@ -15,18 +16,37 @@
-----------------------------------------------------------------------------

module Text.Parsec.Text
( Parser, GenParser, parseFromFile
( Parser, ParserU, GenParser, parseFromFile, parseFromFile'
) where

#if __GLASGOW_HASKELL__ < 710
import Data.Functor((<$>))
#endif

import qualified Data.Text as Text
import Text.Parsec.Prim
import Text.Parsec.Error
import Data.Text.IO as T

type Parser = Parsec Text.Text ()
type ParserU u = Parsec Text.Text u
type Parser = ParserU ()
type GenParser st = Parsec Text.Text st

-- | @parseFromFile p filePath@ runs a strict text parser @p@ on the

-- | @parseFromFile' p u filePath@ runs a strict bytestring parser @p@ on the
-- input read from @filePath@ using 'Data.Text.IO.readFile' with start state @u@.
-- Returns either a 'ParseError' ('Left') or a value of type @a@ ('Right').
--
-- > main = do{ result <- parseFromFile' numbers () "digits.txt"
-- > ; case result of
-- > Left err -> print err
-- > Right xs -> print (sum xs)
-- > }
parseFromFile' :: ParserU u a -> u -> FilePath -> IO (Either ParseError a)
parseFromFile' p u fname = runP p u fname <$> T.readFile fname


-- | @parseFromFile p filePath@ runs a strict bytestring parser @p@ on the
-- input read from @filePath@ using 'Data.Text.IO.readFile'. Returns either a 'ParseError'
-- ('Left') or a value of type @a@ ('Right').
--
Expand All @@ -35,10 +55,5 @@ type GenParser st = Parsec Text.Text st
-- > Left err -> print err
-- > Right xs -> print (sum xs)
-- > }
--
-- @since 3.1.14.0

parseFromFile :: Parser a -> FilePath -> IO (Either ParseError a)
parseFromFile p fname
= do input <- T.readFile fname
return (runP p () fname input)
parseFromFile = (`parseFromFile'` ())
33 changes: 24 additions & 9 deletions src/Text/Parsec/Text/Lazy.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE Safe #-}

-----------------------------------------------------------------------------
Expand All @@ -15,18 +16,37 @@
-----------------------------------------------------------------------------

module Text.Parsec.Text.Lazy
( Parser, GenParser, parseFromFile
( Parser, ParserU, GenParser, parseFromFile, parseFromFile'
) where

#if __GLASGOW_HASKELL__ < 710
import Data.Functor((<$>))
#endif

import qualified Data.Text.Lazy as Text
import Text.Parsec.Prim
import Text.Parsec.Error
import Data.Text.Lazy.IO as TL

type Parser = Parsec Text.Text ()
type ParserU u = Parsec Text.Text u
type Parser = ParserU ()
type GenParser st = Parsec Text.Text st

-- | @parseFromFile p filePath@ runs a strict text parser @p@ on the

-- | @parseFromFile' p u filePath@ runs a strict bytestring parser @p@ on the
-- input read from @filePath@ using 'Data.Text.Lazy.IO.readFile' with start state @u@.
-- Returns either a 'ParseError' ('Left') or a value of type @a@ ('Right').
--
-- > main = do{ result <- parseFromFile' numbers () "digits.txt"
-- > ; case result of
-- > Left err -> print err
-- > Right xs -> print (sum xs)
-- > }
parseFromFile' :: ParserU u a -> u -> FilePath -> IO (Either ParseError a)
parseFromFile' p u fname = runP p u fname <$> TL.readFile fname


-- | @parseFromFile p filePath@ runs a strict bytestring parser @p@ on the
-- input read from @filePath@ using 'Data.Text.Lazy.IO.readFile'. Returns either a 'ParseError'
-- ('Left') or a value of type @a@ ('Right').
--
Expand All @@ -35,10 +55,5 @@ type GenParser st = Parsec Text.Text st
-- > Left err -> print err
-- > Right xs -> print (sum xs)
-- > }
--
-- @since 3.1.14.0

parseFromFile :: Parser a -> FilePath -> IO (Either ParseError a)
parseFromFile p fname
= do input <- TL.readFile fname
return (runP p () fname input)
parseFromFile = (`parseFromFile'` ())