spiros-0.4.2: Spiros Boosalis's Custom Prelude

Safe HaskellNone
LanguageHaskell2010

Prelude.Spiros.Parse

Description

Simple "lookup-based" parsers.

Synopsis

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
Eq ParseError Source # 
Instance details

Defined in Prelude.Spiros.Parse

Ord ParseError Source # 
Instance details

Defined in Prelude.Spiros.Parse

Show ParseError Source #
>>> :set -XOverloadedStrings
>>> Prelude.putStrLn (Prelude.show ("unparseable" :: ParseError))
[ParseError] Can't parse <<< "unparseable" >>>.
Instance details

Defined in Prelude.Spiros.Parse

IsString ParseError Source #

Inject into $sel:stringBeingParsed:ParseError ($sel:thingToParseInto:ParseError stays empty).

Instance details

Defined in Prelude.Spiros.Parse

Generic ParseError Source # 
Instance details

Defined in Prelude.Spiros.Parse

Associated Types

type Rep ParseError :: Type -> Type #

Exception ParseError Source # 
Instance details

Defined in Prelude.Spiros.Parse

NFData ParseError Source # 
Instance details

Defined in Prelude.Spiros.Parse

Methods

rnf :: ParseError -> () #

Hashable ParseError Source # 
Instance details

Defined in Prelude.Spiros.Parse

type Rep ParseError Source # 
Instance details

Defined in Prelude.Spiros.Parse

type Rep ParseError = D1 (MetaData "ParseError" "Prelude.Spiros.Parse" "spiros-0.4.2-AXTfsSIxN6qJkldZU4Dlmr" False) (C1 (MetaCons "ParseError" PrefixI True) (S1 (MetaSel (Just "stringBeingParsed") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 String) :*: S1 (MetaSel (Just "thingToParseInto") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 String)))

data ParseErrorConfig Source #

Instances
Eq ParseErrorConfig Source # 
Instance details

Defined in Prelude.Spiros.Parse

Ord ParseErrorConfig Source # 
Instance details

Defined in Prelude.Spiros.Parse

Show ParseErrorConfig Source # 
Instance details

Defined in Prelude.Spiros.Parse

Generic ParseErrorConfig Source # 
Instance details

Defined in Prelude.Spiros.Parse

Associated Types

type Rep ParseErrorConfig :: Type -> Type #

Default ParseErrorConfig Source #

all False (for portability).

Instance details

Defined in Prelude.Spiros.Parse

NFData ParseErrorConfig Source # 
Instance details

Defined in Prelude.Spiros.Parse

Methods

rnf :: ParseErrorConfig -> () #

Hashable ParseErrorConfig Source # 
Instance details

Defined in Prelude.Spiros.Parse

type Rep ParseErrorConfig Source # 
Instance details

Defined in Prelude.Spiros.Parse

type Rep ParseErrorConfig = D1 (MetaData "ParseErrorConfig" "Prelude.Spiros.Parse" "spiros-0.4.2-AXTfsSIxN6qJkldZU4Dlmr" False) (C1 (MetaCons "ParseErrorConfig" PrefixI True) (S1 (MetaSel (Just "useUnicodeCharacters") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool) :*: S1 (MetaSel (Just "useANSIColorCodes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool)))

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 (doctested)

>>> 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 (Showable) values.

Examples (doctested)

>>> 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 (doctested)

>>> 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 (doctested)

>>> 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 (doctested)

>>> :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" >>>.