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

Symantic.Parser.Haskell

Description

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

Synopsis

Type ValueCode

data ValueCode a Source #

Compile-time value and corresponding code (that can produce that value at runtime).

Constructors

ValueCode 

Fields

Instances

Instances details
Haskellable ValueCode Source # 
Instance details

Defined in Symantic.Parser.Haskell

Methods

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

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

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

bool :: Bool -> ValueCode Bool Source #

char :: Lift tok => tok -> ValueCode tok Source #

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

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

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

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

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

nil :: ValueCode [a] 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 #

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 #

Type Value

newtype Value a Source #

Constructors

Value 

Fields

Instances

Instances details
Haskellable Value Source # 
Instance details

Defined in Symantic.Parser.Haskell

Methods

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

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

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

bool :: Bool -> Value Bool Source #

char :: Lift tok => tok -> Value tok Source #

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

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

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

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

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

nil :: Value [a] Source #

unit :: Value () Source #

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

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

nothing :: Value (Maybe a) Source #

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

Trans Haskell Value Source # 
Instance details

Defined in Symantic.Parser.Haskell

Methods

trans :: Haskell a -> Value a Source #

Class Haskellable

class Haskellable (repr :: Type -> Type) where Source #

Final encoding of some Haskell functions useful for some optimizations in optimizeComb.

Methods

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

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

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

bool :: Bool -> repr Bool Source #

char :: Lift tok => tok -> repr tok Source #

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

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

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

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

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

nil :: repr [a] 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 #

Instances

Instances details
Haskellable Haskell Source # 
Instance details

Defined in Symantic.Parser.Haskell

Methods

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

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

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

bool :: Bool -> Haskell Bool Source #

char :: Lift tok => tok -> Haskell tok Source #

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

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

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

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

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

nil :: Haskell [a] Source #

unit :: Haskell () Source #

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

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

nothing :: Haskell (Maybe a) Source #

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

Haskellable Value Source # 
Instance details

Defined in Symantic.Parser.Haskell

Methods

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

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

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

bool :: Bool -> Value Bool Source #

char :: Lift tok => tok -> Value tok Source #

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

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

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

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

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

nil :: Value [a] Source #

unit :: Value () Source #

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

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

nothing :: Value (Maybe a) Source #

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

Haskellable ValueCode Source # 
Instance details

Defined in Symantic.Parser.Haskell

Methods

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

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

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

bool :: Bool -> ValueCode Bool Source #

char :: Lift tok => tok -> ValueCode tok Source #

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

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

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

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

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

nil :: ValueCode [a] 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 #

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

Defined in Symantic.Parser.Haskell

Methods

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

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

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

bool :: Bool -> CodeQ Bool Source #

char :: Lift tok => tok -> CodeQ tok Source #

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

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

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

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

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

nil :: CodeQ [a] 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 #

Type Haskellable

data Haskell a where Source #

Initial encoding of Haskellable.

Constructors

Haskell :: ValueCode a -> Haskell a 
(:.) :: Haskell ((b -> c) -> (a -> b) -> a -> c) infixr 9 
(:$) :: Haskell ((a -> b) -> a -> b) infixr 0 
(:@) :: Haskell (a -> b) -> Haskell a -> Haskell b infixl 9 
Cons :: Haskell (a -> [a] -> [a]) 
Const :: Haskell (a -> b -> a) 
Eq :: Eq a => Haskell a -> Haskell (a -> Bool) 
Flip :: Haskell ((a -> b -> c) -> b -> a -> c) 
Id :: Haskell (a -> a) 
Unit :: Haskell () 

Instances

Instances details
Haskellable Haskell Source # 
Instance details

Defined in Symantic.Parser.Haskell

Methods

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

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

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

bool :: Bool -> Haskell Bool Source #

char :: Lift tok => tok -> Haskell tok Source #

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

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

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

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

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

nil :: Haskell [a] Source #

unit :: Haskell () Source #

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

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

nothing :: Haskell (Maybe a) Source #

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

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 Haskell (CodeQ :: Type -> Type) Source # 
Instance details

Defined in Symantic.Parser.Haskell

Methods

trans :: Haskell a -> CodeQ a Source #

Show (Haskell a) Source # 
Instance details

Defined in Symantic.Parser.Haskell

Methods

showsPrec :: Int -> Haskell a -> ShowS #

show :: Haskell a -> String #

showList :: [Haskell a] -> ShowS #

type Output Haskell Source # 
Instance details

Defined in Symantic.Parser.Haskell