| Safe Haskell | None |
|---|---|
| Language | GHC2021 |
Cauldron.Args
Synopsis
- data Args a
- arg :: Typeable a => Args a
- runArgs :: (forall b. Typeable b => Maybe b) -> Args a -> a
- getArgsReps :: Args a -> Set TypeRep
- contramapArgs :: (forall t. Typeable t => Maybe t -> Maybe t) -> Args a -> Args a
- class Wireable curried tip | curried -> tip where
- newtype LazilyReadBeanMissing = LazilyReadBeanMissing TypeRep
- data Regs a
- foretellReg :: (Typeable a, Monoid a) => Args (a -> Regs ())
- runRegs :: Set SomeMonoidTypeRep -> Regs a -> (Beans, a)
- getRegsReps :: Args a -> Set SomeMonoidTypeRep
- class Registrable nested tip | nested -> tip where
- data Beans
- taste :: Typeable bean => Beans -> Maybe bean
- fromDynList :: [Dynamic] -> Beans
- data SomeMonoidTypeRep
Arguments
An Applicative that knows how to construct values by searching in a
Beans map, and keeps track of the types that will be searched in the
Beans map.
arg :: Typeable a => Args a Source #
Look for a type in the Beans map and return its corresponding value.
>>>:{fun1 :: Bool -> Int fun1 _ = 5 w1 :: Args Int w1 = fun1 <$> arg fun2 :: String -> Bool -> Int fun2 _ _ = 5 w2 :: Args Int w2 = fun2 <$> arg <*> arg :}
runArgs :: (forall b. Typeable b => Maybe b) -> Args a -> a Source #
Here the Beans map is not passed directly, instead, we pass a
function-like value that, given a type, will return a value of that type or
Nothing. Such function is usually constructed using taste on some Beans
map.
>>>:{let beans = fromDynList [toDyn @Int 5] in runArgs (taste beans) (arg @Int) :} 5
See also LazilyReadBeanMissing.
getArgsReps :: Args a -> Set TypeRep Source #
Inspect ahead of time what types will be searched in the Beans map.
>>>:{let beans = fromDynList [toDyn @Int 5, toDyn False] args = (,) <$> arg @Int <*> arg @Bool in (getArgsReps args, runArgs (taste beans) args) :} (fromList [Int,Bool],(5,False))
contramapArgs :: (forall t. Typeable t => Maybe t -> Maybe t) -> Args a -> Args a Source #
Tweak the look-by-type function that is eventually passed to runArgs.
Unlikely to be commonly useful.
>>>:{let tweak :: forall t. Typeable t => Maybe t -> Maybe t tweak _ = case Type.Reflection.typeRep @t `Type.Reflection.eqTypeRep` Type.Reflection.typeRep @Int of Just HRefl -> Just 5 Nothing -> Nothing in runArgs (taste Cauldron.Beans.empty) $ contramapArgs tweak $ arg @Int :} 5
Reducing arg boilerplate with wire
class Wireable curried tip | curried -> tip where Source #
Convenience typeclass for wiring all the arguments of a curried function in one go.
Methods
wire :: curried -> Args tip Source #
Takes a curried function and reads all of its arguments by type using
arg, returning an Args for the final result value of the function.
>>>:{fun0 :: Int fun0 = 5 w0 :: Args Int w0 = wire fun0 fun1 :: Bool -> Int fun1 _ = 5 w1 :: Args Int w1 = wire fun1 fun2 :: String -> Bool -> Int fun2 _ _ = 5 w2 :: Args Int w2 = wire fun2 :}
When a bean is missing
newtype LazilyReadBeanMissing Source #
Imprecise exception that might lie hidden in the result of runArgs, if
the Beans map lacks a value for some type demanded by the Args.
Why not make runArgs return a Maybe instead of throwing an imprecise
exception? The answer is that, for my purposes, using Maybe or Either
caused undesirable strictness when doing weird things like reading values
"from the future".
>>>:{runArgs (taste Cauldron.Beans.empty) (arg @Int) :} *** Exception: LazilyReadBeanMissing Int
If more safety is needed, one can perform additional preliminary checks with
the help of getArgsReps.
Constructors
| LazilyReadBeanMissing TypeRep |
Instances
| Exception LazilyReadBeanMissing Source # | |
Defined in Cauldron.Args | |
| Show LazilyReadBeanMissing Source # | |
Defined in Cauldron.Args Methods showsPrec :: Int -> LazilyReadBeanMissing -> ShowS # show :: LazilyReadBeanMissing -> String # showList :: [LazilyReadBeanMissing] -> ShowS # | |
Registrations
The Args applicative has an additional feature: it lets you "register"
ahead of time the types of some values that might be included in the result
of the Args, but without being reflected in the result type. It's not
mandatory that these values must be ultimately produced, however.
Here's an example. We have an Args value that returns a Regs. While
constructing the Args value, we register the Sum Int and All types
using foretellReg, which also gives us the means of later writing into the
Regs. By using getRegsReps, we can inspect the TypeReps of the types we
registered without having to run the Args,
>>>:{fun2 :: String -> Bool -> Int fun2 _ _ = 5 args :: Args (Regs Int) args = do -- Using ApplicativeDo r <- fun2 <$> arg <*> arg -- could also have used 'wire' tell1 <- foretellReg @(Sum Int) tell2 <- foretellReg @All pure $ do tell1 (Sum 11) tell2 (All False) pure r :}
>>>:{let reps = getRegsReps args in ( reps == Data.Set.fromList [ SomeMonoidTypeRep $ Type.Reflection.typeRep @(Sum Int) , SomeMonoidTypeRep $ Type.Reflection.typeRep @All] , args & runArgs (taste $ fromDynList [toDyn @String "foo", toDyn False]) & runRegs reps & \(beans,_) -> (taste @(Sum Int) beans, taste @All beans) ) :} (True,(Just (Sum {getSum = 11}),Just (All {getAll = False})))
A writer-like monad for collecting the values of registrations.
runRegs :: Set SomeMonoidTypeRep -> Regs a -> (Beans, a) Source #
Extract the Beans map of registrations, along with the main result value.
The Set of SomeMonoidTypeReps will typically come from getRegsReps.
Only values for TypeReps present in the set will be returned. There will be
values for all TypeReps present in the set (some of them might be the
mempty for that type).
getRegsReps :: Args a -> Set SomeMonoidTypeRep Source #
Inspect ahead of time the types of registrations that might be contained in
the result value of an Args.
>>>:{let args = foretellReg @(Sum Int) *> pure () in getRegsReps args :} fromList [Sum Int]
Reducing foretellReg boilerplate with register
class Registrable nested tip | nested -> tip where Source #
Convenience typeclass for automatically extracting registrations from a value.
Counterpart of Wireable for registrations.
Methods
register :: Functor m => Args (m nested) -> Args (m (Regs tip)) Source #
We look for (potentially nested) tuples in the value. All tuple
components except the rightmost-innermost must have Monoid instances, and
are put into a Regs.
>>>:{args :: Args (Identity (Sum Int, All, String)) args = pure (Identity (Sum 5, All False, "foo")) registeredArgs :: Args (Identity (Regs String)) registeredArgs = register args :}
>>>:{let reps = getRegsReps registeredArgs in ( reps == Data.Set.fromList [ SomeMonoidTypeRep $ Type.Reflection.typeRep @(Sum Int) , SomeMonoidTypeRep $ Type.Reflection.typeRep @All] , registeredArgs & runArgs (taste Cauldron.Beans.empty) & runIdentity & runRegs reps & \(beans,_) -> (taste @(Sum Int) beans, taste @All beans) ) :} (True,(Just (Sum {getSum = 5}),Just (All {getAll = False})))
Tuples can be nested:
>>>:{args :: Args (Identity (Sum Int, (All, String))) args = pure (Identity (Sum 5, (All False, "foo"))) registeredArgs :: Args (Identity (Regs String)) registeredArgs = register args :}
If there are no tuples in the result type, no values are put into Regs.
>>>:{args :: Args (Identity String) args = pure (Identity "foo") registeredArgs :: Args (Identity (Regs String)) registeredArgs = register args :}
Re-exports
A map of Dynamic values, indexed by the TypeRep of each Dynamic.
Maintains the invariant that the TypeRep of the key matches the TypeRep
of the Dynamic.
taste :: Typeable bean => Beans -> Maybe bean Source #
Check if the Beans map contains a value of type bean.
fromDynList :: [Dynamic] -> Beans Source #
>>>:{let beans = fromDynList [toDyn False, toDyn @Int 5] in (taste @Bool beans, taste @Int beans, taste @String beans) :} (Just False,Just 5,Nothing)
data SomeMonoidTypeRep Source #
Like SomeTypeRep, but also remembering that the type has a Monoid instance, which can be "recovered"
after pattern-matching on the SomeMonoidTypeRep.
Instances
| Show SomeMonoidTypeRep Source # | |
Defined in Cauldron.Beans Methods showsPrec :: Int -> SomeMonoidTypeRep -> ShowS # show :: SomeMonoidTypeRep -> String # showList :: [SomeMonoidTypeRep] -> ShowS # | |
| Eq SomeMonoidTypeRep Source # | |
Defined in Cauldron.Beans Methods (==) :: SomeMonoidTypeRep -> SomeMonoidTypeRep -> Bool # (/=) :: SomeMonoidTypeRep -> SomeMonoidTypeRep -> Bool # | |
| Ord SomeMonoidTypeRep Source # | |
Defined in Cauldron.Beans Methods compare :: SomeMonoidTypeRep -> SomeMonoidTypeRep -> Ordering # (<) :: SomeMonoidTypeRep -> SomeMonoidTypeRep -> Bool # (<=) :: SomeMonoidTypeRep -> SomeMonoidTypeRep -> Bool # (>) :: SomeMonoidTypeRep -> SomeMonoidTypeRep -> Bool # (>=) :: SomeMonoidTypeRep -> SomeMonoidTypeRep -> Bool # max :: SomeMonoidTypeRep -> SomeMonoidTypeRep -> SomeMonoidTypeRep # min :: SomeMonoidTypeRep -> SomeMonoidTypeRep -> SomeMonoidTypeRep # | |