Safe Haskell | None |
---|---|
Language | Haskell2010 |
Prairie.Distributed
Description
This module provides an advanced functionality for working with
Prairie Record
s. The Distributed
type wraps each field in a type
constructor, allowing you to work flexibly with Record
s that are
construted and manipulated effectfully.
As an example, consider a
. This would be
similar to a Distributed
Parser rec
, but instead of producing a complete Parser
recrec
,
we actually have a field-wise Parser
- this allows us to access the
result of parsing a single field without requiring that all fields parse
correctly.
For another example, consider a
. This would
describe a means of producing a Distributed
DB recrec
by describing how to produce each
Field
of that rec
using the DB
type - possibly by fetching the
appropriate row.
This module provides power equivalent to the HKD
design pattern, but
without requiring any complication to the underlying datatypes.
Since: 0.1.0.0
Synopsis
- newtype Distributed (f :: Type -> Type) rec = Distributed (forall x. Field rec x -> f x)
- getRecordFieldDistributed :: Record rec => Field rec ty -> Distributed f rec -> f ty
- buildDistributed :: forall f rec. (forall ty. Field rec ty -> f ty) -> Distributed f rec
- distribute :: forall (f :: Type -> Type) rec. (Applicative f, Record rec) => rec -> Distributed f rec
- distributeF :: (Functor f, Record rec) => f rec -> Distributed f rec
- sequenceDistributedA :: (Applicative f, Record rec) => Distributed f rec -> f rec
- sequenceDistributedApply :: (Apply f, Record rec) => Distributed f rec -> f rec
- zipWithDistributed :: (forall x. f x -> g x -> h x) -> Distributed f rec -> Distributed g rec -> Distributed h rec
- distributedRecordFieldNames :: Record rec => Distributed (Const Text :: Type -> Type) rec
- distributedToSemigroup :: (Record rec, forall a1. Semigroup (f a1), Applicative f) => Distributed (Const a :: Type -> Type) rec -> f (Text, a)
- buildConst :: forall a rec. (forall x. Field rec x -> a) -> Distributed (Const a :: Type -> Type) rec
Documentation
newtype Distributed (f :: Type -> Type) rec Source #
A
is a Distributed
f recRecord
with fields that are wrapped in
the f
type constructor.
The simplest example is the trivial Identity
-
wraps each field in Distributed
Identity
recIdentity
, which doesn't do
anything.
But you can also represent a
, where each field
is an Distributed
IO
recIO
action.
This type is equivalently powerful to the Higher Kinded Data
pattern,
but significantly more flexible, since you don't need to munge the
underlying datatype with the complexity of this.
You can use OverloadedRecordDot
to access fields on this directly, or
you can also use getRecordFieldDistributed
.
Since: 0.1.0.0
Constructors
Distributed (forall x. Field rec x -> f x) |
Instances
SymbolToField sym rec typ => HasField (sym :: Symbol) (Distributed f rec) (f typ) Source # | This instance allows you to use the data User = User { name :: String } mkRecord ''User userIO :: Distributed IO User userIO = buildDistributed \case UserName -> getLine main :: IO () main = do userName <- userIO.name putStrLn userName Since: 0.1.0.0 |
Defined in Prairie.Distributed Methods getField :: Distributed f rec -> f typ # |
getRecordFieldDistributed :: Record rec => Field rec ty -> Distributed f rec -> f ty Source #
Use a
to access that field in the Field
rec ty
.Distributed
f rec
Since: 0.1.0.0
buildDistributed :: forall f rec. (forall ty. Field rec ty -> f ty) -> Distributed f rec Source #
Given a function that specifies how to construct a field of a record
wrapped in a type f
, this constructs a
.Distributed
f record
Since: 0.1.0.0
distribute :: forall (f :: Type -> Type) rec. (Applicative f, Record rec) => rec -> Distributed f rec Source #
Takes a Record
and creates a pure Distributed
record over any
Applicative
.
Since: 0.1.0.0
distributeF :: (Functor f, Record rec) => f rec -> Distributed f rec Source #
Like distribute
, but the record is already wrapped in a Functor
f.
Since: 0.1.0.0
sequenceDistributedA :: (Applicative f, Record rec) => Distributed f rec -> f rec Source #
Remove the Distributed
wrapper, providing an f rec
that can be
used directly.
Since: 0.1.0.0
sequenceDistributedApply :: (Apply f, Record rec) => Distributed f rec -> f rec Source #
Like sequenceDistributedA
, but works on the Apply
class, which
allows for semigroup-only construction.
Since: 0.1.0.0
zipWithDistributed :: (forall x. f x -> g x -> h x) -> Distributed f rec -> Distributed g rec -> Distributed h rec Source #
This function allows you to combine the two type wrappers into a third. This merges the two records based on how you combine their merging functions.
Since: 0.1.0.0
distributedRecordFieldNames :: Record rec => Distributed (Const Text :: Type -> Type) rec Source #
distributedToSemigroup :: (Record rec, forall a1. Semigroup (f a1), Applicative f) => Distributed (Const a :: Type -> Type) rec -> f (Text, a) Source #
If you've used buildConst
to convert all record fields into a single
type, then you can use distributedToSemigroup
to tag each value with
the field name that it came from.
Since: 0.1.0.0
buildConst :: forall a rec. (forall x. Field rec x -> a) -> Distributed (Const a :: Type -> Type) rec Source #
Like buildDistributed
but it wraps the result in Const
. The result
is a record
but accessing the field is
Since: 0.1.0.0