ghc-lib-parser-9.10.1.20240511: The GHC API, decoupled from GHC versions
Copyright(c) The University of Glasgow 2001
LicenseBSD-style (see the file LICENSE)
MaintainerJeffrey Young <jeffrey.young@iohk.io> Luite Stegeman <luite.stegeman@iohk.io> Sylvain Henry <sylvain.henry@iohk.io> Josh Meredith <josh.meredith@iohk.io>
Stabilityexperimental
Safe HaskellIgnore
LanguageGHC2021

GHC.JS.JStg.Syntax

Description

  • Domain and Purpose

    GHC.JS.JStg.Syntax defines the eDSL that the JS backend's runtime system is written in. Nothing fancy, its just a straightforward deeply embedded DSL.

Synopsis

Deeply embedded JS datatypes

data JStgStat Source #

JavaScript statements, see the ECMA262 Reference for details

Constructors

DeclStat !Ident !(Maybe JStgExpr)

Variable declarations: var foo [= e]

ReturnStat JStgExpr

Return

IfStat JStgExpr JStgStat JStgStat

If

WhileStat Bool JStgExpr JStgStat

While, bool is "do" when True

ForStat JStgStat JStgExpr JStgStat JStgStat

For

ForInStat Bool Ident JStgExpr JStgStat

For-in, bool is "each' when True

SwitchStat JStgExpr [(JStgExpr, JStgStat)] JStgStat

Switch

TryStat JStgStat Ident JStgStat JStgStat

Try

BlockStat [JStgStat]

Blocks

ApplStat JStgExpr [JStgExpr]

Application

UOpStat UOp JStgExpr

Unary operators

AssignStat JStgExpr AOp JStgExpr

Binding form: foo = bar

LabelStat JsLabel JStgStat

Statement Labels, makes me nostalgic for qbasic

BreakStat (Maybe JsLabel)

Break

ContinueStat (Maybe JsLabel)

Continue

FuncStat !Ident [Ident] JStgStat

an explicit function definition

Instances

Instances details
Monoid JStgStat Source # 
Instance details

Defined in GHC.JS.JStg.Syntax

Semigroup JStgStat Source # 
Instance details

Defined in GHC.JS.JStg.Syntax

Generic JStgStat Source # 
Instance details

Defined in GHC.JS.JStg.Syntax

Associated Types

type Rep JStgStat :: Type -> Type #

Methods

from :: JStgStat -> Rep JStgStat x #

to :: Rep JStgStat x -> JStgStat #

ToStat JStgStat Source # 
Instance details

Defined in GHC.JS.Make

Eq JStgStat Source # 
Instance details

Defined in GHC.JS.JStg.Syntax

ToStat [JStgStat] Source # 
Instance details

Defined in GHC.JS.Make

type Rep JStgStat Source # 
Instance details

Defined in GHC.JS.JStg.Syntax

