symantic-parser-0.0.0.20210102: Parser combinators statically optimized and staged via typed meta-programming
Safe HaskellNone
LanguageHaskell2010

Symantic.Univariant.Trans

Synopsis

Type family Output

type family Output (repr :: Type -> Type) :: Type -> Type Source #

Instances

Instances details
type Output Haskell Source # 
Instance details

Defined in Symantic.Parser.Haskell

type Output (Any repr) Source # 
Instance details

Defined in Symantic.Univariant.Trans

type Output (Any repr) = repr
type Output (Comb repr) Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

type Output (Comb repr) = repr
type Output (CleanDefs _letName repr) Source # 
Instance details

Defined in Symantic.Univariant.Letable

type Output (CleanDefs _letName repr) = repr
type Output (ObserveSharing letName repr) Source # 
Instance details

Defined in Symantic.Univariant.Letable

type Output (ObserveSharing letName repr) = CleanDefs letName repr
type Output (OptimizeComb _letName repr) Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

type Output (OptimizeComb _letName repr) = Comb repr

Class Trans

class Trans from to where Source #

A translation from an interpreter (from) to an interpreter (to).

Methods

trans :: from a -> to a Source #

Instances

Instances details
Trans Haskell Value Source # 
Instance details

Defined in Symantic.Parser.Haskell

Methods

trans :: Haskell a -> Value a Source #

Trans Haskell ValueCode Source # 
Instance details

Defined in Symantic.Parser.Haskell

Methods

trans :: Haskell a -> ValueCode a Source #

Trans ValueCode Haskell Source # 
Instance details

Defined in Symantic.Parser.Haskell

Methods

trans :: ValueCode a -> Haskell a Source #

Trans repr (Any repr) Source # 
Instance details

Defined in Symantic.Univariant.Trans

Methods

trans :: repr a -> Any repr a Source #

Trans Haskell (CodeQ :: Type -> Type) Source # 
Instance details

Defined in Symantic.Parser.Haskell

Methods

trans :: Haskell a -> CodeQ a Source #

Trans InstrPure (CodeQ :: Type -> Type) Source # 
Instance details

Defined in Symantic.Parser.Machine.Instructions

Methods

trans :: InstrPure a -> CodeQ a Source #

Trans repr (CleanDefs letName repr) Source # 
Instance details

Defined in Symantic.Univariant.Letable

Methods

trans :: repr a -> CleanDefs letName repr a Source #

Trans (Any repr) repr Source # 
Instance details

Defined in Symantic.Univariant.Trans

Methods

trans :: Any repr a -> repr a Source #

(Applicable repr, Alternable repr, Selectable repr, Foldable repr, Lookable repr, Matchable repr, Letable Name repr) => Trans (Comb repr) repr Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

Methods

trans :: Comb repr a -> repr a Source #

Trans (Comb repr) (OptimizeComb letName repr) Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

Methods

trans :: Comb repr a -> OptimizeComb letName repr a Source #

Trans (Comb repr) repr => Trans (OptimizeComb letName repr) repr Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

Methods

trans :: OptimizeComb letName repr a -> repr a Source #

Trans (OptimizeComb letName repr) (Comb repr) Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

Methods

trans :: OptimizeComb letName repr a -> Comb repr a Source #

(Letable letName repr, MakeLetName letName, Eq letName, Hashable letName) => Trans (CleanDefs letName repr) (ObserveSharing letName repr) Source # 
Instance details

Defined in Symantic.Univariant.Letable

Methods

trans :: CleanDefs letName repr a -> ObserveSharing letName repr a Source #

(Executable repr, Readable repr (InputToken inp)) => Trans (Instr inp vs es) (repr inp vs es) Source # 
Instance details

Defined in Symantic.Parser.Machine.Instructions

Methods

trans :: Instr inp vs es a -> repr inp vs es a Source #

Class BiTrans

type BiTrans from to = (Trans from to, Trans to from) Source #

Convenient type class synonym. Note that this is not necessarily a bijective translation, a trans being not necessarily injective nor surjective.

Class Liftable

type Liftable repr = Trans (Output repr) repr Source #

Convenient type class synonym for using Output

lift :: forall repr a. Liftable repr => Output repr a -> repr a Source #

