Safe Haskell | None |
---|---|
Language | Haskell2010 |
TonaParser
Description
Integrated parser library created for tonatona meta application framework.
It can construct system configuration from environment variables, command line arguments, and any IO values depends on them.
See details for example/Main.hs
.
Synopsis
- data Parser a
- withConfig :: Parser a -> (a -> IO ()) -> IO ()
- optionalVal :: Var a => Description -> Source -> a -> Parser a
- requiredVal :: Var a => Description -> Source -> Parser a
- optionalEnum :: (Var a, Enum a, Bounded a) => Description -> Source -> a -> Parser a
- requiredEnum :: (Var a, Enum a, Bounded a) => Description -> Source -> Parser a
- liftWith :: ((a -> IO ()) -> IO ()) -> Parser a
- data Source
- class Typeable a => Var a where
- data Description
- (.||) :: Source -> Source -> Source
- envVar :: String -> Source
- argLong :: String -> Source
- modify :: ParserMods -> Parser a -> Parser a
- defParserMods :: ParserMods
- data ParserMods
- cmdLineLongMods :: ParserMods -> String -> String
- envVarMods :: ParserMods -> String -> String
Run parser
Main type representing how to construct system configuration.
Construct primitive parsers
optionalVal :: Var a => Description -> Source -> a -> Parser a Source #
A Parser
constructor for optional values.
requiredVal :: Var a => Description -> Source -> Parser a Source #
A Parser
constructor for required values.
optionalEnum :: (Var a, Enum a, Bounded a) => Description -> Source -> a -> Parser a Source #
A Parser
constructor for optional values.
requiredEnum :: (Var a, Enum a, Bounded a) => Description -> Source -> Parser a Source #
A Parser
constructor for required values.
class Typeable a => Var a where #
Class for converting to / from an environment variable
Methods
Convert a value into an environment variable.
fromVar :: String -> Maybe a #
Parse an environment variable.
Instances
Var Bool | |
Var Double | |
Var Int | |
Var Int8 | |
Var Int16 | |
Var Int32 | |
Var Int64 | |
Var Integer | |
Var Word8 | |
Var Word16 | |
Var Word32 | |
Var Word64 | |
Var () | |
Var String | |
Var ByteString | |
Defined in System.Envy | |
Var ByteString | |
Defined in System.Envy | |
Var Day | |
Var UTCTime | |
Var Text | |
Var Text | |
Var a => Var (Maybe a) | |
(Var a, Typeable a) => Var (Identity a) | |
(Var a, Typeable a) => Var (First a) | |
(Var a, Typeable a) => Var (Last a) | |
(Typeable a, Show a, Read a) => Var (ReadShowVar a) | |
Defined in System.Envy |
data Description Source #
Instances
Eq Description Source # | |
Defined in TonaParser | |
Read Description Source # | |
Defined in TonaParser Methods readsPrec :: Int -> ReadS Description # readList :: ReadS [Description] # readPrec :: ReadPrec Description # readListPrec :: ReadPrec [Description] # | |
Show Description Source # | |
Defined in TonaParser Methods showsPrec :: Int -> Description -> ShowS # show :: Description -> String # showList :: [Description] -> ShowS # | |
IsString Description Source # | |
Defined in TonaParser Methods fromString :: String -> Description # |
Modify parsers
data ParserMods Source #
Instances
Semigroup ParserMods Source # | |
Defined in TonaParser Methods (<>) :: ParserMods -> ParserMods -> ParserMods # sconcat :: NonEmpty ParserMods -> ParserMods # stimes :: Integral b => b -> ParserMods -> ParserMods # | |
Monoid ParserMods Source # | |
Defined in TonaParser Methods mempty :: ParserMods # mappend :: ParserMods -> ParserMods -> ParserMods # mconcat :: [ParserMods] -> ParserMods # |
cmdLineLongMods :: ParserMods -> String -> String Source #
envVarMods :: ParserMods -> String -> String Source #