{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleInstances, TypeSynonymInstances, ScopedTypeVariables #-}
{-# LANGUAGE RecordWildCards #-}
module Foreign.JavaScript.Marshal (
ToJS(..), FromJS,
FFI, JSFunction, toCode, marshalResult, ffi,
IsHandler, convertArguments, handle,
NewJSObject, wrapImposeStablePtr,
) where
import Data.Aeson as JSON
#if defined(CABAL)
#if MIN_VERSION_aeson(1,0,0)
import qualified Data.Aeson.Text as JSON (encodeToTextBuilder)
#else
import qualified Data.Aeson.Encode as JSON (encodeToTextBuilder)
#endif
#else
import qualified Data.Aeson.Text as JSON (encodeToTextBuilder)
#endif
import Data.List (intercalate)
import qualified Data.Text as T
import qualified Data.Text.Lazy
import qualified Data.Text.Lazy.Builder
import qualified Data.Vector as Vector
import Safe (atMay)
import Foreign.JavaScript.EventLoop (fromJSStablePtr, newJSObjectFromCoupon )
import Foreign.JavaScript.Types
import Foreign.RemotePtr
newtype JSCode = JSCode { JSCode -> String
unJSCode :: String }
deriving (JSCode -> JSCode -> Bool
(JSCode -> JSCode -> Bool)
-> (JSCode -> JSCode -> Bool) -> Eq JSCode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: JSCode -> JSCode -> Bool
== :: JSCode -> JSCode -> Bool
$c/= :: JSCode -> JSCode -> Bool
/= :: JSCode -> JSCode -> Bool
Eq, Eq JSCode
Eq JSCode =>
(JSCode -> JSCode -> Ordering)
-> (JSCode -> JSCode -> Bool)
-> (JSCode -> JSCode -> Bool)
-> (JSCode -> JSCode -> Bool)
-> (JSCode -> JSCode -> Bool)
-> (JSCode -> JSCode -> JSCode)
-> (JSCode -> JSCode -> JSCode)
-> Ord JSCode
JSCode -> JSCode -> Bool
JSCode -> JSCode -> Ordering
JSCode -> JSCode -> JSCode
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
$ccompare :: JSCode -> JSCode -> Ordering
compare :: JSCode -> JSCode -> Ordering
$c< :: JSCode -> JSCode -> Bool
< :: JSCode -> JSCode -> Bool
$c<= :: JSCode -> JSCode -> Bool
<= :: JSCode -> JSCode -> Bool
$c> :: JSCode -> JSCode -> Bool
> :: JSCode -> JSCode -> Bool
$c>= :: JSCode -> JSCode -> Bool
>= :: JSCode -> JSCode -> Bool
$cmax :: JSCode -> JSCode -> JSCode
max :: JSCode -> JSCode -> JSCode
$cmin :: JSCode -> JSCode -> JSCode
min :: JSCode -> JSCode -> JSCode
Ord, Int -> JSCode -> String -> String
[JSCode] -> String -> String
JSCode -> String
(Int -> JSCode -> String -> String)
-> (JSCode -> String)
-> ([JSCode] -> String -> String)
-> Show JSCode
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> JSCode -> String -> String
showsPrec :: Int -> JSCode -> String -> String
$cshow :: JSCode -> String
show :: JSCode -> String
$cshowList :: [JSCode] -> String -> String
showList :: [JSCode] -> String -> String
Show)
class ToJS a where
render :: a -> IO JSCode
renderList :: [a] -> IO JSCode
renderList [a]
xs = do
[JSCode]
ys <- (a -> IO JSCode) -> [a] -> IO [JSCode]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM a -> IO JSCode
forall a. ToJS a => a -> IO JSCode
render [a]
xs
String -> IO JSCode
jsCode (String -> IO JSCode) -> String -> IO JSCode
forall a b. (a -> b) -> a -> b
$ String
"[" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"," ((JSCode -> String) -> [JSCode] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map JSCode -> String
unJSCode [JSCode]
ys) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"]"
jsCode :: String -> IO JSCode
jsCode :: String -> IO JSCode
jsCode = JSCode -> IO JSCode
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSCode -> IO JSCode) -> (String -> JSCode) -> String -> IO JSCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> JSCode
JSCode
instance ToJS Float where render :: Float -> IO JSCode
render = Value -> IO JSCode
forall a. ToJS a => a -> IO JSCode
render (Value -> IO JSCode) -> (Float -> Value) -> Float -> IO JSCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Float -> Value
forall a. ToJSON a => a -> Value
JSON.toJSON
instance ToJS Double where render :: Double -> IO JSCode
render = Value -> IO JSCode
forall a. ToJS a => a -> IO JSCode
render (Value -> IO JSCode) -> (Double -> Value) -> Double -> IO JSCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> Value
forall a. ToJSON a => a -> Value
JSON.toJSON
instance ToJS Int where render :: Int -> IO JSCode
render = String -> IO JSCode
jsCode (String -> IO JSCode) -> (Int -> String) -> Int -> IO JSCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String
forall a. Show a => a -> String
show
instance ToJS Bool where render :: Bool -> IO JSCode
render Bool
b = String -> IO JSCode
jsCode (String -> IO JSCode) -> String -> IO JSCode
forall a b. (a -> b) -> a -> b
$ if Bool
b then String
"true" else String
"false"
instance ToJS JSON.Value where render :: Value -> IO JSCode
render = String -> IO JSCode
jsCode (String -> IO JSCode) -> (Value -> String) -> Value -> IO JSCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> String
forall a. ToJSON a => a -> String
showJSON
instance ToJS T.Text where render :: Coupon -> IO JSCode
render = Value -> IO JSCode
forall a. ToJS a => a -> IO JSCode
render (Value -> IO JSCode) -> (Coupon -> Value) -> Coupon -> IO JSCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Coupon -> Value
JSON.String
instance ToJS Char where
render :: Char -> IO JSCode
render Char
x = String -> IO JSCode
forall a. ToJS a => [a] -> IO JSCode
renderList [Char
x]
renderList :: String -> IO JSCode
renderList = Value -> IO JSCode
forall a. ToJS a => a -> IO JSCode
render (Value -> IO JSCode) -> (String -> Value) -> String -> IO JSCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Coupon -> Value
JSON.String (Coupon -> Value) -> (String -> Coupon) -> String -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Coupon
T.pack
instance ToJS a => ToJS [a] where
render :: [a] -> IO JSCode
render = [a] -> IO JSCode
forall a. ToJS a => [a] -> IO JSCode
renderList
instance ToJS HsEvent where
render :: HsEvent -> IO JSCode
render HsEvent
x = Coupon -> IO JSCode
forall a. ToJS a => a -> IO JSCode
render (Coupon -> IO JSCode) -> IO Coupon -> IO JSCode
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< HsEvent -> IO Coupon
forall a. RemotePtr a -> IO Coupon
unprotectedGetCoupon HsEvent
x
instance ToJS JSObject where
render :: JSObject -> IO JSCode
render JSObject
x = String -> JSCode -> JSCode
apply1 String
"Haskell.deRefStablePtr(%1)"
(JSCode -> JSCode) -> IO JSCode -> IO JSCode
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Coupon -> IO JSCode
forall a. ToJS a => a -> IO JSCode
render (Coupon -> IO JSCode) -> IO Coupon -> IO JSCode
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< JSObject -> IO Coupon
forall a. RemotePtr a -> IO Coupon
unprotectedGetCoupon JSObject
x)
showJSON :: ToJSON a => a -> String
showJSON :: forall a. ToJSON a => a -> String
showJSON
= Text -> String
Data.Text.Lazy.unpack
(Text -> String) -> (a -> Text) -> a -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> Text
Data.Text.Lazy.Builder.toLazyText
(Builder -> Text) -> (a -> Builder) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Builder
forall a. ToJSON a => a -> Builder
JSON.encodeToTextBuilder (Value -> Builder) -> (a -> Value) -> a -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Value
forall a. ToJSON a => a -> Value
JSON.toJSON
data FromJS' a = FromJS'
{ forall a. FromJS' a -> JSCode -> JSCode
wrapCode :: (JSCode -> JSCode)
, forall a. FromJS' a -> Window -> Value -> IO a
marshal :: Window -> JSON.Value -> IO a
}
class FromJS a where
fromJS :: FromJS' a
simple :: FromJSON a => (JSCode -> JSCode) -> FromJS' a
simple :: forall a. FromJSON a => (JSCode -> JSCode) -> FromJS' a
simple JSCode -> JSCode
f =
FromJS' { wrapCode :: JSCode -> JSCode
wrapCode = JSCode -> JSCode
f , marshal :: Window -> Value -> IO a
marshal = \Window
_ -> Result a -> IO a
forall {m :: * -> *} {a}. Monad m => Result a -> m a
fromSuccessIO (Result a -> IO a) -> (Value -> Result a) -> Value -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Result a
forall a. FromJSON a => Value -> Result a
JSON.fromJSON }
where
fromSuccessIO :: Result a -> m a
fromSuccessIO (JSON.Success a
a) = a -> m a
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return a
a
instance FromJS String where fromJS :: FromJS' String
fromJS = (JSCode -> JSCode) -> FromJS' String
forall a. FromJSON a => (JSCode -> JSCode) -> FromJS' a
simple ((JSCode -> JSCode) -> FromJS' String)
-> (JSCode -> JSCode) -> FromJS' String
forall a b. (a -> b) -> a -> b
$ String -> JSCode -> JSCode
apply1 String
"%1.toString()"
instance FromJS T.Text where fromJS :: FromJS' Coupon
fromJS = (JSCode -> JSCode) -> FromJS' Coupon
forall a. FromJSON a => (JSCode -> JSCode) -> FromJS' a
simple ((JSCode -> JSCode) -> FromJS' Coupon)
-> (JSCode -> JSCode) -> FromJS' Coupon
forall a b. (a -> b) -> a -> b
$ String -> JSCode -> JSCode
apply1 String
"%1.toString()"
instance FromJS Int where fromJS :: FromJS' Int
fromJS = (JSCode -> JSCode) -> FromJS' Int
forall a. FromJSON a => (JSCode -> JSCode) -> FromJS' a
simple JSCode -> JSCode
forall a. a -> a
id
instance FromJS Double where fromJS :: FromJS' Double
fromJS = (JSCode -> JSCode) -> FromJS' Double
forall a. FromJSON a => (JSCode -> JSCode) -> FromJS' a
simple JSCode -> JSCode
forall a. a -> a
id
instance FromJS Float where fromJS :: FromJS' Float
fromJS = (JSCode -> JSCode) -> FromJS' Float
forall a. FromJSON a => (JSCode -> JSCode) -> FromJS' a
simple JSCode -> JSCode
forall a. a -> a
id
instance FromJS JSON.Value where fromJS :: FromJS' Value
fromJS = (JSCode -> JSCode) -> FromJS' Value
forall a. FromJSON a => (JSCode -> JSCode) -> FromJS' a
simple JSCode -> JSCode
forall a. a -> a
id
instance FromJS () where
fromJS :: FromJS' ()
fromJS = FromJS' { wrapCode :: JSCode -> JSCode
wrapCode = JSCode -> JSCode
forall a. a -> a
id, marshal :: Window -> Value -> IO ()
marshal = \Window
_ Value
_ -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return () }
instance FromJS JSObject where
fromJS :: FromJS' JSObject
fromJS = FromJS'
{ wrapCode :: JSCode -> JSCode
wrapCode = String -> JSCode -> JSCode
apply1 String
"Haskell.getStablePtr(%1)"
, marshal :: Window -> Value -> IO JSObject
marshal = \Window
w Value
v -> Value -> Window -> IO JSObject
fromJSStablePtr Value
v Window
w
}
instance FromJS [JSObject] where
fromJS :: FromJS' [JSObject]
fromJS = FromJS'
{ wrapCode :: JSCode -> JSCode
wrapCode = String -> JSCode -> JSCode
apply1 String
"Haskell.map(Haskell.getStablePtr, %1)"
, marshal :: Window -> Value -> IO [JSObject]
marshal = \Window
w (JSON.Array Array
vs) -> do
(Value -> IO JSObject) -> [Value] -> IO [JSObject]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (\Value
v -> Value -> Window -> IO JSObject
fromJSStablePtr Value
v Window
w) (Array -> [Value]
forall a. Vector a -> [a]
Vector.toList Array
vs)
}
instance FromJS NewJSObject where
fromJS :: FromJS' NewJSObject
fromJS = FromJS' { wrapCode :: JSCode -> JSCode
wrapCode = JSCode -> JSCode
forall a. a -> a
id, marshal :: Window -> Value -> IO NewJSObject
marshal = \Window
_ Value
_ -> NewJSObject -> IO NewJSObject
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return NewJSObject
NewJSObject }
wrapImposeStablePtr :: Window -> JSFunction NewJSObject -> IO (JSFunction JSObject)
wrapImposeStablePtr :: Window -> JSFunction NewJSObject -> IO (JSFunction JSObject)
wrapImposeStablePtr (Window{[Cookie]
IO ()
TVar CallBufferMode
RemotePtr ()
TMVar (String -> String)
Vendor JSPtr
Vendor (Value -> IO ())
Server
String -> IO ()
String -> IO Value
IO () -> IO ()
getServer :: Server
getCookies :: [Cookie]
runEval :: String -> IO ()
callEval :: String -> IO Value
wCallBuffer :: TMVar (String -> String)
wCallBufferMode :: TVar CallBufferMode
timestamp :: IO ()
debug :: String -> IO ()
onDisconnect :: IO () -> IO ()
wRoot :: RemotePtr ()
wEventHandlers :: Vendor (Value -> IO ())
wJSObjects :: Vendor JSPtr
getServer :: Window -> Server
getCookies :: Window -> [Cookie]
runEval :: Window -> String -> IO ()
callEval :: Window -> String -> IO Value
wCallBuffer :: Window -> TMVar (String -> String)
wCallBufferMode :: Window -> TVar CallBufferMode
timestamp :: Window -> IO ()
debug :: Window -> String -> IO ()
onDisconnect :: Window -> IO () -> IO ()
wRoot :: Window -> RemotePtr ()
wEventHandlers :: Window -> Vendor (Value -> IO ())
wJSObjects :: Window -> Vendor JSPtr
..}) JSFunction NewJSObject
f = do
Coupon
coupon <- Vendor JSPtr -> IO Coupon
forall a. Vendor a -> IO Coupon
newCoupon Vendor JSPtr
wJSObjects
JSCode
rcoupon <- Coupon -> IO JSCode
forall a. ToJS a => a -> IO JSCode
render Coupon
coupon
JSCode
rcode <- JSFunction NewJSObject -> IO JSCode
forall a. JSFunction a -> IO JSCode
code JSFunction NewJSObject
f
JSFunction JSObject -> IO (JSFunction JSObject)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSFunction JSObject -> IO (JSFunction JSObject))
-> JSFunction JSObject -> IO (JSFunction JSObject)
forall a b. (a -> b) -> a -> b
$ JSFunction
{ code :: IO JSCode
code = JSCode -> IO JSCode
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSCode -> IO JSCode) -> JSCode -> IO JSCode
forall a b. (a -> b) -> a -> b
$ String -> [JSCode] -> JSCode
apply String
"Haskell.imposeStablePtr(%1,%2)" [JSCode
rcode, JSCode
rcoupon]
, marshalResult :: Window -> Value -> IO JSObject
marshalResult = \Window
w Value
_ -> Window -> Coupon -> IO JSObject
newJSObjectFromCoupon Window
w Coupon
coupon
}
data JSFunction a = JSFunction
{ forall a. JSFunction a -> IO JSCode
code :: IO JSCode
, forall a. JSFunction a -> Window -> Value -> IO a
marshalResult :: Window -> JSON.Value -> IO a
}
instance Functor JSFunction where
fmap :: forall a b. (a -> b) -> JSFunction a -> JSFunction b
fmap a -> b
f (JSFunction IO JSCode
c Window -> Value -> IO a
m) = IO JSCode -> (Window -> Value -> IO b) -> JSFunction b
forall a. IO JSCode -> (Window -> Value -> IO a) -> JSFunction a
JSFunction IO JSCode
c (\Window
w Value
v -> (a -> b) -> IO a -> IO b
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f (IO a -> IO b) -> IO a -> IO b
forall a b. (a -> b) -> a -> b
$ Window -> Value -> IO a
m Window
w Value
v)
toCode :: JSFunction a -> IO String
toCode :: forall a. JSFunction a -> IO String
toCode = (JSCode -> String) -> IO JSCode -> IO String
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSCode -> String
unJSCode (IO JSCode -> IO String)
-> (JSFunction a -> IO JSCode) -> JSFunction a -> IO String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSFunction a -> IO JSCode
forall a. JSFunction a -> IO JSCode
code
class FFI a where
fancy :: ([JSCode] -> IO JSCode) -> a
instance (ToJS a, FFI b) => FFI (a -> b) where
fancy :: ([JSCode] -> IO JSCode) -> a -> b
fancy [JSCode] -> IO JSCode
f a
a = ([JSCode] -> IO JSCode) -> b
forall a. FFI a => ([JSCode] -> IO JSCode) -> a
fancy (([JSCode] -> IO JSCode) -> b) -> ([JSCode] -> IO JSCode) -> b
forall a b. (a -> b) -> a -> b
$ \[JSCode]
xs -> do
JSCode
x <- a -> IO JSCode
forall a. ToJS a => a -> IO JSCode
render a
a
[JSCode] -> IO JSCode
f (JSCode
xJSCode -> [JSCode] -> [JSCode]
forall a. a -> [a] -> [a]
:[JSCode]
xs)
instance FromJS b => FFI (JSFunction b) where
fancy :: ([JSCode] -> IO JSCode) -> JSFunction b
fancy [JSCode] -> IO JSCode
f = JSFunction
{ code :: IO JSCode
code = FromJS' b -> JSCode -> JSCode
forall a. FromJS' a -> JSCode -> JSCode
wrapCode FromJS' b
b (JSCode -> JSCode) -> IO JSCode -> IO JSCode
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [JSCode] -> IO JSCode
f []
, marshalResult :: Window -> Value -> IO b
marshalResult = FromJS' b -> Window -> Value -> IO b
forall a. FromJS' a -> Window -> Value -> IO a
marshal FromJS' b
b
}
where b :: FromJS' b
b = FromJS' b
forall a. FromJS a => FromJS' a
fromJS
ffi :: FFI a => String -> a
ffi :: forall a. FFI a => String -> a
ffi String
macro = ([JSCode] -> IO JSCode) -> a
forall a. FFI a => ([JSCode] -> IO JSCode) -> a
fancy (JSCode -> IO JSCode
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSCode -> IO JSCode)
-> ([JSCode] -> JSCode) -> [JSCode] -> IO JSCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [JSCode] -> JSCode
apply String
macro)
testFFI :: String -> Int -> JSFunction String
testFFI :: String -> Int -> JSFunction String
testFFI = String -> String -> Int -> JSFunction String
forall a. FFI a => String -> a
ffi String
"$(%1).prop('checked',%2)"
class IsHandler a where
convertArgs :: a -> Int -> [JSCode]
handle :: a -> Window -> [JSON.Value] -> IO ()
instance (FromJS a, IsHandler b) => IsHandler (a -> b) where
convertArgs :: (a -> b) -> Int -> [JSCode]
convertArgs = (a -> b) -> Int -> [JSCode]
forall a b. (FromJS a, IsHandler b) => (a -> b) -> Int -> [JSCode]
convertArgs'
handle :: (a -> b) -> Window -> [Value] -> IO ()
handle a -> b
f = \Window
w (Value
a:[Value]
as) -> do
a
x <- FromJS' a -> Window -> Value -> IO a
forall a. FromJS' a -> Window -> Value -> IO a
marshal FromJS' a
forall a. FromJS a => FromJS' a
fromJS Window
w Value
a
b -> Window -> [Value] -> IO ()
forall a. IsHandler a => a -> Window -> [Value] -> IO ()
handle (a -> b
f a
x) Window
w [Value]
as
convertArgs' :: forall a b. (FromJS a, IsHandler b) => (a -> b) -> Int -> [JSCode]
convertArgs' :: forall a b. (FromJS a, IsHandler b) => (a -> b) -> Int -> [JSCode]
convertArgs' a -> b
f Int
n = JSCode -> JSCode
wrap JSCode
arg JSCode -> [JSCode] -> [JSCode]
forall a. a -> [a] -> [a]
: b -> Int -> [JSCode]
forall a. IsHandler a => a -> Int -> [JSCode]
convertArgs (a -> b
f a
x) (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
where
x :: a
x = a
forall a. HasCallStack => a
undefined :: a
wrap :: JSCode -> JSCode
wrap = FromJS' a -> JSCode -> JSCode
forall a. FromJS' a -> JSCode -> JSCode
wrapCode (FromJS' a
forall a. FromJS a => FromJS' a
fromJS :: FromJS' a)
arg :: JSCode
arg = String -> JSCode
JSCode (String -> JSCode) -> String -> JSCode
forall a b. (a -> b) -> a -> b
$ String
"arguments[" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
n String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"]"
instance IsHandler (IO ()) where
convertArgs :: IO () -> Int -> [JSCode]
convertArgs IO ()
_ Int
_ = []
handle :: IO () -> Window -> [Value] -> IO ()
handle IO ()
m = \Window
_ [Value]
_ -> IO ()
m
convertArguments :: IsHandler a => a -> String
convertArguments :: forall a. IsHandler a => a -> String
convertArguments a
f =
String
"[" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"," ((JSCode -> String) -> [JSCode] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map JSCode -> String
unJSCode ([JSCode] -> [String]) -> [JSCode] -> [String]
forall a b. (a -> b) -> a -> b
$ a -> Int -> [JSCode]
forall a. IsHandler a => a -> Int -> [JSCode]
convertArgs a
f Int
0) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"]"
apply :: String -> [JSCode] -> JSCode
apply :: String -> [JSCode] -> JSCode
apply String
code [JSCode]
args = String -> JSCode
JSCode (String -> JSCode) -> String -> JSCode
forall a b. (a -> b) -> a -> b
$ String -> String
go String
code
where
at :: [b] -> Int -> b
at [b]
xs Int
i = b -> (b -> b) -> Maybe b -> b
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> b
forall a. HasCallStack => String -> a
error String
err) b -> b
forall a. a -> a
id (Maybe b -> b) -> Maybe b -> b
forall a b. (a -> b) -> a -> b
$ [b] -> Int -> Maybe b
forall a. [a] -> Int -> Maybe a
atMay [b]
xs Int
i
err :: String
err = String
"Graphics.UI.Threepenny.FFI: Too few arguments in FFI call!"
argument :: Int -> String
argument Int
i = JSCode -> String
unJSCode ([JSCode]
args [JSCode] -> Int -> JSCode
forall {b}. [b] -> Int -> b
`at` Int
i)
go :: String -> String
go [] = []
go (Char
'%':Char
'%':String
cs) = Char
'%' Char -> String -> String
forall a. a -> [a] -> [a]
: String -> String
go String
cs
go (Char
'%':Char
c :String
cs) = Int -> String
argument Int
index String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
go String
cs
where index :: Int
index = Char -> Int
forall a. Enum a => a -> Int
fromEnum Char
c Int -> Int -> Int
forall a. Num a => a -> a -> a
- Char -> Int
forall a. Enum a => a -> Int
fromEnum Char
'1'
go (Char
c:String
cs) = Char
c Char -> String -> String
forall a. a -> [a] -> [a]
: String -> String
go String
cs
apply1 :: String -> JSCode -> JSCode
apply1 :: String -> JSCode -> JSCode
apply1 String
s JSCode
x = String -> [JSCode] -> JSCode
apply String
s [JSCode
x]