unlift :: forall repr a. Trans repr (Output repr) => repr a -> Output repr a Source #

Class Unliftable

type Unliftable repr = Trans repr (Output repr) Source #

Convenient type class synonym for using Output

Class Trans1

class Trans1 from to where Source #

Minimal complete definition

Nothing

Methods

trans1 :: (from a -> from b) -> to a -> to b Source #

trans1 :: BiTrans from to => (from a -> from b) -> to a -> to b Source #

Instances

Instances details
Trans1 repr (Any repr) Source # 
Instance details

Defined in Symantic.Univariant.Trans

Methods

trans1 :: (repr a -> repr b) -> Any repr a -> Any repr b Source #

Trans1 repr (CleanDefs letName repr) Source # 
Instance details

Defined in Symantic.Univariant.Letable

Methods

trans1 :: (repr a -> repr b) -> CleanDefs letName repr a -> CleanDefs letName repr b Source #

Trans1 (Any repr) repr Source # 
Instance details

Defined in Symantic.Univariant.Trans

Methods

trans1 :: (Any repr a -> Any repr b) -> repr a -> repr b Source #

Trans1 (Comb repr) (OptimizeComb letName repr) Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

Methods

trans1 :: (Comb repr a -> Comb repr b) -> OptimizeComb letName repr a -> OptimizeComb letName repr b Source #

(Letable letName repr, MakeLetName letName, Eq letName, Hashable letName) => Trans1 (CleanDefs letName repr) (ObserveSharing letName repr) Source # 
Instance details

Defined in Symantic.Univariant.Letable

Methods

trans1 :: (CleanDefs letName repr a -> CleanDefs letName repr b) -> ObserveSharing letName repr a -> ObserveSharing letName repr b Source #

Class Liftable1

type Liftable1 repr = Trans1 (Output repr) repr Source #

Convenient type class synonym for using Output

lift1 :: forall repr a b. Liftable1 repr => (Output repr a -> Output repr b) -> repr a -> repr b Source #

Class Trans2

class Trans2 from to where Source #

Minimal complete definition

Nothing

Methods

trans2 :: (from a -> from b -> from c) -> to a -> to b -> to c Source #

trans2 :: BiTrans from to => (from a -> from b -> from c) -> to a -> to b -> to c Source #

Instances

Instances details
Trans2 repr (Any repr) Source # 
Instance details

Defined in Symantic.Univariant.Trans

Methods

trans2 :: (repr a -> repr b -> repr c) -> Any repr a -> Any repr b -> Any repr c Source #

Trans2 repr (CleanDefs letName repr) Source # 
Instance details

Defined in Symantic.Univariant.Letable

Methods

trans2 :: (repr a -> repr b -> repr c) -> CleanDefs letName repr a -> CleanDefs letName repr b -> CleanDefs letName repr c Source #

Trans2 (Any repr) repr Source # 
Instance details

Defined in Symantic.Univariant.Trans

Methods

trans2 :: (Any repr a -> Any repr b -> Any repr c) -> repr a -> repr b -> repr c Source #

Trans2 (Comb repr) (OptimizeComb letName repr) Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

Methods

trans2 :: (Comb repr a -> Comb repr b -> Comb repr c) -> OptimizeComb letName repr a -> OptimizeComb letName repr b -> OptimizeComb letName repr c Source #

(Letable letName repr, MakeLetName letName, Eq letName, Hashable letName) => Trans2 (CleanDefs letName repr) (ObserveSharing letName repr) Source # 
Instance details

Defined in Symantic.Univariant.Letable

Methods

trans2 :: (CleanDefs letName repr a -> CleanDefs letName repr b -> CleanDefs letName repr c) -> ObserveSharing letName repr a -> ObserveSharing letName repr b -> ObserveSharing letName repr c Source #

Class Liftable2

type Liftable2 repr = Trans2 (Output repr) repr Source #

Convenient type class synonym for using Output

lift2 :: forall repr a b c. Liftable2 repr => (Output repr a -> Output repr b -> Output repr c) -> repr a -> repr b -> repr c Source #

Class Trans3

class Trans3 from to where Source #

Minimal complete definition

Nothing

Methods

trans3 :: (from a -> from b -> from c -> from d) -> to a -> to b -> to c -> to d Source #

