| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Text.LambdaOptions.Bool
Synopsis
- data Booly (w :: BoolWord) (l :: BoolLetter) (n :: BoolNumber) (c :: BoolCasing) = Booly {}
- data BoolWord
- data BoolLetter
- data BoolNumber
- data BoolCasing
- class ReadBoolWord (w :: BoolWord) where
- readBoolWord :: BoolCasingVal c => String -> Maybe (Booly w l n c)
- class ReadBoolLetter (l :: BoolLetter) where
- readBoolLetter :: BoolCasingVal c => String -> Maybe (Booly w l n c)
- class ReadBoolNumber (n :: BoolNumber) where
- readBoolNumber :: String -> Maybe (Booly w l n c)
- class BoolCasingVal (c :: BoolCasing) where
- readBooly :: (ReadBoolWord w, ReadBoolLetter l, ReadBoolNumber n, BoolCasingVal c) => String -> Maybe (Booly w l n c)
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
Instances
| Eq (Booly w l n c) Source # | |
| (Typeable w, Typeable l, Typeable n, Typeable c) => Data (Booly w l n c) Source # | |
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 # | |
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 # | |
| Read (Booly w l n c) Source # | |
| Show (Booly w l n c) Source # | |
| (ReadBoolWord w, ReadBoolLetter l, ReadBoolNumber n, BoolCasingVal c) => Parseable (Booly w l n c) Source # | |
Controls word representation for Booly.
Constructors
| DisallowWord | Disallow |
| AllowWord | Allow |
data BoolLetter Source #
Controls letter representation for Booly.
Constructors
| DisallowLetter | Disallow |
| AllowLetter | Allow |
data BoolNumber Source #
Controls number representation for Booly.
Constructors
| DisallowNumber | Disallow number representations. |
| AllowBit | Allow |
| AllowNatural | Allow |
| AllowInteger | Allow any |
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 #
Instances
| ReadBoolWord DisallowWord Source # | |
Defined in Text.LambdaOptions.Bool Methods readBoolWord :: BoolCasingVal c => String -> Maybe (Booly DisallowWord l n c) Source # | |
| ReadBoolWord AllowWord Source # | |
Defined in Text.LambdaOptions.Bool Methods readBoolWord :: BoolCasingVal c => String -> Maybe (Booly AllowWord 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 #
Instances
| ReadBoolLetter DisallowLetter Source # | |
Defined in Text.LambdaOptions.Bool Methods readBoolLetter :: BoolCasingVal c => String -> Maybe (Booly w DisallowLetter n c) Source # | |
| ReadBoolLetter AllowLetter Source # | |
Defined in Text.LambdaOptions.Bool Methods readBoolLetter :: BoolCasingVal c => String -> Maybe (Booly w AllowLetter n c) Source # | |
class ReadBoolNumber (n :: BoolNumber) where Source #
Parsers for the various BoolNumber type constructors.
Instances
| ReadBoolNumber DisallowNumber Source # | |
Defined in Text.LambdaOptions.Bool Methods readBoolNumber :: String -> Maybe (Booly w l DisallowNumber c) Source # | |
| ReadBoolNumber AllowBit Source # | |
Defined in Text.LambdaOptions.Bool | |
| ReadBoolNumber AllowNatural Source # | |
Defined in Text.LambdaOptions.Bool Methods readBoolNumber :: String -> Maybe (Booly w l AllowNatural c) Source # | |
| ReadBoolNumber AllowInteger Source # | |
Defined in Text.LambdaOptions.Bool Methods readBoolNumber :: String -> Maybe (Booly w l AllowInteger c) Source # | |
class BoolCasingVal (c :: BoolCasing) where Source #
Turns a type-level BoolCasing into a value-level one.
Methods
Instances
| BoolCasingVal IgnoreCase Source # | |
Defined in Text.LambdaOptions.Bool Methods | |
| BoolCasingVal LowerAll Source # | |
Defined in Text.LambdaOptions.Bool Methods | |
| BoolCasingVal UpperAll Source # | |
Defined in Text.LambdaOptions.Bool Methods | |
| BoolCasingVal UpperHead Source # | |
Defined in Text.LambdaOptions.Bool Methods | |
| (BoolCasingVal a, BoolCasingVal b) => BoolCasingVal (OrCasing a b) Source # | |
Defined in Text.LambdaOptions.Bool Methods | |
readBooly :: (ReadBoolWord w, ReadBoolLetter l, ReadBoolNumber n, BoolCasingVal c) => String -> Maybe (Booly w l n c) Source #