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

Safe HaskellNone
LanguageHaskell2010

LambdaCube.Compiler.DesugaredSource

Documentation

pattern Ticked :: SName -> SName Source #

pattern CaseName :: SName -> SName Source #

pattern MatchName :: SName -> SName Source #

newtype SPos Source #

Constructors

SPos_ Int 

Instances

Eq SPos Source # 

Methods

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

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

Ord SPos Source # 

Methods

compare :: SPos -> SPos -> Ordering #

(<) :: SPos -> SPos -> Bool #

(<=) :: SPos -> SPos -> Bool #

(>) :: SPos -> SPos -> Bool #

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

max :: SPos -> SPos -> SPos #

min :: SPos -> SPos -> SPos #

PShow SPos Source # 

Methods

pShow :: SPos -> Doc Source #

pattern SPos :: Int -> Int -> SPos Source #

data Range Source #

Constructors

Range 

Instances

Eq Range Source # 

Methods

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

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

Ord Range Source # 

Methods

compare :: Range -> Range -> Ordering #

(<) :: Range -> Range -> Bool #

(<=) :: Range -> Range -> Bool #

(>) :: Range -> Range -> Bool #

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

max :: Range -> Range -> Range #

min :: Range -> Range -> Range #

Show Range Source # 

Methods

showsPrec :: Int -> Range -> ShowS #

show :: Range -> String #

showList :: [Range] -> ShowS #

PShow Range Source # 

Methods

pShow :: Range -> Doc Source #

data SI Source #

Constructors

NoSI (Set String) 
RangeSI Range 

Instances

Eq SI Source # 

Methods

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

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

Ord SI Source # 

Methods

compare :: SI -> SI -> Ordering #

(<) :: SI -> SI -> Bool #

(<=) :: SI -> SI -> Bool #

(>) :: SI -> SI -> Bool #

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

max :: SI -> SI -> SI #

min :: SI -> SI -> SI #

Monoid SI Source # 

Methods

mempty :: SI #

mappend :: SI -> SI -> SI #

mconcat :: [SI] -> SI #

PShow SI Source # 

Methods

pShow :: SI -> Doc Source #

SourceInfo SI Source # 

Methods

sourceInfo :: SI -> SI Source #

validate :: SI -> [SI] -> SI Source #

class SourceInfo a where Source #

Minimal complete definition

sourceInfo

Methods

sourceInfo :: a -> SI Source #

class SetSourceInfo a where Source #

Minimal complete definition

setSI

Methods

setSI :: SI -> a -> a Source #

Instances

data SIName Source #

Constructors

SIName__ 

Instances

Eq SIName Source # 

Methods

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

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

Ord SIName Source # 
Show SIName Source # 
PShow SIName Source # 

Methods

pShow :: SIName -> Doc Source #

Rearrange ParPat Source # 
Rearrange Pat Source # 

Methods

rearrange :: Int -> RearrangeFun -> Pat -> Pat Source #

SetSourceInfo SIName Source # 

Methods

setSI :: SI -> SIName -> SIName Source #

SourceInfo SIName Source # 

Methods

sourceInfo :: SIName -> SI Source #

PatVars ParPat Source # 

Methods

getPVars :: ParPat -> [SIName] Source #

PatVars Pat Source # 

Methods

getPVars :: Pat -> [SIName] Source #

DeBruijnify SIName Stmt Source # 

Methods

deBruijnify_ :: Int -> [SIName] -> Stmt -> Stmt Source #

DeBruijnify SIName SExp Source # 

Methods

deBruijnify_ :: Int -> [SIName] -> SExp -> SExp Source #

DeBruijnify SIName GuardTree Source # 
DeBruijnify SIName ParPat Source # 

Methods

deBruijnify_ :: Int -> [SIName] -> ParPat -> ParPat Source #

DeBruijnify SIName PreStmt Source # 
DeBruijnify SIName a => DeBruijnify SIName (Lets a) Source # 

Methods

deBruijnify_ :: Int -> [SIName] -> Lets a -> Lets a Source #

pattern SIName_ :: SI -> Maybe Fixity -> SName -> SIName Source #

pattern SIName :: SI -> SName -> SIName Source #

newtype FName Source #

Constructors

FName 

Fields

Instances

Eq FName Source # 

Methods

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

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

Ord FName Source # 

Methods

compare :: FName -> FName -> Ordering #

(<) :: FName -> FName -> Bool #