trans3 :: BiTrans from to => (from a -> from b -> from c -> from d) -> to a -> to b -> to c -> to d Source #

Instances

Instances details
Trans3 repr (Any repr) Source # 
Instance details

Defined in Symantic.Univariant.Trans

Methods

trans3 :: (repr a -> repr b -> repr c -> repr d) -> Any repr a -> Any repr b -> Any repr c -> Any repr d Source #

Trans3 repr (CleanDefs letName repr) Source # 
Instance details

Defined in Symantic.Univariant.Letable

Methods

trans3 :: (repr a -> repr b -> repr c -> repr d) -> CleanDefs letName repr a -> CleanDefs letName repr b -> CleanDefs letName repr c -> CleanDefs letName repr d Source #

Trans3 (Any repr) repr Source # 
Instance details

Defined in Symantic.Univariant.Trans

Methods

trans3 :: (Any repr a -> Any repr b -> Any repr c -> Any repr d) -> repr a -> repr b -> repr c -> repr d Source #

Trans3 (Comb repr) (OptimizeComb letName repr) Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

Methods

trans3 :: (Comb repr a -> Comb repr b -> Comb repr c -> Comb repr d) -> OptimizeComb letName repr a -> OptimizeComb letName repr b -> OptimizeComb letName repr c -> OptimizeComb letName repr d Source #

(Letable letName repr, MakeLetName letName, Eq letName, Hashable letName) => Trans3 (CleanDefs letName repr) (ObserveSharing letName repr) Source # 
Instance details

Defined in Symantic.Univariant.Letable

Methods

trans3 :: (CleanDefs letName repr a -> CleanDefs letName repr b -> CleanDefs letName repr c -> CleanDefs letName repr d) -> ObserveSharing letName repr a -> ObserveSharing letName repr b -> ObserveSharing letName repr c -> ObserveSharing letName repr d Source #

Class Liftable3

type Liftable3 repr = Trans3 (Output repr) repr Source #

Convenient type class synonym for using Output

lift3 :: forall repr a b c d. Liftable3 repr => (Output repr a -> Output repr b -> Output repr c -> Output repr d) -> repr a -> repr b -> repr c -> repr d Source #

Type Any

newtype Any repr a Source #

A newtype to disambiguate the Trans instance to any other interpreter when there is also one or more Transs to other interpreters with a different interpretation than the generic one.

Constructors

Any 

Fields

Instances

Instances details
Trans3 repr (Any repr) Source # 
Instance details

Defined in Symantic.Univariant.Trans

Methods

trans3 :: (repr a -> repr b -> repr c -> repr d) -> Any repr a -> Any repr b -> Any repr c -> Any repr d Source #

Trans2 repr (Any repr) Source # 
Instance details

Defined in Symantic.Univariant.Trans

Methods

trans2 :: (repr a -> repr b -> repr c) -> Any repr a -> Any repr b -> Any repr c Source #

Trans1 repr (Any repr) Source # 
Instance details

Defined in Symantic.Univariant.Trans

Methods

trans1 :: (repr a -> repr b) -> Any repr a -> Any repr b Source #

Trans repr (Any repr) Source # 
Instance details

Defined in Symantic.Univariant.Trans

Methods

trans :: repr a -> Any repr a Source #

Trans3 (Any repr) repr Source # 
Instance details

Defined in Symantic.Univariant.Trans

Methods

trans3 :: (Any repr a -> Any repr b -> Any repr c -> Any repr d) -> repr a -> repr b -> repr c -> repr d Source #

Trans2 (Any repr) repr Source # 
Instance details

Defined in Symantic.Univariant.Trans

Methods

trans2 :: (Any repr a -> Any repr b -> Any repr c) -> repr a -> repr b -> repr c Source #

Trans1 (Any repr) repr Source # 
Instance details

Defined in Symantic.Univariant.Trans

Methods

trans1 :: (Any repr a -> Any repr b) -> repr a -> repr b Source #

Trans (Any repr) repr Source # 
Instance details

Defined in Symantic.Univariant.Trans

Methods

trans :: Any repr a -> repr a Source #

type Output (Any repr) Source # 
Instance details

Defined in Symantic.Univariant.Trans

type Output (Any repr) = repr