{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeSynonymInstances #-}
module Language.Javascript.JSaddle.Classes.Internal (
MakeObject(..)
, MakeArgs(..)
) where
import Language.Javascript.JSaddle.Types
(JSM, Object(..), JSVal)
class MakeObject this where
makeObject :: this -> JSM Object
instance MakeObject Object where
makeObject :: Object -> JSM Object
makeObject = Object -> JSM Object
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return
class MakeArgs this where
makeArgs :: this -> JSM [JSVal]
instance MakeArgs arg => MakeArgs (JSM arg) where
makeArgs :: JSM arg -> JSM [JSVal]
makeArgs JSM arg
arg = JSM arg
arg JSM arg -> (arg -> JSM [JSVal]) -> JSM [JSVal]
forall a b. JSM a -> (a -> JSM b) -> JSM b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= arg -> JSM [JSVal]
forall this. MakeArgs this => this -> JSM [JSVal]
makeArgs