symantic-base-0.0.1.20200708: Basic symantics for writing Embedded Domain-Specific Languages (EDSL).

Safe HaskellNone
LanguageHaskell2010

Symantic.Base.Composable

Contents

Synopsis

Class Composable

class Composable repr where Source #

Minimal complete definition

Nothing

Methods

(<.>) :: Transformable repr => Composable (UnTrans repr) => repr a b -> repr b c -> repr a c infixr 4 Source #

(<.>) :: repr a b -> repr b c -> repr a c infixr 4 Source #

Class Voidable

class Voidable repr where Source #

Minimal complete definition

Nothing

Methods

void :: Transformable repr => Voidable (UnTrans repr) => a -> repr (a -> b) k -> repr b k Source #

void :: a -> repr (a -> b) k -> repr b k Source #

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.

Minimal complete definition

noTrans, unTrans

Associated Types

type UnTrans repr :: * -> * -> * Source #

The underlying representation that (repr) transforms.

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 UnTransformed representation, or at the end to get the underlying UnTransformed 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 # 
Instance details

Defined in Symantic.Base.Composable

Associated Types

type UnTrans (IdentityTrans repr) :: Type -> Type -> Type Source #

Methods

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.

Constructors

IdentityTrans 

Fields

Instances
Transformable (IdentityTrans repr) Source # 
Instance details

Defined in Symantic.Base.Composable

Associated Types

type UnTrans (IdentityTrans repr) :: Type -> Type -> Type Source #

Methods

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 # 
Instance details

Defined in Symantic.Base.Composable

type UnTrans (IdentityTrans repr) = repr

Class Dimapable

class Dimapable repr where Source #

Minimal complete definition

Nothing

Methods

dimap :: Transformable repr => Dimapable (UnTrans repr) => (a -> b) -> (b -> a) -> repr (a -> k) k -> repr (b -> k) k Source #

dimap :: (a -> b) -> (b -> a) -> repr (a -> k) k -> repr (b -> k) k Source #