Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Using the Generic
facility, this module can derive Parser
s automatically.
If you have a simple record:
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE MultiParamTypeClasses #-}
import Env
import Env.Generic
data Hello = Hello
{ name :: String
, count :: Int
, quiet :: Bool
} deriving (Show, Eq, Generic)
instance Record Error Hello
main :: IO ()
main = do
hello <- Env.parse (header "envparse example") record
print (hello :: Hello)
The generic implementation of the record
method translates named fields to field parsers:
% NAME=bob COUNT=3 runhaskell -isrc example/Generic0.hs Hello {name = "bob", count = 3, quiet = False}
If you want to adorn the ugly default help message, augment the fields with descriptions:
{-# LANGUAGE DataKinds #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE TypeOperators #-} import Env import Env.Generic data Hello = Hello { name :: String ? "Whom shoud I greet?" , count :: Int ? "How many times to greet them?" , quiet :: Bool ? "Should I be quiet instead?" } deriving (Show, Eq, Generic) instance Record Error Hello main :: IO () main = do hello <- Env.parse (header "envparse example") record print (hello :: Hello)
% runhaskell -isrc example/Generic1.hs envparse example Available environment variables: COUNT How many times to greet them? NAME Whom shoud I greet? QUIET Should I be quiet instead? Parsing errors: COUNT is unset NAME is unset
Note that this has an effect of wrapping the values in the Help
constructor:
% NAME=bob COUNT=3 QUIET=YES
runhaskell -isrc example/Generic1.hs
Hello {name = Help {unHelp = "bob"}, count = Help {unHelp = 3}, quiet = Help {unHelp = True}}
Documentation
class Record e a where Source #
Given a Record e a
instance, a value of the type a
can be parsed from the environment.
If the parsing fails, a value of an error type e
is returned.
The record
method has a default implementation for any type that has a Generic
instance. If you
need to choose a concrete type for e
, the default error type Error
is a good candidate. Otherwise,
the features you'll use in your parsers will naturally guide GHC to compute the set of required
constraints on e
.
class Field e a where Source #
Given a Field e a
instance, a value of the type a
can be parsed from an environment variable.
If the parsing fails, a value of an error type e
is returned.
The field
method has a default implementation for any type that has a Read
instance. If you
need to choose a concrete type for e
, the default error type Error
is a good candidate. Otherwise,
the features you'll use in your parsers will naturally guide GHC to compute the set of required
constraints on e
.
The annotated instances do not use the default implementation.
field :: String -> Maybe String -> Parser e a Source #
field :: (AsUnset e, AsUnread e, Read a) => String -> Maybe String -> Parser e a Source #
Instances
A field annotation.
If you annotate a record field with a Symbol
literal (that is, a statically known type level string)
the derivation machinery will use the literal in the help message.
Please remember that the values of the annotated fields are wrapped in the Help
constructor.
Instances
(KnownSymbol tag, Field e a) => Field e (a ? tag) Source # | Augments the underlying field parser with the help message. |
Functor ((?) a :: * -> *) Source # | |
Foldable ((?) a :: * -> *) Source # | |
Defined in Env.Generic fold :: Monoid m => (a ? m) -> m # foldMap :: Monoid m => (a0 -> m) -> (a ? a0) -> m # foldr :: (a0 -> b -> b) -> b -> (a ? a0) -> b # foldr' :: (a0 -> b -> b) -> b -> (a ? a0) -> b # foldl :: (b -> a0 -> b) -> b -> (a ? a0) -> b # foldl' :: (b -> a0 -> b) -> b -> (a ? a0) -> b # foldr1 :: (a0 -> a0 -> a0) -> (a ? a0) -> a0 # foldl1 :: (a0 -> a0 -> a0) -> (a ? a0) -> a0 # elem :: Eq a0 => a0 -> (a ? a0) -> Bool # maximum :: Ord a0 => (a ? a0) -> a0 # minimum :: Ord a0 => (a ? a0) -> a0 # | |
Traversable ((?) a :: * -> *) Source # | |
Eq a => Eq (a ? tag) Source # | |
Show a => Show (a ? tag) Source # | |
Representable types of kind *
.
This class is derivable in GHC with the DeriveGeneric
flag on.
A Generic
instance must satisfy the following laws:
from
.to
≡id
to
.from
≡id