Safe Haskell | None |
---|---|
Language | Haskell2010 |
utility methods for Predicate / methods for displaying the evaluation tree
Synopsis
- data Val a
- _Fail :: forall a. Prism' (Val a) String
- _Val :: forall a a. Prism (Val a) (Val a) a a
- _True :: a ~ Bool => Prism' (Val a) ()
- _False :: a ~ Bool => Prism' (Val a) ()
- _ValEither :: Iso (Val a) (Val b) (Either String a) (Either String b)
- val2P :: Lens' (Val a) ValP
- val2PBool :: a ~ Bool => Lens' (Val a) ValP
- data TT a = TT {}
- ttVal :: Lens (TT a) (TT b) (Val a) (Val b)
- ttValBool :: a ~ Bool => Lens' (TT a) (Val Bool)
- ttString :: forall a. Lens' (TT a) String
- ttForest :: forall a. Lens' (TT a) (Forest PE)
- data PE = PE {}
- peValP :: Lens' PE ValP
- peString :: Lens' PE String
- data ValP
- _FailP :: Prism' ValP String
- _TrueP :: Prism' ValP ()
- _FalseP :: Prism' ValP ()
- _ValP :: Prism' ValP ()
- mkNode :: POpts -> Val a -> String -> [Tree PE] -> TT a
- mkNodeB :: POpts -> Bool -> String -> [Tree PE] -> TT Bool
- mkNodeCopy :: POpts -> TT a -> String -> [Tree PE] -> TT a
- getValAndPE :: TT a -> (Either String a, Tree PE)
- getValLRFromTT :: TT a -> Either String a
- getValueLR :: Inline -> POpts -> String -> TT a -> [Tree PE] -> Either (TT x) a
- data Inline
- prefixNumberToTT :: ((Int, x), TT a) -> TT a
- prefixMsg :: String -> TT a -> TT a
- splitAndAlign :: Show x => POpts -> String -> [((Int, x), TT a)] -> Either (TT w) [(a, (Int, x), TT a)]
- verboseList :: POpts -> TT a -> [Tree PE]
- fixTTBool :: TT Bool -> TT Bool
- topMessage :: TT a -> String
- hasNoTree :: POpts -> Bool
- type POpts = HOpts Identity
- data Debug
- data Disp
- data Color
- isVerbose :: POpts -> Bool
- colorValBool :: POpts -> Val Bool -> String
- colorValP :: Long -> POpts -> ValP -> String
- data Long
- setOtherEffects :: POpts -> String -> String
- type Color1 = OColor "color1" Default Blue Default Red Black Cyan Black Yellow
- type Color2 = OColor "color2" Default Magenta Default Red Black White Black Yellow
- type Color3 = OColor "color3" Default Blue Red Default White Default Black Yellow
- type Color4 = OColor "color4" Default Red Red Default Green Default Black Yellow
- type Color5 = OColor "color5" Blue Default Red Default Cyan Default Yellow Default
- type Other1 = OOther True Yellow Default
- type Other2 = OOther True Default Default
- type OZ = OZ
- type OL = OL
- type OA = OA
- type OAB = OAB
- type OAN = OAN
- type OAV = OAV
- type OANV = OANV
- type OU = OU
- type OUB = OUB
- type OUN = OUN
- type OUV = OUV
- type OUNV = OUNV
- data HOpts f = HOpts {}
- data Opt
- class OptC (k :: Opt)
- type family OptT (xs :: [Opt]) where ...
- getOpt :: forall o. OptC o => POpts
- subopts :: POpts -> POpts
- _DVerbose :: Traversal' POpts ()
- _Debug :: Lens' POpts Debug
- defOpts :: POpts
- show3 :: (Show a1, Show a2) => POpts -> String -> a1 -> a2 -> String
- show3' :: (Show a1, Show a2) => POpts -> String -> a1 -> String -> a2 -> String
- lit3 :: Show a1 => POpts -> String -> a1 -> String -> String -> String
- litVerbose :: POpts -> String -> String -> String
- showVerbose :: Show a => POpts -> String -> a -> String
- showL :: Show a => POpts -> a -> String
- litL :: POpts -> String -> String
- litBL :: POpts -> ByteString -> String
- litBS :: POpts -> ByteString -> String
- prtTreePure :: POpts -> Tree PE -> String
- formatOMsg :: POpts -> String -> String
- prtTree :: Show x => POpts -> TT x -> String
- class Monad m => MonadEval m where
- hh :: TT a -> Tree PE
- chkSize :: Foldable t => POpts -> String -> t a -> [Tree PE] -> Either (TT x) [a]
- chkSize2 :: (Foldable t, Foldable u) => POpts -> String -> t a -> u b -> [Tree PE] -> Either (TT x) ([a], [b])
- badLength :: Foldable t => t a -> Int -> String
Val
contains the typed result from evaluating an expression
Instances
Monad Val # | |
Functor Val # | |
Applicative Val # | |
Foldable Val # | |
Defined in Predicate.Util fold :: Monoid m => Val m -> m # foldMap :: Monoid m => (a -> m) -> Val a -> m # foldr :: (a -> b -> b) -> b -> Val a -> b # foldr' :: (a -> b -> b) -> b -> Val a -> b # foldl :: (b -> a -> b) -> b -> Val a -> b # foldl' :: (b -> a -> b) -> b -> Val a -> b # foldr1 :: (a -> a -> a) -> Val a -> a # foldl1 :: (a -> a -> a) -> Val a -> a # elem :: Eq a => a -> Val a -> Bool # maximum :: Ord a => Val a -> a # | |
Traversable Val # | |
Eq a => Eq (Val a) # | |
Ord a => Ord (Val a) # | |
Read a => Read (Val a) # | |
Show a => Show (Val a) # | |
Generic (Val a) # | |
Semigroup (Val a) # | semigroup instance for
|
Monoid a => Monoid (Val a) # | monoid instance for
|
Generic1 Val # | |
type Rep (Val a) # | |
Defined in Predicate.Util type Rep (Val a) = D1 (MetaData "Val" "Predicate.Util" "predicate-typed-0.7.4.0-AMxhQNc83qND3FQMGxAFxs" False) (C1 (MetaCons "Fail" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 String)) :+: C1 (MetaCons "Val" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a))) | |
type Rep1 Val # | |
Defined in Predicate.Util type Rep1 Val = D1 (MetaData "Val" "Predicate.Util" "predicate-typed-0.7.4.0-AMxhQNc83qND3FQMGxAFxs" False) (C1 (MetaCons "Fail" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 String)) :+: C1 (MetaCons "Val" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) Par1)) |
_True :: a ~ Bool => Prism' (Val a) () #
prism for Val True
>>>
Val True ^? _True
Just ()
>>>
Val False ^? _True
Nothing
_False :: a ~ Bool => Prism' (Val a) () #
prism for Val False
>>>
(_True # ()) ^? _True
Just ()
>>>
(_False # ()) ^? _False
Just ()
>>>
Val False ^? _False
Just ()
>>>
Val True ^? _False
Nothing
_ValEither :: Iso (Val a) (Val b) (Either String a) (Either String b) #
iso for Val
>>>
Val 123 ^. _ValEither
Right 123
>>>
Val 123 & _ValEither %~ right' (show . succ)
Val "124"
>>>
Fail "abc" & _ValEither %~ ((<>"def") +++ (show . succ))
Fail "abcdef"
>>>
Right 1.2 & from _ValEither %~ fmap (show . (*10))
Right "12.0"
>>>
Val True ^. _ValEither
Right True
>>>
Fail "abc" ^. _ValEither
Left "abc"
>>>
Left "abc" ^. from _ValEither
Fail "abc"
>>>
_ValEither # Right False
Val False
>>>
[Just (Val 'x')] ^. mapping (mapping _ValEither)
[Just (Right 'x')]
>>>
Just (Fail "abcd") ^. mapping _ValEither
Just (Left "abcd")
TT typed tree
Read
instance for Val
>>>
reads @(Val Int) "Val 123"
[(Val 123,"")]
>>>
reads @(Val Bool) "Val False abc"
[(Val False," abc")]
>>>
reads @(Val Bool) "Fail \"some error message\""
[(Fail "some error message","")]
>>>
reads @(Val Double) "Fail \"some error message\""
[(Fail "some error message","")]
typed tree holding the results of evaluating a type level expression
Instances
ttVal :: Lens (TT a) (TT b) (Val a) (Val b) #
lens from TT to Val that also keeps ValP in sync with Val
>>>
(TT FalseP (Val True) "xxx" [] & ttVal %~ id) == TT ValP (Val True) "xxx" []
True
>>>
(TT FalseP (Val 123) "xxx" [] & ttVal .~ Fail "aa") == TT (FailP "aa") (Fail "aa") "xxx" []
True
>>>
(TT (FailP "sdf") (Val 123) "xxx" [] & ttVal %~ fmap show) == TT ValP (Val "123") "xxx" []
True
ttValBool :: a ~ Bool => Lens' (TT a) (Val Bool) #
lens that keeps ValP in sync with Val for TT Bool
>>>
(TT ValP (Val True) "xxx" [] & ttValBool %~ \b -> fmap not b) == TT FalseP (Val False) "xxx" []
True
>>>
(TT ValP (Val True) "xxx" [] & ttValBool .~ Fail "abc") == TT (FailP "abc") (Fail "abc") "xxx" []
True
>>>
(TT ValP (Val True) "xxx" [] & ttValBool %~ id) == TT TrueP (Val True) "xxx" []
True
>>>
(TT FalseP (Val True) "xxx" [] & ttValBool %~ id) == TT TrueP (Val True) "xxx" []
True
PE untyped tree
untyped child node for TT
Instances
Eq PE # | |
Read PE # | |
Show PE # | |
Generic PE # | |
Semigroup PE # | |
Monoid PE # | |
type Rep PE # | |
Defined in Predicate.Util type Rep PE = D1 (MetaData "PE" "Predicate.Util" "predicate-typed-0.7.4.0-AMxhQNc83qND3FQMGxAFxs" False) (C1 (MetaCons "PE" PrefixI True) (S1 (MetaSel (Just "_peValP") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ValP) :*: S1 (MetaSel (Just "_peString") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 String))) |
ValP
contains the untyped result from evaluating an expression
Instances
Eq ValP # | |
Ord ValP # | |
Read ValP # | |
Show ValP # | |
Generic ValP # | |
Semigroup ValP # | semigroup for ValP
|
Monoid ValP # | |
type Rep ValP # | |
Defined in Predicate.Util type Rep ValP = D1 (MetaData "ValP" "Predicate.Util" "predicate-typed-0.7.4.0-AMxhQNc83qND3FQMGxAFxs" False) ((C1 (MetaCons "FailP" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 String)) :+: C1 (MetaCons "FalseP" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "TrueP" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ValP" PrefixI False) (U1 :: Type -> Type))) |
create tree
mkNodeB :: POpts -> Bool -> String -> [Tree PE] -> TT Bool #
creates a Boolean node for a predicate type
tree manipulation
getValueLR :: Inline -> POpts -> String -> TT a -> [Tree PE] -> Either (TT x) a #
decorate the tree with more detail when there are errors but inline the error node
prefixNumberToTT :: ((Int, x), TT a) -> TT a #
render numbered tree
splitAndAlign :: Show x => POpts -> String -> [((Int, x), TT a)] -> Either (TT w) [(a, (Int, x), TT a)] #
extract values from the trees or if there are errors return a tree with context
topMessage :: TT a -> String #
extract message part from tree
options
how much detail to show in the expression tree
DZero | one line summary used mainly for testing |
DLite | one line summary with additional context from the top of the evaluation tree |
DNormal | outputs the evaluation tree but skips noisy subtrees |
DVerbose | outputs the entire evaluation tree |
setOtherEffects :: POpts -> String -> String #
render a string for messages using optional color and underline
customizable options for running a typelevel expression
HOpts | |
|
Display options
OEmpty | mempty |
OWidth !Nat | set display width |
OMsg !Symbol | set text to add context to a failure message for refined types |
ORecursion !Nat | set recursion limit eg for regex |
OOther | set effects for messages |
!Opt :# !Opt infixr 6 | mappend |
OColor | set color palette |
OColorOn | turn on colors |
OColorOff | turn off colors |
OAnsi | ansi display |
OUnicode | unicode display |
OZero | debug mode return nothing |
OLite | debug mode return one line |
ONormal | debug mode normal |
OVerbose | debug mode verbose |
OZ | composite: no messages |
OL | composite: lite version |
OA | composite: ansi + colors |
OAB | composite: ansi + colors + background |
OAN | composite: ansi + no colors |
OAV | composite: ansi + colors + verbose |
OANV | composite: ansi + no colors + verbose |
OU | composite: unicode + colors |
OUB | composite: unicode + colors + background |
OUN | composite: unicode + no colors |
OUV | composite: unicode + colors + verbose |
OUNV | composite: unicode + no colors + verbose |
extract options from the typelevel
getOptC
Instances
type family OptT (xs :: [Opt]) where ... #
mconcat Opt
options at the type level
>>>
x = getOpt @(OptT '[ 'OMsg "test", 'ORecursion 123, OU, OL, 'OMsg "field2"])
>>>
oMsg x
["test","field2"]>>>
oRecursion x
123
getOpt :: forall o. OptC o => POpts #
convert typelevel options to POpts
>>>
(oDisp &&& fst . oColor &&& oWidth) (getOpt @(OA ':# OU ':# OA ':# 'OWidth 321 ':# Color4 ':# 'OMsg "test message"))
(Ansi,("color4",321))
>>>
oMsg (getOpt @('OMsg "abc" ':# 'OMsg "def"))
["abc","def"]
>>>
oOther (getOpt @('OOther 'False 'Red 'White ':# 'OOther 'True 'Red 'Black))
(True,Red,Black)
>>>
a = show (getOpt @('OEmpty ':# OU))
>>>
b = show (getOpt @(OU ':# 'OEmpty));
>>>
c = show (getOpt @OU)
>>>
a==b && b==c
True
_DVerbose :: Traversal' POpts () #
traversal for DVerbose
>>>
has _DVerbose (getOpt @OU)
False
>>>
has _DVerbose (getOpt @OUV)
True
formatting functions
litVerbose :: POpts -> String -> String -> String #
more restrictive: only display data in verbose debug mode
litBL :: POpts -> ByteString -> String #
litBS :: POpts -> ByteString -> String #
printing methods
formatOMsg :: POpts -> String -> String #
pretty print a message
MonadEval
class Monad m => MonadEval m where #
a typeclass for choosing which monad to run in
>>>
hasIO @IO
True
>>>
hasIO @Identity
False
runIO :: IO a -> m (Maybe a) #
catchit :: a -> m (Either String a) #
miscellaneous
chkSize :: Foldable t => POpts -> String -> t a -> [Tree PE] -> Either (TT x) [a] #
deal with possible recursion on a list