type Rep JStgStat = D1 ('MetaData "JStgStat" "GHC.JS.JStg.Syntax" "ghc-lib-parser-9.10.1.20240511-FCOK3MWDKkc1AE2Ll0xWIs" 'False) ((((C1 ('MetaCons "DeclStat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Ident) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe JStgExpr))) :+: C1 ('MetaCons "ReturnStat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStgExpr))) :+: (C1 ('MetaCons "IfStat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStgExpr) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStgStat) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStgStat))) :+: C1 ('MetaCons "WhileStat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStgExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStgStat))))) :+: ((C1 ('MetaCons "ForStat" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStgStat) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStgExpr)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStgStat) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStgStat))) :+: C1 ('MetaCons "ForInStat" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStgExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStgStat)))) :+: (C1 ('MetaCons "SwitchStat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStgExpr) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(JStgExpr, JStgStat)]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStgStat))) :+: C1 ('MetaCons "TryStat" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStgStat) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStgStat) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStgStat)))))) :+: (((C1 ('MetaCons "BlockStat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [JStgStat])) :+: C1 ('MetaCons "ApplStat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStgExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [JStgExpr]))) :+: (C1 ('MetaCons "UOpStat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UOp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStgExpr)) :+: C1 ('MetaCons "AssignStat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStgExpr) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AOp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStgExpr))))) :+: ((C1 ('MetaCons "LabelStat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JsLabel) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStgStat)) :+: C1 ('MetaCons "BreakStat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe JsLabel)))) :+: (C1 ('MetaCons "ContinueStat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe JsLabel))) :+: C1 ('MetaCons "FuncStat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Ident) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Ident]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStgStat)))))))

data JStgExpr Source #

JavaScript Expressions

Constructors

ValExpr JVal

All values are trivially expressions

SelExpr JStgExpr Ident

Selection: Obj.foo, see .^

IdxExpr JStgExpr JStgExpr

Indexing: Obj[foo], see .!

InfixExpr Op JStgExpr JStgExpr

Infix Expressions, see JStgExpr pattern synonyms

UOpExpr UOp JStgExpr

Unary Expressions

IfExpr JStgExpr JStgExpr JStgExpr

If-expression

ApplExpr JStgExpr [JStgExpr]

Application

Instances

Instances details
Generic JStgExpr Source # 
Instance details

Defined in GHC.JS.JStg.Syntax

Associated Types

type Rep JStgExpr :: Type -> Type #

Methods

from :: JStgExpr -> Rep JStgExpr x #

to :: Rep JStgExpr x -> JStgExpr #

Num JStgExpr Source # 
Instance details

Defined in GHC.JS.Make

Fractional JStgExpr Source # 
Instance details

Defined in GHC.JS.Make

JVarMagic JStgExpr Source # 
Instance details

Defined in GHC.JS.Make

ToJExpr JStgExpr Source # 
Instance details

Defined in GHC.JS.Make

ToStat JStgExpr Source # 
Instance details

Defined in GHC.JS.Make

Outputable JStgExpr Source # 
Instance details

Defined in GHC.JS.JStg.Syntax

Methods

ppr :: JStgExpr -> SDoc Source #

Eq JStgExpr Source # 
Instance details

Defined in GHC.JS.JStg.Syntax

ToStat [JStgExpr] Source # 
Instance details

Defined in GHC.JS.Make

type Rep JStgExpr Source # 
Instance details

Defined in GHC.JS.JStg.Syntax

type Rep JStgExpr = D1 ('MetaData "JStgExpr" "GHC.JS.JStg.Syntax" "ghc-lib-parser-9.10.1.20240511-FCOK3MWDKkc1AE2Ll0xWIs" 'False) ((C1 ('MetaCons "ValExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JVal)) :+: (C1 ('MetaCons "SelExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStgExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident)) :+: C1 ('MetaCons "IdxExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStgExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStgExpr)))) :+: ((C1 ('MetaCons "InfixExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Op) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStgExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStgExpr))) :+: C1 ('MetaCons "UOpExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UOp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStgExpr))) :+: (C1 ('MetaCons "IfExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStgExpr) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStgExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStgExpr))) :+: C1 ('MetaCons "ApplExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStgExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [JStgExpr])))))

data JVal Source #

JavaScript values

Constructors

JVar Ident

A variable reference

JList [JStgExpr]

A JavaScript list, or what JS calls an Array

JDouble SaneDouble

A Double

JInt Integer

A BigInt

JStr FastString

A String

JRegEx FastString

A Regex

JBool Bool

A Boolean

JHash (UniqMap FastString JStgExpr)

A JS HashMap: {"foo": 0}

JFunc [Ident] JStgStat

A function

Instances

Instances details
Generic JVal Source # 
Instance details

Defined in GHC.JS.JStg.Syntax

Associated Types

type Rep JVal :: Type -> Type #

Methods

from :: JVal -> Rep JVal x #

to :: Rep JVal x -> JVal #

JVarMagic JVal Source # 
Instance details

Defined in GHC.JS.Make

Methods

fresh :: JSM JVal Source #

ToJExpr JVal Source # 
Instance details

Defined in GHC.JS.Make

Eq JVal Source # 
Instance details

Defined in GHC.JS.JStg.Syntax

Methods

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

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

type Rep JVal Source # 
Instance details

Defined in GHC.JS.JStg.Syntax

type Rep JVal = D1 ('MetaData "JVal" "GHC.JS.JStg.Syntax" "ghc-lib-parser-9.10.1.20240511-FCOK3MWDKkc1AE2Ll0xWIs" 'False) (((C1 ('MetaCons "JVar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident)) :+: C1 ('MetaCons "JList" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [JStgExpr]))) :+: (C1 ('MetaCons "JDouble" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SaneDouble)) :+: C1 ('MetaCons "JInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)))) :+: ((C1 ('MetaCons "JStr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FastString)) :+: C1 ('MetaCons "JRegEx" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FastString))) :+: (C1 ('MetaCons "JBool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :+: (C1 ('MetaCons "JHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (UniqMap FastString JStgExpr))) :+: C1 ('MetaCons "JFunc" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Ident]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStgStat))))))

data Op Source #

JS Binary Operators. We do not deeply embed the comma operator and the assignment operators

Constructors

EqOp

Equality: ==

StrictEqOp

Strict Equality: ===

NeqOp

InEquality: !=

StrictNeqOp

Strict InEquality !==

GtOp

Greater Than: >

GeOp

Greater Than or Equal: >=

LtOp

Less Than: <

LeOp

Less Than or Equal: <=

AddOp

Addition: +

SubOp

Subtraction: -

MulOp

Multiplication *

DivOp

Division: /

ModOp

Remainder: %

LeftShiftOp

Left Shift: <<

RightShiftOp

Right Shift: >>

ZRightShiftOp

Unsigned RightShift: >>>

BAndOp

Bitwise And: &

BOrOp

Bitwise Or: |

BXorOp

Bitwise XOr: ^

LAndOp

Logical And: &&

LOrOp

Logical Or: ||

InstanceofOp
instanceof
InOp
in

Instances

Instances details
Data Op Source # 
Instance details

Defined in GHC.JS.JStg.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Op -> c Op #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Op #

toConstr :: Op -> Constr #

dataTypeOf :: Op -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Op) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Op) #

