Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- 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]
Instances
newtype AsOp (t :: * -> *) a op Source #
AsOp (op t a) |
_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
.
Instances
(HFoldableAt k (OpChoice ops), HFunctor (OpChoice ops)) => HFoldableAt (k :: Type -> Type) (HFree' ops :: (Type -> Type) -> Type -> Type) Source # | |
Defined in Language.Expression.Choice | |
HTraversable (OpChoice ops) => HTraversable (HFree' ops :: (Type -> Type) -> Type -> Type) Source # | |
Defined in Language.Expression.Choice | |
HFunctor (OpChoice ops) => HMonad (HFree' ops :: (Type -> Type) -> Type -> Type) Source # | |
Defined in Language.Expression.Choice | |
HFunctor (OpChoice ops) => HBind (HFree' ops :: (Type -> Type) -> Type -> Type) Source # | |
HPointed (HFree' ops :: (Type -> Type) -> Type -> Type) Source # | |
Defined in Language.Expression.Choice | |
HFunctor (OpChoice ops) => HFunctor (HFree' ops :: (Type -> Type) -> Type -> Type) Source # | |
Pretty2 (OpChoice ops) => Pretty2 (HFree' ops :: (Type -> Type) -> Type -> Type) Source # | |
(Data (HFree (OpChoice ops) v a), Typeable (HFree' ops v a)) => Data (HFree' ops v a) Source # | |
Defined in Language.Expression.Choice gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HFree' ops v a -> c (HFree' ops v a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HFree' ops v a) # toConstr :: HFree' ops v a -> Constr # dataTypeOf :: HFree' ops v a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HFree' ops v a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HFree' ops v a)) # gmapT :: (forall b. Data b => b -> b) -> HFree' ops v a -> HFree' ops v a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HFree' ops v a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HFree' ops v a -> r # gmapQ :: (forall d. Data d => d -> u) -> HFree' ops v a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HFree' ops v a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HFree' ops v a -> m (HFree' ops v a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HFree' ops v a -> m (HFree' ops v a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HFree' ops v a -> m (HFree' ops v a) # | |
Wrapped (HFree' ops v a) Source # | |
HFree' ops1 v1 a1 ~ t => Rewrapped (HFree' ops2 v2 a2) t Source # | |
Defined in Language.Expression.Choice | |
type Unwrapped (HFree' ops v a) Source # | |
Defined in Language.Expression.Choice |