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

Safe HaskellNone
LanguageHaskell2010

LambdaCube.Compiler.Parser

Documentation

newtype SData a Source

Constructors

SData a 

Instances

pattern MatchName :: [Char] -> [Char] Source

pattern SVar :: SIName -> Int -> SExp' t Source

pattern SType :: SExp' t Source

pattern Wildcard :: SExp' t -> SExp' t Source

pattern SAppV :: SExp' t -> SExp' t -> SExp' t infixl 2 Source

pattern SLamV :: SExp' t -> SExp' t Source

pattern SAnn :: SExp' t -> SExp' t -> SExp' t Source

pattern SBuiltin :: SName -> SExp' t Source

pattern SPi :: Visibility -> SExp' t -> SExp' t -> SExp' t Source

pattern Primitive :: SIName -> SExp -> Stmt Source

pattern SLabelEnd :: SExp' t -> SExp' t Source

pattern SLam :: Visibility -> SExp' t -> SExp' t -> SExp' t Source

pattern Parens :: SExp' t -> SExp' t Source

pattern TyType :: SExp' t -> SExp' t Source

pattern Wildcard_ :: SI -> SExp' t -> SExp' t Source

lowerDB :: a -> a Source

cmpDB :: Up a => t -> a -> Bool Source

newtype MaxDB Source

Constructors

MaxDB 

Fields

getMaxDB :: Int
 

iterateN :: Int -> (a -> a) -> a -> a Source

traceD :: String -> a -> a Source

addParamsS :: Foldable t => t (Visibility, SExp' t1) -> SExp' t1 -> SExp' t1 Source

apps' :: Foldable t => SExp' a -> t (Visibility, SExp' a) -> SExp' a Source

downToS :: [Char] -> Int -> Int -> [SExp' t] Source

addForalls :: Up a => Extensions -> [SName] -> SExp' a -> SExp' a Source

class Up a where Source

Minimal complete definition

fold, maxDB_

Methods

up_ :: Int -> Int -> a -> a Source

up1_ :: Int -> a -> a Source

fold :: Monoid e => (Int -> Int -> e) -> Int -> a -> e Source

used :: Int -> a -> Bool Source

maxDB_ :: a -> MaxDB Source

closedExp :: a -> a Source

Instances

Up Neutral Source 
Up Exp Source 
Up a => Up (SExp' a) Source 
(Up a, Up b) => Up (a, b) Source 

up1 :: Up a => a -> a Source

up :: Up a => Int -> a -> a Source

type Doc = NameDB PrecString Source

shLam :: (MonadReader [[Char]] m, MonadState [[Char]] m) => Bool -> Binder -> PS [Char] -> m (PS String) -> m (PS String) Source

shApp :: Visibility -> PrecString -> PS String -> PS String Source

shLet :: MonadReader [[Char]] m => Int -> m (PS String) -> m (PS [Char]) -> m (PS String) Source

shLet_ :: (MonadReader [String] m, MonadState [String] m) => m (PS String) -> m (PS [Char]) -> m (PS String) Source

shAtom :: a -> PS a Source

shAnn :: [Char] -> Bool -> PS [Char] -> PS [Char] -> PS [Char] Source

shVar :: MonadReader [[Char]] m => Int -> m [Char] Source

epar :: Functor f => f [Char] -> f [Char] Source

sExpDoc :: Up a => SExp' a -> Doc Source

shCstr :: PS String -> PS String -> PS String Source

shTuple :: IsString [a] => [PS [a]] -> PS [a] Source

mtrace :: Monad m => String -> m () Source

sortDefs :: t -> [Stmt] -> [Stmt] Source

trSExp' :: SExp' Void -> SExp' b Source

substSG0 :: Up a => SIName -> SExp' a -> SExp' a Source

substS :: Up a => Int -> a -> SExp' a -> SExp' a Source

data Stmt Source

Constructors

Let SIName (Maybe SExp) SExp 
Data SIName [(Visibility, SExp)] SExp Bool [(SIName, SExp)] 
PrecDef SIName Fixity 
TypeFamily SIName [(Visibility, SExp)] SExp 
Class SIName [SExp] [(SIName, SExp)] 
Instance SIName [Pat] [SExp] [Stmt] 
TypeAnn SIName SExp 
FunAlt SIName [((Visibility, SExp), Pat)] (Either [(SExp, SExp)] SExp) 

Instances