gmapT :: (forall b. Data b => b -> b) -> Op -> Op #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Op -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Op -> r #

gmapQ :: (forall d. Data d => d -> u) -> Op -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Op -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Op -> m Op #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Op -> m Op #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Op -> m Op #

Enum Op Source # 
Instance details

Defined in GHC.JS.JStg.Syntax

Methods

succ :: Op -> Op #

pred :: Op -> Op #

toEnum :: Int -> Op #

fromEnum :: Op -> Int #

enumFrom :: Op -> [Op] #

enumFromThen :: Op -> Op -> [Op] #

enumFromTo :: Op -> Op -> [Op] #

enumFromThenTo :: Op -> Op -> Op -> [Op] #

Generic Op Source # 
Instance details

Defined in GHC.JS.JStg.Syntax

Associated Types

type Rep Op :: Type -> Type #

Methods

from :: Op -> Rep Op x #

to :: Rep Op x -> Op #

Show Op Source # 
Instance details

Defined in GHC.JS.JStg.Syntax

Methods

showsPrec :: Int -> Op -> ShowS #

show :: Op -> String #

showList :: [Op] -> ShowS #

NFData Op Source # 
Instance details

Defined in GHC.JS.JStg.Syntax

Methods

rnf :: Op -> () #

Eq Op Source # 
Instance details

Defined in GHC.JS.JStg.Syntax

Methods

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

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

Ord Op Source # 
Instance details

Defined in GHC.JS.JStg.Syntax

Methods

compare :: Op -> Op -> Ordering #

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

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

(>) :: Op -> Op -> Bool #

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

max :: Op -> Op -> Op #

min :: Op -> Op -> Op #

type Rep Op Source # 
Instance details

Defined in GHC.JS.JStg.Syntax

