{-# LANGUAGE DeriveDataTypeable, DeriveGeneric, FlexibleContexts, Safe, TemplateHaskellQuotes #-}
module Dep.Data.ThreeValue (
ThreeValue(DontCare, Zero, One)
, threeValue, toMaybeBool, toChar
, fromBool, fromMaybeBool, toUpper, toLower
, opposite
, ThreeValues
, parseThreeValue, parseThreeValues, parseThreeValues1
) where
import Control.Applicative((<|>))
import Control.DeepSeq(NFData)
import Data.Bool(bool)
import Data.Binary(Binary(put, get), getWord8, putWord8)
import Data.Data(Data)
import Data.Default(Default(def))
import Data.Hashable(Hashable)
import Data.List(find)
import Data.List.NonEmpty(NonEmpty((:|)))
import Dep.Class.Mergeable(Mergeable(merge))
import Dep.Class.Opposite(Opposite(opposite))
import Dep.Class.Renderable(Renderable, CharRenderable(charRenderItem))
import GHC.Generics(Generic)
import Language.Haskell.TH.Lib(conE)
import Language.Haskell.TH.Syntax(Lift(lift, liftTyped), TExp(TExp))
import Test.QuickCheck.Arbitrary(Arbitrary(arbitrary), arbitraryBoundedEnum)
import Text.Parsec(ParsecT, Stream, many)
import Text.Parsec.Char(oneOf)
data ThreeValue
= Zero
| One
| DontCare
deriving (ThreeValue
ThreeValue -> ThreeValue -> Bounded ThreeValue
forall a. a -> a -> Bounded a
maxBound :: ThreeValue
$cmaxBound :: ThreeValue
minBound :: ThreeValue
$cminBound :: ThreeValue
Bounded, Typeable ThreeValue
DataType
Constr
Typeable ThreeValue
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ThreeValue -> c ThreeValue)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ThreeValue)
-> (ThreeValue -> Constr)
-> (ThreeValue -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ThreeValue))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ThreeValue))
-> ((forall b. Data b => b -> b) -> ThreeValue -> ThreeValue)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ThreeValue -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ThreeValue -> r)
-> (forall u. (forall d. Data d => d -> u) -> ThreeValue -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> ThreeValue -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ThreeValue -> m ThreeValue)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ThreeValue -> m ThreeValue)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ThreeValue -> m ThreeValue)
-> Data ThreeValue
ThreeValue -> DataType
ThreeValue -> Constr
(forall b. Data b => b -> b) -> ThreeValue -> ThreeValue
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ThreeValue -> c ThreeValue
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ThreeValue
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> ThreeValue -> u
forall u. (forall d. Data d => d -> u) -> ThreeValue -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ThreeValue -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ThreeValue -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ThreeValue -> m ThreeValue
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ThreeValue -> m ThreeValue
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ThreeValue
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ThreeValue -> c ThreeValue
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ThreeValue)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ThreeValue)
$cDontCare :: Constr
$cOne :: Constr
$cZero :: Constr
$tThreeValue :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> ThreeValue -> m ThreeValue
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ThreeValue -> m ThreeValue
gmapMp :: (forall d. Data d => d -> m d) -> ThreeValue -> m ThreeValue
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ThreeValue -> m ThreeValue
gmapM :: (forall d. Data d => d -> m d) -> ThreeValue -> m ThreeValue
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ThreeValue -> m ThreeValue
gmapQi :: Int -> (forall d. Data d => d -> u) -> ThreeValue -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ThreeValue -> u
gmapQ :: (forall d. Data d => d -> u) -> ThreeValue -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ThreeValue -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ThreeValue -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ThreeValue -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ThreeValue -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ThreeValue -> r
gmapT :: (forall b. Data b => b -> b) -> ThreeValue -> ThreeValue
$cgmapT :: (forall b. Data b => b -> b) -> ThreeValue -> ThreeValue
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ThreeValue)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ThreeValue)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c ThreeValue)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ThreeValue)
dataTypeOf :: ThreeValue -> DataType
$cdataTypeOf :: ThreeValue -> DataType
toConstr :: ThreeValue -> Constr
$ctoConstr :: ThreeValue -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ThreeValue
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ThreeValue
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ThreeValue -> c ThreeValue
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ThreeValue -> c ThreeValue
$cp1Data :: Typeable ThreeValue
Data, Int -> ThreeValue
ThreeValue -> Int
ThreeValue -> [ThreeValue]
ThreeValue -> ThreeValue
ThreeValue -> ThreeValue -> [ThreeValue]
ThreeValue -> ThreeValue -> ThreeValue -> [ThreeValue]
(ThreeValue -> ThreeValue)
-> (ThreeValue -> ThreeValue)
-> (Int -> ThreeValue)
-> (ThreeValue -> Int)
-> (ThreeValue -> [ThreeValue])
-> (ThreeValue -> ThreeValue -> [ThreeValue])
-> (ThreeValue -> ThreeValue -> [ThreeValue])
-> (ThreeValue -> ThreeValue -> ThreeValue -> [ThreeValue])
-> Enum ThreeValue
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: ThreeValue -> ThreeValue -> ThreeValue -> [ThreeValue]
$cenumFromThenTo :: ThreeValue -> ThreeValue -> ThreeValue -> [ThreeValue]
enumFromTo :: ThreeValue -> ThreeValue -> [ThreeValue]
$cenumFromTo :: ThreeValue -> ThreeValue -> [ThreeValue]
enumFromThen :: ThreeValue -> ThreeValue -> [ThreeValue]
$cenumFromThen :: ThreeValue -> ThreeValue -> [ThreeValue]
enumFrom :: ThreeValue -> [ThreeValue]
$cenumFrom :: ThreeValue -> [ThreeValue]
fromEnum :: ThreeValue -> Int
$cfromEnum :: ThreeValue -> Int
toEnum :: Int -> ThreeValue
$ctoEnum :: Int -> ThreeValue
pred :: ThreeValue -> ThreeValue
$cpred :: ThreeValue -> ThreeValue
succ :: ThreeValue -> ThreeValue
$csucc :: ThreeValue -> ThreeValue
Enum, ThreeValue -> ThreeValue -> Bool
(ThreeValue -> ThreeValue -> Bool)
-> (ThreeValue -> ThreeValue -> Bool) -> Eq ThreeValue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ThreeValue -> ThreeValue -> Bool
$c/= :: ThreeValue -> ThreeValue -> Bool
== :: ThreeValue -> ThreeValue -> Bool
$c== :: ThreeValue -> ThreeValue -> Bool
Eq, (forall x. ThreeValue -> Rep ThreeValue x)
-> (forall x. Rep ThreeValue x -> ThreeValue) -> Generic ThreeValue
forall x. Rep ThreeValue x -> ThreeValue
forall x. ThreeValue -> Rep ThreeValue x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ThreeValue x -> ThreeValue
$cfrom :: forall x. ThreeValue -> Rep ThreeValue x
Generic, Eq ThreeValue
Eq ThreeValue
-> (ThreeValue -> ThreeValue -> Ordering)
-> (ThreeValue -> ThreeValue -> Bool)
-> (ThreeValue -> ThreeValue -> Bool)
-> (ThreeValue -> ThreeValue -> Bool)
-> (ThreeValue -> ThreeValue -> Bool)
-> (ThreeValue -> ThreeValue -> ThreeValue)
-> (ThreeValue -> ThreeValue -> ThreeValue)
-> Ord ThreeValue
ThreeValue -> ThreeValue -> Bool
ThreeValue -> ThreeValue -> Ordering
ThreeValue -> ThreeValue -> ThreeValue
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ThreeValue -> ThreeValue -> ThreeValue
$cmin :: ThreeValue -> ThreeValue -> ThreeValue
max :: ThreeValue -> ThreeValue -> ThreeValue
$cmax :: ThreeValue -> ThreeValue -> ThreeValue
>= :: ThreeValue -> ThreeValue -> Bool
$c>= :: ThreeValue -> ThreeValue -> Bool
> :: ThreeValue -> ThreeValue -> Bool
$c> :: ThreeValue -> ThreeValue -> Bool
<= :: ThreeValue -> ThreeValue -> Bool
$c<= :: ThreeValue -> ThreeValue -> Bool
< :: ThreeValue -> ThreeValue -> Bool
$c< :: ThreeValue -> ThreeValue -> Bool
compare :: ThreeValue -> ThreeValue -> Ordering
$ccompare :: ThreeValue -> ThreeValue -> Ordering
$cp1Ord :: Eq ThreeValue
Ord, ReadPrec [ThreeValue]
ReadPrec ThreeValue
Int -> ReadS ThreeValue
ReadS [ThreeValue]
(Int -> ReadS ThreeValue)
-> ReadS [ThreeValue]
-> ReadPrec ThreeValue
-> ReadPrec [ThreeValue]
-> Read ThreeValue
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ThreeValue]
$creadListPrec :: ReadPrec [ThreeValue]
readPrec :: ReadPrec ThreeValue
$creadPrec :: ReadPrec ThreeValue
readList :: ReadS [ThreeValue]
$creadList :: ReadS [ThreeValue]
readsPrec :: Int -> ReadS ThreeValue
$creadsPrec :: Int -> ReadS ThreeValue
Read, Int -> ThreeValue -> ShowS
[ThreeValue] -> ShowS
ThreeValue -> String
(Int -> ThreeValue -> ShowS)
-> (ThreeValue -> String)
-> ([ThreeValue] -> ShowS)
-> Show ThreeValue
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ThreeValue] -> ShowS
$cshowList :: [ThreeValue] -> ShowS
show :: ThreeValue -> String
$cshow :: ThreeValue -> String
showsPrec :: Int -> ThreeValue -> ShowS
$cshowsPrec :: Int -> ThreeValue -> ShowS
Show)
instance Arbitrary ThreeValue where
arbitrary :: Gen ThreeValue
arbitrary = Gen ThreeValue
forall a. (Bounded a, Enum a) => Gen a
arbitraryBoundedEnum
instance CharRenderable ThreeValue where
charRenderItem :: ThreeValue -> Char
charRenderItem = Char -> Char -> Char -> ThreeValue -> Char
forall a. a -> a -> a -> ThreeValue -> a
threeValue Char
'-' Char
'0' Char
'1'
instance Default ThreeValue where
def :: ThreeValue
def = ThreeValue
DontCare
instance Hashable ThreeValue
instance Lift ThreeValue where
liftTyped :: ThreeValue -> Q (TExp ThreeValue)
liftTyped = (Exp -> TExp ThreeValue) -> Q Exp -> Q (TExp ThreeValue)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Exp -> TExp ThreeValue
forall a. Exp -> TExp a
TExp (Q Exp -> Q (TExp ThreeValue))
-> (ThreeValue -> Q Exp) -> ThreeValue -> Q (TExp ThreeValue)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ThreeValue -> Q Exp
forall t. Lift t => t -> Q Exp
lift
lift :: ThreeValue -> Q Exp
lift ThreeValue
Zero = Name -> Q Exp
conE 'Zero
lift ThreeValue
One = Name -> Q Exp
conE 'One
lift ~ThreeValue
DontCare = Name -> Q Exp
conE 'DontCare
instance Mergeable ThreeValue where
merge :: ThreeValue -> ThreeValue -> Maybe ThreeValue
merge ThreeValue
DontCare ThreeValue
x = ThreeValue -> Maybe ThreeValue
forall a. a -> Maybe a
Just ThreeValue
x
merge ThreeValue
x ThreeValue
DontCare = ThreeValue -> Maybe ThreeValue
forall a. a -> Maybe a
Just ThreeValue
x
merge ThreeValue
x ThreeValue
y
| ThreeValue
x ThreeValue -> ThreeValue -> Bool
forall a. Eq a => a -> a -> Bool
== ThreeValue
y = ThreeValue -> Maybe ThreeValue
forall a. a -> Maybe a
Just ThreeValue
x
| Bool
otherwise = Maybe ThreeValue
forall a. Maybe a
Nothing
instance Monoid ThreeValue where
mempty :: ThreeValue
mempty = ThreeValue
DontCare
mconcat :: [ThreeValue] -> ThreeValue
mconcat [ThreeValue]
xs
| Just ThreeValue
x <- (ThreeValue -> Bool) -> [ThreeValue] -> Maybe ThreeValue
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (ThreeValue
DontCare ThreeValue -> ThreeValue -> Bool
forall a. Eq a => a -> a -> Bool
/=) [ThreeValue]
xs = ThreeValue
x
| Bool
otherwise = ThreeValue
DontCare
instance NFData ThreeValue
instance Opposite ThreeValue where
opposite :: ThreeValue -> ThreeValue
opposite ThreeValue
Zero = ThreeValue
One
opposite ThreeValue
One = ThreeValue
Zero
opposite ThreeValue
x = ThreeValue
x
instance Renderable ThreeValue
instance Semigroup ThreeValue where
<> :: ThreeValue -> ThreeValue -> ThreeValue
(<>) ThreeValue
DontCare = ThreeValue -> ThreeValue
forall a. a -> a
id
(<>) ThreeValue
x = ThreeValue -> ThreeValue -> ThreeValue
forall a b. a -> b -> a
const ThreeValue
x
toUpper
:: ThreeValue
-> Bool
toUpper :: ThreeValue -> Bool
toUpper ThreeValue
Zero = Bool
False
toUpper ThreeValue
_ = Bool
True
toLower
:: ThreeValue
-> Bool
toLower :: ThreeValue -> Bool
toLower ThreeValue
One = Bool
True
toLower ThreeValue
_ = Bool
False
threeValue
:: a
-> a
-> a
-> ThreeValue
-> a
threeValue :: a -> a -> a -> ThreeValue -> a
threeValue a
d a
z a
o = ThreeValue -> a
go
where go :: ThreeValue -> a
go ThreeValue
DontCare = a
d
go ThreeValue
Zero = a
z
go ~ThreeValue
One = a
o
fromBool
:: Bool
-> ThreeValue
fromBool :: Bool -> ThreeValue
fromBool = ThreeValue -> ThreeValue -> Bool -> ThreeValue
forall a. a -> a -> Bool -> a
bool ThreeValue
Zero ThreeValue
One
fromMaybeBool
:: Maybe Bool
-> ThreeValue
fromMaybeBool :: Maybe Bool -> ThreeValue
fromMaybeBool = ThreeValue -> (Bool -> ThreeValue) -> Maybe Bool -> ThreeValue
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ThreeValue
DontCare Bool -> ThreeValue
fromBool
toMaybeBool
:: ThreeValue
-> Maybe Bool
toMaybeBool :: ThreeValue -> Maybe Bool
toMaybeBool = Maybe Bool -> Maybe Bool -> Maybe Bool -> ThreeValue -> Maybe Bool
forall a. a -> a -> a -> ThreeValue -> a
threeValue Maybe Bool
forall a. Maybe a
Nothing (Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
False) (Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
True)
toChar
:: ThreeValue
-> Char
toChar :: ThreeValue -> Char
toChar = Char -> Char -> Char -> ThreeValue -> Char
forall a. a -> a -> a -> ThreeValue -> a
threeValue Char
'-' Char
'0' Char
'1'
type ThreeValues = [ThreeValue]
instance Binary ThreeValue where
put :: ThreeValue -> Put
put = Word8 -> Put
putWord8 (Word8 -> Put) -> (ThreeValue -> Word8) -> ThreeValue -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word8) -> (ThreeValue -> Int) -> ThreeValue -> Word8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ThreeValue -> Int
forall a. Enum a => a -> Int
fromEnum
get :: Get ThreeValue
get = Int -> ThreeValue
forall a. Enum a => Int -> a
toEnum (Int -> ThreeValue) -> (Word8 -> Int) -> Word8 -> ThreeValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> ThreeValue) -> Get Word8 -> Get ThreeValue
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word8
getWord8
parseThreeValue :: Stream s m Char => ParsecT s u m ThreeValue
parseThreeValue :: ParsecT s u m ThreeValue
parseThreeValue = (ThreeValue
Zero ThreeValue -> ParsecT s u m Char -> ParsecT s u m ThreeValue
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ String -> ParsecT s u m Char
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
oneOf String
"0fF") ParsecT s u m ThreeValue
-> ParsecT s u m ThreeValue -> ParsecT s u m ThreeValue
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (ThreeValue
One ThreeValue -> ParsecT s u m Char -> ParsecT s u m ThreeValue
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ String -> ParsecT s u m Char
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
oneOf String
"1tT") ParsecT s u m ThreeValue
-> ParsecT s u m ThreeValue -> ParsecT s u m ThreeValue
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (ThreeValue
DontCare ThreeValue -> ParsecT s u m Char -> ParsecT s u m ThreeValue
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ String -> ParsecT s u m Char
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
oneOf String
"-dD")
parseThreeValues :: Stream s m Char => ParsecT s u m ThreeValues
parseThreeValues :: ParsecT s u m [ThreeValue]
parseThreeValues = ParsecT s u m ThreeValue -> ParsecT s u m [ThreeValue]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT s u m ThreeValue
forall s (m :: * -> *) u.
Stream s m Char =>
ParsecT s u m ThreeValue
parseThreeValue
parseThreeValues1 :: Stream s m Char => ParsecT s u m (NonEmpty ThreeValue)
parseThreeValues1 :: ParsecT s u m (NonEmpty ThreeValue)
parseThreeValues1 = ThreeValue -> [ThreeValue] -> NonEmpty ThreeValue
forall a. a -> [a] -> NonEmpty a
(:|) (ThreeValue -> [ThreeValue] -> NonEmpty ThreeValue)
-> ParsecT s u m ThreeValue
-> ParsecT s u m ([ThreeValue] -> NonEmpty ThreeValue)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT s u m ThreeValue
forall s (m :: * -> *) u.
Stream s m Char =>
ParsecT s u m ThreeValue
parseThreeValue ParsecT s u m ([ThreeValue] -> NonEmpty ThreeValue)
-> ParsecT s u m [ThreeValue]
-> ParsecT s u m (NonEmpty ThreeValue)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParsecT s u m [ThreeValue]
forall s (m :: * -> *) u.
Stream s m Char =>
ParsecT s u m [ThreeValue]
parseThreeValues