purescript-0.15.9: PureScript Programming Language Compiler
Safe HaskellSafe-Inferred
LanguageHaskell2010

Language.PureScript.CoreImp.AST

Description

Data types for the imperative core AST

Synopsis

Documentation

data UnaryOperator Source #

Built-in unary operators

Constructors

Negate 
Not 
BitwiseNot 
Positive 
New 

data CIComments Source #

Data type for CoreImp comments, which can come from either the PureScript source or internal transformations.

Instances

Instances details
Show CIComments Source # 
Instance details

Defined in Language.PureScript.CoreImp.AST

Eq CIComments Source # 
Instance details

Defined in Language.PureScript.CoreImp.AST

data InitializerEffects Source #

Indicates whether the initializer of a variable is known not to have side effects, and thus can be inlined if needed or removed if unneeded.

Constructors

NoEffects 
UnknownEffects 

data AST Source #

Data type for simplified JavaScript expressions

Constructors

NumericLiteral (Maybe SourceSpan) (Either Integer Double)

A numeric literal

StringLiteral (Maybe SourceSpan) PSString

A string literal

BooleanLiteral (Maybe SourceSpan) Bool

A boolean literal

Unary (Maybe SourceSpan) UnaryOperator AST

A unary operator application

Binary (Maybe SourceSpan) BinaryOperator AST AST

A binary operator application

ArrayLiteral (Maybe SourceSpan) [AST]

An array literal

Indexer (Maybe SourceSpan) AST AST

An array indexer expression

ObjectLiteral (Maybe SourceSpan) [(PSString, AST)]

An object literal

Function (Maybe SourceSpan) (Maybe Text) [Text] AST

A function introduction (optional name, arguments, body)

App (Maybe SourceSpan) AST [AST]

Function application

Var (Maybe SourceSpan) Text

Variable

ModuleAccessor (Maybe SourceSpan) ModuleName PSString

Value from another module

Block (Maybe SourceSpan) [AST]

A block of expressions in braces

VariableIntroduction (Maybe SourceSpan) Text (Maybe (InitializerEffects, AST))

A variable introduction and optional initialization

Assignment (Maybe SourceSpan) AST AST

A variable assignment

While (Maybe SourceSpan) AST AST

While loop

For (Maybe SourceSpan) Text AST AST AST

For loop

ForIn (Maybe SourceSpan) Text AST AST

ForIn loop

IfElse (Maybe SourceSpan) AST AST (Maybe AST)

If-then-else statement

Return (Maybe SourceSpan) AST

Return statement

ReturnNoResult (Maybe SourceSpan)

Return statement with no return value

Throw (Maybe SourceSpan) AST

Throw statement

InstanceOf (Maybe SourceSpan) AST AST

instanceof check

Comment CIComments AST

Commented JavaScript

Instances

Instances details
Show AST Source # 
Instance details

Defined in Language.PureScript.CoreImp.AST

Methods

showsPrec :: Int -> AST -> ShowS #

show :: AST -> String #

showList :: [AST] -> ShowS #

Eq AST Source # 
Instance details

Defined in Language.PureScript.CoreImp.AST

Methods

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

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

everywhere :: (AST -> AST) -> AST -> AST Source #

everywhereTopDownM :: Monad m => (AST -> m AST) -> AST -> m AST Source #

everything :: (r -> r -> r) -> (AST -> r) -> AST -> r Source #