{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE Safe #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
module Text.LambdaOptions.Parseable.Booly (
Booly(..),
BoolWord(..),
BoolLetter(..),
BoolNumber(..),
BoolCasing(..),
ReadBoolWord(..),
ReadBoolLetter(..),
ReadBoolNumber(..),
BoolCasingVal(..),
readBooly,
) where
import Data.Char
( toLower )
import Data.Data
( Data, Typeable )
import Data.Monoid
( mconcat, Alt(Alt, getAlt) )
import Text.LambdaOptions.Parseable
( Parseable(parse), maybeParse )
import Text.Read
( readMaybe )
data BoolWord
= DisallowWord
| AllowWord
data BoolLetter
= DisallowLetter
| AllowLetter
data BoolNumber
= DisallowNumber
| AllowBit
| AllowNatural
| AllowInteger
data BoolCasing
= IgnoreCase
| OrCasing BoolCasing BoolCasing
| LowerAll
| UpperAll
| UpperHead
data Booly
(w :: BoolWord)
(l :: BoolLetter)
(n :: BoolNumber)
(c :: BoolCasing)
= Booly { unBooly :: Bool }
deriving (Typeable, Data, Show, Read, Eq, Ord)
class BoolCasingVal (c :: BoolCasing) where
boolCasingVal :: BoolCasing
instance
( BoolCasingVal a
, BoolCasingVal b)
=> BoolCasingVal ('OrCasing a b) where
boolCasingVal = OrCasing (boolCasingVal @a) (boolCasingVal @b)
instance BoolCasingVal 'IgnoreCase where
boolCasingVal = IgnoreCase
instance BoolCasingVal 'LowerAll where
boolCasingVal = LowerAll
instance BoolCasingVal 'UpperAll where
boolCasingVal = UpperAll
instance BoolCasingVal 'UpperHead where
boolCasingVal = UpperHead
class ReadBoolWord (w :: BoolWord) where
readBoolWord :: BoolCasingVal c => String -> Maybe (Booly w l n c)
instance ReadBoolWord 'DisallowWord where
readBoolWord _ = Nothing
instance ReadBoolWord 'AllowWord where
readBoolWord
:: forall l n c
. BoolCasingVal c
=> String
-> Maybe (Booly 'AllowWord l n c)
readBoolWord = fmap Booly . readBoolWord' (boolCasingVal @c)
readBoolWord' :: BoolCasing -> String -> Maybe Bool
readBoolWord' casing str = case casing of
IgnoreCase -> case map toLower str of
"true" -> Just True
"false" -> Just False
_ -> Nothing
LowerAll -> case str of
"true" -> Just True
"false" -> Just False
_ -> Nothing
UpperAll -> case str of
"TRUE" -> Just True
"FALSE" -> Just False
_ -> Nothing
UpperHead -> case str of
"True" -> Just True
"False" -> Just False
_ -> Nothing
OrCasing x y -> case readBoolWord' x str of
Just b -> Just b
Nothing -> readBoolWord' y str
class ReadBoolLetter (l :: BoolLetter) where
readBoolLetter :: BoolCasingVal c => String -> Maybe (Booly w l n c)
instance ReadBoolLetter 'DisallowLetter where
readBoolLetter _ = Nothing
instance ReadBoolLetter 'AllowLetter where
readBoolLetter
:: forall w n c
. BoolCasingVal c
=> String
-> Maybe (Booly w 'AllowLetter n c)
readBoolLetter = fmap Booly . readBoolLetter' (boolCasingVal @c)
readBoolLetter' :: BoolCasing -> String -> Maybe Bool
readBoolLetter' casing str = case casing of
IgnoreCase -> case map toLower str of
"t" -> Just True
"f" -> Just False
_ -> Nothing
LowerAll -> case str of
"t" -> Just True
"f" -> Just False
_ -> Nothing
UpperAll -> case str of
"T" -> Just True
"F" -> Just False
_ -> Nothing
UpperHead -> case str of
"T" -> Just True
"F" -> Just False
_ -> Nothing
OrCasing x y -> case readBoolLetter' x str of
Just b -> Just b
Nothing -> readBoolLetter' y str
class ReadBoolNumber (n :: BoolNumber) where
readBoolNumber :: String -> Maybe (Booly w l n c)
instance ReadBoolNumber 'DisallowNumber where
readBoolNumber _ = Nothing
instance ReadBoolNumber 'AllowBit where
readBoolNumber = \case
"0" -> Just $ Booly False
"1" -> Just $ Booly True
_ -> Nothing
instance ReadBoolNumber 'AllowNatural where
readBoolNumber str = case readMaybe str of
Nothing -> Nothing
Just (n :: Integer) -> case n of
0 -> Just $ Booly False
_ -> case n < 0 of
True -> Nothing
False -> Just $ Booly True
instance ReadBoolNumber 'AllowInteger where
readBoolNumber str = case readMaybe str of
Nothing -> Nothing
Just (n :: Integer) -> case n of
0 -> Just $ Booly False
_ -> Just $ Booly True
readBooly
:: (ReadBoolWord w, ReadBoolLetter l, ReadBoolNumber n, BoolCasingVal c)
=> String
-> Maybe (Booly w l n c)
readBooly s = getAlt $ mconcat
[ Alt $ r s
| r <- [readBoolWord, readBoolLetter, readBoolNumber]
]
instance
( ReadBoolWord w
, ReadBoolLetter l
, ReadBoolNumber n
, BoolCasingVal c)
=> Parseable (Booly w l n c) where
parse = maybeParse readBooly