| Safe Haskell | None |
|---|---|
| Language | GHC2021 |
Cauldron.Beans
Description
A map of Dynamic values.
Synopsis
- data Beans
- empty :: Beans
- insert :: Typeable bean => bean -> Beans -> Beans
- delete :: TypeRep -> Beans -> Beans
- restrictKeys :: Beans -> Set TypeRep -> Beans
- keysSet :: Beans -> Set TypeRep
- singleton :: Typeable bean => bean -> Beans
- fromDynList :: [Dynamic] -> Beans
- toDynMap :: Beans -> Map TypeRep Dynamic
- taste :: Typeable bean => Beans -> Maybe bean
- unionBeansMonoidally :: Set SomeMonoidTypeRep -> Beans -> Beans -> Beans
- data SomeMonoidTypeRep where
- SomeMonoidTypeRep :: forall a. Monoid a => TypeRep a -> SomeMonoidTypeRep
- someMonoidTypeRepMempty :: SomeMonoidTypeRep -> Dynamic
- toDyn :: Typeable a => a -> Dynamic
Documentation
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.
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)
Looking for values
taste :: Typeable bean => Beans -> Maybe bean Source #
Check if the Beans map contains a value of type bean.
Monoidal stuff
unionBeansMonoidally :: Set SomeMonoidTypeRep -> Beans -> Beans -> Beans Source #
Union of to Beans maps. If both share a TypeRep key and the key is
present in the SomeMonoidTypeRep Set, combine the values monoidally.
Otherwise, keep the value from the second Beans map.
data SomeMonoidTypeRep where Source #
Like SomeTypeRep, but also remembering that the type has a Monoid instance, which can be "recovered"
after pattern-matching on the SomeMonoidTypeRep.
Constructors
| SomeMonoidTypeRep :: forall a. Monoid a => TypeRep a -> 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 # | |
Re-exported
toDyn :: Typeable a => a -> Dynamic #
Converts an arbitrary value into an object of type Dynamic.
The type of the object must be an instance of Typeable, which
ensures that only monomorphically-typed objects may be converted to
Dynamic. To convert a polymorphic object into Dynamic, give it
a monomorphic type signature. For example:
toDyn (id :: Int -> Int)