ghc-9.8.2: The GHC API
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 HaskellNone
LanguageHaskell2010

GHC.JS.Unsat.Syntax

Description

  • Domain and Purpose

    GHC.JS.Unsat.Syntax defines the Syntax for the JS backend in GHC. It comports with the ECMA-262 although not every production rule of the standard is represented. Code in this module is a fork of JMacro (BSD 3 Clause) by Gershom Bazerman, heavily modified to accomodate GHC's constraints.

  • Strategy

    Nothing fancy in this module, this is a classic deeply embeded AST for JS. We define numerous ADTs and pattern synonyms to make pattern matching and constructing ASTs easier.

  • Consumers

    The entire JS backend consumes this module, e.g., the modules in GHC.StgToJS.*. Please see Make for a module which provides helper functions that use the deeply embedded DSL defined in this module to provide some of the benefits of a shallow embedding.

Synopsis

Deeply embedded JS datatypes

data JStat Source #

JavaScript statements, see the ECMA262 Reference for details

Constructors

DeclStat !Ident !(Maybe JExpr)

Variable declarations: var foo [= e]

ReturnStat JExpr

Return

IfStat JExpr JStat JStat

If

WhileStat Bool JExpr JStat

While, bool is "do" when True

ForStat JStat JExpr JStat JStat

For

ForInStat Bool Ident JExpr JStat

For-in, bool is "each' when True

SwitchStat JExpr [(JExpr, JStat)] JStat

Switch

TryStat JStat Ident JStat JStat

Try

BlockStat [JStat]

Blocks

ApplStat JExpr [JExpr]

Application

UOpStat JUOp JExpr

Unary operators

AssignStat JExpr JExpr

Binding form: foo = bar

UnsatBlock (IdentSupply JStat)

Unsaturated blocks see pseudoSaturate

LabelStat JsLabel JStat

Statement Labels, makes me nostalgic for qbasic

BreakStat (Maybe JsLabel)

Break

ContinueStat (Maybe JsLabel)

Continue

FuncStat !Ident [Ident] JStat

an explicit function definition

Instances

Instances details
Monoid JStat Source # 
Instance details

Defined in GHC.JS.Unsat.Syntax

Semigroup JStat Source # 
Instance details

Defined in GHC.JS.Unsat.Syntax

Generic JStat Source # 
Instance details

Defined in GHC.JS.Unsat.Syntax

Associated Types

type Rep JStat 
Instance details

Defined in GHC.JS.Unsat.Syntax

