lambdacube-compiler-0.6.0.1: LambdaCube 3D is a DSL to program GPUs

Safe HaskellNone
LanguageHaskell2010

LambdaCube.Compiler.Core

Documentation

data FunDef Source #

Constructors

DeltaDef !Int (FreeVars -> [Exp] -> Exp) 
NoDef 
ExpDef Exp 

data Freq Source #

Constructors

CompileTime 
RunTime 

Instances

Eq Freq Source # 

Methods

(==) :: Freq -> Freq -> Bool #

(/=) :: Freq -> Freq -> Bool #

type Type = Exp Source #

pattern TType :: Exp Source #

pattern NoRHS :: Exp Source #

pattern Fun :: FunName -> [Exp] -> Exp -> Neutral Source #

pattern App_ :: Neutral -> Exp -> Neutral Source #

pattern Con :: ConName -> Int -> [Exp] -> Exp Source #

pattern TyCon :: TyConName -> [Exp] -> Exp Source #

pattern Lam :: Exp -> Exp Source #

pattern Pi :: Visibility -> Exp -> Exp -> Exp Source #

pattern Let :: ExpType -> Exp -> Exp Source #

pattern SubstLet :: Exp -> Exp Source #

pattern CaseFun :: CaseFunName -> [Exp] -> Neutral -> Exp Source #

pattern TyCaseFun :: TyCaseFunName -> [Exp] -> Neutral -> Exp Source #

pattern Var :: Int -> Exp Source #

pattern App :: Exp -> Exp -> Exp infixl 2 Source #

pattern DFun :: FNameTag -> [Exp] -> Exp Source #

pattern DFun_ :: FreeVars -> FNameTag -> [Exp] -> Exp Source #

pattern UFun :: FNameTag -> [Exp] -> Exp Source #

pattern DFunN :: FNameTag -> [Exp] -> Neutral Source #

pattern DFunN_ :: FreeVars -> FNameTag -> [Exp] -> Neutral Source #

pattern ConN :: FNameTag -> [Exp] -> Exp Source #

tCon :: FNameTag -> Int -> Type -> [Exp] -> Exp Source #

tCon_ :: Int -> FNameTag -> Int -> Type -> [Exp] -> Exp Source #

pattern TyConN :: FName -> [Exp] -> Exp Source #

pattern TTyCon0 :: FNameTag -> Exp Source #

pattern (:~>) :: Exp -> Exp -> Exp infixr 1 Source #

pattern TConstraint :: Exp Source #

pattern Unit :: Exp Source #

pattern TInt :: Exp Source #

pattern TNat :: Exp Source #

pattern TBool :: Exp Source #

pattern TFloat :: Exp Source #

pattern TString :: Exp Source #

pattern TChar :: Exp Source #

pattern TOrdering :: Exp Source #

pattern TVec :: Exp -> Exp -> Exp Source #

pattern Empty :: String -> Exp Source #

pattern TT :: Exp Source #

pattern CUnit :: Exp Source #

pattern CEmpty :: String -> Exp Source #

pattern CstrT :: Exp -> Exp -> Exp -> Exp Source #

pattern CstrT' :: Exp -> Exp -> Exp -> Neutral Source #

pattern Coe :: Exp -> Exp -> Exp -> Exp -> Exp Source #

pattern ParEval :: Exp -> Exp -> Exp -> Exp Source #

pattern T2 :: FreeVars -> Exp -> Exp -> Exp Source #

pattern CW :: Exp -> Exp Source #

pattern CW_ :: FreeVars -> Exp -> Exp Source #

pattern CSplit :: Exp -> Exp -> Exp -> Exp Source #

pattern HLit :: Lit -> Exp Source #

pattern HInt :: Integer -> Exp Source #

pattern HFloat :: Double -> Exp Source #

pattern HChar :: Char -> Exp Source #

pattern HString :: String -> Exp Source #

pattern EBool :: Bool -> Exp Source #

pattern ENat :: Int -> Exp Source #

mkFun :: FunName -> [Exp] -> Exp -> Exp Source #

pattern ReducedN :: Exp -> Neutral Source #

pattern Reduced :: Exp -> Exp Source #

class Subst b a where Source #

Minimal complete definition

subst_

Methods

subst_ :: Int -> FreeVars -> b -> a -> a Source #

subst :: (HasFreeVars b, Subst b a) => Int -> b -> a -> a Source #

down :: (PShow a, Subst Exp a, HasFreeVars a) => Int -> a -> Maybe a Source #

varType' :: Int -> [Exp] -> Exp Source #

class MkDoc a where Source #

Minimal complete definition

mkDoc

Methods

mkDoc :: (Bool, Bool) -> a -> Doc Source #

Instances

MkDoc ExpType Source # 

Methods

mkDoc :: (Bool, Bool) -> ExpType -> Doc Source #

MkDoc Neutral Source # 

Methods

mkDoc :: (Bool, Bool) -> Neutral -> Doc Source #

MkDoc Exp Source # 

Methods

mkDoc :: (Bool, Bool) -> Exp -> Doc Source #

pattern FFix :: Exp -> Neutral Source #

evalCoe :: Exp -> Exp -> Exp -> Exp -> Exp Source #

cstr_ :: Exp -> Exp -> Exp -> Exp Source #

cstr :: Exp -> Exp -> Exp -> Exp Source #

pattern NonNeut :: Exp Source #

t2C :: Exp -> Exp -> Exp Source #

cw :: Exp -> Exp Source #

t2_ :: FreeVars -> Exp -> Exp -> Exp Source #

t2 :: Exp -> Exp -> Exp Source #

app_ :: Exp -> Exp -> Exp infixl 2 Source #

appTy :: (Subst b Exp, HasFreeVars b) => Exp -> b -> Exp Source #

class NType a where Source #

Minimal complete definition

nType

Methods

nType :: a -> Type Source #