type Rep Op = D1 ('MetaData "Op" "GHC.JS.JStg.Syntax" "ghc-lib-parser-9.10.1.20240511-FCOK3MWDKkc1AE2Ll0xWIs" 'False) ((((C1 ('MetaCons "EqOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StrictEqOp" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NeqOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "StrictNeqOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GtOp" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "GeOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LtOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LeOp" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "AddOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SubOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MulOp" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "DivOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ModOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LeftShiftOp" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "RightShiftOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ZRightShiftOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BAndOp" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "BOrOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BXorOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LAndOp" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "LOrOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "InstanceofOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InOp" 'PrefixI 'False) (U1 :: Type -> Type))))))

data AOp Source #

JS Unary Operators

Constructors

AssignOp

Vanilla Assignment: =

AddAssignOp

Addition Assignment: +=

SubAssignOp

Subtraction Assignment: -=

Instances

Instances details
Data AOp Source # 
Instance details

Defined in GHC.JS.JStg.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AOp -> c AOp #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AOp #

toConstr :: AOp -> Constr #

dataTypeOf :: AOp -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AOp) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AOp) #

gmapT :: (forall b. Data b => b -> b) -> AOp -> AOp #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AOp -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AOp -> r #

gmapQ :: (forall d. Data d => d -> u) -> AOp -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AOp -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AOp -> m AOp #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AOp -> m AOp #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AOp -> m AOp #

Enum AOp Source # 
Instance details

Defined in GHC.JS.JStg.Syntax

Methods

succ :: AOp -> AOp #

pred :: AOp -> AOp #

toEnum :: Int -> AOp #

fromEnum :: AOp -> Int #

enumFrom :: AOp -> [AOp] #

enumFromThen :: AOp -> AOp -> [AOp] #

enumFromTo :: AOp -> AOp -> [AOp] #

enumFromThenTo :: AOp -> AOp -> AOp -> [AOp] #

Generic AOp Source # 
Instance details

Defined in GHC.JS.JStg.Syntax

Associated Types

type Rep AOp :: Type -> Type #

Methods

from :: AOp -> Rep AOp x #

to :: Rep AOp x -> AOp #

Show AOp Source # 
Instance details

Defined in GHC.JS.JStg.Syntax

Methods

showsPrec :: Int -> AOp -> ShowS #

show :: AOp -> String #

showList :: [AOp] -> ShowS #

NFData AOp Source # 
Instance details

Defined in GHC.JS.JStg.Syntax

Methods

rnf :: AOp -> () #

Eq AOp Source # 
Instance details

Defined in GHC.JS.JStg.Syntax

Methods

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

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

Ord AOp Source # 
Instance details

Defined in GHC.JS.JStg.Syntax

Methods

compare :: AOp -> AOp -> Ordering #

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

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

(>) :: AOp -> AOp -> Bool #

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

max :: AOp -> AOp -> AOp #

min :: AOp -> AOp -> AOp #

type Rep AOp Source # 
Instance details

Defined in GHC.JS.JStg.Syntax

type Rep AOp = D1 ('MetaData "AOp" "GHC.JS.JStg.Syntax" "ghc-lib-parser-9.10.1.20240511-FCOK3MWDKkc1AE2Ll0xWIs" 'False) (C1 ('MetaCons "AssignOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AddAssignOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SubAssignOp" 'PrefixI 'False) (U1 :: Type -> Type)))

data UOp Source #

JS Unary Operators

Constructors

NotOp

Logical Not: !

BNotOp

Bitwise Not: ~

NegOp

Negation: -

PlusOp

Unary Plus: +x

NewOp

new x

TypeofOp

typeof x

DeleteOp

delete x

YieldOp

yield x

VoidOp

void x

PreIncOp

Prefix Increment: ++x

PostIncOp

Postfix Increment: x++

PreDecOp

Prefix Decrement: --x

PostDecOp

Postfix Decrement: x--

Instances

Instances details
Data UOp Source # 
Instance details

Defined in GHC.JS.JStg.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UOp -> c UOp #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UOp #

toConstr :: UOp -> Constr #

dataTypeOf :: UOp -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UOp) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UOp) #

gmapT :: (forall b. Data b => b -> b) -> UOp -> UOp #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UOp -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UOp -> r #

gmapQ :: (forall d. Data d => d -> u) -> UOp -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UOp -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UOp -> m UOp #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UOp -> m UOp #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UOp -> m UOp #

Enum UOp Source # 
Instance details

Defined in GHC.JS.JStg.Syntax

Methods

succ :: UOp -> UOp #

pred :: UOp -> UOp #

toEnum :: Int -> UOp #

fromEnum :: UOp -> Int #

enumFrom :: UOp -> [UOp] #

enumFromThen :: UOp -> UOp -> [UOp] #

enumFromTo :: UOp -> UOp -> [UOp] #

enumFromThenTo :: UOp -> UOp -> UOp -> [UOp] #

Generic UOp Source # 
Instance details

Defined in GHC.JS.JStg.Syntax

Associated Types

type Rep UOp :: Type -> Type #

Methods

from :: UOp -> Rep UOp x #

to :: Rep UOp x -> UOp #

Show UOp Source # 
Instance details

Defined in GHC.JS.JStg.Syntax

Methods

showsPrec :: Int -> UOp -> ShowS #

show :: UOp -> String #

showList :: [UOp] -> ShowS #

NFData UOp Source # 
Instance details

Defined in GHC.JS.JStg.Syntax

Methods

rnf :: UOp -> () #

Eq UOp Source # 
Instance details

Defined in GHC.JS.JStg.Syntax

Methods

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

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

Ord UOp Source # 
Instance details

Defined in GHC.JS.JStg.Syntax

Methods

compare :: UOp -> UOp -> Ordering #

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

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

(>) :: UOp -> UOp -> Bool #

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

max :: UOp -> UOp -> UOp #

min :: UOp -> UOp -> UOp #

type Rep UOp Source # 
Instance details

Defined in GHC.JS.JStg.Syntax

type Rep UOp = D1 ('MetaData "UOp" "GHC.JS.JStg.Syntax" "ghc-lib-parser-9.10.1.20240511-FCOK3MWDKkc1AE2Ll0xWIs" 'False) (((C1 ('MetaCons "NotOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BNotOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NegOp" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "PlusOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NewOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TypeofOp" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "DeleteOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "YieldOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "VoidOp" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "PreIncOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PostIncOp" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PreDecOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PostDecOp" 'PrefixI 'False) (U1 :: Type -> Type)))))

type JsLabel = LexicalFastString Source #

A Label used for JStgStat, specifically BreakStat, ContinueStat and of course LabelStat

pattern synonyms over JS operators

pattern New :: JStgExpr -> JStgExpr Source #

pattern synonym for a unary operator new

pattern Not :: JStgExpr -> JStgExpr Source #

pattern synonym for logical not !

pattern Negate :: JStgExpr -> JStgExpr Source #

pattern synonym for unary negation -

pattern Add :: JStgExpr -> JStgExpr -> JStgExpr Source #

pattern synonym for addition +

pattern Sub :: JStgExpr -> JStgExpr -> JStgExpr Source #

pattern synonym for subtraction -

pattern Mul :: JStgExpr -> JStgExpr -> JStgExpr Source #

pattern synonym for multiplication *

pattern Div :: JStgExpr -> JStgExpr -> JStgExpr Source #

pattern synonym for division *

pattern Mod :: JStgExpr -> JStgExpr -> JStgExpr Source #

pattern synonym for remainder %

pattern BOr :: JStgExpr -> JStgExpr -> JStgExpr Source #

pattern synonym for Bitwise Or |

pattern BAnd :: JStgExpr -> JStgExpr -> JStgExpr Source #

pattern synonym for Bitwise And &

pattern BXor :: JStgExpr -> JStgExpr -> JStgExpr Source #

pattern synonym for Bitwise XOr ^

pattern BNot :: JStgExpr -> JStgExpr Source #

pattern synonym for Bitwise Not ~

pattern LOr :: JStgExpr -> JStgExpr -> JStgExpr Source #

pattern synonym for logical Or ||

pattern LAnd :: JStgExpr -> JStgExpr -> JStgExpr Source #

pattern synonym for logical And &&

pattern Int :: Integer -> JStgExpr Source #

pattern synonym to create integer values

pattern String :: FastString -> JStgExpr Source #

pattern synonym to create string values

pattern Var :: Ident -> JStgExpr Source #

pattern synonym to create a local variable reference

pattern PreInc :: JStgExpr -> JStgExpr Source #

pattern synonym for prefix increment ++x

pattern PostInc :: JStgExpr -> JStgExpr Source #

pattern synonym for postfix increment x++

pattern PreDec :: JStgExpr -> JStgExpr Source #

pattern synonym for prefix decrement --x

pattern PostDec :: JStgExpr -> JStgExpr Source #

pattern synonym for postfix decrement --x

Utility

newtype SaneDouble Source #

A newtype wrapper around Double to ensure we never generate a Double that becomes a NaN, see instances for details on sanity.

Constructors

SaneDouble 

Fields

Instances

Instances details
Num SaneDouble Source # 
Instance details

Defined in GHC.Types.SaneDouble

Fractional SaneDouble Source # 
Instance details

Defined in GHC.Types.SaneDouble

Show SaneDouble Source # 
Instance details

Defined in GHC.Types.SaneDouble

Binary SaneDouble Source # 
Instance details

Defined in GHC.Types.SaneDouble

Eq SaneDouble Source # 
Instance details

Defined in GHC.Types.SaneDouble

Ord SaneDouble Source # 
Instance details

Defined in GHC.Types.SaneDouble

pattern Func :: [Ident] -> JStgStat -> JStgExpr Source #

pattern synonym to create an anonymous function

var :: FastString -> JStgExpr Source #

construct a JS variable reference