ContentsIndex
HJS.Interpreter.InterpM
Documentation
class Convert a where
Methods
toBoolean :: a -> Value
toNumber :: a -> Value
toString :: a -> Value
isUndefined :: a -> Bool
show/hide Instances
class SubType sub sup where
Methods
inj :: sub -> sup
prj :: sup -> Maybe sub
show/hide Instances
SubType sub ()
SubType a (Either a b)
SubType a b => SubType a (Either c b)
toRealInt :: Convert a => a -> Int
toRealString :: Convert a => a -> String
toRealBool :: Convert a => a -> Bool
data Ref
Constructors
Ref String
RefObj Int String
show/hide Instances
Convert Ref
Eq Ref
Ord Ref
Show Ref
data Undefined
Constructors
Undefined
show/hide Instances
data Null
Constructors
Null
show/hide Instances
data CallValue
Constructors
CallJS [SourceElement]
CallBuiltIn (InterpM Value)
show/hide Instances
data BreakContinue
Constructors
Break
Continue
show/hide Instances
data ArgList
Constructors
ArgList [String]
VarArgList
type Value = Either Int (Either String (Either Bool (Either Undefined (Either Null (Either Ref (Either [Int] (Either CallValue (Either [String] (Either BreakContinue ())))))))))
data Attribute
Constructors
ReadOnly
DontEnum
DontDelete
Internal
show/hide Instances
data Object
Constructors
Object
prototype :: (Maybe Int)
klass :: String
value :: (Maybe Value)
properties :: (Map String (Value, [Attribute]))
show/hide Instances
Show Object
getObject :: Int -> InterpM Object
putObject :: Int -> Object -> InterpM ()
getProperty' :: Object -> String -> InterpM Value
getProperty :: Int -> String -> InterpM Value
putProperty :: Int -> String -> Value -> InterpM ()
canPut :: Object -> String -> InterpM Bool
hasProperty :: Object -> String -> Bool
deleteProperty :: Object -> String -> Object
newObject :: String -> InterpM Int
getValue :: Value -> InterpM Value
getValue' :: [Int] -> String -> InterpM Value
putValue :: Value -> Value -> InterpM ()
newBuiltInFunction :: [String] -> InterpM Value -> InterpM Int
type Ctx = ([Int], Int, Int)
type JSState = ([Ctx], Map Int Object)
data Throwable
Constructors
ThrowReturn Value
ThrowBreak (Maybe String)
ThrowContinue (Maybe String)
ThrowException Value
ThrowTypeError String
ThrowInternalError String
show/hide Instances
type InterpM = ErrorT Throwable (StateT JSState Identity)
putGlobalContext :: InterpM ()
pushContext :: Ctx -> InterpM ()
popContext :: InterpM ()
Produced by Haddock version 0.7