module Text.Parsec.Utils ( -- * Main parse functions parseString, parseFile, -- * Number parsers nat, int, float, -- * Parser operators -- |Mostly synonyms for the operators from "Control.Applicative", -- but left-associative and with different priorities for easier -- composition with fewer parentheses. (=:), (+:), (-:), (.:), ($:), (<:) ) where import Control.Applicative hiding (many) import Text.Parsec import Text.Parsec.String infixl 4 +:, -: infixl 5 .:, <:, =: infixl 3 $: -- |Parse a string. Parse errors are reported through the 'error' function. -- -- >>> parseString int "123" == 123 -- True parseString :: Parser a -> String -> a parseString p = either (error . show) id . parse p "" -- |Parse the contents of a file. Parse errors are reported -- through the 'error' function. parseFile :: Parser a -> FilePath -> IO a parseFile p f = parseString p .: readFile f -- |Parse a natural (i.e. non-negative) number -- -- >>> parseString nat "123" == 123 -- True nat :: Integral a => Parser a nat = fromInteger . read .: many1 digit -- |Parse an integer (or any instance of Integral) -- -- >>> parseString int "-123" == -123 -- True int :: Integral a => Parser a int = (*) .: option 1 (-1 =: char '-') +: nat -- |Parse a floating point number -- -- >>> parseString float "-12.34" == -12.34 -- True float :: (Read a, RealFloat a) => Parser a float = read $: (++) .: show .: int +: option "" ((:) .: char '.' +: show .: nat) -- |Synonym for '<$' -- -- >>> parseString (2 =: char 'a') "a" == 2 -- True (=:) :: Functor f => b -> f a -> f b (=:) = (<$) -- |Synonym for '<*>' -- -- >>> parseString ((,) .: char 'a' +: int) "a1" == ('a', 1) -- True (+:) :: Applicative f => f (a -> b) -> f a -> f b (+:) = (<*>) -- |Synonym for '<*' -- Allows chaining parsers without the need for parentheses -- -- >>> parseString ((+) .: int -: space +: int) "1 2" == 3 -- True (-:) :: Applicative f => f a -> f b -> f a (-:) = (<*) -- |Synonym for '<$>' -- -- >>> parseString ((,) .: char 'a' +: int) "a1" == ('a', 1) -- True (.:) :: Functor f => (a -> b) -> f a -> f b (.:) = (<$>) -- |Synonym for '<*' -- Identical to '.:' but with lower precedence. -- -- >>> parseString (show $: (+) .: int -: space +: int) "1 2" == "3" -- True ($:) :: Functor f => (a -> b) -> f a -> f b ($:) = (<$>) -- |Apply a parser that returns a 'String' and parse the result with -- another parser. -- -- >>> parseString (int <: manyTill anyChar (char '9')) "129" == 12 -- True (<:) :: Parser t -> Parser String -> Parser t a <: b = either (fail . show) return . parse a "" =<< b