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

Safe HaskellNone
LanguageHaskell2010

Symantic.Base.Algebrable

Contents

Synopsis

Documentation

adt :: forall adt repr k. Dimapable repr => Generic adt => RepOfEoT adt => EoTOfRep adt => repr (EoT (ADT adt) -> k) k -> repr (adt -> k) k Source #

(adt SomeADT some_expr) wrap/unwrap (some_expr) input/output value to/from the Algebraic Data Type (SomeADT). (SomeADT) must have a Generic instance (using the DeriveGeneric language extension to GHC).

Class Tupable

class Tupable repr where Source #

Minimal complete definition

Nothing

Methods

(<:>) :: Transformable repr => Tupable (UnTrans repr) => repr (a -> k) k -> repr (b -> k) k -> repr ((a, b) -> k) k infixr 4 Source #

(<:>) :: repr (a -> k) k -> repr (b -> k) k -> repr ((a, b) -> k) k infixr 4 Source #

Class Unitable

class Unitable repr where Source #

Minimal complete definition

Nothing

Methods

unit :: Transformable repr => Unitable (UnTrans repr) => repr (() -> k) k Source #

unit :: repr (() -> k) k Source #

Class Constant

class Constant repr where Source #

Minimal complete definition

Nothing

Methods

constant :: Transformable repr => Constant (UnTrans repr) => a -> repr (a -> k) k Source #

constant :: a -> repr (a -> k) k Source #

Class Eitherable

class Eitherable repr where Source #

Minimal complete definition

Nothing

Methods

(<+>) :: Transformable repr => Eitherable (UnTrans repr) => repr (a -> k) k -> repr (b -> k) k -> repr (Either a b -> k) k infixr 3 Source #

(<+>) :: repr (a -> k) k -> repr (b -> k) k -> repr (Either a b -> k) k infixr 3 Source #

Class Emptyable

class Emptyable repr where Source #

Minimal complete definition

Nothing

Methods

empty :: Transformable repr => Emptyable (UnTrans repr) => repr k k Source #

empty :: repr k k Source #

Class Optionable

class Optionable repr where Source #

Minimal complete definition

Nothing

Methods

option :: Transformable repr => Optionable (UnTrans repr) => repr k k -> repr k k Source #

option :: repr k k -> repr k k Source #

optional :: Transformable repr => Optionable (UnTrans repr) => repr (a -> k) k -> repr (Maybe a -> k) k Source #

optional :: repr (a -> k) k -> repr (Maybe a -> k) k Source #

Class Repeatable

class Repeatable repr where Source #

Minimal complete definition

Nothing

Methods

many0 :: Transformable repr => Repeatable (UnTrans repr) => repr (a -> k) k -> repr ([a] -> k) k Source #

many0 :: repr (a -> k) k -> repr ([a] -> k) k Source #

many1 :: Transformable repr => Repeatable (UnTrans repr) => repr (a -> k) k -> repr ([a] -> k) k Source #

many1 :: repr (a -> k) k -> repr ([a] -> k) k Source #

Class Substractable

class Substractable repr where Source #

Minimal complete definition

Nothing

Methods

(<->) :: Transformable repr => Substractable (UnTrans repr) => repr a k -> repr k' k' -> repr a k infixr 3 Source #

(<->) :: repr a k -> repr k' k' -> repr a k infixr 3 Source #

Class Dicurryable

class Dicurryable repr where Source #

Minimal complete definition

Nothing

Methods

dicurry :: CurryN args => proxy args -> (args -..-> r) -> (r -> Tuples args) -> repr (args -..-> k) k -> repr (r -> k) k Source #

dicurry :: Transformable repr => Dicurryable (UnTrans repr) => CurryN args => proxy args -> (args -..-> r) -> (r -> Tuples args) -> repr (args -..-> k) k -> repr (r -> k) k Source #

construct :: forall args a k repr. Dicurryable repr => Generic a => EoTOfRep a => CurryN args => Tuples args ~ EoT (ADT a) => args ~ Args (args -..-> a) => (args -..-> a) -> repr (args -..-> k) k -> repr (a -> k) k Source #