module GHCJS.Foreign.Internal (
    jsTrue
  , jsFalse
  , jsNull
  , toJSBool
  , jsUndefined
  , isTruthy
  , isNull
  , isUndefined
  , JSType(..)
) where
import Language.Javascript.JSaddle.Types (JSVal(..), GHCJSPure(..))
import Language.Javascript.JSaddle.Native.Internal
       (valueToBool)
import Data.Typeable (Typeable)
import GHCJS.Prim (isNull, isUndefined)
import System.IO.Unsafe (unsafePerformIO)
import Data.IORef (newIORef)
jsTrue :: JSVal
jsTrue :: JSVal
jsTrue = IORef JSValueRef -> JSVal
JSVal (IORef JSValueRef -> JSVal)
-> (IO (IORef JSValueRef) -> IORef JSValueRef)
-> IO (IORef JSValueRef)
-> JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO (IORef JSValueRef) -> IORef JSValueRef
forall a. IO a -> a
unsafePerformIO (IO (IORef JSValueRef) -> JSVal) -> IO (IORef JSValueRef) -> JSVal
forall a b. (a -> b) -> a -> b
$ JSValueRef -> IO (IORef JSValueRef)
forall a. a -> IO (IORef a)
newIORef JSValueRef
3
{-# NOINLINE jsTrue #-}
jsFalse :: JSVal
jsFalse :: JSVal
jsFalse = IORef JSValueRef -> JSVal
JSVal (IORef JSValueRef -> JSVal)
-> (IO (IORef JSValueRef) -> IORef JSValueRef)
-> IO (IORef JSValueRef)
-> JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO (IORef JSValueRef) -> IORef JSValueRef
forall a. IO a -> a
unsafePerformIO (IO (IORef JSValueRef) -> JSVal) -> IO (IORef JSValueRef) -> JSVal
forall a b. (a -> b) -> a -> b
$ JSValueRef -> IO (IORef JSValueRef)
forall a. a -> IO (IORef a)
newIORef JSValueRef
2
{-# NOINLINE jsFalse #-}
jsNull :: JSVal
jsNull :: JSVal
jsNull = IORef JSValueRef -> JSVal
JSVal (IORef JSValueRef -> JSVal)
-> (IO (IORef JSValueRef) -> IORef JSValueRef)
-> IO (IORef JSValueRef)
-> JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO (IORef JSValueRef) -> IORef JSValueRef
forall a. IO a -> a
unsafePerformIO (IO (IORef JSValueRef) -> JSVal) -> IO (IORef JSValueRef) -> JSVal
forall a b. (a -> b) -> a -> b
$ JSValueRef -> IO (IORef JSValueRef)
forall a. a -> IO (IORef a)
newIORef JSValueRef
0
{-# NOINLINE jsNull #-}
toJSBool :: Bool -> JSVal
toJSBool :: Bool -> JSVal
toJSBool Bool
b = IORef JSValueRef -> JSVal
JSVal (IORef JSValueRef -> JSVal)
-> (JSValueRef -> IORef JSValueRef) -> JSValueRef -> JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO (IORef JSValueRef) -> IORef JSValueRef
forall a. IO a -> a
unsafePerformIO (IO (IORef JSValueRef) -> IORef JSValueRef)
-> (JSValueRef -> IO (IORef JSValueRef))
-> JSValueRef
-> IORef JSValueRef
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSValueRef -> IO (IORef JSValueRef)
forall a. a -> IO (IORef a)
newIORef (JSValueRef -> JSVal) -> JSValueRef -> JSVal
forall a b. (a -> b) -> a -> b
$ if Bool
b then JSValueRef
3 else JSValueRef
2
{-# NOINLINE toJSBool #-}
jsUndefined :: JSVal
jsUndefined :: JSVal
jsUndefined = IORef JSValueRef -> JSVal
JSVal (IORef JSValueRef -> JSVal)
-> (IO (IORef JSValueRef) -> IORef JSValueRef)
-> IO (IORef JSValueRef)
-> JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO (IORef JSValueRef) -> IORef JSValueRef
forall a. IO a -> a
unsafePerformIO (IO (IORef JSValueRef) -> JSVal) -> IO (IORef JSValueRef) -> JSVal
forall a b. (a -> b) -> a -> b
$ JSValueRef -> IO (IORef JSValueRef)
forall a. a -> IO (IORef a)
newIORef JSValueRef
1
{-# NOINLINE jsUndefined #-}
isTruthy :: JSVal -> GHCJSPure Bool
isTruthy :: JSVal -> GHCJSPure Bool
isTruthy = JSM Bool -> GHCJSPure Bool
forall a. JSM a -> GHCJSPure a
GHCJSPure (JSM Bool -> GHCJSPure Bool)
-> (JSVal -> JSM Bool) -> JSVal -> GHCJSPure Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> JSM Bool
valueToBool
{-# INLINE isTruthy #-}
data JSType = Undefined
            | Object
            | Boolean
            | Number
            | String
            | Symbol
            | Function
            | Other    
            deriving (Int -> JSType -> ShowS
[JSType] -> ShowS
JSType -> String
(Int -> JSType -> ShowS)
-> (JSType -> String) -> ([JSType] -> ShowS) -> Show JSType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [JSType] -> ShowS
$cshowList :: [JSType] -> ShowS
show :: JSType -> String
$cshow :: JSType -> String
showsPrec :: Int -> JSType -> ShowS
$cshowsPrec :: Int -> JSType -> ShowS
Show, JSType -> JSType -> Bool
(JSType -> JSType -> Bool)
-> (JSType -> JSType -> Bool) -> Eq JSType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: JSType -> JSType -> Bool
$c/= :: JSType -> JSType -> Bool
== :: JSType -> JSType -> Bool
$c== :: JSType -> JSType -> Bool
Eq, Eq JSType
Eq JSType
-> (JSType -> JSType -> Ordering)
-> (JSType -> JSType -> Bool)
-> (JSType -> JSType -> Bool)
-> (JSType -> JSType -> Bool)
-> (JSType -> JSType -> Bool)
-> (JSType -> JSType -> JSType)
-> (JSType -> JSType -> JSType)
-> Ord JSType
JSType -> JSType -> Bool
JSType -> JSType -> Ordering
JSType -> JSType -> JSType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: JSType -> JSType -> JSType
$cmin :: JSType -> JSType -> JSType
max :: JSType -> JSType -> JSType
$cmax :: JSType -> JSType -> JSType
>= :: JSType -> JSType -> Bool
$c>= :: JSType -> JSType -> Bool
> :: JSType -> JSType -> Bool
$c> :: JSType -> JSType -> Bool
<= :: JSType -> JSType -> Bool
$c<= :: JSType -> JSType -> Bool
< :: JSType -> JSType -> Bool
$c< :: JSType -> JSType -> Bool
compare :: JSType -> JSType -> Ordering
$ccompare :: JSType -> JSType -> Ordering
$cp1Ord :: Eq JSType
Ord, Int -> JSType
JSType -> Int
JSType -> [JSType]
JSType -> JSType
JSType -> JSType -> [JSType]
JSType -> JSType -> JSType -> [JSType]
(JSType -> JSType)
-> (JSType -> JSType)
-> (Int -> JSType)
-> (JSType -> Int)
-> (JSType -> [JSType])
-> (JSType -> JSType -> [JSType])
-> (JSType -> JSType -> [JSType])
-> (JSType -> JSType -> JSType -> [JSType])
-> Enum JSType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: JSType -> JSType -> JSType -> [JSType]
$cenumFromThenTo :: JSType -> JSType -> JSType -> [JSType]
enumFromTo :: JSType -> JSType -> [JSType]
$cenumFromTo :: JSType -> JSType -> [JSType]
enumFromThen :: JSType -> JSType -> [JSType]
$cenumFromThen :: JSType -> JSType -> [JSType]
enumFrom :: JSType -> [JSType]
$cenumFrom :: JSType -> [JSType]
fromEnum :: JSType -> Int
$cfromEnum :: JSType -> Int
toEnum :: Int -> JSType
$ctoEnum :: Int -> JSType
pred :: JSType -> JSType
$cpred :: JSType -> JSType
succ :: JSType -> JSType
$csucc :: JSType -> JSType
Enum, Typeable)