Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class Composable repr where
- (<.>) :: repr a b -> repr b c -> repr a c
- class Voidable repr where
- void :: a -> repr (a -> b) k -> repr b k
- class Transformable repr where
- newtype IdentityTrans repr a k = IdentityTrans {
- unIdentityTrans :: repr a k
- class Dimapable repr where
- dimap :: (a -> b) -> (b -> a) -> repr (a -> k) k -> repr (b -> k) k
Class Composable
class Composable repr where Source #
Nothing
(<.>) :: Transformable repr => Composable (UnTrans repr) => repr a b -> repr b c -> repr a c infixr 4 Source #
Class Voidable
Class Transformable
class Transformable repr where Source #
Used with DefaultSignatures
and default methods,
in the symantics class definition,
it then avoids on an interpreter instance
to define unused methods.
noTrans :: UnTrans repr a b -> repr a b Source #
Lift the underlying representation to (repr)
.
Useful to define a combinator that does nothing
in a transformation.
unTrans :: repr a b -> UnTrans repr a b Source #
Unlift a representation. Useful when a transformation
combinator needs to access the UnTrans
formed representation,
or at the end to get the underlying UnTrans
formed representation
from the inferred (repr)
value.
trans1 :: (UnTrans repr a b -> UnTrans repr c d) -> repr a b -> repr c d Source #
Convenient helper lifing an unary operator, but also enables to identify unary operators.
trans2 :: (UnTrans repr a b -> UnTrans repr c d -> UnTrans repr e f) -> repr a b -> repr c d -> repr e f Source #
Convenient helper lifting a binary operator, but also enables to identify binary operators.
Instances
Transformable (IdentityTrans repr) Source # | |
Defined in Symantic.Base.Composable noTrans :: UnTrans (IdentityTrans repr) a b -> IdentityTrans repr a b Source # unTrans :: IdentityTrans repr a b -> UnTrans (IdentityTrans repr) a b Source # trans1 :: (UnTrans (IdentityTrans repr) a b -> UnTrans (IdentityTrans repr) c d) -> IdentityTrans repr a b -> IdentityTrans repr c d Source # trans2 :: (UnTrans (IdentityTrans repr) a b -> UnTrans (IdentityTrans repr) c d -> UnTrans (IdentityTrans repr) e f) -> IdentityTrans repr a b -> IdentityTrans repr c d -> IdentityTrans repr e f Source # |
Type IdentityTrans
newtype IdentityTrans repr a k Source #
A Transformable
that does nothing.
IdentityTrans | |
|
Instances
Transformable (IdentityTrans repr) Source # | |
Defined in Symantic.Base.Composable noTrans :: UnTrans (IdentityTrans repr) a b -> IdentityTrans repr a b Source # unTrans :: IdentityTrans repr a b -> UnTrans (IdentityTrans repr) a b Source # trans1 :: (UnTrans (IdentityTrans repr) a b -> UnTrans (IdentityTrans repr) c d) -> IdentityTrans repr a b -> IdentityTrans repr c d Source # trans2 :: (UnTrans (IdentityTrans repr) a b -> UnTrans (IdentityTrans repr) c d -> UnTrans (IdentityTrans repr) e f) -> IdentityTrans repr a b -> IdentityTrans repr c d -> IdentityTrans repr e f Source # | |
type UnTrans (IdentityTrans repr) Source # | |
Defined in Symantic.Base.Composable |