{-# LANGUAGE CPP #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
#ifdef ghcjs_HOST_OS
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE JavaScriptFFI #-}
#endif
module Foreign.JavaScript.TH ( module Foreign.JavaScript.TH
#ifdef USE_TEMPLATE_HASKELL
, Safety (..)
#endif
) where
import Foreign.JavaScript.Orphans ()
import Prelude hiding ((!!))
import Reflex.Class
import Reflex.Adjustable.Class
import Reflex.Host.Class
import Reflex.PerformEvent.Class
#ifdef USE_TEMPLATE_HASKELL
import Language.Haskell.TH
#endif
import GHCJS.DOM.Types (JSContextRef, askJSM)
#ifdef ghcjs_HOST_OS
import qualified GHCJS.Buffer as JS
import GHCJS.DOM.Types (MonadJSM)
import qualified GHCJS.DOM.Types as JS
import qualified GHCJS.Foreign as JS
#if __GLASGOW_HASKELL__ < 900
import qualified GHCJS.Foreign.Callback as JS
import qualified GHCJS.Foreign.Callback.Internal (Callback (..))
#else
import qualified GHC.JS.Foreign.Callback as JS
#endif
import qualified JavaScript.Array as JS
import qualified JavaScript.Array.Internal (SomeJSArray (..))
import qualified JavaScript.Object as JS
import qualified JavaScript.Object.Internal (Object (..))
import qualified JavaScript.TypedArray.ArrayBuffer as JSArrayBuffer
import Data.Hashable
import Data.Word
import Foreign.C.Types
import Foreign.Ptr
import Text.Encoding.Z
#else
import GHCJS.DOM.Types (MonadJSM (..), runJSM)
#endif
import Control.Monad.Exception
import Control.Monad.Fix
import Control.Monad.IO.Class
import Control.Monad.Primitive
import Control.Monad.Reader
import Control.Monad.Ref
import Control.Monad.Trans.Control
import Data.Coerce (coerce)
newtype WithJSContextSingleton x m a = WithJSContextSingleton { forall x (m :: * -> *) a.
WithJSContextSingleton x m a -> ReaderT (JSContextSingleton x) m a
unWithJSContextSingleton :: ReaderT (JSContextSingleton x) m a } deriving ((forall a b.
(a -> b)
-> WithJSContextSingleton x m a -> WithJSContextSingleton x m b)
-> (forall a b.
a -> WithJSContextSingleton x m b -> WithJSContextSingleton x m a)
-> Functor (WithJSContextSingleton x m)
forall a b.
a -> WithJSContextSingleton x m b -> WithJSContextSingleton x m a
forall a b.
(a -> b)
-> WithJSContextSingleton x m a -> WithJSContextSingleton x m b
forall x (m :: * -> *) a b.
Functor m =>
a -> WithJSContextSingleton x m b -> WithJSContextSingleton x m a
forall x (m :: * -> *) a b.
Functor m =>
(a -> b)
-> WithJSContextSingleton x m a -> WithJSContextSingleton x m b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall x (m :: * -> *) a b.
Functor m =>
(a -> b)
-> WithJSContextSingleton x m a -> WithJSContextSingleton x m b
fmap :: forall a b.
(a -> b)
-> WithJSContextSingleton x m a -> WithJSContextSingleton x m b
$c<$ :: forall x (m :: * -> *) a b.
Functor m =>
a -> WithJSContextSingleton x m b -> WithJSContextSingleton x m a
<$ :: forall a b.
a -> WithJSContextSingleton x m b -> WithJSContextSingleton x m a
Functor, Functor (WithJSContextSingleton x m)
Functor (WithJSContextSingleton x m) =>
(forall a. a -> WithJSContextSingleton x m a)
-> (forall a b.
WithJSContextSingleton x m (a -> b)
-> WithJSContextSingleton x m a -> WithJSContextSingleton x m b)
-> (forall a b c.
(a -> b -> c)
-> WithJSContextSingleton x m a
-> WithJSContextSingleton x m b
-> WithJSContextSingleton x m c)
-> (forall a b.
WithJSContextSingleton x m a
-> WithJSContextSingleton x m b -> WithJSContextSingleton x m b)
-> (forall a b.
WithJSContextSingleton x m a
-> WithJSContextSingleton x m b -> WithJSContextSingleton x m a)
-> Applicative (WithJSContextSingleton x m)
forall a. a -> WithJSContextSingleton x m a
forall a b.
WithJSContextSingleton x m a
-> WithJSContextSingleton x m b -> WithJSContextSingleton x m a
forall a b.
WithJSContextSingleton x m a
-> WithJSContextSingleton x m b -> WithJSContextSingleton x m b
forall a b.
WithJSContextSingleton x m (a -> b)
-> WithJSContextSingleton x m a -> WithJSContextSingleton x m b
forall a b c.
(a -> b -> c)
-> WithJSContextSingleton x m a
-> WithJSContextSingleton x m b
-> WithJSContextSingleton x m c
forall x (m :: * -> *).
Applicative m =>
Functor (WithJSContextSingleton x m)
forall x (m :: * -> *) a.
Applicative m =>
a -> WithJSContextSingleton x m a
forall x (m :: * -> *) a b.
Applicative m =>
WithJSContextSingleton x m a
-> WithJSContextSingleton x m b -> WithJSContextSingleton x m a
forall x (m :: * -> *) a b.
Applicative m =>
WithJSContextSingleton x m a
-> WithJSContextSingleton x m b -> WithJSContextSingleton x m b
forall x (m :: * -> *) a b.
Applicative m =>
WithJSContextSingleton x m (a -> b)
-> WithJSContextSingleton x m a -> WithJSContextSingleton x m b
forall x (m :: * -> *) a b c.
Applicative m =>
(a -> b -> c)
-> WithJSContextSingleton x m a
-> WithJSContextSingleton x m b
-> WithJSContextSingleton x m c
forall (f :: * -> *).
Functor f =>
(forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
$cpure :: forall x (m :: * -> *) a.
Applicative m =>
a -> WithJSContextSingleton x m a
pure :: forall a. a -> WithJSContextSingleton x m a
$c<*> :: forall x (m :: * -> *) a b.
Applicative m =>
WithJSContextSingleton x m (a -> b)
-> WithJSContextSingleton x m a -> WithJSContextSingleton x m b
<*> :: forall a b.
WithJSContextSingleton x m (a -> b)
-> WithJSContextSingleton x m a -> WithJSContextSingleton x m b
$cliftA2 :: forall x (m :: * -> *) a b c.
Applicative m =>
(a -> b -> c)
-> WithJSContextSingleton x m a
-> WithJSContextSingleton x m b
-> WithJSContextSingleton x m c
liftA2 :: forall a b c.
(a -> b -> c)
-> WithJSContextSingleton x m a
-> WithJSContextSingleton x m b
-> WithJSContextSingleton x m c
$c*> :: forall x (m :: * -> *) a b.
Applicative m =>
WithJSContextSingleton x m a
-> WithJSContextSingleton x m b -> WithJSContextSingleton x m b
*> :: forall a b.
WithJSContextSingleton x m a
-> WithJSContextSingleton x m b -> WithJSContextSingleton x m b
$c<* :: forall x (m :: * -> *) a b.
Applicative m =>
WithJSContextSingleton x m a
-> WithJSContextSingleton x m b -> WithJSContextSingleton x m a
<* :: forall a b.
WithJSContextSingleton x m a
-> WithJSContextSingleton x m b -> WithJSContextSingleton x m a
Applicative, Applicative (WithJSContextSingleton x m)
Applicative (WithJSContextSingleton x m) =>
(forall a b.
WithJSContextSingleton x m a
-> (a -> WithJSContextSingleton x m b)
-> WithJSContextSingleton x m b)
-> (forall a b.
WithJSContextSingleton x m a
-> WithJSContextSingleton x m b -> WithJSContextSingleton x m b)
-> (forall a. a -> WithJSContextSingleton x m a)
-> Monad (WithJSContextSingleton x m)
forall a. a -> WithJSContextSingleton x m a
forall a b.
WithJSContextSingleton x m a
-> WithJSContextSingleton x m b -> WithJSContextSingleton x m b
forall a b.
WithJSContextSingleton x m a
-> (a -> WithJSContextSingleton x m b)
-> WithJSContextSingleton x m b
forall x (m :: * -> *).
Monad m =>
Applicative (WithJSContextSingleton x m)
forall x (m :: * -> *) a.
Monad m =>
a -> WithJSContextSingleton x m a
forall x (m :: * -> *) a b.
Monad m =>
WithJSContextSingleton x m a
-> WithJSContextSingleton x m b -> WithJSContextSingleton x m b
forall x (m :: * -> *) a b.
Monad m =>
WithJSContextSingleton x m a
-> (a -> WithJSContextSingleton x m b)
-> WithJSContextSingleton x m b
forall (m :: * -> *).
Applicative m =>
(forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
$c>>= :: forall x (m :: * -> *) a b.
Monad m =>
WithJSContextSingleton x m a
-> (a -> WithJSContextSingleton x m b)
-> WithJSContextSingleton x m b
>>= :: forall a b.
WithJSContextSingleton x m a
-> (a -> WithJSContextSingleton x m b)
-> WithJSContextSingleton x m b
$c>> :: forall x (m :: * -> *) a b.
Monad m =>
WithJSContextSingleton x m a
-> WithJSContextSingleton x m b -> WithJSContextSingleton x m b
>> :: forall a b.
WithJSContextSingleton x m a
-> WithJSContextSingleton x m b -> WithJSContextSingleton x m b
$creturn :: forall x (m :: * -> *) a.
Monad m =>
a -> WithJSContextSingleton x m a
return :: forall a. a -> WithJSContextSingleton x m a
Monad, Monad (WithJSContextSingleton x m)
Monad (WithJSContextSingleton x m) =>
(forall a. IO a -> WithJSContextSingleton x m a)
-> MonadIO (WithJSContextSingleton x m)
forall a. IO a -> WithJSContextSingleton x m a
forall x (m :: * -> *).
MonadIO m =>
Monad (WithJSContextSingleton x m)
forall x (m :: * -> *) a.
MonadIO m =>
IO a -> WithJSContextSingleton x m a
forall (m :: * -> *).
Monad m =>
(forall a. IO a -> m a) -> MonadIO m
$cliftIO :: forall x (m :: * -> *) a.
MonadIO m =>
IO a -> WithJSContextSingleton x m a
liftIO :: forall a. IO a -> WithJSContextSingleton x m a
MonadIO, Monad (WithJSContextSingleton x m)
Monad (WithJSContextSingleton x m) =>
(forall a.
(a -> WithJSContextSingleton x m a)
-> WithJSContextSingleton x m a)
-> MonadFix (WithJSContextSingleton x m)
forall a.
(a -> WithJSContextSingleton x m a) -> WithJSContextSingleton x m a
forall x (m :: * -> *).
MonadFix m =>
Monad (WithJSContextSingleton x m)
forall x (m :: * -> *) a.
MonadFix m =>
(a -> WithJSContextSingleton x m a) -> WithJSContextSingleton x m a
forall (m :: * -> *).
Monad m =>
(forall a. (a -> m a) -> m a) -> MonadFix m
$cmfix :: forall x (m :: * -> *) a.
MonadFix m =>
(a -> WithJSContextSingleton x m a) -> WithJSContextSingleton x m a
mfix :: forall a.
(a -> WithJSContextSingleton x m a) -> WithJSContextSingleton x m a
MonadFix, (forall (m :: * -> *).
Monad m =>
Monad (WithJSContextSingleton x m)) =>
(forall (m :: * -> *) a.
Monad m =>
m a -> WithJSContextSingleton x m a)
-> MonadTrans (WithJSContextSingleton x)
forall x (m :: * -> *).
Monad m =>
Monad (WithJSContextSingleton x m)
forall x (m :: * -> *) a.
Monad m =>
m a -> WithJSContextSingleton x m a
forall (m :: * -> *). Monad m => Monad (WithJSContextSingleton x m)
forall (m :: * -> *) a.
Monad m =>
m a -> WithJSContextSingleton x m a
forall (t :: (* -> *) -> * -> *).
(forall (m :: * -> *). Monad m => Monad (t m)) =>
(forall (m :: * -> *) a. Monad m => m a -> t m a) -> MonadTrans t
$clift :: forall x (m :: * -> *) a.
Monad m =>
m a -> WithJSContextSingleton x m a
lift :: forall (m :: * -> *) a.
Monad m =>
m a -> WithJSContextSingleton x m a
MonadTrans, Monad (WithJSContextSingleton x m)
Monad (WithJSContextSingleton x m) =>
(forall e a. Exception e => e -> WithJSContextSingleton x m a)
-> (forall e a.
Exception e =>
WithJSContextSingleton x m a
-> (e -> WithJSContextSingleton x m a)
-> WithJSContextSingleton x m a)
-> (forall a b.
WithJSContextSingleton x m a
-> WithJSContextSingleton x m b -> WithJSContextSingleton x m a)
-> MonadException (WithJSContextSingleton x m)
forall e a. Exception e => e -> WithJSContextSingleton x m a
forall e a.
Exception e =>
WithJSContextSingleton x m a
-> (e -> WithJSContextSingleton x m a)
-> WithJSContextSingleton x m a
forall a b.
WithJSContextSingleton x m a
-> WithJSContextSingleton x m b -> WithJSContextSingleton x m a
forall x (m :: * -> *).
MonadException m =>
Monad (WithJSContextSingleton x m)
forall x (m :: * -> *) e a.
(MonadException m, Exception e) =>
e -> WithJSContextSingleton x m a
forall x (m :: * -> *) e a.
(MonadException m, Exception e) =>
WithJSContextSingleton x m a
-> (e -> WithJSContextSingleton x m a)
-> WithJSContextSingleton x m a
forall x (m :: * -> *) a b.
MonadException m =>
WithJSContextSingleton x m a
-> WithJSContextSingleton x m b -> WithJSContextSingleton x m a
forall (m :: * -> *).
Monad m =>
(forall e a. Exception e => e -> m a)
-> (forall e a. Exception e => m a -> (e -> m a) -> m a)
-> (forall a b. m a -> m b -> m a)
-> MonadException m
$cthrow :: forall x (m :: * -> *) e a.
(MonadException m, Exception e) =>
e -> WithJSContextSingleton x m a
throw :: forall e a. Exception e => e -> WithJSContextSingleton x m a
$ccatch :: forall x (m :: * -> *) e a.
(MonadException m, Exception e) =>
WithJSContextSingleton x m a
-> (e -> WithJSContextSingleton x m a)
-> WithJSContextSingleton x m a
catch :: forall e a.
Exception e =>
WithJSContextSingleton x m a
-> (e -> WithJSContextSingleton x m a)
-> WithJSContextSingleton x m a
$cfinally :: forall x (m :: * -> *) a b.
MonadException m =>
WithJSContextSingleton x m a
-> WithJSContextSingleton x m b -> WithJSContextSingleton x m a
finally :: forall a b.
WithJSContextSingleton x m a
-> WithJSContextSingleton x m b -> WithJSContextSingleton x m a
MonadException, MonadIO (WithJSContextSingleton x m)
MonadException (WithJSContextSingleton x m)
(MonadIO (WithJSContextSingleton x m),
MonadException (WithJSContextSingleton x m)) =>
(forall b.
((forall a.
WithJSContextSingleton x m a -> WithJSContextSingleton x m a)
-> WithJSContextSingleton x m b)
-> WithJSContextSingleton x m b)
-> MonadAsyncException (WithJSContextSingleton x m)
forall b.
((forall a.
WithJSContextSingleton x m a -> WithJSContextSingleton x m a)
-> WithJSContextSingleton x m b)
-> WithJSContextSingleton x m b
forall x (m :: * -> *).
MonadAsyncException m =>
MonadIO (WithJSContextSingleton x m)
forall x (m :: * -> *).
MonadAsyncException m =>
MonadException (WithJSContextSingleton x m)
forall x (m :: * -> *) b.
MonadAsyncException m =>
((forall a.
WithJSContextSingleton x m a -> WithJSContextSingleton x m a)
-> WithJSContextSingleton x m b)
-> WithJSContextSingleton x m b
forall (m :: * -> *).
(MonadIO m, MonadException m) =>
(forall b. ((forall a. m a -> m a) -> m b) -> m b)
-> MonadAsyncException m
$cmask :: forall x (m :: * -> *) b.
MonadAsyncException m =>
((forall a.
WithJSContextSingleton x m a -> WithJSContextSingleton x m a)
-> WithJSContextSingleton x m b)
-> WithJSContextSingleton x m b
mask :: forall b.
((forall a.
WithJSContextSingleton x m a -> WithJSContextSingleton x m a)
-> WithJSContextSingleton x m b)
-> WithJSContextSingleton x m b
MonadAsyncException)
instance PrimMonad m => PrimMonad (WithJSContextSingleton x m) where
type PrimState (WithJSContextSingleton x m) = PrimState m
primitive :: forall a.
(State# (PrimState (WithJSContextSingleton x m))
-> (# State# (PrimState (WithJSContextSingleton x m)), a #))
-> WithJSContextSingleton x m a
primitive = m a -> WithJSContextSingleton x m a
forall (m :: * -> *) a.
Monad m =>
m a -> WithJSContextSingleton x m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m a -> WithJSContextSingleton x m a)
-> ((State# (PrimState m) -> (# State# (PrimState m), a #)) -> m a)
-> (State# (PrimState m) -> (# State# (PrimState m), a #))
-> WithJSContextSingleton x m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (State# (PrimState m) -> (# State# (PrimState m), a #)) -> m a
forall a.
(State# (PrimState m) -> (# State# (PrimState m), a #)) -> m a
forall (m :: * -> *) a.
PrimMonad m =>
(State# (PrimState m) -> (# State# (PrimState m), a #)) -> m a
primitive
instance Adjustable t m => Adjustable t (WithJSContextSingleton x m) where
runWithReplace :: forall a b.
WithJSContextSingleton x m a
-> Event t (WithJSContextSingleton x m b)
-> WithJSContextSingleton x m (a, Event t b)
runWithReplace WithJSContextSingleton x m a
a0 Event t (WithJSContextSingleton x m b)
a' = ReaderT (JSContextSingleton x) m (a, Event t b)
-> WithJSContextSingleton x m (a, Event t b)
forall x (m :: * -> *) a.
ReaderT (JSContextSingleton x) m a -> WithJSContextSingleton x m a
WithJSContextSingleton (ReaderT (JSContextSingleton x) m (a, Event t b)
-> WithJSContextSingleton x m (a, Event t b))
-> ReaderT (JSContextSingleton x) m (a, Event t b)
-> WithJSContextSingleton x m (a, Event t b)
forall a b. (a -> b) -> a -> b
$ ReaderT (JSContextSingleton x) m a
-> Event t (ReaderT (JSContextSingleton x) m b)
-> ReaderT (JSContextSingleton x) m (a, Event t b)
forall a b.
ReaderT (JSContextSingleton x) m a
-> Event t (ReaderT (JSContextSingleton x) m b)
-> ReaderT (JSContextSingleton x) m (a, Event t b)
forall t (m :: * -> *) a b.
Adjustable t m =>
m a -> Event t (m b) -> m (a, Event t b)
runWithReplace (WithJSContextSingleton x m a -> ReaderT (JSContextSingleton x) m a
forall a b. Coercible a b => a -> b
coerce WithJSContextSingleton x m a
a0) (Event t (WithJSContextSingleton x m b)
-> Event t (ReaderT (JSContextSingleton x) m b)
forall {k} (t :: k) a b.
(Reflex t, Coercible a b) =>
Event t a -> Event t b
coerceEvent Event t (WithJSContextSingleton x m b)
a')
traverseIntMapWithKeyWithAdjust :: forall v v'.
(Key -> v -> WithJSContextSingleton x m v')
-> IntMap v
-> Event t (PatchIntMap v)
-> WithJSContextSingleton x m (IntMap v', Event t (PatchIntMap v'))
traverseIntMapWithKeyWithAdjust Key -> v -> WithJSContextSingleton x m v'
f IntMap v
dm0 Event t (PatchIntMap v)
dm' = ReaderT
(JSContextSingleton x) m (IntMap v', Event t (PatchIntMap v'))
-> WithJSContextSingleton x m (IntMap v', Event t (PatchIntMap v'))
forall x (m :: * -> *) a.
ReaderT (JSContextSingleton x) m a -> WithJSContextSingleton x m a
WithJSContextSingleton (ReaderT
(JSContextSingleton x) m (IntMap v', Event t (PatchIntMap v'))
-> WithJSContextSingleton
x m (IntMap v', Event t (PatchIntMap v')))
-> ReaderT
(JSContextSingleton x) m (IntMap v', Event t (PatchIntMap v'))
-> WithJSContextSingleton x m (IntMap v', Event t (PatchIntMap v'))
forall a b. (a -> b) -> a -> b
$ (Key -> v -> ReaderT (JSContextSingleton x) m v')
-> IntMap v
-> Event t (PatchIntMap v)
-> ReaderT
(JSContextSingleton x) m (IntMap v', Event t (PatchIntMap v'))
forall v v'.
(Key -> v -> ReaderT (JSContextSingleton x) m v')
-> IntMap v
-> Event t (PatchIntMap v)
-> ReaderT
(JSContextSingleton x) m (IntMap v', Event t (PatchIntMap v'))
forall t (m :: * -> *) v v'.
Adjustable t m =>
(Key -> v -> m v')
-> IntMap v
-> Event t (PatchIntMap v)
-> m (IntMap v', Event t (PatchIntMap v'))
traverseIntMapWithKeyWithAdjust (\Key
k v
v -> WithJSContextSingleton x m v'
-> ReaderT (JSContextSingleton x) m v'
forall x (m :: * -> *) a.
WithJSContextSingleton x m a -> ReaderT (JSContextSingleton x) m a
unWithJSContextSingleton (WithJSContextSingleton x m v'
-> ReaderT (JSContextSingleton x) m v')
-> WithJSContextSingleton x m v'
-> ReaderT (JSContextSingleton x) m v'
forall a b. (a -> b) -> a -> b
$ Key -> v -> WithJSContextSingleton x m v'
f Key
k v
v) (IntMap v -> IntMap v
forall a b. Coercible a b => a -> b
coerce IntMap v
dm0) (Event t (PatchIntMap v) -> Event t (PatchIntMap v)
forall {k} (t :: k) a b.
(Reflex t, Coercible a b) =>
Event t a -> Event t b
coerceEvent Event t (PatchIntMap v)
dm')
traverseDMapWithKeyWithAdjust :: forall (k :: * -> *) (v :: * -> *) (v' :: * -> *).
GCompare k =>
(forall a. k a -> v a -> WithJSContextSingleton x m (v' a))
-> DMap k v
-> Event t (PatchDMap k v)
-> WithJSContextSingleton x m (DMap k v', Event t (PatchDMap k v'))
traverseDMapWithKeyWithAdjust forall a. k a -> v a -> WithJSContextSingleton x m (v' a)
f DMap k v
dm0 Event t (PatchDMap k v)
dm' = ReaderT
(JSContextSingleton x) m (DMap k v', Event t (PatchDMap k v'))
-> WithJSContextSingleton x m (DMap k v', Event t (PatchDMap k v'))
forall x (m :: * -> *) a.
ReaderT (JSContextSingleton x) m a -> WithJSContextSingleton x m a
WithJSContextSingleton (ReaderT
(JSContextSingleton x) m (DMap k v', Event t (PatchDMap k v'))
-> WithJSContextSingleton
x m (DMap k v', Event t (PatchDMap k v')))
-> ReaderT
(JSContextSingleton x) m (DMap k v', Event t (PatchDMap k v'))
-> WithJSContextSingleton x m (DMap k v', Event t (PatchDMap k v'))
forall a b. (a -> b) -> a -> b
$ (forall a. k a -> v a -> ReaderT (JSContextSingleton x) m (v' a))
-> DMap k v
-> Event t (PatchDMap k v)
-> ReaderT
(JSContextSingleton x) m (DMap k v', Event t (PatchDMap k v'))
forall t (m :: * -> *) (k :: * -> *) (v :: * -> *) (v' :: * -> *).
(Adjustable t m, GCompare k) =>
(forall a. k a -> v a -> m (v' a))
-> DMap k v
-> Event t (PatchDMap k v)
-> m (DMap k v', Event t (PatchDMap k v'))
forall (k :: * -> *) (v :: * -> *) (v' :: * -> *).
GCompare k =>
(forall a. k a -> v a -> ReaderT (JSContextSingleton x) m (v' a))
-> DMap k v
-> Event t (PatchDMap k v)
-> ReaderT
(JSContextSingleton x) m (DMap k v', Event t (PatchDMap k v'))
traverseDMapWithKeyWithAdjust (\k a
k v a
v -> WithJSContextSingleton x m (v' a)
-> ReaderT (JSContextSingleton x) m (v' a)
forall x (m :: * -> *) a.
WithJSContextSingleton x m a -> ReaderT (JSContextSingleton x) m a
unWithJSContextSingleton (WithJSContextSingleton x m (v' a)
-> ReaderT (JSContextSingleton x) m (v' a))
-> WithJSContextSingleton x m (v' a)
-> ReaderT (JSContextSingleton x) m (v' a)
forall a b. (a -> b) -> a -> b
$ k a -> v a -> WithJSContextSingleton x m (v' a)
forall a. k a -> v a -> WithJSContextSingleton x m (v' a)
f k a
k v a
v) (DMap k v -> DMap k v
forall a b. Coercible a b => a -> b
coerce DMap k v
dm0) (Event t (PatchDMap k v) -> Event t (PatchDMap k v)
forall {k} (t :: k) a b.
(Reflex t, Coercible a b) =>
Event t a -> Event t b
coerceEvent Event t (PatchDMap k v)
dm')
traverseDMapWithKeyWithAdjustWithMove :: forall (k :: * -> *) (v :: * -> *) (v' :: * -> *).
GCompare k =>
(forall a. k a -> v a -> WithJSContextSingleton x m (v' a))
-> DMap k v
-> Event t (PatchDMapWithMove k v)
-> WithJSContextSingleton
x m (DMap k v', Event t (PatchDMapWithMove k v'))
traverseDMapWithKeyWithAdjustWithMove forall a. k a -> v a -> WithJSContextSingleton x m (v' a)
f DMap k v
dm0 Event t (PatchDMapWithMove k v)
dm' = ReaderT
(JSContextSingleton x)
m
(DMap k v', Event t (PatchDMapWithMove k v'))
-> WithJSContextSingleton
x m (DMap k v', Event t (PatchDMapWithMove k v'))
forall x (m :: * -> *) a.
ReaderT (JSContextSingleton x) m a -> WithJSContextSingleton x m a
WithJSContextSingleton (ReaderT
(JSContextSingleton x)
m
(DMap k v', Event t (PatchDMapWithMove k v'))
-> WithJSContextSingleton
x m (DMap k v', Event t (PatchDMapWithMove k v')))
-> ReaderT
(JSContextSingleton x)
m
(DMap k v', Event t (PatchDMapWithMove k v'))
-> WithJSContextSingleton
x m (DMap k v', Event t (PatchDMapWithMove k v'))
forall a b. (a -> b) -> a -> b
$ (forall a. k a -> v a -> ReaderT (JSContextSingleton x) m (v' a))
-> DMap k v
-> Event t (PatchDMapWithMove k v)
-> ReaderT
(JSContextSingleton x)
m
(DMap k v', Event t (PatchDMapWithMove k v'))
forall t (m :: * -> *) (k :: * -> *) (v :: * -> *) (v' :: * -> *).
(Adjustable t m, GCompare k) =>
(forall a. k a -> v a -> m (v' a))
-> DMap k v
-> Event t (PatchDMapWithMove k v)
-> m (DMap k v', Event t (PatchDMapWithMove k v'))
forall (k :: * -> *) (v :: * -> *) (v' :: * -> *).
GCompare k =>
(forall a. k a -> v a -> ReaderT (JSContextSingleton x) m (v' a))
-> DMap k v
-> Event t (PatchDMapWithMove k v)
-> ReaderT
(JSContextSingleton x)
m
(DMap k v', Event t (PatchDMapWithMove k v'))
traverseDMapWithKeyWithAdjustWithMove (\k a
k v a
v -> WithJSContextSingleton x m (v' a)
-> ReaderT (JSContextSingleton x) m (v' a)
forall x (m :: * -> *) a.
WithJSContextSingleton x m a -> ReaderT (JSContextSingleton x) m a
unWithJSContextSingleton (WithJSContextSingleton x m (v' a)
-> ReaderT (JSContextSingleton x) m (v' a))
-> WithJSContextSingleton x m (v' a)
-> ReaderT (JSContextSingleton x) m (v' a)
forall a b. (a -> b) -> a -> b
$ k a -> v a -> WithJSContextSingleton x m (v' a)
forall a. k a -> v a -> WithJSContextSingleton x m (v' a)
f k a
k v a
v) (DMap k v -> DMap k v
forall a b. Coercible a b => a -> b
coerce DMap k v
dm0) (Event t (PatchDMapWithMove k v) -> Event t (PatchDMapWithMove k v)
forall {k} (t :: k) a b.
(Reflex t, Coercible a b) =>
Event t a -> Event t b
coerceEvent Event t (PatchDMapWithMove k v)
dm')
instance MonadReflexCreateTrigger t m => MonadReflexCreateTrigger t (WithJSContextSingleton x m) where
{-# INLINABLE newEventWithTrigger #-}
newEventWithTrigger :: forall a.
(EventTrigger t a -> IO (IO ()))
-> WithJSContextSingleton x m (Event t a)
newEventWithTrigger = m (Event t a) -> WithJSContextSingleton x m (Event t a)
forall (m :: * -> *) a.
Monad m =>
m a -> WithJSContextSingleton x m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Event t a) -> WithJSContextSingleton x m (Event t a))
-> ((EventTrigger t a -> IO (IO ())) -> m (Event t a))
-> (EventTrigger t a -> IO (IO ()))
-> WithJSContextSingleton x m (Event t a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (EventTrigger t a -> IO (IO ())) -> m (Event t a)
forall a. (EventTrigger t a -> IO (IO ())) -> m (Event t a)
forall t (m :: * -> *) a.
MonadReflexCreateTrigger t m =>
(EventTrigger t a -> IO (IO ())) -> m (Event t a)
newEventWithTrigger
{-# INLINABLE newFanEventWithTrigger #-}
newFanEventWithTrigger :: forall (k :: * -> *).
GCompare k =>
(forall a. k a -> EventTrigger t a -> IO (IO ()))
-> WithJSContextSingleton x m (EventSelector t k)
newFanEventWithTrigger forall a. k a -> EventTrigger t a -> IO (IO ())
f = m (EventSelector t k)
-> WithJSContextSingleton x m (EventSelector t k)
forall (m :: * -> *) a.
Monad m =>
m a -> WithJSContextSingleton x m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (EventSelector t k)
-> WithJSContextSingleton x m (EventSelector t k))
-> m (EventSelector t k)
-> WithJSContextSingleton x m (EventSelector t k)
forall a b. (a -> b) -> a -> b
$ (forall a. k a -> EventTrigger t a -> IO (IO ()))
-> m (EventSelector t k)
forall t (m :: * -> *) (k :: * -> *).
(MonadReflexCreateTrigger t m, GCompare k) =>
(forall a. k a -> EventTrigger t a -> IO (IO ()))
-> m (EventSelector t k)
forall (k :: * -> *).
GCompare k =>
(forall a. k a -> EventTrigger t a -> IO (IO ()))
-> m (EventSelector t k)
newFanEventWithTrigger k a -> EventTrigger t a -> IO (IO ())
forall a. k a -> EventTrigger t a -> IO (IO ())
f
instance MonadSubscribeEvent t m => MonadSubscribeEvent t (WithJSContextSingleton x m) where
{-# INLINABLE subscribeEvent #-}
subscribeEvent :: forall a. Event t a -> WithJSContextSingleton x m (EventHandle t a)
subscribeEvent = m (EventHandle t a) -> WithJSContextSingleton x m (EventHandle t a)
forall (m :: * -> *) a.
Monad m =>
m a -> WithJSContextSingleton x m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (EventHandle t a)
-> WithJSContextSingleton x m (EventHandle t a))
-> (Event t a -> m (EventHandle t a))
-> Event t a
-> WithJSContextSingleton x m (EventHandle t a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Event t a -> m (EventHandle t a)
forall a. Event t a -> m (EventHandle t a)
forall t (m :: * -> *) a.
MonadSubscribeEvent t m =>
Event t a -> m (EventHandle t a)
subscribeEvent
instance MonadReflexHost t m => MonadReflexHost t (WithJSContextSingleton x m) where
type ReadPhase (WithJSContextSingleton x m) = ReadPhase m
{-# INLINABLE fireEventsAndRead #-}
fireEventsAndRead :: forall a.
[DSum (EventTrigger t) Identity]
-> ReadPhase (WithJSContextSingleton x m) a
-> WithJSContextSingleton x m a
fireEventsAndRead [DSum (EventTrigger t) Identity]
dm ReadPhase (WithJSContextSingleton x m) a
a = m a -> WithJSContextSingleton x m a
forall (m :: * -> *) a.
Monad m =>
m a -> WithJSContextSingleton x m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m a -> WithJSContextSingleton x m a)
-> m a -> WithJSContextSingleton x m a
forall a b. (a -> b) -> a -> b
$ [DSum (EventTrigger t) Identity] -> ReadPhase m a -> m a
forall a. [DSum (EventTrigger t) Identity] -> ReadPhase m a -> m a
forall t (m :: * -> *) a.
MonadReflexHost t m =>
[DSum (EventTrigger t) Identity] -> ReadPhase m a -> m a
fireEventsAndRead [DSum (EventTrigger t) Identity]
dm ReadPhase m a
ReadPhase (WithJSContextSingleton x m) a
a
{-# INLINABLE runHostFrame #-}
runHostFrame :: forall a. HostFrame t a -> WithJSContextSingleton x m a
runHostFrame = m a -> WithJSContextSingleton x m a
forall (m :: * -> *) a.
Monad m =>
m a -> WithJSContextSingleton x m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m a -> WithJSContextSingleton x m a)
-> (HostFrame t a -> m a)
-> HostFrame t a
-> WithJSContextSingleton x m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HostFrame t a -> m a
forall a. HostFrame t a -> m a
forall t (m :: * -> *) a.
MonadReflexHost t m =>
HostFrame t a -> m a
runHostFrame
instance MonadSample t m => MonadSample t (WithJSContextSingleton x m) where
{-# INLINABLE sample #-}
sample :: forall a. Behavior t a -> WithJSContextSingleton x m a
sample = m a -> WithJSContextSingleton x m a
forall (m :: * -> *) a.
Monad m =>
m a -> WithJSContextSingleton x m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m a -> WithJSContextSingleton x m a)
-> (Behavior t a -> m a)
-> Behavior t a
-> WithJSContextSingleton x m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Behavior t a -> m a
forall a. Behavior t a -> m a
forall {k} (t :: k) (m :: * -> *) a.
MonadSample t m =>
Behavior t a -> m a
sample
instance MonadHold t m => MonadHold t (WithJSContextSingleton x m) where
{-# INLINABLE hold #-}
hold :: forall a.
a -> Event t a -> WithJSContextSingleton x m (Behavior t a)
hold a
v0 = m (Behavior t a) -> WithJSContextSingleton x m (Behavior t a)
forall (m :: * -> *) a.
Monad m =>
m a -> WithJSContextSingleton x m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Behavior t a) -> WithJSContextSingleton x m (Behavior t a))
-> (Event t a -> m (Behavior t a))
-> Event t a
-> WithJSContextSingleton x m (Behavior t a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Event t a -> m (Behavior t a)
forall a. a -> Event t a -> m (Behavior t a)
forall {k} (t :: k) (m :: * -> *) a.
MonadHold t m =>
a -> Event t a -> m (Behavior t a)
hold a
v0
{-# INLINABLE holdDyn #-}
holdDyn :: forall a.
a -> Event t a -> WithJSContextSingleton x m (Dynamic t a)
holdDyn a
v0 = m (Dynamic t a) -> WithJSContextSingleton x m (Dynamic t a)
forall (m :: * -> *) a.
Monad m =>
m a -> WithJSContextSingleton x m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Dynamic t a) -> WithJSContextSingleton x m (Dynamic t a))
-> (Event t a -> m (Dynamic t a))
-> Event t a
-> WithJSContextSingleton x m (Dynamic t a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Event t a -> m (Dynamic t a)
forall a. a -> Event t a -> m (Dynamic t a)
forall {k} (t :: k) (m :: * -> *) a.
MonadHold t m =>
a -> Event t a -> m (Dynamic t a)
holdDyn a
v0
{-# INLINABLE holdIncremental #-}
holdIncremental :: forall p.
Patch p =>
PatchTarget p
-> Event t p -> WithJSContextSingleton x m (Incremental t p)
holdIncremental PatchTarget p
v0 = m (Incremental t p) -> WithJSContextSingleton x m (Incremental t p)
forall (m :: * -> *) a.
Monad m =>
m a -> WithJSContextSingleton x m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Incremental t p)
-> WithJSContextSingleton x m (Incremental t p))
-> (Event t p -> m (Incremental t p))
-> Event t p
-> WithJSContextSingleton x m (Incremental t p)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PatchTarget p -> Event t p -> m (Incremental t p)
forall p.
Patch p =>
PatchTarget p -> Event t p -> m (Incremental t p)
forall {k} (t :: k) (m :: * -> *) p.
(MonadHold t m, Patch p) =>
PatchTarget p -> Event t p -> m (Incremental t p)
holdIncremental PatchTarget p
v0
{-# INLINABLE buildDynamic #-}
buildDynamic :: forall a.
PushM t a -> Event t a -> WithJSContextSingleton x m (Dynamic t a)
buildDynamic PushM t a
a0 = m (Dynamic t a) -> WithJSContextSingleton x m (Dynamic t a)
forall (m :: * -> *) a.
Monad m =>
m a -> WithJSContextSingleton x m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Dynamic t a) -> WithJSContextSingleton x m (Dynamic t a))
-> (Event t a -> m (Dynamic t a))
-> Event t a
-> WithJSContextSingleton x m (Dynamic t a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PushM t a -> Event t a -> m (Dynamic t a)
forall a. PushM t a -> Event t a -> m (Dynamic t a)
forall {k} (t :: k) (m :: * -> *) a.
MonadHold t m =>
PushM t a -> Event t a -> m (Dynamic t a)
buildDynamic PushM t a
a0
{-# INLINABLE headE #-}
headE :: forall a. Event t a -> WithJSContextSingleton x m (Event t a)
headE = m (Event t a) -> WithJSContextSingleton x m (Event t a)
forall (m :: * -> *) a.
Monad m =>
m a -> WithJSContextSingleton x m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Event t a) -> WithJSContextSingleton x m (Event t a))
-> (Event t a -> m (Event t a))
-> Event t a
-> WithJSContextSingleton x m (Event t a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Event t a -> m (Event t a)
forall a. Event t a -> m (Event t a)
forall {k} (t :: k) (m :: * -> *) a.
MonadHold t m =>
Event t a -> m (Event t a)
headE
instance MonadTransControl (WithJSContextSingleton x) where
type StT (WithJSContextSingleton x) a = StT (ReaderT (JSContextSingleton x)) a
{-# INLINABLE liftWith #-}
liftWith :: forall (m :: * -> *) a.
Monad m =>
(Run (WithJSContextSingleton x) -> m a)
-> WithJSContextSingleton x m a
liftWith = (forall b.
ReaderT (JSContextSingleton x) m b -> WithJSContextSingleton x m b)
-> (forall (o :: * -> *) b.
WithJSContextSingleton x o b -> ReaderT (JSContextSingleton x) o b)
-> (RunDefault
(WithJSContextSingleton x) (ReaderT (JSContextSingleton x))
-> m a)
-> WithJSContextSingleton x m a
forall (m :: * -> *) (n :: (* -> *) -> * -> *)
(t :: (* -> *) -> * -> *) a.
(Monad m, MonadTransControl n) =>
(forall b. n m b -> t m b)
-> (forall (o :: * -> *) b. t o b -> n o b)
-> (RunDefault t n -> m a)
-> t m a
defaultLiftWith ReaderT (JSContextSingleton x) m b -> WithJSContextSingleton x m b
forall b.
ReaderT (JSContextSingleton x) m b -> WithJSContextSingleton x m b
forall x (m :: * -> *) a.
ReaderT (JSContextSingleton x) m a -> WithJSContextSingleton x m a
WithJSContextSingleton WithJSContextSingleton x o b -> ReaderT (JSContextSingleton x) o b
forall x (m :: * -> *) a.
WithJSContextSingleton x m a -> ReaderT (JSContextSingleton x) m a
forall (o :: * -> *) b.
WithJSContextSingleton x o b -> ReaderT (JSContextSingleton x) o b
unWithJSContextSingleton
{-# INLINABLE restoreT #-}
restoreT :: forall (m :: * -> *) a.
Monad m =>
m (StT (WithJSContextSingleton x) a)
-> WithJSContextSingleton x m a
restoreT = (ReaderT (JSContextSingleton x) m a
-> WithJSContextSingleton x m a)
-> m (StT (ReaderT (JSContextSingleton x)) a)
-> WithJSContextSingleton x m a
forall (m :: * -> *) (n :: (* -> *) -> * -> *) a
(t :: (* -> *) -> * -> *).
(Monad m, MonadTransControl n) =>
(n m a -> t m a) -> m (StT n a) -> t m a
defaultRestoreT ReaderT (JSContextSingleton x) m a -> WithJSContextSingleton x m a
forall x (m :: * -> *) a.
ReaderT (JSContextSingleton x) m a -> WithJSContextSingleton x m a
WithJSContextSingleton
instance PerformEvent t m => PerformEvent t (WithJSContextSingleton x m) where
type Performable (WithJSContextSingleton x m) = WithJSContextSingleton x (Performable m)
{-# INLINABLE performEvent_ #-}
performEvent_ :: Event t (Performable (WithJSContextSingleton x m) ())
-> WithJSContextSingleton x m ()
performEvent_ Event t (Performable (WithJSContextSingleton x m) ())
e = (Run (WithJSContextSingleton x) -> m ())
-> WithJSContextSingleton x m ()
forall (m :: * -> *) a.
Monad m =>
(Run (WithJSContextSingleton x) -> m a)
-> WithJSContextSingleton x m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTransControl t, Monad m) =>
(Run t -> m a) -> t m a
liftWith ((Run (WithJSContextSingleton x) -> m ())
-> WithJSContextSingleton x m ())
-> (Run (WithJSContextSingleton x) -> m ())
-> WithJSContextSingleton x m ()
forall a b. (a -> b) -> a -> b
$ \Run (WithJSContextSingleton x)
run -> Event t (Performable m ()) -> m ()
forall t (m :: * -> *).
PerformEvent t m =>
Event t (Performable m ()) -> m ()
performEvent_ (Event t (Performable m ()) -> m ())
-> Event t (Performable m ()) -> m ()
forall a b. (a -> b) -> a -> b
$ (WithJSContextSingleton x (Performable m) () -> Performable m ())
-> Event t (WithJSContextSingleton x (Performable m) ())
-> Event t (Performable m ())
forall a b. (a -> b) -> Event t a -> Event t b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap WithJSContextSingleton x (Performable m) () -> Performable m ()
WithJSContextSingleton x (Performable m) ()
-> Performable m (StT (WithJSContextSingleton x) ())
Run (WithJSContextSingleton x)
run Event t (Performable (WithJSContextSingleton x m) ())
Event t (WithJSContextSingleton x (Performable m) ())
e
{-# INLINABLE performEvent #-}
performEvent :: forall a.
Event t (Performable (WithJSContextSingleton x m) a)
-> WithJSContextSingleton x m (Event t a)
performEvent Event t (Performable (WithJSContextSingleton x m) a)
e = (Run (WithJSContextSingleton x) -> m (Event t a))
-> WithJSContextSingleton x m (Event t a)
forall (m :: * -> *) a.
Monad m =>
(Run (WithJSContextSingleton x) -> m a)
-> WithJSContextSingleton x m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTransControl t, Monad m) =>
(Run t -> m a) -> t m a
liftWith ((Run (WithJSContextSingleton x) -> m (Event t a))
-> WithJSContextSingleton x m (Event t a))
-> (Run (WithJSContextSingleton x) -> m (Event t a))
-> WithJSContextSingleton x m (Event t a)
forall a b. (a -> b) -> a -> b
$ \Run (WithJSContextSingleton x)
run -> Event t (Performable m a) -> m (Event t a)
forall a. Event t (Performable m a) -> m (Event t a)
forall t (m :: * -> *) a.
PerformEvent t m =>
Event t (Performable m a) -> m (Event t a)
performEvent (Event t (Performable m a) -> m (Event t a))
-> Event t (Performable m a) -> m (Event t a)
forall a b. (a -> b) -> a -> b
$ (WithJSContextSingleton x (Performable m) a -> Performable m a)
-> Event t (WithJSContextSingleton x (Performable m) a)
-> Event t (Performable m a)
forall a b. (a -> b) -> Event t a -> Event t b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap WithJSContextSingleton x (Performable m) a -> Performable m a
WithJSContextSingleton x (Performable m) a
-> Performable m (StT (WithJSContextSingleton x) a)
Run (WithJSContextSingleton x)
run Event t (Performable (WithJSContextSingleton x m) a)
Event t (WithJSContextSingleton x (Performable m) a)
e
runWithJSContextSingleton :: WithJSContextSingleton x m a -> JSContextSingleton x -> m a
runWithJSContextSingleton :: forall x (m :: * -> *) a.
WithJSContextSingleton x m a -> JSContextSingleton x -> m a
runWithJSContextSingleton = ReaderT (JSContextSingleton x) m a -> JSContextSingleton x -> m a
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT (ReaderT (JSContextSingleton x) m a -> JSContextSingleton x -> m a)
-> (WithJSContextSingleton x m a
-> ReaderT (JSContextSingleton x) m a)
-> WithJSContextSingleton x m a
-> JSContextSingleton x
-> m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WithJSContextSingleton x m a -> ReaderT (JSContextSingleton x) m a
forall x (m :: * -> *) a.
WithJSContextSingleton x m a -> ReaderT (JSContextSingleton x) m a
unWithJSContextSingleton
instance MonadRef m => MonadRef (WithJSContextSingleton x m) where
type Ref (WithJSContextSingleton x m) = Ref m
newRef :: forall a.
a
-> WithJSContextSingleton x m (Ref (WithJSContextSingleton x m) a)
newRef = m (Ref m a) -> WithJSContextSingleton x m (Ref m a)
forall (m :: * -> *) a.
Monad m =>
m a -> WithJSContextSingleton x m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Ref m a) -> WithJSContextSingleton x m (Ref m a))
-> (a -> m (Ref m a)) -> a -> WithJSContextSingleton x m (Ref m a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> m (Ref m a)
forall a. a -> m (Ref m a)
forall (m :: * -> *) a. MonadRef m => a -> m (Ref m a)
newRef
readRef :: forall a.
Ref (WithJSContextSingleton x m) a -> WithJSContextSingleton x m a
readRef = m a -> WithJSContextSingleton x m a
forall (m :: * -> *) a.
Monad m =>
m a -> WithJSContextSingleton x m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m a -> WithJSContextSingleton x m a)
-> (Ref m a -> m a) -> Ref m a -> WithJSContextSingleton x m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ref m a -> m a
forall a. Ref m a -> m a
forall (m :: * -> *) a. MonadRef m => Ref m a -> m a
readRef
writeRef :: forall a.
Ref (WithJSContextSingleton x m) a
-> a -> WithJSContextSingleton x m ()
writeRef Ref (WithJSContextSingleton x m) a
r = m () -> WithJSContextSingleton x m ()
forall (m :: * -> *) a.
Monad m =>
m a -> WithJSContextSingleton x m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m () -> WithJSContextSingleton x m ())
-> (a -> m ()) -> a -> WithJSContextSingleton x m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ref m a -> a -> m ()
forall a. Ref m a -> a -> m ()
forall (m :: * -> *) a. MonadRef m => Ref m a -> a -> m ()
writeRef Ref m a
Ref (WithJSContextSingleton x m) a
r
instance MonadAtomicRef m => MonadAtomicRef (WithJSContextSingleton x m) where
atomicModifyRef :: forall a b.
Ref (WithJSContextSingleton x m) a
-> (a -> (a, b)) -> WithJSContextSingleton x m b
atomicModifyRef Ref (WithJSContextSingleton x m) a
r = m b -> WithJSContextSingleton x m b
forall (m :: * -> *) a.
Monad m =>
m a -> WithJSContextSingleton x m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m b -> WithJSContextSingleton x m b)
-> ((a -> (a, b)) -> m b)
-> (a -> (a, b))
-> WithJSContextSingleton x m b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ref m a -> (a -> (a, b)) -> m b
forall a b. Ref m a -> (a -> (a, b)) -> m b
forall (m :: * -> *) a b.
MonadAtomicRef m =>
Ref m a -> (a -> (a, b)) -> m b
atomicModifyRef Ref m a
Ref (WithJSContextSingleton x m) a
r
withJSContextSingleton :: MonadJSM m => (forall x. JSContextSingleton x -> m r) -> m r
withJSContextSingleton :: forall (m :: * -> *) r.
MonadJSM m =>
(forall x. JSContextSingleton x -> m r) -> m r
withJSContextSingleton forall x. JSContextSingleton x -> m r
f = m JSContextRef
forall (m :: * -> *). MonadJSM m => m JSContextRef
askJSM m JSContextRef -> (JSContextRef -> m r) -> m r
forall a b. m a -> (a -> m b) -> m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= JSContextSingleton Any -> m r
forall x. JSContextSingleton x -> m r
f (JSContextSingleton Any -> m r)
-> (JSContextRef -> JSContextSingleton Any) -> JSContextRef -> m r
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSContextRef -> JSContextSingleton Any
forall x. JSContextRef -> JSContextSingleton x
JSContextSingleton
withJSContextSingletonMono :: MonadJSM m => (JSContextSingleton () -> m r) -> m r
withJSContextSingletonMono :: forall (m :: * -> *) r.
MonadJSM m =>
(JSContextSingleton () -> m r) -> m r
withJSContextSingletonMono JSContextSingleton () -> m r
f = m JSContextRef
forall (m :: * -> *). MonadJSM m => m JSContextRef
askJSM m JSContextRef -> (JSContextRef -> m r) -> m r
forall a b. m a -> (a -> m b) -> m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= JSContextSingleton () -> m r
f (JSContextSingleton () -> m r)
-> (JSContextRef -> JSContextSingleton ()) -> JSContextRef -> m r
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSContextRef -> JSContextSingleton ()
forall x. JSContextRef -> JSContextSingleton x
JSContextSingleton
newtype JSContextSingleton x = JSContextSingleton { forall x. JSContextSingleton x -> JSContextRef
unJSContextSingleton :: JSContextRef }
#ifndef ghcjs_HOST_OS
instance MonadIO m => MonadJSM (WithJSContextSingleton x m) where
liftJSM' :: forall a. JSM a -> WithJSContextSingleton x m a
liftJSM' JSM a
f = do
JSContextSingleton x
wv <- ReaderT (JSContextSingleton x) m (JSContextSingleton x)
-> WithJSContextSingleton x m (JSContextSingleton x)
forall x (m :: * -> *) a.
ReaderT (JSContextSingleton x) m a -> WithJSContextSingleton x m a
WithJSContextSingleton ReaderT (JSContextSingleton x) m (JSContextSingleton x)
forall r (m :: * -> *). MonadReader r m => m r
ask
JSM a -> JSContextRef -> WithJSContextSingleton x m a
forall (m :: * -> *) a. MonadIO m => JSM a -> JSContextRef -> m a
runJSM JSM a
f (JSContextRef -> WithJSContextSingleton x m a)
-> JSContextRef -> WithJSContextSingleton x m a
forall a b. (a -> b) -> a -> b
$ JSContextSingleton x -> JSContextRef
forall x. JSContextSingleton x -> JSContextRef
unJSContextSingleton JSContextSingleton x
wv
#endif