{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module GHCJS.Prim.Internal ( JSVal(..)
, JSValueRef
, JSException(..)
, WouldBlockException(..)
, mkJSException
, jsNull
) where
import Control.DeepSeq (NFData(..))
import Data.Int (Int64)
import Data.Typeable (Typeable)
import Unsafe.Coerce (unsafeCoerce)
import Data.Aeson (ToJSON(..), FromJSON(..))
import qualified GHC.Exception as Ex
import Data.IORef (newIORef, IORef)
import System.IO.Unsafe (unsafePerformIO)
type JSValueRef = Int64
newtype JSVal = JSVal (IORef JSValueRef)
instance NFData JSVal where
rnf :: JSVal -> ()
rnf JSVal
x = JSVal
x JSVal -> () -> ()
`seq` ()
data JSException = JSException JSVal String
deriving (Typeable)
instance Ex.Exception JSException
instance Show JSException where
show :: JSException -> String
show (JSException JSVal
_ String
xs) = String
"JavaScript exception: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
xs
mkJSException :: JSVal -> IO JSException
mkJSException :: JSVal -> IO JSException
mkJSException JSVal
ref =
JSException -> IO JSException
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> String -> JSException
JSException (JSVal -> JSVal
forall a b. a -> b
unsafeCoerce JSVal
ref) String
"")
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 #-}
data WouldBlockException = WouldBlockException
deriving (Typeable)
instance Show WouldBlockException where
show :: WouldBlockException -> String
show WouldBlockException
_ = String
"thread would block"
instance Ex.Exception WouldBlockException