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

Symantic.Parser.Haskell.Term

Description

Haskell terms which are interesting to pattern-match when optimizing.

Synopsis

Class Termable

class Termable repr where Source #

Single-out some Haskell terms in order to

Minimal complete definition

Nothing

Methods

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

Application, aka. unabstract.

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

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

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.

bool :: Bool -> repr Bool Source #

char :: (Lift tok, Show tok) => tok -> repr tok Source #

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

nil :: repr [a] Source #

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

unit :: repr () Source #

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

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

nothing :: repr (Maybe a) Source #

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

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

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

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

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

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

(.@) :: Liftable2 repr => Termable (Output repr) => repr (a -> b) -> repr a -> repr b infixl 9 Source #

Application, aka. unabstract.

lam :: Liftable repr => Unliftable repr => Termable (Output repr) => (repr a -> repr b) -> repr (a -> b) Source #

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

lam1 :: Liftable repr => Unliftable repr => Termable (Output repr) => (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.

bool :: Liftable repr => Termable (Output repr) => Bool -> repr Bool Source #

char :: Liftable repr => Termable (Output repr) => Lift tok => Show tok => tok -> repr tok Source #

cons :: Liftable repr => Termable (Output repr) => repr (a -> [a] -> [a]) Source #

nil :: Liftable repr => Termable (Output repr) => repr [a] Source #

eq :: Liftable repr => Termable (Output repr) => Eq a => repr (a -> a -> Bool) Source #

unit :: Liftable repr => Termable (Output repr) => repr () Source #

left :: Liftable repr => Termable (Output repr) => repr (l -> Either l r) Source #

right :: Liftable repr => Termable (Output repr) => repr (r -> Either l r) Source #

nothing :: Liftable repr => Termable (Output repr) => repr (Maybe a) Source #

just :: Liftable repr => Termable (Output repr) => repr (a -> Maybe a) Source #

const :: Liftable repr => Termable (Output repr) => repr (a -> b -> a) Source #

flip :: Liftable repr => Termable (Output repr) => repr ((a -> b -> c) -> b -> a -> c) Source #

id :: Liftable repr => Termable (Output repr) => repr (a -> a) Source #

(.) :: Liftable repr => Termable (Output repr) => repr ((b -> c) -> (a -> b) -> a -> c) infixr 9 Source #

($) :: Liftable repr => Termable (Output repr) => repr ((a -> b) -> a -> b) infixr 0 Source #

Instances

Instances details
Termable Identity Source # 
Instance details

Defined in Symantic.Parser.Haskell.Term

Methods

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

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

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

bool :: Bool -> Identity Bool Source #

char :: (Lift tok, Show tok) => tok -> Identity tok Source #

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

nil :: Identity [a] Source #

eq :: Eq a => Identity (a -> a -> Bool) Source #

unit :: Identity () Source #

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

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

nothing :: Identity (Maybe a) Source #

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

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

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

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

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

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

Termable ValueCode Source # 
Instance details

Defined in Symantic.Parser.Haskell.Term

Methods

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

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

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

bool :: Bool -> ValueCode Bool Source #

char :: (Lift tok, Show tok) => tok -> ValueCode tok Source #

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

nil :: ValueCode [a] Source #

eq :: Eq a => ValueCode (a -> a -> Bool) Source #

unit :: ValueCode () Source #

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

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

nothing :: ValueCode (Maybe a) Source #

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

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

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

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

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

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

Termable (CodeQ :: Type -> Type) Source # 
Instance details

Defined in Symantic.Parser.Haskell.Term

Methods

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

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

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

bool :: Bool -> CodeQ Bool Source #

char :: (Lift tok, Show tok) => tok -> CodeQ tok Source #

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

nil :: CodeQ [a] Source #

eq :: Eq a => CodeQ (a -> a -> Bool) Source #

unit :: CodeQ () Source #

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

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

nothing :: CodeQ (Maybe a) Source #

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

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

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

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

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

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

Termable repr => Termable (Term repr) Source # 
Instance details

Defined in Symantic.Parser.Haskell.Optimize

Methods

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

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

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

bool :: Bool -> Term repr Bool Source #

char :: (Lift tok, Show tok) => tok -> Term repr tok Source #

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

nil :: Term repr [a] Source #

eq :: Eq a => Term repr (a -> a -> Bool) Source #

unit :: Term repr () Source #

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

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

nothing :: Term repr (Maybe a) Source #

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

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

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

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

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

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

Type ValueCode

data ValueCode a Source #

Constructors

ValueCode 

Fields

Instances

Instances details
Termable ValueCode Source # 
Instance details

Defined in Symantic.Parser.Haskell.Term

Methods

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

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

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

bool :: Bool -> ValueCode Bool Source #

char :: (Lift tok, Show tok) => tok -> ValueCode tok Source #

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

nil :: ValueCode [a] Source #

eq :: Eq a => ValueCode (a -> a -> Bool) Source #

unit :: ValueCode () Source #

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

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

nothing :: ValueCode (Maybe a) Source #

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

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

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

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

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

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

Trans (Term ValueCode) ValueCode Source # 
Instance details

Defined in Symantic.Parser.Haskell.Optimize

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 #