| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Data.GI.Base.DynVal
Description
This is an experimental module that introduces support for dynamic
values: these are functions from a record model to some type a
which keep track of which selectors of model does the result depend
on. For example, for a record of the form
data Example = Example {
first :: Int,
second :: Bool,
third :: Float
}a `DynVal Example String` could be constructed, assuming that you are
given a record DynVal representing the full record, using:
let format = \f s -> "First is " <> f <> " and second is " <> s
formatted = format <$> record.first <*> record.second :: DynVal Example StringHere we are showcasing two properties of DynVals: they can be
conveniently constructed using OverloadedRecordDot, and they provide
an Applicative instance. The resulting formatted DynVal keeps
track of the fact that it depends on the first and second record
selectors.
Synopsis
- data DynVal model a = DynVal DVKey (model -> a)
- data DVKey
- = DVKeyDirect [Text]
- | DVKeyDerived (Set [Text])
- data ModelProxy model = ModelProxy (IO model) (DVKey -> (model -> IO ()) -> IO ()) ([Text] -> (model -> Maybe model) -> IO ())
- dvKeys :: DynVal model a -> DVKey
- dvRead :: DynVal model a -> model -> a
- modelProxyCurrentValue :: ModelProxy model -> IO model
- modelProxyRegisterHandler :: ModelProxy model -> DVKey -> (model -> IO ()) -> IO ()
- modelProxyUpdate :: ModelProxy model -> [Text] -> (model -> Maybe model) -> IO ()
Documentation
A DynVal is a way of extracting values of type a from
model, which keeps track of which fields (parameterised by
dvKeys) in model are needed for computing the DynVal.
Instances
| (HasField fieldName field a, KnownSymbol fieldName) => HasField (fieldName :: Symbol) (DynVal model field) (DynVal model a) Source # | |
Defined in Data.GI.Base.DynVal | |
| Applicative (DynVal model) Source # | |
Defined in Data.GI.Base.DynVal | |
| Functor (DynVal model) Source # | |
| IsString (DynVal model Text) Source # | |
Defined in Data.GI.Base.DynVal Methods fromString :: String -> DynVal model Text # | |
Constructors
| DVKeyDirect [Text] | Direct access to subfields: for example writing
|
| DVKeyDerived (Set [Text]) | Value derived from a direct key, by acting with the functor or applicative instances. |
data ModelProxy model Source #
A ModelProxy is a way of obtaining records of type model,
which allows for registering for notifications whenever certain
keys (typically associated to record fields) get modified, and
allows to modify fields of the model.
modelProxyCurrentValue :: ModelProxy model -> IO model Source #
Obtain the current value of the model.
modelProxyRegisterHandler :: ModelProxy model -> DVKey -> (model -> IO ()) -> IO () Source #
Register a handler that will be executed whenever any of the fields in the model pointed to by the keys is modified.
modelProxyUpdate :: ModelProxy model -> [Text] -> (model -> Maybe model) -> IO () Source #
Modify the given keys in the proxy, using the given update function, of type (model -> Maybe model). If this function returns Nothing no modification will be performed, otherwise the modified model will be stored in the ModelProxy, and any listeners will be notified of a change.