symantic-base-0.2.0.20210831: Basic symantics combinators for Embedded Domain-Specific Languages (EDSL)
Safe HaskellNone
LanguageHaskell2010

Symantic.Lang

Synopsis

Type ReprKind

Class Abstractable

class Abstractable repr where Source #

Minimal complete definition

Nothing

Methods

(.@) :: repr (a -> b) -> repr a -> repr b infixl 9 Source #

Application, aka. unabstract.

default (.@) :: FromDerived2 Abstractable repr => repr (a -> b) -> repr a -> repr b Source #

lam :: (repr a -> repr b) -> repr (a -> b) Source #

Lambda term abstraction, in HOAS (Higher-Order Abstract Syntax) style.

default lam :: FromDerived Abstractable repr => Derivable repr => (repr a -> repr b) -> repr (a -> b) Source #

lam1 :: (repr a -> repr b) -> repr (a -> b) Source #

Like lam but whose argument is used only once, hence safe to beta-reduce (inline) without duplicating work.

default lam1 :: FromDerived Abstractable repr => Derivable repr => (repr a -> repr b) -> repr (a -> b) Source #

const :: repr (a -> b -> a) Source #

default const :: FromDerived Abstractable repr => repr (a -> b -> a) Source #

flip :: repr ((a -> b -> c) -> b -> a -> c) Source #

default flip :: FromDerived Abstractable repr => repr ((a -> b -> c) -> b -> a -> c) Source #

id :: repr (a -> a) Source #

default id :: FromDerived Abstractable repr => repr (a -> a) Source #

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

default (.) :: FromDerived Abstractable repr => repr ((b -> c) -> (a -> b) -> a -> c) Source #

($) :: repr ((a -> b) -> a -> b) infixr 0 Source #

default ($) :: FromDerived Abstractable repr => repr ((a -> b) -> a -> b) Source #

var :: repr a -> repr a Source #

default var :: FromDerived1 Abstractable repr => repr a -> repr a Source #

Instances

Instances details
Abstractable View Source # 
Instance details

Defined in Symantic.View

Methods

(.@) :: View (a -> b) -> View a -> View b Source #

lam :: (View a -> View b) -> View (a -> b) Source #

lam1 :: (View a -> View b) -> View (a -> b) Source #

const :: View (a -> b -> a) Source #

flip :: View ((a -> b -> c) -> b -> a -> c) Source #

id :: View (a -> a) Source #

(.) :: View ((b -> c) -> (a -> b) -> a -> c) Source #

($) :: View ((a -> b) -> a -> b) Source #

var :: View a -> View a Source #

Abstractable repr => Abstractable (SomeData repr) Source # 
Instance details

Defined in Symantic.Data

Methods

(.@) :: SomeData repr (a -> b) -> SomeData repr a -> SomeData repr b Source #

lam :: (SomeData repr a -> SomeData repr b) -> SomeData repr (a -> b) Source #

lam1 :: (SomeData repr a -> SomeData repr b) -> SomeData repr (a -> b) Source #

const :: SomeData repr (a -> b -> a) Source #

flip :: SomeData repr ((a -> b -> c) -> b -> a -> c) Source #

id :: SomeData repr (a -> a) Source #

(.) :: SomeData repr ((b -> c) -> (a -> b) -> a -> c) Source #

($) :: SomeData repr ((a -> b) -> a -> b) Source #

var :: SomeData repr a -> SomeData repr a Source #

Abstractable repr => Derivable (Data Abstractable repr) Source # 
Instance details

Defined in Symantic.Data

Methods

derive :: Data Abstractable repr a -> Derived (Data Abstractable repr) a Source #

data Data Abstractable repr a Source # 
Instance details

Defined in Symantic.Data

data Data Abstractable repr a where

Class Anythingable

class Anythingable repr where Source #

Minimal complete definition

Nothing

Methods

anything :: repr a -> repr a Source #

Instances

Instances details
Anythingable View Source # 
Instance details

Defined in Symantic.View

Methods

anything :: View a -> View a Source #

Anythingable (SomeData repr) Source # 
Instance details

Defined in Symantic.Data

Methods

anything :: SomeData repr a -> SomeData repr a Source #

Anythingable repr => Derivable (Data Anythingable repr) Source # 
Instance details

Defined in Symantic.Data

Methods

derive :: Data Anythingable repr a -> Derived (Data Anythingable repr) a Source #

Anythingable (Data Anythingable repr) Source # 
Instance details

Defined in Symantic.Data

Methods

anything :: Data Anythingable repr a -> Data Anythingable repr a Source #

data Data Anythingable repr a Source # 
Instance details

Defined in Symantic.Data

data Data Anythingable repr a where

Class Bottomable

class Bottomable repr where Source #

Methods

bottom :: repr a Source #

Instances

Instances details
Bottomable View Source # 
Instance details

Defined in Symantic.View

Methods

bottom :: View a Source #

Bottomable repr => Derivable (Data Bottomable repr) Source # 
Instance details

Defined in Symantic.Data

Methods