(<=) :: FName -> FName -> Bool #

(>) :: FName -> FName -> Bool #

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

max :: FName -> FName -> FName #

min :: FName -> FName -> FName #

Show FName Source # 

Methods

showsPrec :: Int -> FName -> ShowS #

show :: FName -> String #

showList :: [FName] -> ShowS #

PShow FName Source # 

Methods

pShow :: FName -> Doc Source #

data FNameTag Source #

pattern Tag :: FNameTag -> SIName Source #

pattern FTag :: FNameTag -> FName Source #

toTag :: Enum a => Int -> Maybe a Source #

data Lit Source #

Instances

Eq Lit Source # 

Methods

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

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

PShow Lit Source # 

Methods

pShow :: Lit -> Doc Source #

NType Lit Source # 

Methods

nType :: Lit -> Type Source #

sLHS :: SIName -> SExp' a -> SExp' a Source #

data Binder Source #

Instances

pattern SBind :: forall t. Binder -> SData SIName -> SExp' t -> SExp' t -> SExp' t Source #

pattern SPi :: forall t. Visibility -> SExp' t -> SExp' t -> SExp' t Source #

pattern SLam :: forall t. Visibility -> SExp' t -> SExp' t -> SExp' t Source #

pattern Wildcard :: forall t. SExp' t -> SExp' t Source #

pattern SLet :: forall t. SIName -> SExp' t -> SExp' t -> SExp' t Source #

pattern SLamV :: forall t. SExp' t -> SExp' t Source #

pattern SVar :: forall t. SIName -> Int -> SExp' t Source #

pattern SApp :: forall t. Visibility -> SExp' t -> SExp' t -> SExp' t Source #

pattern SAppH :: forall t. SExp' t -> SExp' t -> SExp' t infixl 2 Source #

pattern SAppV :: forall t. SExp' t -> SExp' t -> SExp' t infixl 2 Source #

pattern SAppV2 :: forall t. SExp' t -> SExp' t -> SExp' t -> SExp' t Source #

pattern SBuiltin :: forall t. FNameTag -> SExp' t Source #

pattern SRHS :: forall t. SExp' t -> SExp' t Source #

pattern Section :: forall t. SExp' t -> SExp' t Source #

pattern SType :: forall t. SExp' t Source #

pattern SConstraint :: forall t. SExp' t Source #

pattern Parens :: forall t. SExp' t -> SExp' t Source #

pattern SAnn :: forall t. SExp' t -> SExp' t -> SExp' t Source #

pattern TyType :: forall t. SExp' t -> SExp' t Source #

pattern SCW :: forall t. SExp' t -> SExp' t Source #

pattern HList :: forall t. SExp' t -> SExp' t Source #

pattern HCons :: forall t. SExp' t -> SExp' t -> SExp' t Source #

pattern HNil :: forall t. SExp' t Source #

pattern BList :: forall t. SExp' t -> SExp' t Source #

pattern BCons :: forall t. SExp' t -> SExp' t -> SExp' t Source #

pattern BNil :: forall t. SExp' t Source #

pattern UncurryS :: forall a. [(Visibility, SExp' a)] -> SExp' a -> SExp' a Source #

pattern AppsS :: forall a. SExp' a -> [(Visibility, SExp' a)] -> SExp' a Source #

getApps :: SExp' t -> (SExp' t, [(Visibility, SExp' t)]) Source #

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

foldS :: Monoid m => (Int -> t -> m) -> (SIName -> Int -> m) -> (SIName -> Int -> Int -> m) -> Int -> SExp' t -> m Source #

foldName :: Monoid m => (SIName -> m) -> SExp' Void -> m Source #

mapS :: (Int -> a -> SExp' a) -> (SIName -> Int -> SExp' a) -> (SIName -> Int -> Int -> SExp' a) -> Int -> SExp' a -> SExp' a Source #

trSExp :: (a -> b) -> SExp' a -> SExp' b Source #

usedVar' :: HasFreeVars a1 => Int -> a1 -> a -> Maybe a Source #

shLet :: Int -> Doc -> Doc -> Doc Source #

pattern StLet :: SIName -> Maybe (SExp' Void) -> SExp' Void -> Stmt Source #

getSAnn :: SExp' t -> (SExp' t, Maybe (SExp' t)) Source #

data Fixity Source #

Constructors

Infix !Int 
InfixL !Int 
InfixR !Int 

Instances