type Rep JStat = D1 ('MetaData "JStat" "GHC.JS.Unsat.Syntax" "ghc-9.8.2-f9d1" '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 JExpr))) :+: C1 ('MetaCons "ReturnStat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JExpr))) :+: (C1 ('MetaCons "IfStat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JExpr) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStat) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStat))) :+: C1 ('MetaCons "WhileStat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStat))))) :+: ((C1 ('MetaCons "ForStat" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStat) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JExpr)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStat) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStat))) :+: 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 JExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStat)))) :+: (C1 ('MetaCons "SwitchStat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JExpr) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(JExpr, JStat)]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStat))) :+: C1 ('MetaCons "TryStat" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStat) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStat) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStat)))))) :+: (((C1 ('MetaCons "BlockStat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [JStat])) :+: C1 ('MetaCons "ApplStat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [JExpr]))) :+: (C1 ('MetaCons "UOpStat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JUOp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JExpr)) :+: C1 ('MetaCons "AssignStat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JExpr)))) :+: ((C1 ('MetaCons "UnsatBlock" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (IdentSupply JStat))) :+: C1 ('MetaCons "LabelStat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JsLabel) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStat))) :+: (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 JStat))))))))

Methods

from :: JStat -> Rep JStat x Source #

to :: Rep JStat x -> JStat Source #

ToStat JStat Source # 
Instance details

Defined in GHC.JS.Make

Methods

toStat :: JStat -> JStat Source #

JMacro JStat Source # 
Instance details

Defined in GHC.JS.Transform

Eq JStat Source # 
Instance details

Defined in GHC.JS.Unsat.Syntax

Methods

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

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

ToStat [JStat] Source # 
Instance details

Defined in GHC.JS.Make

Methods

toStat :: [JStat] -> JStat Source #

type Rep JStat Source # 
Instance details

Defined in GHC.JS.Unsat.Syntax

type Rep JStat = D1 ('MetaData "JStat" "GHC.JS.Unsat.Syntax" "ghc-9.8.2-f9d1" '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 JExpr))) :+: C1 ('MetaCons "ReturnStat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JExpr))) :+: (C1 ('MetaCons "IfStat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JExpr) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStat) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStat))) :+: C1 ('MetaCons "WhileStat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStat))))) :+: ((C1 ('MetaCons "ForStat" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStat) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JExpr)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStat) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStat))) :+: 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 JExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStat)))) :+: (C1 ('MetaCons "SwitchStat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JExpr) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(JExpr, JStat)]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStat))) :+: C1 ('MetaCons "TryStat" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStat) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStat) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStat)))))) :+: (((C1 ('MetaCons "BlockStat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [JStat])) :+: C1 ('MetaCons "ApplStat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [JExpr]))) :+: (C1 ('MetaCons "UOpStat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JUOp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JExpr)) :+: C1 ('MetaCons "AssignStat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JExpr)))) :+: ((C1 ('MetaCons "UnsatBlock" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (IdentSupply JStat))) :+: C1 ('MetaCons "LabelStat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JsLabel) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStat))) :+: (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 JStat))))))))

data JExpr Source #

JavaScript Expressions

Constructors

ValExpr JVal

All values are trivially expressions

SelExpr JExpr Ident

Selection: Obj.foo, see .^

IdxExpr JExpr JExpr

Indexing: Obj[foo], see .!

InfixExpr JOp JExpr JExpr

Infix Expressions, see JExpr pattern synonyms

UOpExpr JUOp JExpr

Unary Expressions

IfExpr JExpr JExpr JExpr

If-expression

ApplExpr JExpr [JExpr]

Application

UnsatExpr (IdentSupply JExpr)

An Saturated expression. See pseudoSaturate

Instances

Instances details
Generic JExpr Source # 
Instance details

Defined in GHC.JS.Unsat.Syntax

Associated Types

type Rep JExpr 
Instance details

Defined in GHC.JS.Unsat.Syntax

type Rep JExpr = D1 ('MetaData "JExpr" "GHC.JS.Unsat.Syntax" "ghc-9.8.2-f9d1" '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 JExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident))) :+: (C1 ('MetaCons "IdxExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JExpr)) :+: C1 ('MetaCons "InfixExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JOp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JExpr))))) :+: ((C1 ('MetaCons "UOpExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JUOp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JExpr)) :+: C1 ('MetaCons "IfExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JExpr) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JExpr)))) :+: (C1 ('MetaCons "ApplExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [JExpr])) :+: C1 ('MetaCons "UnsatExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (IdentSupply JExpr))))))

Methods

from :: JExpr -> Rep JExpr x Source #

to :: Rep JExpr x -> JExpr Source #

Num JExpr Source # 
Instance details

Defined in GHC.JS.Make

Fractional JExpr Source # 
Instance details

Defined in GHC.JS.Make

ToJExpr JExpr Source # 
Instance details

Defined in GHC.JS.Make

ToStat JExpr Source # 
Instance details

Defined in GHC.JS.Make

Methods

toStat :: JExpr -> JStat Source #

JMacro JExpr Source # 
Instance details

Defined in GHC.JS.Transform

Eq JExpr Source # 
Instance details

Defined in GHC.JS.Unsat.Syntax

Methods

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

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

ToStat [JExpr] Source # 
Instance details

Defined in GHC.JS.Make

Methods

toStat :: [JExpr] -> JStat Source #

type Rep JExpr Source # 
Instance details

Defined in GHC.JS.Unsat.Syntax

type Rep JExpr = D1 ('MetaData "JExpr" "GHC.JS.Unsat.Syntax" "ghc-9.8.2-f9d1" '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 JExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident))) :+: (C1 ('MetaCons "IdxExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JExpr)) :+: C1 ('MetaCons "InfixExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JOp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JExpr))))) :+: ((C1 ('MetaCons "UOpExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JUOp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JExpr)) :+: C1 ('MetaCons "IfExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JExpr) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JExpr)))) :+: (C1 ('MetaCons "ApplExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [JExpr])) :+: C1 ('MetaCons "UnsatExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (IdentSupply JExpr))))))

data JVal Source #

JavaScript values

Constructors

JVar Ident

A variable reference

JList [JExpr]

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

JHash (UniqMap FastString JExpr)

A JS HashMap: {"foo": 0}

JFunc [Ident] JStat

A function