derive :: Data Bottomable repr a -> Derived (Data Bottomable repr) a Source #

data Data Bottomable repr a Source # 
Instance details

Defined in Symantic.Data

data Data Bottomable repr a where

Class Constantable

class Constantable c repr where Source #

Minimal complete definition

Nothing

Methods

constant :: c -> repr c Source #

default constant :: FromDerived (Constantable c) repr => c -> repr c Source #

Instances

Instances details
Show c => Constantable c View Source # 
Instance details

Defined in Symantic.View

Methods

constant :: c -> View c Source #

(Constantable c repr, Typeable c) => Constantable c (SomeData repr) Source # 
Instance details

Defined in Symantic.Data

Methods

constant :: c -> SomeData repr c Source #

Constantable c (Data (Constantable c) repr) Source # 
Instance details

Defined in Symantic.Data

Methods

constant :: c -> Data (Constantable c) repr c Source #

Constantable c repr => Derivable (Data (Constantable c) repr) Source # 
Instance details

Defined in Symantic.Data

Methods

derive :: Data (Constantable c) repr a -> Derived (Data (Constantable c) repr) a Source #

data Data (Constantable c) repr a Source # 
Instance details

Defined in Symantic.Data

data Data (Constantable c) repr a where

bool :: Constantable Bool repr => Bool -> repr Bool Source #

char :: Constantable Char repr => Char -> repr Char Source #

unit :: Constantable () repr => repr () Source #

Class Eitherable

class Eitherable repr where Source #

Minimal complete definition

Nothing

Methods

left :: repr (l -> Either l r) Source #

default left :: FromDerived Eitherable repr => repr (l -> Either l r) Source #

right :: repr (r -> Either l r) Source #

default right :: FromDerived Eitherable repr => repr (r -> Either l r) Source #

Instances

Instances details
Eitherable View Source # 
Instance details

Defined in Symantic.View

Methods

left :: View (l -> Either l r) Source #

right :: View (r -> Either l r) Source #

Eitherable repr => Eitherable (SomeData repr) Source # 
Instance details

Defined in Symantic.Data

Methods

left :: SomeData repr (l -> Either l r) Source #

right :: SomeData repr (r -> Either l r) Source #

Eitherable repr => Derivable (Data Eitherable repr) Source # 
Instance details

Defined in Symantic.Data

Methods

derive :: Data Eitherable repr a -> Derived (Data Eitherable repr) a Source #

Eitherable (Data Eitherable repr) Source # 
Instance details

Defined in Symantic.Data

Methods

left :: Data Eitherable repr (l -> Either l r) Source #

right :: Data Eitherable repr (r -> Either l r) Source #

data Data Eitherable repr a Source # 
Instance details

Defined in Symantic.Data

data Data Eitherable repr a where

Class Equalable

class Equalable repr where Source #

Minimal complete definition

Nothing

Methods

equal :: Eq a => repr (a -> a -> Bool) infix 4 Source #

default equal :: FromDerived Equalable repr => Eq a => repr (a -> a -> Bool) Source #

Instances

Instances details
Equalable View Source # 
Instance details

Defined in Symantic.View

Methods

equal :: Eq a => View (a -> a -> Bool) Source #

Equalable repr => Equalable (SomeData repr) Source # 
Instance details

Defined in Symantic.Data

Methods

equal :: Eq a => SomeData repr (a -> a -> Bool) Source #

Equalable repr => Derivable (Data Equalable repr) Source # 
Instance details

Defined in Symantic.Data

Methods

derive :: Data Equalable repr a -> Derived (Data Equalable repr) a Source #

Equalable (Data Equalable repr) Source # 
Instance details

Defined in Symantic.Data

Methods

equal :: Eq a => Data Equalable repr (a -> a -> Bool) Source #

data Data Equalable repr a Source # 
Instance details

Defined in Symantic.Data

data Data Equalable repr a where

(==) :: (Abstractable repr, Equalable repr, Eq a) => repr (a -> a -> Bool) infix 4 Source #

Class IfThenElseable

class IfThenElseable repr where Source #

Minimal complete definition

Nothing

Methods

ifThenElse :: repr Bool -> repr a -> repr a -> repr a Source #

default ifThenElse :: FromDerived3 IfThenElseable repr => repr Bool -> repr a -> repr a -> repr a Source #

Instances

Instances details
IfThenElseable repr => IfThenElseable (SomeData repr) Source # 
Instance details

Defined in Symantic.Data

Methods

ifThenElse :: SomeData repr Bool -> SomeData repr a -> SomeData repr a -> SomeData repr a Source #

IfThenElseable repr => Derivable (Data IfThenElseable repr) Source # 
Instance details

Defined in Symantic.Data

IfThenElseable repr => IfThenElseable (Data IfThenElseable repr) Source # 
Instance details

Defined in Symantic.Data

data Data IfThenElseable repr a Source # 
Instance details

Defined in Symantic.Data

data Data IfThenElseable repr a where

Class Listable

class Listable repr where Source #

Minimal complete definition

Nothing

Methods

cons :: repr (a -> [a] -> [a]) Source #

