symantic-base-0.1.0.20210703: Commonly useful symantics for Embedded Domain-Specific Languages (EDSL)
Safe HaskellNone
LanguageHaskell2010

Symantic.Dityped.Lang

Synopsis

Class Composable

class Composable repr where Source #

Minimal complete definition

Nothing

Methods

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

default (<.>) :: FromDerived2 Composable repr => repr a b -> repr b c -> repr a c Source #

Class Constant

class Constant repr where Source #

Minimal complete definition

Nothing

Methods

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

default constant :: FromDerived Constant repr => a -> repr (a -> k) k 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 #

default dicurry :: FromDerived1 Dicurryable 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 #

Class Dimapable

class Dimapable repr where Source #

Minimal complete definition

Nothing

Methods

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

default dimap :: FromDerived1 Dimapable repr => (a -> b) -> (b -> a) -> repr (a -> k) k -> repr (b -> k) k Source #

Class Eitherable

class Eitherable repr where Source #

Minimal complete definition

Nothing

Methods

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

default (<+>) :: FromDerived2 Eitherable repr => repr (a -> k) k -> repr (b -> k) k -> repr (Either a b -> k) k Source #

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 Emptyable

class Emptyable repr where Source #

Minimal complete definition

Nothing

Methods

empty :: repr k k Source #

default empty :: FromDerived Emptyable repr => repr k k Source #

Class Optionable

class Optionable repr where Source #

Minimal complete definition

Nothing

Methods

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

default option :: FromDerived1 Optionable repr => repr k k -> repr k k Source #

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

default optional :: FromDerived1 Optionable repr => repr (a -> k) k -> repr (Maybe a -> k) k Source #

Class Permutable

class Permutable repr where Source #

Minimal complete definition

permutable, perm, noPerm, permWithDefault

Associated Types

type Permutation (repr :: * -> * -> *) = (r :: * -> * -> *) | r -> repr Source #

type Permutation repr = Permutation (Derived repr)

Methods

permutable :: Permutation repr (a -> k) k -> repr (a -> k) k Source #

perm :: repr (a -> k) k -> Permutation repr (a -> k) k Source #

noPerm :: Permutation repr k k Source #

permWithDefault :: a -> repr (a -> k) k -> Permutation repr (a -> k) k Source #

optionalPerm :: Eitherable repr => Dimapable repr => Permutable repr => repr (a -> k) k -> Permutation repr (Maybe a -> k) k Source #

(<&>) :: Permutable repr => Tupable (Permutation repr) => repr (a -> k) k -> Permutation repr (b -> k) k -> Permutation repr ((a, b) -> k) k infixr 4 Source #

(<?&>) :: Eitherable repr => Dimapable repr => Permutable repr => Tupable (Permutation repr) => repr (a -> k) k -> Permutation repr (b -> k) k -> Permutation repr ((Maybe a, b) -> k) k infixr 4 Source #

(<*&>) :: Eitherable repr => Repeatable repr => Dimapable repr => Permutable repr => Tupable (Permutation repr) => repr (a -> k) k -> Permutation repr (b -> k) k -> Permutation repr (([a], b) -> k) k infixr 4 Source #

(<+&>) :: Eitherable repr => Repeatable repr => Dimapable repr => Permutable repr => Tupable (Permutation repr) => repr (a -> k) k -> Permutation repr (b -> k) k -> Permutation repr (([a], b) -> k) k infixr 4 Source #

Class Repeatable

class Repeatable repr where Source #

Minimal complete definition

Nothing

Methods

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

default many0 :: FromDerived1 Repeatable repr => repr (a -> k) k -> repr ([a] -> k) k Source #

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

default many1 :: FromDerived1 Repeatable repr => repr (a -> k) k -> repr ([a] -> k) k Source #

Class Routable

class Routable repr where Source #

Minimal complete definition

Nothing

Methods

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

default (<!>) :: FromDerived2 Routable repr => repr a k -> repr b k -> repr (a :!: b) k Source #

Type (:!:)

data a :!: b infixr 3 Source #

Like (,) but infixr. Mostly useful for clarity when using Routable.

Constructors

a :!: b infixr 3 

Instances

Instances details
(Eq a, Eq b) => Eq (a :!: b) Source # 
Instance details

Defined in Symantic.Dityped.Lang

Methods

(==) :: (a :!: b) -> (a :!: b) -> Bool #

(/=) :: (a :!: b) -> (a :!: b) -> Bool #

(Show a, Show b) => Show (a :!: b) Source # 
Instance details

Defined in Symantic.Dityped.Lang

Methods

showsPrec :: Int -> (a :!: b) -> ShowS #

show :: (a :!: b) -> String #

showList :: [a :!: b] -> ShowS #

Class Substractable

class Substractable repr where Source #

Minimal complete definition

Nothing

Methods

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

default (<->) :: FromDerived2 Substractable repr => repr a k -> repr k' k' -> repr a k Source #

Class Tupable

class Tupable repr where Source #

Minimal complete definition

Nothing

Methods

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

default (<:>) :: FromDerived2 Tupable repr => repr (a -> k) k -> repr (b -> k) k -> repr ((a, b) -> k) k Source #

Class Unitable

class Unitable repr where Source #

Minimal complete definition

Nothing

Methods

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

default unit :: FromDerived Unitable repr => repr (() -> k) k Source #

Class Voidable

class Voidable repr where Source #

Minimal complete definition

Nothing

Methods

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

default void :: FromDerived1 Voidable repr => a -> repr (a -> b) k -> repr b k Source #