Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data OpChoice ops (t :: * -> *) a where
- _OpThis :: Prism' (OpChoice (op ': ops) t a) (op t a)
- _OpThat :: Prism' (OpChoice (op ': ops) t a) (OpChoice ops t a)
- noOps :: OpChoice '[] t a -> x
- newtype AsOp (t :: * -> *) a op = AsOp (op t a)
- choiceToUnion :: OpChoice ops t a -> Union (AsOp t a) ops
- unionToChoice :: Union (AsOp t a) ops -> OpChoice ops t a
- _OpChoice :: Iso (OpChoice ops t a) (OpChoice ops' t' a') (Union (AsOp t a) ops) (Union (AsOp t' a') ops')
- class ChooseOp op ops where
- class SubsetOp ops1 ops2 where
- newtype HFree' ops v a = HFree' {}
- squashExpression :: (HFunctor op1, HFunctor op2, HFunctor (OpChoice ops), ChooseOp op1 ops, ChooseOp op2 ops) => HFree op1 (HFree op2 v) a -> HFree' ops v a
- hwrap' :: (HFunctor op, HFunctor (OpChoice ops), ChooseOp op ops) => op (HFree' ops v) a -> HFree' ops v a
Documentation
data OpChoice ops (t :: * -> *) a where Source #
Form the union of a list of operators. This creates an operator which is a choice from one of its constituents.
For example,
is an operator that can either
represent an arithmetic operation or an equality comparison.OpChoice
'[NumOp, EqOp]
(HFoldableAt * k op, HFoldableAt * k (OpChoice ops)) => HFoldableAt * k (OpChoice ((:) ((* -> *) -> * -> *) op ops)) Source # | |
HFoldableAt * k (OpChoice ([] ((* -> *) -> * -> *))) Source # | |
(HTraversable * op, HTraversable * (OpChoice ops)) => HTraversable * (OpChoice ((:) ((* -> *) -> * -> *) op ops)) Source # | |
HTraversable * (OpChoice ([] ((* -> *) -> * -> *))) Source # | |
(HFunctor * op, HFunctor * (OpChoice ops)) => HFunctor * (OpChoice ((:) ((* -> *) -> * -> *) op ops)) Source # | |
HFunctor * (OpChoice ([] ((* -> *) -> * -> *))) Source # | |
(Pretty2 * * op, Pretty2 * * (OpChoice ops)) => Pretty2 * * (OpChoice ((:) ((* -> *) -> * -> *) op ops)) Source # | |
Pretty2 * * (OpChoice ([] ((* -> *) -> * -> *))) Source # | |
_OpChoice :: Iso (OpChoice ops t a) (OpChoice ops' t' a') (Union (AsOp t a) ops) (Union (AsOp t' a') ops') Source #
class ChooseOp op ops where Source #
This class provides a low-boilerplate way of lifting individual operators into a union, and extracting operators from a union.
newtype HFree' ops v a Source #
is a higher-order free monad over the list of operators
HFree'
ops v aops
with variables in the type v
and it represents a value of type a
.
Intuitively, it represents an expression which may contain operations from
any of the operators in the list ops
.
(HFoldableAt * k (OpChoice ops), HFunctor * (OpChoice ops)) => HFoldableAt * k (HFree' ops) Source # | |
Pretty2 * * (OpChoice ops) => Pretty2 * * (HFree' ops) Source # | |
HTraversable * (OpChoice ops) => HTraversable * (HFree' ops) Source # | |
HFunctor * (OpChoice ops) => HMonad * (HFree' ops) Source # | |
HFunctor * (OpChoice ops) => HBind * (HFree' ops) Source # | |
HPointed * (HFree' ops) Source # | |
HFunctor * (OpChoice ops) => HFunctor * (HFree' ops) Source # | |
(Data (HFree * (OpChoice ops) v a), Typeable * (HFree' ops v a)) => Data (HFree' ops v a) Source # | |
Wrapped (HFree' ops v a) Source # | |
(~) * (HFree' ops1 v1 a1) t => Rewrapped (HFree' ops2 v2 a2) t Source # | |
type Unwrapped (HFree' ops v a) Source # | |