{-# LANGUAGE OverloadedStrings, DeriveDataTypeable #-}
module Foreign.JavaScript.Types where
import Control.Applicative
import qualified Control.Exception as E
import Control.Concurrent.STM as STM
import Control.Concurrent.Chan as Chan
import Control.Concurrent.MVar
import Control.DeepSeq
import Data.Aeson as JSON
import Data.ByteString.Char8 (ByteString)
import qualified Data.ByteString.Char8 as BS (hPutStrLn)
import Data.IORef
import Data.Map as Map
import Data.String
import Data.Text
import Data.Typeable
import Snap.Core (Cookie(..))
import System.IO (stderr)
import Foreign.RemotePtr
data Config = Config
{ Config -> Maybe Int
jsPort :: Maybe Int
, Config -> Maybe ByteString
jsAddr :: Maybe ByteString
, Config -> Maybe [Char]
jsCustomHTML :: Maybe FilePath
, Config -> Maybe [Char]
jsStatic :: Maybe FilePath
, Config -> ByteString -> IO ()
jsLog :: ByteString -> IO ()
, Config -> Bool
jsWindowReloadOnDisconnect :: Bool
, Config -> CallBufferMode
jsCallBufferMode :: CallBufferMode
, Config -> Maybe ConfigSSL
jsUseSSL :: Maybe ConfigSSL
}
data ConfigSSL = ConfigSSL
{ ConfigSSL -> ByteString
jsSSLBind :: ByteString
, ConfigSSL -> [Char]
jsSSLCert :: FilePath
, ConfigSSL -> Bool
jsSSLChainCert :: Bool
, ConfigSSL -> [Char]
jsSSLKey :: FilePath
, ConfigSSL -> Int
jsSSLPort :: Int
}
defaultPort :: Int
defaultPort :: Int
defaultPort = Int
8023
defaultAddr :: ByteString
defaultAddr :: ByteString
defaultAddr = ByteString
"127.0.0.1"
defaultConfig :: Config
defaultConfig :: Config
defaultConfig = Config
{ jsPort :: Maybe Int
jsPort = forall a. Maybe a
Nothing
, jsAddr :: Maybe ByteString
jsAddr = forall a. Maybe a
Nothing
, jsWindowReloadOnDisconnect :: Bool
jsWindowReloadOnDisconnect = Bool
True
, jsCustomHTML :: Maybe [Char]
jsCustomHTML = forall a. Maybe a
Nothing
, jsStatic :: Maybe [Char]
jsStatic = forall a. Maybe a
Nothing
, jsLog :: ByteString -> IO ()
jsLog = Handle -> ByteString -> IO ()
BS.hPutStrLn Handle
stderr
, jsCallBufferMode :: CallBufferMode
jsCallBufferMode = CallBufferMode
FlushOften
, jsUseSSL :: Maybe ConfigSSL
jsUseSSL = forall a. Maybe a
Nothing
}
type URI = String
type MimeType = String
data Server = Server
{ Server -> MVar Filepaths
sFiles :: MVar Filepaths
, Server -> MVar Filepaths
sDirs :: MVar Filepaths
, Server -> ByteString -> IO ()
sLog :: ByteString -> IO ()
}
type Filepaths = (Integer, Map ByteString (FilePath, MimeType))
newFilepaths :: (Integer, Map k a)
newFilepaths = (Integer
0, forall k a. Map k a
Map.empty)
data Comm = Comm
{ Comm -> TQueue Value
commIn :: TQueue JSON.Value
, Comm -> TQueue Value
commOut :: TQueue JSON.Value
, Comm -> TVar Bool
commOpen :: TVar Bool
, Comm -> IO ()
commClose :: IO ()
}
writeComm :: Comm -> JSON.Value -> STM ()
writeComm :: Comm -> Value -> STM ()
writeComm Comm
c = forall a. TQueue a -> a -> STM ()
STM.writeTQueue (Comm -> TQueue Value
commOut Comm
c)
readComm :: Comm -> STM JSON.Value
readComm :: Comm -> STM Value
readComm Comm
c = forall a. TQueue a -> STM a
STM.readTQueue (Comm -> TQueue Value
commIn Comm
c)
data ClientMsg
= Event Coupon JSON.Value
| Result JSON.Value
| Exception String
| Quit
deriving (ClientMsg -> ClientMsg -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ClientMsg -> ClientMsg -> Bool
$c/= :: ClientMsg -> ClientMsg -> Bool
== :: ClientMsg -> ClientMsg -> Bool
$c== :: ClientMsg -> ClientMsg -> Bool
Eq, Int -> ClientMsg -> ShowS
[ClientMsg] -> ShowS
ClientMsg -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [ClientMsg] -> ShowS
$cshowList :: [ClientMsg] -> ShowS
show :: ClientMsg -> [Char]
$cshow :: ClientMsg -> [Char]
showsPrec :: Int -> ClientMsg -> ShowS
$cshowsPrec :: Int -> ClientMsg -> ShowS
Show)
instance FromJSON ClientMsg where
parseJSON :: Value -> Parser ClientMsg
parseJSON (Object Object
msg) = do
Coupon
tag <- Object
msg forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"tag"
case (Coupon
tag :: Text) of
Coupon
"Event" -> Coupon -> Value -> ClientMsg
Event forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Object
msg forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name") forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Object
msg forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"arguments")
Coupon
"Result" -> Value -> ClientMsg
Result forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Object
msg forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"contents")
Coupon
"Exception" -> [Char] -> ClientMsg
Exception forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Object
msg forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"contents")
Coupon
"Quit" -> forall (m :: * -> *) a. Monad m => a -> m a
return ClientMsg
Quit
readClient :: Comm -> STM ClientMsg
readClient :: Comm -> STM ClientMsg
readClient Comm
c = do
Value
msg <- Comm -> STM Value
readComm Comm
c
case forall a. FromJSON a => Value -> Result a
JSON.fromJSON Value
msg of
Error [Char]
s -> forall a. HasCallStack => [Char] -> a
error forall a b. (a -> b) -> a -> b
$ [Char]
"Foreign.JavaScript: Error parsing client message " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show [Char]
s
Success ClientMsg
x -> forall (m :: * -> *) a. Monad m => a -> m a
return ClientMsg
x
data ServerMsg
= RunEval String
| CallEval String
| Debug String
| Timestamp
deriving (ServerMsg -> ServerMsg -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ServerMsg -> ServerMsg -> Bool
$c/= :: ServerMsg -> ServerMsg -> Bool
== :: ServerMsg -> ServerMsg -> Bool
$c== :: ServerMsg -> ServerMsg -> Bool
Eq,Int -> ServerMsg -> ShowS
[ServerMsg] -> ShowS
ServerMsg -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [ServerMsg] -> ShowS
$cshowList :: [ServerMsg] -> ShowS
show :: ServerMsg -> [Char]
$cshow :: ServerMsg -> [Char]
showsPrec :: Int -> ServerMsg -> ShowS
$cshowsPrec :: Int -> ServerMsg -> ShowS
Show)
instance NFData ServerMsg where
rnf :: ServerMsg -> ()
rnf (RunEval [Char]
x) = forall a. NFData a => a -> ()
rnf [Char]
x
rnf (CallEval [Char]
x) = forall a. NFData a => a -> ()
rnf [Char]
x
rnf (Debug [Char]
x) = forall a. NFData a => a -> ()
rnf [Char]
x
rnf (ServerMsg
Timestamp ) = ()
instance ToJSON ServerMsg where
toJSON :: ServerMsg -> Value
toJSON (Debug [Char]
x) = [Pair] -> Value
object [ Key
"tag" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Char] -> Coupon
t [Char]
"Debug" , Key
"contents" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= forall a. ToJSON a => a -> Value
toJSON [Char]
x]
toJSON (ServerMsg
Timestamp ) = [Pair] -> Value
object [ Key
"tag" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Char] -> Coupon
t [Char]
"Timestamp" ]
toJSON (RunEval [Char]
x) = [Pair] -> Value
object [ Key
"tag" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Char] -> Coupon
t [Char]
"RunEval" , Key
"contents" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= forall a. ToJSON a => a -> Value
toJSON [Char]
x]
toJSON (CallEval [Char]
x) = [Pair] -> Value
object [ Key
"tag" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Char] -> Coupon
t [Char]
"CallEval", Key
"contents" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= forall a. ToJSON a => a -> Value
toJSON [Char]
x]
t :: [Char] -> Coupon
t [Char]
s = forall a. IsString a => [Char] -> a
fromString [Char]
s :: Text
writeServer :: Comm -> ServerMsg -> STM ()
writeServer :: Comm -> ServerMsg -> STM ()
writeServer Comm
c = Comm -> Value -> STM ()
writeComm Comm
c forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToJSON a => a -> Value
toJSON forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. NFData a => a -> a
force
data JavaScriptException = JavaScriptException String deriving Typeable
instance E.Exception JavaScriptException
instance Show JavaScriptException where
showsPrec :: Int -> JavaScriptException -> ShowS
showsPrec Int
_ (JavaScriptException [Char]
err) = [Char] -> ShowS
showString forall a b. (a -> b) -> a -> b
$ [Char]
"JavaScript error: " forall a. [a] -> [a] -> [a]
++ [Char]
err
type Event = (Coupon, JSON.Value)
type HsEvent = RemotePtr (JSON.Value -> IO ())
quit :: Event
quit :: Event
quit = (Coupon
"quit", Value
JSON.Null)
data CallBufferMode
= NoBuffering
| BufferRun
| FlushOften
| FlushPeriodically
flushPeriod :: Int
flushPeriod = Int
300 :: Int
type EventLoop = Server -> RequestInfo -> Comm -> IO ()
type RequestInfo = [Cookie]
data Window = Window
{ Window -> Server
getServer :: Server
, Window -> [Cookie]
getCookies :: [Cookie]
, Window -> [Char] -> IO ()
runEval :: String -> IO ()
, Window -> [Char] -> IO Value
callEval :: String -> IO JSON.Value
, Window -> TMVar ShowS
wCallBuffer :: TMVar (String -> String)
, Window -> TVar CallBufferMode
wCallBufferMode :: TVar CallBufferMode
, Window -> IO ()
timestamp :: IO ()
, Window -> [Char] -> IO ()
debug :: String -> IO ()
, Window -> IO () -> IO ()
onDisconnect :: IO () -> IO ()
, Window -> RemotePtr ()
wRoot :: RemotePtr ()
, Window -> Vendor (Value -> IO ())
wEventHandlers :: Vendor (JSON.Value -> IO ())
, Window -> Vendor JSPtr
wJSObjects :: Vendor JSPtr
}
newPartialWindow :: IO Window
newPartialWindow :: IO Window
newPartialWindow = do
RemotePtr ()
ptr <- forall a. Coupon -> a -> Vendor a -> IO (RemotePtr a)
newRemotePtr Coupon
"" () forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall a. IO (Vendor a)
newVendor
TMVar ShowS
b1 <- forall a. a -> IO (TMVar a)
newTMVarIO forall a. a -> a
id
TVar CallBufferMode
b2 <- forall a. a -> IO (TVar a)
newTVarIO CallBufferMode
NoBuffering
let nop :: b -> IO ()
nop = forall a b. a -> b -> a
const forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. Monad m => a -> m a
return ()
Server
-> [Cookie]
-> ([Char] -> IO ())
-> ([Char] -> IO Value)
-> TMVar ShowS
-> TVar CallBufferMode
-> IO ()
-> ([Char] -> IO ())
-> (IO () -> IO ())
-> RemotePtr ()
-> Vendor (Value -> IO ())
-> Vendor JSPtr
-> Window
Window forall a. HasCallStack => a
undefined [] forall {b}. b -> IO ()
nop forall a. HasCallStack => a
undefined TMVar ShowS
b1 TVar CallBufferMode
b2 (forall (m :: * -> *) a. Monad m => a -> m a
return ()) forall {b}. b -> IO ()
nop forall {b}. b -> IO ()
nop RemotePtr ()
ptr forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. IO (Vendor a)
newVendor forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. IO (Vendor a)
newVendor
root :: Window -> RemotePtr ()
root :: Window -> RemotePtr ()
root = Window -> RemotePtr ()
wRoot
newtype JSPtr = JSPtr { JSPtr -> Coupon
unsJSPtr :: Coupon }
type JSObject = RemotePtr JSPtr
data NewJSObject = NewJSObject