lambda-options-1.0.2.0: Declarative command-line parser using type-driven pattern matching.

Safe HaskellSafe
LanguageHaskell2010

Text.LambdaOptions.Bool

Description

Booly data type used for fine control of Bool parsers.

Synopsis

Documentation

data Booly (w :: BoolWord) (l :: BoolLetter) (n :: BoolNumber) (c :: BoolCasing) Source #

Data type used for parsing Bool values with various schemes.

It can be useful to alias for this type:

type B = Booly 'AllowWord 'DisallowLetter 'DisallowNumber 'LowerAll

pattern B :: Bool -> B
pattern B x = Booly x

b :: B -> Bool
b = unBooly

Constructors

Booly 

Fields

Instances
Eq (Booly w l n c) Source # 
Instance details

Defined in Text.LambdaOptions.Bool

Methods

(==) :: Booly w l n c -> Booly w l n c -> Bool #

(/=) :: Booly w l n c -> Booly w l n c -> Bool #

(Typeable w, Typeable l, Typeable n, Typeable c) => Data (Booly w l n c) Source # 
Instance details

Defined in Text.LambdaOptions.Bool

Methods

gfoldl :: (forall d b. Data d => c0 (d -> b) -> d -> c0 b) -> (forall g. g -> c0 g) -> Booly w l n c -> c0 (Booly w l n c) #

gunfold :: (forall b r. Data b => c0 (b -> r) -> c0 r) -> (forall r. r -> c0 r) -> Constr -> c0 (Booly w l n c) #

toConstr :: Booly w l n c -> Constr #

dataTypeOf :: Booly w l n c -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c0 (t d)) -> Maybe (c0 (Booly w l n c)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c0 (t d e)) -> Maybe (c0 (Booly w l n c)) #

gmapT :: (forall b. Data b => b -> b) -> Booly w l n c -> Booly w l n c #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Booly w l n c -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Booly w l n c -> r #

gmapQ :: (forall d. Data d => d -> u) -> Booly w l n c -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Booly w l n c -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Booly w l n c -> m (Booly w l n c) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Booly w l n c -> m (Booly w l n c) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Booly w l n c -> m (Booly w l n c) #

Ord (Booly w l n c) Source # 
Instance details

Defined in Text.LambdaOptions.Bool

Methods

compare :: Booly w l n c -> Booly w l n c -> Ordering #

(<) :: Booly w l n c -> Booly w l n c -> Bool #

(<=) :: Booly w l n c -> Booly w l n c -> Bool #

(>) :: Booly w l n c -> Booly w l n c -> Bool #

(>=) :: Booly w l n c -> Booly w l n c -> Bool #

max :: Booly w l n c -> Booly w l n c -> Booly w l n c #

min :: Booly w l n c -> Booly w l n c -> Booly w l n c #

Read (Booly w l n c) Source # 
Instance details

Defined in Text.LambdaOptions.Bool

Methods

readsPrec :: Int -> ReadS (Booly w l n c) #

readList :: ReadS [Booly w l n c] #

readPrec :: ReadPrec (Booly w l n c) #

readListPrec :: ReadPrec [Booly w l n c] #

Show (Booly w l n c) Source # 
Instance details

Defined in Text.LambdaOptions.Bool

Methods

showsPrec :: Int -> Booly w l n c -> ShowS #

show :: Booly w l n c -> String #

showList :: [Booly w l n c] -> ShowS #

(ReadBoolWord w, ReadBoolLetter l, ReadBoolNumber n, BoolCasingVal c) => Parseable (Booly w l n c) Source #

Parses a Booly using readBooly.

Instance details

Defined in Text.LambdaOptions.Bool

Methods

parse :: [String] -> (Maybe (Booly w l n c), Int) Source #

data BoolWord Source #

Controls word representation for Booly.

Constructors

DisallowWord

Disallow "true" and "false" word representations.

AllowWord

Allow "true" and "false" word representations.

data BoolLetter Source #

Controls letter representation for Booly.

Constructors

DisallowLetter

Disallow "t" and "f" letter representations.

AllowLetter

Allow "t" and "f" letter representations.

data BoolNumber Source #

Controls number representation for Booly.

Constructors

DisallowNumber

Disallow number representations.

AllowBit

Allow 0 and 1 number representations.

AllowNatural

Allow N >= 0 integer representations. 0 maps to False. N > 0 maps to True.

AllowInteger

Allow any N integer representation. 0 maps to False. N /= 0 maps to True.

data BoolCasing Source #

Controls required casing for Booly.

Constructors

IgnoreCase

Casing is completely ignored.

OrCasing BoolCasing BoolCasing

Either casing satisfies a parse.

LowerAll

Fully lowercase is required.

UpperAll

Fully uppercase is required.

UpperHead

The first letter must be uppercase. The rest must be lowercase.

class ReadBoolWord (w :: BoolWord) where Source #

Parsers for the various BoolWord type constructors.

Methods

readBoolWord :: BoolCasingVal c => String -> Maybe (Booly w l n c) Source #

class ReadBoolLetter (l :: BoolLetter) where Source #

Parsers for the various BoolLetter type constructors.

Methods

readBoolLetter :: BoolCasingVal c => String -> Maybe (Booly w l n c) Source #

class ReadBoolNumber (n :: BoolNumber) where Source #

Parsers for the various BoolNumber type constructors.

Methods

readBoolNumber :: String -> Maybe (Booly w l n c) Source #

class BoolCasingVal (c :: BoolCasing) where Source #

Turns a type-level BoolCasing into a value-level one.