UnsatVal (IdentSupply JVal)

An Saturated value, see pseudoSaturate

Instances

Instances details
Generic JVal Source # 
Instance details

Defined in GHC.JS.Unsat.Syntax

Associated Types

type Rep JVal 
Instance details

Defined in GHC.JS.Unsat.Syntax

type Rep JVal = D1 ('MetaData "JVal" "GHC.JS.Unsat.Syntax" "ghc-9.8.2-f9d1" '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 [JExpr]))) :+: (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 "JHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (UniqMap FastString JExpr))) :+: (C1 ('MetaCons "JFunc" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Ident]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStat)) :+: C1 ('MetaCons "UnsatVal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (IdentSupply JVal)))))))

Methods

from :: JVal -> Rep JVal x Source #

to :: Rep JVal x -> JVal Source #

ToJExpr JVal Source # 
Instance details

Defined in GHC.JS.Make

JMacro JVal Source # 
Instance details

Defined in GHC.JS.Transform

Eq JVal Source # 
Instance details

Defined in GHC.JS.Unsat.Syntax

Methods

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

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

type Rep JVal Source # 
Instance details

Defined in GHC.JS.Unsat.Syntax

type Rep JVal = D1 ('MetaData "JVal" "GHC.JS.Unsat.Syntax" "ghc-9.8.2-f9d1" '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 [JExpr]))) :+: (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 "JHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (UniqMap FastString JExpr))) :+: (C1 ('MetaCons "JFunc" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Ident]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JStat)) :+: C1 ('MetaCons "UnsatVal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (IdentSupply JVal)))))))

data JOp 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 JOp Source # 
Instance details

Defined in GHC.JS.Unsat.Syntax

Methods

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

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

toConstr :: JOp -> Constr Source #

dataTypeOf :: JOp -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Enum JOp Source # 
Instance details

Defined in GHC.JS.Unsat.Syntax

Generic JOp Source # 
Instance details

Defined in GHC.JS.Unsat.Syntax

Associated Types

type Rep JOp 
Instance details

Defined in GHC.JS.Unsat.Syntax

type Rep JOp = D1 ('MetaData "JOp" "GHC.JS.Unsat.Syntax" "ghc-9.8.2-f9d1" '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))))))

Methods

from :: JOp -> Rep JOp x Source #

to :: Rep JOp x -> JOp Source #

Show JOp Source # 
Instance details

Defined in GHC.JS.Unsat.Syntax

NFData JOp Source # 
Instance details

Defined in GHC.JS.Unsat.Syntax

Methods

rnf :: JOp -> () Source #

Eq JOp Source # 
Instance details

Defined in GHC.JS.Unsat.Syntax

Methods

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

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

Ord JOp Source # 
Instance details

Defined in GHC.JS.Unsat.Syntax

Methods

compare :: JOp -> JOp -> Ordering #

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

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

(>) :: JOp -> JOp -> Bool #

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

max :: JOp -> JOp -> JOp #

min :: JOp -> JOp -> JOp #

type Rep JOp Source # 
Instance details

Defined in GHC.JS.Unsat.Syntax

type Rep JOp = D1 ('MetaData "JOp" "GHC.JS.Unsat.Syntax" "ghc-9.8.2-f9d1" '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 JUOp 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 JUOp Source # 
Instance details

Defined in GHC.JS.Unsat.Syntax

Methods

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

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

toConstr :: JUOp -> Constr Source #

dataTypeOf :: JUOp -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Enum JUOp Source # 
Instance details

Defined in GHC.JS.Unsat.Syntax

Generic JUOp Source # 
Instance details

Defined in GHC.JS.Unsat.Syntax

Associated Types

type Rep JUOp 
Instance details

Defined in GHC.JS.Unsat.Syntax

type Rep JUOp = D1 ('MetaData "JUOp" "GHC.JS.Unsat.Syntax" "ghc-9.8.2-f9d1" '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)))))

Methods

from :: JUOp -> Rep JUOp x Source #

to :: Rep JUOp x -> JUOp Source #

Show JUOp Source # 
Instance details

Defined in GHC.JS.Unsat.Syntax

NFData JUOp Source # 
Instance details

Defined in GHC.JS.Unsat.Syntax

Methods

rnf :: JUOp -> () Source #

Eq JUOp Source # 
Instance details

Defined in GHC.JS.Unsat.Syntax

Methods

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

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

Ord JUOp Source # 
Instance details

Defined in GHC.JS.Unsat.Syntax

