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

Symantic.Classes

Description

Comibnators in this module conflict with usual ones from the Prelude hence they are meant to be imported either explicitely or qualified.

Synopsis

Type ReprKind

type ReprKind = Type -> Type Source #

The kind of repr(esentations) throughout this library.

Class Abstractable

class Abstractable repr where Source #

Minimal complete definition

Nothing

Methods

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 must be 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 #

var :: repr a -> repr a Source #

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

(.@) :: 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 #

Instances

Instances details
Abstractable Viewer Source # 
Instance details

Defined in Symantic.Viewer

Methods

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

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

var :: Viewer a -> Viewer a Source #

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

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

Defined in Symantic.Data

Methods

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

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

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

(.@) :: SomeData repr (a -> b) -> SomeData repr a -> SomeData repr b 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 Functionable

class Functionable repr where Source #

Minimal complete definition

Nothing

Methods

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

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

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

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

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

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

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

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

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

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

Instances

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

Defined in Symantic.Data

Methods

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 #

Class Anythingable

class Anythingable repr where Source #

Minimal complete definition

Nothing

Methods

anything :: repr a -> repr a Source #

Instances

Instances details
Anythingable Viewer Source # 
Instance details

Defined in Symantic.Viewer

Methods

anything :: Viewer a -> Viewer 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 Viewer Source # 
Instance details

Defined in Symantic.Viewer

Methods

bottom :: Viewer 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 Viewer Source # 
Instance details

Defined in Symantic.Viewer

Methods

constant :: c -> Viewer 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

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

Defined in Symantic.Viewer

Methods

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

right :: Viewer (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 Viewer Source # 
Instance details

Defined in Symantic.Viewer

Methods

equal :: Eq a => Viewer (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 -> repr a -> repr 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 Inferable

class Inferable a repr where Source #

Minimal complete definition

Nothing

Methods

infer :: repr a Source #

default infer :: FromDerived (Inferable a) repr => repr a Source #

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

bool :: Inferable Bool repr => repr Bool Source #

char :: Inferable Char repr => repr Char Source #

int :: Inferable Int repr => repr Int Source #

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

Defined in Symantic.Viewer

Methods

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

nil :: Viewer [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 Viewer Source # 
Instance details

Defined in Symantic.Viewer

Methods

nothing :: Viewer (Maybe a) Source #

just :: Viewer (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 infixl 4 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
     

Instances

Instances details
Category Iso Source # 
Instance details

Defined in Symantic.Classes

Methods

id :: forall (a :: k). Iso a a #

(.) :: forall (b :: k) (c :: k) (a :: k). Iso b c -> Iso a b -> Iso a c #

Class ProductFunctor

class ProductFunctor repr where Source #

Beware that this is an infixr, not infixl like <*>; this is to follow what is expected by ADT.

Minimal complete definition

Nothing

Methods

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

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

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

default (<.) :: IsoFunctor repr => repr a -> repr () -> repr a Source #

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

default (.>) :: IsoFunctor repr => repr () -> repr a -> repr a Source #

Class SumFunctor

class SumFunctor repr where Source #

Beware that this is an infixr, not infixl like <|>; this is to follow what is expected by ADT.

Minimal complete definition

Nothing

Methods

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

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

Class AlternativeFunctor

class AlternativeFunctor repr where Source #

Beware that this is an infixr, not infixl like <|>; this is to follow what is expected by ADT.

Minimal complete definition

Nothing

Methods

(<|>) :: repr a -> repr a -> repr a infixr 3 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 -..-> a) -> (a -> Tuples args) -> repr (Tuples args) -> repr a Source #

default dicurry :: FromDerived1 Dicurryable repr => CurryN args => proxy args -> (args -..-> a) -> (a -> Tuples args) -> repr (Tuples args) -> repr a Source #

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

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

Class Monoidable

class (Emptyable repr, Semigroupable repr) => Monoidable repr Source #

Instances

Instances details
(Emptyable repr, Semigroupable repr) => Monoidable repr Source # 
Instance details

Defined in Symantic.Classes

Class Emptyable

class Emptyable repr where Source #

Minimal complete definition

Nothing

Methods

empty :: repr a Source #

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

Instances

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

Defined in Symantic.Data

Methods

empty :: SomeData repr a Source #

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

Defined in Symantic.Data

Methods

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

Emptyable (Data Emptyable repr) Source # 
Instance details

Defined in Symantic.Data

Methods

empty :: Data Emptyable repr a Source #

data Data Emptyable repr a Source # 
Instance details

Defined in Symantic.Data

data Data Emptyable repr a where

Class Semigroupable

class Semigroupable repr where Source #

Minimal complete definition

Nothing

Methods

concat :: Semigroup a => repr (a -> a -> a) infixr 6 Source #

default concat :: FromDerived Semigroupable repr => Semigroup a => repr (a -> a -> a) Source #

Instances

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

Defined in Symantic.Data

Methods

concat :: Semigroup a => SomeData repr (a -> a -> a) Source #

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

Defined in Symantic.Data

Methods

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

Semigroupable (Data Semigroupable repr) Source # 
Instance details

Defined in Symantic.Data

Methods

concat :: Semigroup a => Data Semigroupable repr (a -> a -> a) Source #

data Data Semigroupable repr a Source # 
Instance details

Defined in Symantic.Data

data Data Semigroupable repr a where

(<>) :: Abstractable repr => Semigroupable repr => Semigroup a => repr a -> repr a -> repr a infixr 6 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 #

many :: Repeatable repr => repr a -> repr [a] Source #

Alias to many0.

some :: Repeatable repr => repr a -> repr [a] Source #

Alias to many1.

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) infixr 4 Source #

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

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

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

Class Voidable

class Voidable repr where Source #

Minimal complete definition

Nothing

Methods

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

Useful to supply (a) to a (repr) consuming (a), for example in the format of a printing interpreter.

default void :: FromDerived1 Voidable repr => a -> 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 #