default cons :: FromDerived Listable repr => repr (a -> [a] -> [a]) Source #

nil :: repr [a] Source #

default nil :: FromDerived Listable repr => repr [a] Source #

Instances

Instances details
Listable View Source # 
Instance details

Defined in Symantic.View

Methods

cons :: View (a -> [a] -> [a]) Source #

nil :: View [a] Source #

Listable repr => Listable (SomeData repr) Source # 
Instance details

Defined in Symantic.Data

Methods

cons :: SomeData repr (a -> [a] -> [a]) Source #

nil :: SomeData repr [a] Source #

Listable repr => Derivable (Data Listable repr) Source # 
Instance details

Defined in Symantic.Data

Methods

derive :: Data Listable repr a -> Derived (Data Listable repr) a Source #

Listable (Data Listable repr) Source # 
Instance details

Defined in Symantic.Data

Methods

cons :: Data Listable repr (a -> [a] -> [a]) Source #

nil :: Data Listable repr [a] Source #

data Data Listable repr a Source # 
Instance details

Defined in Symantic.Data

data Data Listable repr a where

Class Maybeable

class Maybeable repr where Source #

Minimal complete definition

Nothing

Methods

nothing :: repr (Maybe a) Source #

default nothing :: FromDerived Maybeable repr => repr (Maybe a) Source #

just :: repr (a -> Maybe a) Source #

default just :: FromDerived Maybeable repr => repr (a -> Maybe a) Source #

Instances

Instances details
Maybeable View Source # 
Instance details

Defined in Symantic.View

Methods

nothing :: View (Maybe a) Source #

just :: View (a -> Maybe a) Source #

Maybeable repr => Maybeable (SomeData repr) Source # 
Instance details

Defined in Symantic.Data

Methods

nothing :: SomeData repr (Maybe a) Source #

just :: SomeData repr (a -> Maybe a) Source #

Maybeable repr => Derivable (Data Maybeable repr) Source # 
Instance details

Defined in Symantic.Data

Methods

derive :: Data Maybeable repr a -> Derived (Data Maybeable repr) a Source #

Maybeable (Data Maybeable repr) Source # 
Instance details

Defined in Symantic.Data

Methods

nothing :: Data Maybeable repr (Maybe a) Source #

just :: Data Maybeable repr (a -> Maybe a) Source #

data Data Maybeable repr a Source # 
Instance details

Defined in Symantic.Data

data Data Maybeable repr a where

Class IsoFunctor

class IsoFunctor repr where Source #

Minimal complete definition

Nothing

Methods

(<%>) :: Iso a b -> repr a -> repr b Source #

default (<%>) :: FromDerived1 IsoFunctor repr => Iso a b -> repr a -> repr b Source #

Type Iso

data Iso a b Source #

Constructors

Iso 

Fields

  • a2b :: a -> b
     
  • b2a :: b -> a
     

Class ProductFunctor

class ProductFunctor repr where Source #

Minimal complete definition

Nothing

Methods

(<.>) :: repr a -> repr b -> repr (a, b) Source #

default (<.>) :: FromDerived2 ProductFunctor repr => repr a -> repr b -> repr (a, b) Source #

Class AlternativeFunctor

class AlternativeFunctor repr where Source #

Minimal complete definition

Nothing

Methods

(<+>) :: repr a -> repr a -> repr a Source #

default (<+>) :: FromDerived2 AlternativeFunctor repr => repr a -> repr a -> repr a 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) -> repr (r -> k) Source #

default dicurry :: FromDerived1 Dicurryable repr => CurryN args => proxy args -> (args -..-> r) -> (r -> Tuples args) -> repr (args -..-> k) -> repr (r -> 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) -> repr (a -> k) Source #

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

Class Emptyable

class Emptyable repr where Source #

Minimal complete definition

Nothing

Methods

empty :: repr a Source #

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

Class Optionable

class Optionable repr where Source #

Minimal complete definition

Nothing

Methods

option :: repr a -> repr a Source #

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

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

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

Class Repeatable

class Repeatable repr where Source #

Minimal complete definition

Nothing

Methods

many0 :: repr a -> repr [a] Source #

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

many1 :: repr a -> repr [a] Source #

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

Class Permutable

class Permutable repr where Source #

Minimal complete definition

permutable, perm, noPerm, permWithDefault

Associated Types

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

type Permutation repr = Permutation (Derived repr)

Methods

permutable :: Permutation repr a -> repr a Source #

perm :: repr a -> Permutation repr a Source #

noPerm :: Permutation repr () Source #

permWithDefault :: a -> repr a -> Permutation repr a Source #

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

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

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

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

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

Class Routable

class Routable repr where Source #

Minimal complete definition

Nothing

Methods

(<!>) :: repr a -> repr b -> repr (a, b) Source #

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

pattern (:!:) :: a -> b -> (a, b) infixr 3 Source #

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

Class Voidable

class Voidable repr where Source #

Minimal complete definition

Nothing

Methods

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

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

Class Substractable

class Substractable repr where Source #

Minimal complete definition

Nothing

Methods

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

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