Copyright | (c) The University of Glasgow 2001 |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Jeffrey Young <jeffrey.young@iohk.io> Luite Stegeman <luite.stegeman@iohk.io> Sylvain Henry <sylvain.henry@iohk.io> Josh Meredith <josh.meredith@iohk.io> |
Stability | experimental |
Safe Haskell | None |
Language | GHC2021 |
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.
In general, one should not use these constructors explicitly in the JS backend. Instead, prefer using the combinators in GHC.JS.Make, if those are suitable then prefer using the patterns exported from this module
Synopsis
- data JStgStat
- = DeclStat !Ident !(Maybe JStgExpr)
- | ReturnStat JStgExpr
- | IfStat JStgExpr JStgStat JStgStat
- | WhileStat Bool JStgExpr JStgStat
- | ForStat JStgStat JStgExpr JStgStat JStgStat
- | ForInStat Bool Ident JStgExpr JStgStat
- | SwitchStat JStgExpr [(JStgExpr, JStgStat)] JStgStat
- | TryStat JStgStat Ident JStgStat JStgStat
- | BlockStat [JStgStat]
- | ApplStat JStgExpr [JStgExpr]
- | UOpStat UOp JStgExpr
- | AssignStat JStgExpr AOp JStgExpr
- | LabelStat JsLabel JStgStat
- | BreakStat (Maybe JsLabel)
- | ContinueStat (Maybe JsLabel)
- | FuncStat !Ident [Ident] JStgStat
- data JStgExpr
- data JVal
- data Op
- = EqOp
- | StrictEqOp
- | NeqOp
- | StrictNeqOp
- | GtOp
- | GeOp
- | LtOp
- | LeOp
- | AddOp
- | SubOp
- | MulOp
- | DivOp
- | ModOp
- | LeftShiftOp
- | RightShiftOp
- | ZRightShiftOp
- | BAndOp
- | BOrOp
- | BXorOp
- | LAndOp
- | LOrOp
- | InstanceofOp
- | InOp
- data AOp
- data UOp
- type JsLabel = LexicalFastString
- pattern New :: JStgExpr -> JStgExpr
- pattern Not :: JStgExpr -> JStgExpr
- pattern Negate :: JStgExpr -> JStgExpr
- pattern Add :: JStgExpr -> JStgExpr -> JStgExpr
- pattern Sub :: JStgExpr -> JStgExpr -> JStgExpr
- pattern Mul :: JStgExpr -> JStgExpr -> JStgExpr
- pattern Div :: JStgExpr -> JStgExpr -> JStgExpr
- pattern Mod :: JStgExpr -> JStgExpr -> JStgExpr
- pattern BOr :: JStgExpr -> JStgExpr -> JStgExpr
- pattern BAnd :: JStgExpr -> JStgExpr -> JStgExpr
- pattern BXor :: JStgExpr -> JStgExpr -> JStgExpr
- pattern BNot :: JStgExpr -> JStgExpr
- pattern LOr :: JStgExpr -> JStgExpr -> JStgExpr
- pattern LAnd :: JStgExpr -> JStgExpr -> JStgExpr
- pattern Int :: Integer -> JStgExpr
- pattern String :: FastString -> JStgExpr
- pattern Var :: Ident -> JStgExpr
- pattern PreInc :: JStgExpr -> JStgExpr
- pattern PostInc :: JStgExpr -> JStgExpr
- pattern PreDec :: JStgExpr -> JStgExpr
- pattern PostDec :: JStgExpr -> JStgExpr
- newtype SaneDouble = SaneDouble {}
- pattern Func :: [Ident] -> JStgStat -> JStgExpr
- global :: FastString -> JStgExpr
- local :: FastString -> JStgExpr
Deeply embedded JS datatypes
JavaScript statements, see the ECMA262 Reference for details
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: |
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
JavaScript Expressions
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 |
UOpExpr UOp JStgExpr | Unary Expressions |
IfExpr JStgExpr JStgExpr JStgExpr | If-expression |
ApplExpr JStgExpr [JStgExpr] | Application |
Instances
JVarMagic JStgExpr Source # | |||||
ToJExpr JStgExpr Source # | |||||
ToStat JStgExpr Source # | |||||
Outputable JStgExpr Source # | |||||
Generic JStgExpr Source # | |||||
Defined in GHC.JS.JStg.Syntax
| |||||
Num JStgExpr Source # | |||||
Fractional JStgExpr Source # | |||||
Eq JStgExpr Source # | |||||
ToStat [JStgExpr] Source # | |||||
type Rep JStgExpr Source # | |||||
Defined in GHC.JS.JStg.Syntax type Rep JStgExpr = D1 ('MetaData "JStgExpr" "GHC.JS.JStg.Syntax" "ghc-9.13-inplace" '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]))))) |
JavaScript values
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: |
JFunc [Ident] JStgStat | A function |
Instances
JVarMagic JVal Source # | |||||
ToJExpr JVal Source # | |||||
Generic JVal Source # | |||||
Defined in GHC.JS.JStg.Syntax
| |||||
Eq JVal Source # | |||||
type Rep JVal Source # | |||||
Defined in GHC.JS.JStg.Syntax type Rep JVal = D1 ('MetaData "JVal" "GHC.JS.JStg.Syntax" "ghc-9.13-inplace" '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)))))) |
JS Binary Operators. We do not deeply embed the comma operator and the assignment operators
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
NFData Op Source # | |||||
Defined in GHC.JS.JStg.Syntax | |||||
Data Op Source # | |||||
Defined in GHC.JS.JStg.Syntax 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 # 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 # | |||||
Generic Op Source # | |||||
Defined in GHC.JS.JStg.Syntax
| |||||
Show Op Source # | |||||
Eq Op Source # | |||||
Ord Op Source # | |||||
type Rep Op Source # | |||||
Defined in GHC.JS.JStg.Syntax type Rep Op = D1 ('MetaData "Op" "GHC.JS.JStg.Syntax" "ghc-9.13-inplace" '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)))))) |
JS Unary Operators
AssignOp | Vanilla Assignment: = |
AddAssignOp | Addition Assignment: += |
SubAssignOp | Subtraction Assignment: -= |
Instances
NFData AOp Source # | |||||
Defined in GHC.JS.JStg.Syntax | |||||
Data AOp Source # | |||||
Defined in GHC.JS.JStg.Syntax 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 # 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 # | |||||
Generic AOp Source # | |||||
Defined in GHC.JS.JStg.Syntax
| |||||
Show AOp Source # | |||||
Eq AOp Source # | |||||
Ord AOp Source # | |||||
type Rep AOp Source # | |||||
Defined in GHC.JS.JStg.Syntax |
JS Unary Operators
NotOp | Logical Not: |
BNotOp | Bitwise Not: |
NegOp | Negation: |
PlusOp | Unary Plus: |
NewOp | new x |
TypeofOp | typeof x |
DeleteOp | delete x |
YieldOp | yield x |
VoidOp | void x |
PreIncOp | Prefix Increment: |
PostIncOp | Postfix Increment: |
PreDecOp | Prefix Decrement: |
PostDecOp | Postfix Decrement: |
Instances
NFData UOp Source # | |||||
Defined in GHC.JS.JStg.Syntax | |||||
Data UOp Source # | |||||
Defined in GHC.JS.JStg.Syntax 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 # 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 # | |||||
Generic UOp Source # | |||||
Defined in GHC.JS.JStg.Syntax
| |||||
Show UOp Source # | |||||
Eq UOp Source # | |||||
Ord UOp Source # | |||||
type Rep UOp Source # | |||||
Defined in GHC.JS.JStg.Syntax type Rep UOp = D1 ('MetaData "UOp" "GHC.JS.JStg.Syntax" "ghc-9.13-inplace" '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 String :: FastString -> JStgExpr Source #
pattern synonym to create string values
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.
Instances
Binary SaneDouble Source # | |
Defined in GHC.Types.SaneDouble put_ :: WriteBinHandle -> SaneDouble -> IO () Source # put :: WriteBinHandle -> SaneDouble -> IO (Bin SaneDouble) Source # get :: ReadBinHandle -> IO SaneDouble Source # | |
Num SaneDouble Source # | |
Defined in GHC.Types.SaneDouble (+) :: SaneDouble -> SaneDouble -> SaneDouble # (-) :: SaneDouble -> SaneDouble -> SaneDouble # (*) :: SaneDouble -> SaneDouble -> SaneDouble # negate :: SaneDouble -> SaneDouble # abs :: SaneDouble -> SaneDouble # signum :: SaneDouble -> SaneDouble # fromInteger :: Integer -> SaneDouble # | |
Fractional SaneDouble Source # | |
Defined in GHC.Types.SaneDouble (/) :: SaneDouble -> SaneDouble -> SaneDouble # recip :: SaneDouble -> SaneDouble # fromRational :: Rational -> SaneDouble # | |
Show SaneDouble Source # | |
Defined in GHC.Types.SaneDouble showsPrec :: Int -> SaneDouble -> ShowS # show :: SaneDouble -> String # showList :: [SaneDouble] -> ShowS # | |
Eq SaneDouble Source # | |
Defined in GHC.Types.SaneDouble (==) :: SaneDouble -> SaneDouble -> Bool # (/=) :: SaneDouble -> SaneDouble -> Bool # | |
Ord SaneDouble Source # | |
Defined in GHC.Types.SaneDouble compare :: SaneDouble -> SaneDouble -> Ordering # (<) :: SaneDouble -> SaneDouble -> Bool # (<=) :: SaneDouble -> SaneDouble -> Bool # (>) :: SaneDouble -> SaneDouble -> Bool # (>=) :: SaneDouble -> SaneDouble -> Bool # max :: SaneDouble -> SaneDouble -> SaneDouble # min :: SaneDouble -> SaneDouble -> SaneDouble # |
pattern Func :: [Ident] -> JStgStat -> JStgExpr Source #
pattern synonym to create an anonymous function
global :: FastString -> JStgExpr Source #
construct a JS reference, intended to refer to a global name
local :: FastString -> JStgExpr Source #
construct a JS reference, intended to refer to a local name