symantic-parser-0.1.0.20210201: 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 (Any repr) Source # 
Instance details

Defined in Symantic.Univariant.Trans

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

Defined in Symantic.Parser.Haskell.Optimize

type Output (Term 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

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 repr (Any repr) Source # 
Instance details

Defined in Symantic.Univariant.Trans

Methods

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

Trans repr (Term repr) Source # 
Instance details

Defined in Symantic.Parser.Haskell.Optimize

Methods

trans :: repr a -> Term repr 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 #

Trans (Term Identity) Identity Source # 
Instance details

Defined in Symantic.Parser.Haskell.Optimize

Methods

trans :: Term Identity a -> Identity a Source #

Trans (Term ValueCode) ValueCode Source # 
Instance details

Defined in Symantic.Parser.Haskell.Optimize

Trans (SomeComb repr) repr Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

Methods

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

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

Defined in Symantic.Parser.Haskell.Optimize

Methods

trans :: Term CodeQ a -> CodeQ a Source #

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

Defined in Symantic.Parser.Haskell.Optimize

Methods

trans :: Term CodeQ a -> Term ValueCode a Source #

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

Defined in Symantic.Parser.Haskell.Optimize

Methods

trans :: Term ValueCode a -> Term CodeQ a Source #

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

Defined in Symantic.Parser.Grammar.Optimize

Methods

trans :: Comb (Letable letName) repr a -> repr a Source #

Lookable repr => Trans (Comb Lookable repr) repr Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

Methods

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

Satisfiable tok repr => Trans (Comb (Satisfiable tok) repr) repr Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

Methods

trans :: Comb (Satisfiable tok) repr a -> repr a Source #

Foldable repr => Trans (Comb Foldable repr) repr Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

Methods

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

Matchable repr => Trans (Comb Matchable repr) repr Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

Methods

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

Selectable repr => Trans (Comb Selectable repr) repr Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

Methods

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

Alternable repr => Trans (Comb Alternable repr) repr Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

Methods

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

Applicable repr => Trans (Comb Applicable repr) repr Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

Methods

trans :: Comb Applicable repr a -> 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 #

Trans (SomeInstr repr inp vs es) (repr inp vs es) Source # 
Instance details

Defined in Symantic.Parser.Machine.Optimize

Methods

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

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

Defined in Symantic.Parser.Machine.Optimize

Methods

trans :: Instr (Readable tok) repr inp vs es a -> repr inp vs es a Source #

Joinable repr => Trans (Instr Joinable repr inp vs es) (repr inp vs es) Source # 
Instance details

Defined in Symantic.Parser.Machine.Optimize

Methods

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

Inputable repr => Trans (Instr Inputable repr inp vs es) (repr inp vs es) Source # 
Instance details

Defined in Symantic.Parser.Machine.Optimize

Methods

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

Failable repr => Trans (Instr Failable repr inp vs es) (repr inp vs es) Source # 
Instance details

Defined in Symantic.Parser.Machine.Optimize

Methods

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

Branchable repr => Trans (Instr Branchable repr inp vs es) (repr inp vs es) Source # 
Instance details

Defined in Symantic.Parser.Machine.Optimize

Methods

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

Routinable repr => Trans (Instr Routinable repr inp vs es) (repr inp vs es) Source # 
Instance details

Defined in Symantic.Parser.Machine.Optimize

Methods

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

Stackable repr => Trans (Instr Stackable repr inp vs es) (repr inp vs es) Source # 
Instance details

Defined in Symantic.Parser.Machine.Optimize

Methods

trans :: Instr Stackable repr 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 #

(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 #

(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 #

(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