Safe Haskell | None |
---|---|
Language | Haskell2010 |
Simple "lookup-based" parsers.
Synopsis
- type SimpleParse a = forall m. MonadThrow m => SimpleParseM m a
- type SimpleParseM m a = String -> m a
- data ParseError = ParseError {}
- data ParseErrorConfig = ParseErrorConfig {}
- mkBoundedEnumParser :: forall a. forall m. (MonadThrow m, BoundedEnum a, Show a, Typeable a) => SimpleParseM m a
- mkShowParserWith :: forall a. forall m. (MonadThrow m, Show a, Typeable a) => [a] -> SimpleParseM m a
- mkParserFromList :: MonadThrow m => String -> [(a, [String])] -> SimpleParseM m a
- mkParserFromPrinterWith :: MonadThrow m => String -> (a -> String) -> [a] -> SimpleParseM m a
- displayParseError :: ParseError -> String
- displayParseErrorWith :: ParseErrorConfig -> ParseError -> String
Documentation
type SimpleParse a = forall m. MonadThrow m => SimpleParseM m a Source #
Simple parser.
a Type Alias for parsing values from strings:
(readThrow) :: (Read a) => SimpleParse
a
Expansions.
SimpleParse
a ≡ (MonadThrow
m) =>ParseM
m a ≡ (MonadThrow
m) => (String -> m a)
Specializations.
Specializations include:
SimpleParse
a ≡ (String ->Maybe
a)SimpleParse
a ≡ (String -> [a])SimpleParse
a ≡ (String ->Either
SomeException
a)SimpleParse
a ≡ (String ->IO
a)
Usage:
-- an example printer:
parseVerbosity :: SimpleParse
Verbosity
parseVerbosity s = go s
where
go = case
"concise" -> return Concise
"verbose" -> return Verbose
"Concise" -> return Concise
"Verbose" -> return Verbose
"default" -> return def
_ -> throwString s
-- for this type:
data Verbosity = Concise | Verbose
instance Default Verbosity where def = Concise
Also see SimpleParseM
.
type SimpleParseM m a = String -> m a Source #
Simple (monadic) parser.
Usage:
-- an example printer: parseVerbosity :: (MonadThrow
m) =>SimpleParseM
m Verbosity parseVerbosity s = go s where go = case "concise" -> return Concise "verbose" -> return Verbose "Concise" -> return Concise "Verbose" -> return Verbose "default" -> return def _ -> throwString s -- for this type: data Verbosity = Concise | Verbose instance Default Verbosity where def = Concise -- which can be instantiated as: parseVerbosity_Maybe ::SimpleParseM
Maybe
Verbosity parseVerbosity_Maybe = parseVerbosity parseVerbosity_Either ::SimpleParseM
Either
Verbosity parseVerbosity_Either = parseVerbosity parseVerbosity_List ::SimpleParseM
[] Verbosity parseVerbosity_List = parseVerbosity parseVerbosity_IO ::SimpleParseM
IO
Verbosity parseVerbosity_IO = parseVerbosity
data ParseError Source #
Instances
data ParseErrorConfig Source #
Instances
mkBoundedEnumParser :: forall a. forall m. (MonadThrow m, BoundedEnum a, Show a, Typeable a) => SimpleParseM m a Source #
Create a simple parser for a type.
≡mkShowParserWith
(constructors
_)
Examples (doctest
ed)
>>>
parseBool = mkBoundedEnumParser :: String -> Maybe Bool
>>>
parseBool "True"
Just True>>>
parseBool "Abolish ICE"
Nothing
Exceptions
throws ParseError
.
mkShowParserWith :: forall a. forall m. (MonadThrow m, Show a, Typeable a) => [a] -> SimpleParseM m a Source #
Create a simple parser from a list of (Show
able) values.
Examples (doctest
ed)
>>>
parseHaskellBool = mkShowParserWith [False, True]
>>>
parseHaskellBool "True"
True>>>
parseHaskellBool "true"
*** Exception: [ParseError] Can't parse <<< ghc-prim:GHC.Types.(type Bool) >>> from <<< "true" >>>.
Exceptions
throws ParseError
.
mkParserFromList :: MonadThrow m => String -> [(a, [String])] -> SimpleParseM m a Source #
Create a simple parser from a list.
Examples (doctest
ed)
>>>
parseINIBool = mkParserFromList "INI Bool" [ False -: ["false","no","0"], True -: ["true","yes","1"] ]
>>>
parseINIBool "true"
True>>>
parseINIBool "2"
*** Exception: [ParseError] Can't parse <<< INI Bool >>> from <<< "2" >>>.
Strings should be distinct. Within a [String]
, duplicates are ignored.
Across each [(a, [String])]
, all but one are ignored.
Exceptions
throws ParseError
.
Implementation
Internally, builds a Map
.
mkParserFromPrinterWith :: MonadThrow m => String -> (a -> String) -> [a] -> SimpleParseM m a Source #
Create a simple parser from a "printing" function.
Examples (doctest
ed)
>>>
printINIBool = (fmap Data.Char.toLower . show)
>>>
parseINIBool = mkParserFromPrinterWith "INI Bool" printINIBool [False,True]
>>>
parseINIBool "true" :: Maybe Bool
Just True>>>
parseINIBool "2" :: Maybe Bool
Nothing
in (mkParserFromPrinterWith _ p)
, the printing function p
should be injective
(otherwise, some values will be ignored).
e.g. for a type XYZ
:
data XYZ = ... deriving (Show, Enum, Eq, Ord, ...) allXYZs :: [XYZ] allXYZs =constructors
printXYZ :: XYZ -> String printXYZ = show parseXYZ :: (MonadThrow
m) => String -> m XYZ parseXYZ =mkParserFromPrinterWith
XYZ printXYZ allXYZs
Exceptions
throws ParseError
.
displayParseErrorWith :: ParseErrorConfig -> ParseError -> String Source #
Examples (doctest
ed)
>>>
:set -XOverloadedStrings
>>>
Prelude.putStrLn (Control.Exception.displayException ("unparseable" :: ParseError))
[ParseError] Can't parse <<< "unparseable" >>>.
>>>
Prelude.putStrLn (displayParseErrorWith def{ useUnicodeCharacters = True } ParseError{ stringBeingParsed = "2", thingToParseInto = "INI Bool" })
[ParseError] Can't parse « INI Bool » from « "2" ».
>>>
Prelude.putStrLn (displayParseErrorWith def{ useUnicodeCharacters = False } ParseError{ stringBeingParsed = "2", thingToParseInto = "INI Bool" })
[ParseError] Can't parse <<< INI Bool >>> from <<< "2" >>>.