Safe Haskell | None |
---|---|
Language | Haskell2010 |
Data.Packed.Needs
Synopsis
- newtype Needs (p :: [Type]) (t :: [Type]) = Needs Builder
- withEmptyNeeds :: forall (a :: [Type]) (b :: [Type]) (x :: [Type]) (y :: [Type]). NeedsBuilder a b x y -> Needs x y
- finish :: forall (t :: [Type]). Needs ('[] :: [Type]) t -> Packed t
- newtype NeedsBuilder (ps :: [Type]) (ts :: [Type]) (pd :: [Type]) (td :: [Type]) = NeedsBuilder {
- runBuilder :: Needs ps ts -> Needs pd td
- type NeedsWriter a (r :: [Type]) (t :: [Type]) = NeedsBuilder (a ': r) t r t
- type NeedsWriter' (a :: [Type]) (r :: [Type]) (t :: [Type]) = NeedsBuilder (a :++: r) t r t
- (>>) :: forall (p1 :: [Type]) (t1 :: [Type]) (p2 :: [Type]) (t2 :: [Type]) (p3 :: [Type]) (t3 :: [Type]). NeedsBuilder p1 t1 p2 t2 -> NeedsBuilder p2 t2 p3 t3 -> NeedsBuilder p1 t1 p3 t3
- mkNeedsBuilder :: forall (ps :: [Type]) (ts :: [Type]) (pd :: [Type]) (td :: [Type]). (Needs ps ts -> Needs pd td) -> NeedsBuilder ps ts pd td
- withNeeds :: forall (x :: [Type]) (y :: [Type]) (x1 :: [Type]) (y1 :: [Type]). Needs x y -> NeedsBuilder x y x1 y1 -> Needs x1 y1
- concatNeeds :: forall (p :: [Type]) (t :: [Type]) (t1 :: [Type]). Needs p t -> NeedsBuilder ('[] :: [Type]) t1 p (t1 :++: t)
- applyNeeds :: forall (t1 :: [Type]) (r :: [Type]) (t :: [Type]). Needs ('[] :: [Type]) t1 -> NeedsBuilder (t1 :++: r) t r t
- unsafeCastNeeds :: forall (a :: [Type]) (b :: [Type]) (c :: [Type]) (d :: [Type]). Needs a b -> Needs c d
- type family (a :: [Type]) :++: (b :: [Type]) :: [Type] where ...
Type
newtype Needs (p :: [Type]) (t :: [Type]) Source #
A buffer where packed values can be written
The order to write these values is defined by the l
type list
If p
is an empty list, then a value of type t
can be extracted from that buffer.
(See finish
)
withEmptyNeeds :: forall (a :: [Type]) (b :: [Type]) (x :: [Type]) (y :: [Type]). NeedsBuilder a b x y -> Needs x y Source #
Builders
newtype NeedsBuilder (ps :: [Type]) (ts :: [Type]) (pd :: [Type]) (td :: [Type]) Source #
A wrapper around a function that builds a Needs
ps
: The type of the expected input of the source Needs
ts
: The type of the final packed data of the source Needs
pd
: The type of the expected input of the resuling Needs
td
: The type of the final packed data of the resulting Needs
Note: It is an indexed monad.
Constructors
NeedsBuilder | |
Fields
|
type NeedsWriter a (r :: [Type]) (t :: [Type]) = NeedsBuilder (a ': r) t r t Source #
Shortcut type for NeedsBuilder
's that simply write a value to a Needs
without changing the final packed type
type NeedsWriter' (a :: [Type]) (r :: [Type]) (t :: [Type]) = NeedsBuilder (a :++: r) t r t Source #
Shortcut type for NeedsBuilder
's that simply write multiple values to a Needs
without changing the final packed type
(>>) :: forall (p1 :: [Type]) (t1 :: [Type]) (p2 :: [Type]) (t2 :: [Type]) (p3 :: [Type]) (t3 :: [Type]). NeedsBuilder p1 t1 p2 t2 -> NeedsBuilder p2 t2 p3 t3 -> NeedsBuilder p1 t1 p3 t3 Source #
mkNeedsBuilder :: forall (ps :: [Type]) (ts :: [Type]) (pd :: [Type]) (td :: [Type]). (Needs ps ts -> Needs pd td) -> NeedsBuilder ps ts pd td Source #
withNeeds :: forall (x :: [Type]) (y :: [Type]) (x1 :: [Type]) (y1 :: [Type]). Needs x y -> NeedsBuilder x y x1 y1 -> Needs x1 y1 Source #
Mixing Needs together
concatNeeds :: forall (p :: [Type]) (t :: [Type]) (t1 :: [Type]). Needs p t -> NeedsBuilder ('[] :: [Type]) t1 p (t1 :++: t) Source #
applyNeeds :: forall (t1 :: [Type]) (r :: [Type]) (t :: [Type]). Needs ('[] :: [Type]) t1 -> NeedsBuilder (t1 :++: r) t r t Source #