Methods

compare :: JUOp -> JUOp -> Ordering #

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

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

(>) :: JUOp -> JUOp -> Bool #

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

max :: JUOp -> JUOp -> JUOp #

min :: JUOp -> JUOp -> JUOp #

type Rep JUOp Source # 
Instance details

Defined in GHC.JS.Unsat.Syntax

type Rep JUOp = D1 ('MetaData "JUOp" "GHC.JS.Unsat.Syntax" "ghc-9.8.2-f9d1" '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)))))

newtype Ident Source #

A newtype wrapper around FastString for JS identifiers.

Constructors

TxtI 

Fields

Instances

Instances details
Show Ident Source # 
Instance details

Defined in GHC.JS.Unsat.Syntax

ToJExpr Ident Source # 
Instance details

Defined in GHC.JS.Make

JsToDoc Ident Source # 
Instance details

Defined in GHC.JS.Ppr

Methods

jsToDocR :: JsRender doc => RenderJs doc -> Ident -> doc Source #

JMacro Ident Source # 
Instance details

Defined in GHC.JS.Transform

Uniquable Ident Source # 
Instance details

Defined in GHC.JS.Unsat.Syntax

Binary Ident Source # 
Instance details

Defined in GHC.StgToJS.Object

Eq Ident Source # 
Instance details

Defined in GHC.JS.Unsat.Syntax

Methods

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

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

type JsLabel = LexicalFastString Source #

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

pattern synonyms over JS operators

pattern New :: JExpr -> JExpr Source #

pattern synonym for a unary operator new

pattern Not :: JExpr -> JExpr Source #

pattern synonym for logical not !

pattern Negate :: JExpr -> JExpr Source #

pattern synonym for unary negation -

pattern Add :: JExpr -> JExpr -> JExpr Source #

pattern synonym for addition +

pattern Sub :: JExpr -> JExpr -> JExpr Source #

pattern synonym for subtraction -

pattern Mul :: JExpr -> JExpr -> JExpr Source #

pattern synonym for multiplication *

pattern Div :: JExpr -> JExpr -> JExpr Source #

pattern synonym for division *

pattern Mod :: JExpr -> JExpr -> JExpr Source #

pattern synonym for remainder %

pattern BOr :: JExpr -> JExpr -> JExpr Source #

pattern synonym for Bitwise Or |

pattern BAnd :: JExpr -> JExpr -> JExpr Source #

pattern synonym for Bitwise And &

pattern BXor :: JExpr -> JExpr -> JExpr Source #

pattern synonym for Bitwise XOr ^

pattern BNot :: JExpr -> JExpr Source #

pattern synonym for Bitwise Not ~

pattern LOr :: JExpr -> JExpr -> JExpr Source #

pattern synonym for logical Or ||

pattern LAnd :: JExpr -> JExpr -> JExpr Source #

pattern synonym for logical And &&

pattern Int :: Integer -> JExpr Source #

pattern synonym to create integer values

pattern String :: FastString -> JExpr Source #

pattern synonym to create string values

pattern PreInc :: JExpr -> JExpr Source #

pattern synonym for prefix increment ++x

pattern PostInc :: JExpr -> JExpr Source #

pattern synonym for postfix increment x++

pattern PreDec :: JExpr -> JExpr Source #

pattern synonym for prefix decrement --x

pattern PostDec :: JExpr -> JExpr Source #

pattern synonym for postfix decrement --x

Ident supply

newtype IdentSupply a Source #

A supply of identifiers, possibly empty

Constructors

IS 

Fields

Instances

Instances details
Functor IdentSupply Source # 
Instance details

Defined in GHC.JS.Unsat.Syntax

Methods

fmap :: (a -> b) -> IdentSupply a -> IdentSupply b Source #

(<$) :: a -> IdentSupply b -> IdentSupply a Source #

Show a => Show (IdentSupply a) Source # 
Instance details

Defined in GHC.JS.Unsat.Syntax

NFData (IdentSupply a) Source # 
Instance details

Defined in GHC.JS.Unsat.Syntax

Methods

rnf :: IdentSupply a -> () Source #

Eq a => Eq (IdentSupply a) Source # 
Instance details

Defined in GHC.JS.Unsat.Syntax

Ord a => Ord (IdentSupply a) Source # 
Instance details

Defined in GHC.JS.Unsat.Syntax

pseudoSaturate :: IdentSupply a -> a Source #

Given a Pseudo-saturate a value with garbage identifiers.

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