{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE EmptyDataDecls #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Reflex.Dom.Builder.Static where
import Data.IORef (IORef)
import Blaze.ByteString.Builder.Html.Utf8
import Control.Lens hiding (element)
import Control.Monad.Exception
import Control.Monad.Identity
import Control.Monad.Primitive
import Control.Monad.Ref
import Control.Monad.State.Strict
import Control.Monad.Trans.Reader
import Data.ByteString (ByteString)
import Data.ByteString.Builder (Builder, byteString, toLazyByteString)
import qualified Data.ByteString.Lazy as LBS
import Data.Default
import Data.Dependent.Map (DMap)
import qualified Data.Dependent.Map as DMap
import Data.Dependent.Sum (DSum (..))
import Data.Functor.Compose
import Data.Functor.Constant
import Data.IntMap (IntMap)
import qualified Data.IntMap as IntMap
import qualified Data.Map as Map
import Data.Map.Misc (applyMap)
import Data.Monoid ((<>))
import qualified Data.Set as Set
import Data.Text (Text)
import qualified Data.Text as T
import Data.Text.Encoding
import Data.Tuple
import GHC.Generics
import Reflex.Adjustable.Class
import Reflex.Class
import Reflex.Dom.Main (DomHost, DomTimeline, runDomHost)
import Reflex.Dom.Builder.Class
import Reflex.Dynamic
import Reflex.Host.Class
import Reflex.PerformEvent.Base
import Reflex.PerformEvent.Class
import Reflex.PostBuild.Base
import Reflex.PostBuild.Class
import Reflex.TriggerEvent.Class
data StaticDomBuilderEnv t = StaticDomBuilderEnv
{ StaticDomBuilderEnv t -> Bool
_staticDomBuilderEnv_shouldEscape :: Bool
, StaticDomBuilderEnv t -> Maybe (Behavior t Text)
_staticDomBuilderEnv_selectValue :: Maybe (Behavior t Text)
, StaticDomBuilderEnv t -> IORef Int
_staticDomBuilderEnv_nextRunWithReplaceKey :: IORef Int
}
newtype StaticDomBuilderT t m a = StaticDomBuilderT
{ StaticDomBuilderT t m a
-> ReaderT
(StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) a
unStaticDomBuilderT :: ReaderT (StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) a
}
deriving (a -> StaticDomBuilderT t m b -> StaticDomBuilderT t m a
(a -> b) -> StaticDomBuilderT t m a -> StaticDomBuilderT t m b
(forall a b.
(a -> b) -> StaticDomBuilderT t m a -> StaticDomBuilderT t m b)
-> (forall a b.
a -> StaticDomBuilderT t m b -> StaticDomBuilderT t m a)
-> Functor (StaticDomBuilderT t m)
forall k (t :: k) (m :: * -> *) a b.
Functor m =>
a -> StaticDomBuilderT t m b -> StaticDomBuilderT t m a
forall k (t :: k) (m :: * -> *) a b.
Functor m =>
(a -> b) -> StaticDomBuilderT t m a -> StaticDomBuilderT t m b
forall a b. a -> StaticDomBuilderT t m b -> StaticDomBuilderT t m a
forall a b.
(a -> b) -> StaticDomBuilderT t m a -> StaticDomBuilderT t m b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> StaticDomBuilderT t m b -> StaticDomBuilderT t m a
$c<$ :: forall k (t :: k) (m :: * -> *) a b.
Functor m =>
a -> StaticDomBuilderT t m b -> StaticDomBuilderT t m a
fmap :: (a -> b) -> StaticDomBuilderT t m a -> StaticDomBuilderT t m b
$cfmap :: forall k (t :: k) (m :: * -> *) a b.
Functor m =>
(a -> b) -> StaticDomBuilderT t m a -> StaticDomBuilderT t m b
Functor, Functor (StaticDomBuilderT t m)
a -> StaticDomBuilderT t m a
Functor (StaticDomBuilderT t m) =>
(forall a. a -> StaticDomBuilderT t m a)
-> (forall a b.
StaticDomBuilderT t m (a -> b)
-> StaticDomBuilderT t m a -> StaticDomBuilderT t m b)
-> (forall a b c.
(a -> b -> c)
-> StaticDomBuilderT t m a
-> StaticDomBuilderT t m b
-> StaticDomBuilderT t m c)
-> (forall a b.
StaticDomBuilderT t m a
-> StaticDomBuilderT t m b -> StaticDomBuilderT t m b)
-> (forall a b.
StaticDomBuilderT t m a
-> StaticDomBuilderT t m b -> StaticDomBuilderT t m a)
-> Applicative (StaticDomBuilderT t m)
StaticDomBuilderT t m a
-> StaticDomBuilderT t m b -> StaticDomBuilderT t m b
StaticDomBuilderT t m a
-> StaticDomBuilderT t m b -> StaticDomBuilderT t m a
StaticDomBuilderT t m (a -> b)
-> StaticDomBuilderT t m a -> StaticDomBuilderT t m b
(a -> b -> c)
-> StaticDomBuilderT t m a
-> StaticDomBuilderT t m b
-> StaticDomBuilderT t m c
forall a. a -> StaticDomBuilderT t m a
forall k (t :: k) (m :: * -> *).
Monad m =>
Functor (StaticDomBuilderT t m)
forall k (t :: k) (m :: * -> *) a.
Monad m =>
a -> StaticDomBuilderT t m a
forall k (t :: k) (m :: * -> *) a b.
Monad m =>
StaticDomBuilderT t m a
-> StaticDomBuilderT t m b -> StaticDomBuilderT t m a
forall k (t :: k) (m :: * -> *) a b.
Monad m =>
StaticDomBuilderT t m a
-> StaticDomBuilderT t m b -> StaticDomBuilderT t m b
forall k (t :: k) (m :: * -> *) a b.
Monad m =>
StaticDomBuilderT t m (a -> b)
-> StaticDomBuilderT t m a -> StaticDomBuilderT t m b
forall k (t :: k) (m :: * -> *) a b c.
Monad m =>
(a -> b -> c)
-> StaticDomBuilderT t m a
-> StaticDomBuilderT t m b
-> StaticDomBuilderT t m c
forall a b.
StaticDomBuilderT t m a
-> StaticDomBuilderT t m b -> StaticDomBuilderT t m a
forall a b.
StaticDomBuilderT t m a
-> StaticDomBuilderT t m b -> StaticDomBuilderT t m b
forall a b.
StaticDomBuilderT t m (a -> b)
-> StaticDomBuilderT t m a -> StaticDomBuilderT t m b
forall a b c.
(a -> b -> c)
-> StaticDomBuilderT t m a
-> StaticDomBuilderT t m b
-> StaticDomBuilderT t 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
<* :: StaticDomBuilderT t m a
-> StaticDomBuilderT t m b -> StaticDomBuilderT t m a
$c<* :: forall k (t :: k) (m :: * -> *) a b.
Monad m =>
StaticDomBuilderT t m a
-> StaticDomBuilderT t m b -> StaticDomBuilderT t m a
*> :: StaticDomBuilderT t m a
-> StaticDomBuilderT t m b -> StaticDomBuilderT t m b
$c*> :: forall k (t :: k) (m :: * -> *) a b.
Monad m =>
StaticDomBuilderT t m a
-> StaticDomBuilderT t m b -> StaticDomBuilderT t m b
liftA2 :: (a -> b -> c)
-> StaticDomBuilderT t m a
-> StaticDomBuilderT t m b
-> StaticDomBuilderT t m c
$cliftA2 :: forall k (t :: k) (m :: * -> *) a b c.
Monad m =>
(a -> b -> c)
-> StaticDomBuilderT t m a
-> StaticDomBuilderT t m b
-> StaticDomBuilderT t m c
<*> :: StaticDomBuilderT t m (a -> b)
-> StaticDomBuilderT t m a -> StaticDomBuilderT t m b
$c<*> :: forall k (t :: k) (m :: * -> *) a b.
Monad m =>
StaticDomBuilderT t m (a -> b)
-> StaticDomBuilderT t m a -> StaticDomBuilderT t m b
pure :: a -> StaticDomBuilderT t m a
$cpure :: forall k (t :: k) (m :: * -> *) a.
Monad m =>
a -> StaticDomBuilderT t m a
$cp1Applicative :: forall k (t :: k) (m :: * -> *).
Monad m =>
Functor (StaticDomBuilderT t m)
Applicative, Applicative (StaticDomBuilderT t m)
a -> StaticDomBuilderT t m a
Applicative (StaticDomBuilderT t m) =>
(forall a b.
StaticDomBuilderT t m a
-> (a -> StaticDomBuilderT t m b) -> StaticDomBuilderT t m b)
-> (forall a b.
StaticDomBuilderT t m a
-> StaticDomBuilderT t m b -> StaticDomBuilderT t m b)
-> (forall a. a -> StaticDomBuilderT t m a)
-> Monad (StaticDomBuilderT t m)
StaticDomBuilderT t m a
-> (a -> StaticDomBuilderT t m b) -> StaticDomBuilderT t m b
StaticDomBuilderT t m a
-> StaticDomBuilderT t m b -> StaticDomBuilderT t m b
forall a. a -> StaticDomBuilderT t m a
forall k (t :: k) (m :: * -> *).
Monad m =>
Applicative (StaticDomBuilderT t m)
forall k (t :: k) (m :: * -> *) a.
Monad m =>
a -> StaticDomBuilderT t m a
forall k (t :: k) (m :: * -> *) a b.
Monad m =>
StaticDomBuilderT t m a
-> StaticDomBuilderT t m b -> StaticDomBuilderT t m b
forall k (t :: k) (m :: * -> *) a b.
Monad m =>
StaticDomBuilderT t m a
-> (a -> StaticDomBuilderT t m b) -> StaticDomBuilderT t m b
forall a b.
StaticDomBuilderT t m a
-> StaticDomBuilderT t m b -> StaticDomBuilderT t m b
forall a b.
StaticDomBuilderT t m a
-> (a -> StaticDomBuilderT t m b) -> StaticDomBuilderT t 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
return :: a -> StaticDomBuilderT t m a
$creturn :: forall k (t :: k) (m :: * -> *) a.
Monad m =>
a -> StaticDomBuilderT t m a
>> :: StaticDomBuilderT t m a
-> StaticDomBuilderT t m b -> StaticDomBuilderT t m b
$c>> :: forall k (t :: k) (m :: * -> *) a b.
Monad m =>
StaticDomBuilderT t m a
-> StaticDomBuilderT t m b -> StaticDomBuilderT t m b
>>= :: StaticDomBuilderT t m a
-> (a -> StaticDomBuilderT t m b) -> StaticDomBuilderT t m b
$c>>= :: forall k (t :: k) (m :: * -> *) a b.
Monad m =>
StaticDomBuilderT t m a
-> (a -> StaticDomBuilderT t m b) -> StaticDomBuilderT t m b
$cp1Monad :: forall k (t :: k) (m :: * -> *).
Monad m =>
Applicative (StaticDomBuilderT t m)
Monad, Monad (StaticDomBuilderT t m)
Monad (StaticDomBuilderT t m) =>
(forall a.
(a -> StaticDomBuilderT t m a) -> StaticDomBuilderT t m a)
-> MonadFix (StaticDomBuilderT t m)
(a -> StaticDomBuilderT t m a) -> StaticDomBuilderT t m a
forall a. (a -> StaticDomBuilderT t m a) -> StaticDomBuilderT t m a
forall k (t :: k) (m :: * -> *).
MonadFix m =>
Monad (StaticDomBuilderT t m)
forall k (t :: k) (m :: * -> *) a.
MonadFix m =>
(a -> StaticDomBuilderT t m a) -> StaticDomBuilderT t m a
forall (m :: * -> *).
Monad m =>
(forall a. (a -> m a) -> m a) -> MonadFix m
mfix :: (a -> StaticDomBuilderT t m a) -> StaticDomBuilderT t m a
$cmfix :: forall k (t :: k) (m :: * -> *) a.
MonadFix m =>
(a -> StaticDomBuilderT t m a) -> StaticDomBuilderT t m a
$cp1MonadFix :: forall k (t :: k) (m :: * -> *).
MonadFix m =>
Monad (StaticDomBuilderT t m)
MonadFix, Monad (StaticDomBuilderT t m)
Monad (StaticDomBuilderT t m) =>
(forall a. IO a -> StaticDomBuilderT t m a)
-> MonadIO (StaticDomBuilderT t m)
IO a -> StaticDomBuilderT t m a
forall a. IO a -> StaticDomBuilderT t m a
forall k (t :: k) (m :: * -> *).
MonadIO m =>
Monad (StaticDomBuilderT t m)
forall k (t :: k) (m :: * -> *) a.
MonadIO m =>
IO a -> StaticDomBuilderT t m a
forall (m :: * -> *).
Monad m =>
(forall a. IO a -> m a) -> MonadIO m
liftIO :: IO a -> StaticDomBuilderT t m a
$cliftIO :: forall k (t :: k) (m :: * -> *) a.
MonadIO m =>
IO a -> StaticDomBuilderT t m a
$cp1MonadIO :: forall k (t :: k) (m :: * -> *).
MonadIO m =>
Monad (StaticDomBuilderT t m)
MonadIO, Monad (StaticDomBuilderT t m)
e -> StaticDomBuilderT t m a
Monad (StaticDomBuilderT t m) =>
(forall e a. Exception e => e -> StaticDomBuilderT t m a)
-> (forall e a.
Exception e =>
StaticDomBuilderT t m a
-> (e -> StaticDomBuilderT t m a) -> StaticDomBuilderT t m a)
-> (forall a b.
StaticDomBuilderT t m a
-> StaticDomBuilderT t m b -> StaticDomBuilderT t m a)
-> MonadException (StaticDomBuilderT t m)
StaticDomBuilderT t m a
-> (e -> StaticDomBuilderT t m a) -> StaticDomBuilderT t m a
StaticDomBuilderT t m a
-> StaticDomBuilderT t m b -> StaticDomBuilderT t m a
forall k (t :: k) (m :: * -> *).
MonadException m =>
Monad (StaticDomBuilderT t m)
forall k (t :: k) (m :: * -> *) e a.
(MonadException m, Exception e) =>
e -> StaticDomBuilderT t m a
forall k (t :: k) (m :: * -> *) e a.
(MonadException m, Exception e) =>
StaticDomBuilderT t m a
-> (e -> StaticDomBuilderT t m a) -> StaticDomBuilderT t m a
forall k (t :: k) (m :: * -> *) a b.
MonadException m =>
StaticDomBuilderT t m a
-> StaticDomBuilderT t m b -> StaticDomBuilderT t m a
forall e a. Exception e => e -> StaticDomBuilderT t m a
forall e a.
Exception e =>
StaticDomBuilderT t m a
-> (e -> StaticDomBuilderT t m a) -> StaticDomBuilderT t m a
forall a b.
StaticDomBuilderT t m a
-> StaticDomBuilderT t m b -> StaticDomBuilderT t 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
finally :: StaticDomBuilderT t m a
-> StaticDomBuilderT t m b -> StaticDomBuilderT t m a
$cfinally :: forall k (t :: k) (m :: * -> *) a b.
MonadException m =>
StaticDomBuilderT t m a
-> StaticDomBuilderT t m b -> StaticDomBuilderT t m a
catch :: StaticDomBuilderT t m a
-> (e -> StaticDomBuilderT t m a) -> StaticDomBuilderT t m a
$ccatch :: forall k (t :: k) (m :: * -> *) e a.
(MonadException m, Exception e) =>
StaticDomBuilderT t m a
-> (e -> StaticDomBuilderT t m a) -> StaticDomBuilderT t m a
throw :: e -> StaticDomBuilderT t m a
$cthrow :: forall k (t :: k) (m :: * -> *) e a.
(MonadException m, Exception e) =>
e -> StaticDomBuilderT t m a
$cp1MonadException :: forall k (t :: k) (m :: * -> *).
MonadException m =>
Monad (StaticDomBuilderT t m)
MonadException, MonadIO (StaticDomBuilderT t m)
MonadException (StaticDomBuilderT t m)
(MonadIO (StaticDomBuilderT t m),
MonadException (StaticDomBuilderT t m)) =>
(forall b.
((forall a. StaticDomBuilderT t m a -> StaticDomBuilderT t m a)
-> StaticDomBuilderT t m b)
-> StaticDomBuilderT t m b)
-> MonadAsyncException (StaticDomBuilderT t m)
((forall a. StaticDomBuilderT t m a -> StaticDomBuilderT t m a)
-> StaticDomBuilderT t m b)
-> StaticDomBuilderT t m b
forall b.
((forall a. StaticDomBuilderT t m a -> StaticDomBuilderT t m a)
-> StaticDomBuilderT t m b)
-> StaticDomBuilderT t m b
forall k (t :: k) (m :: * -> *).
MonadAsyncException m =>
MonadIO (StaticDomBuilderT t m)
forall k (t :: k) (m :: * -> *).
MonadAsyncException m =>
MonadException (StaticDomBuilderT t m)
forall k (t :: k) (m :: * -> *) b.
MonadAsyncException m =>
((forall a. StaticDomBuilderT t m a -> StaticDomBuilderT t m a)
-> StaticDomBuilderT t m b)
-> StaticDomBuilderT t m b
forall (m :: * -> *).
(MonadIO m, MonadException m) =>
(forall b. ((forall a. m a -> m a) -> m b) -> m b)
-> MonadAsyncException m
mask :: ((forall a. StaticDomBuilderT t m a -> StaticDomBuilderT t m a)
-> StaticDomBuilderT t m b)
-> StaticDomBuilderT t m b
$cmask :: forall k (t :: k) (m :: * -> *) b.
MonadAsyncException m =>
((forall a. StaticDomBuilderT t m a -> StaticDomBuilderT t m a)
-> StaticDomBuilderT t m b)
-> StaticDomBuilderT t m b
$cp2MonadAsyncException :: forall k (t :: k) (m :: * -> *).
MonadAsyncException m =>
MonadException (StaticDomBuilderT t m)
$cp1MonadAsyncException :: forall k (t :: k) (m :: * -> *).
MonadAsyncException m =>
MonadIO (StaticDomBuilderT t m)
MonadAsyncException)
instance PrimMonad m => PrimMonad (StaticDomBuilderT x m) where
type PrimState (StaticDomBuilderT x m) = PrimState m
primitive :: (State# (PrimState (StaticDomBuilderT x m))
-> (# State# (PrimState (StaticDomBuilderT x m)), a #))
-> StaticDomBuilderT x m a
primitive = m a -> StaticDomBuilderT x m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m a -> StaticDomBuilderT x m a)
-> ((State# (PrimState m) -> (# State# (PrimState m), a #)) -> m a)
-> (State# (PrimState m) -> (# State# (PrimState m), a #))
-> StaticDomBuilderT x m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (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 MonadTrans (StaticDomBuilderT t) where
lift :: m a -> StaticDomBuilderT t m a
lift = ReaderT (StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) a
-> StaticDomBuilderT t m a
forall k (t :: k) (m :: * -> *) a.
ReaderT (StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) a
-> StaticDomBuilderT t m a
StaticDomBuilderT (ReaderT (StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) a
-> StaticDomBuilderT t m a)
-> (m a
-> ReaderT
(StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) a)
-> m a
-> StaticDomBuilderT t m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StateT [Behavior t Builder] m a
-> ReaderT
(StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (StateT [Behavior t Builder] m a
-> ReaderT
(StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) a)
-> (m a -> StateT [Behavior t Builder] m a)
-> m a
-> ReaderT
(StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. m a -> StateT [Behavior t Builder] m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift
runStaticDomBuilderT :: (Monad m, Reflex t) => StaticDomBuilderT t m a -> StaticDomBuilderEnv t -> m (a, Behavior t Builder)
runStaticDomBuilderT :: StaticDomBuilderT t m a
-> StaticDomBuilderEnv t -> m (a, Behavior t Builder)
runStaticDomBuilderT (StaticDomBuilderT a :: ReaderT (StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) a
a) e :: StaticDomBuilderEnv t
e = do
(result :: a
result, a' :: [Behavior t Builder]
a') <- StateT [Behavior t Builder] m a
-> [Behavior t Builder] -> m (a, [Behavior t Builder])
forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
runStateT (ReaderT (StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) a
-> StaticDomBuilderEnv t -> StateT [Behavior t Builder] m a
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT ReaderT (StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) a
a StaticDomBuilderEnv t
e) []
(a, Behavior t Builder) -> m (a, Behavior t Builder)
forall (m :: * -> *) a. Monad m => a -> m a
return (a
result, [Behavior t Builder] -> Behavior t Builder
forall a. Monoid a => [a] -> a
mconcat ([Behavior t Builder] -> Behavior t Builder)
-> [Behavior t Builder] -> Behavior t Builder
forall a b. (a -> b) -> a -> b
$ [Behavior t Builder] -> [Behavior t Builder]
forall a. [a] -> [a]
reverse [Behavior t Builder]
a')
instance PostBuild t m => PostBuild t (StaticDomBuilderT t m) where
{-# INLINABLE getPostBuild #-}
getPostBuild :: StaticDomBuilderT t m (Event t ())
getPostBuild = m (Event t ()) -> StaticDomBuilderT t m (Event t ())
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift m (Event t ())
forall t (m :: * -> *). PostBuild t m => m (Event t ())
getPostBuild
instance MonadReflexCreateTrigger t m => MonadReflexCreateTrigger t (StaticDomBuilderT t m) where
{-# INLINABLE newEventWithTrigger #-}
newEventWithTrigger :: (EventTrigger t a -> IO (IO ()))
-> StaticDomBuilderT t m (Event t a)
newEventWithTrigger = m (Event t a) -> StaticDomBuilderT t m (Event t a)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Event t a) -> StaticDomBuilderT t m (Event t a))
-> ((EventTrigger t a -> IO (IO ())) -> m (Event t a))
-> (EventTrigger t a -> IO (IO ()))
-> StaticDomBuilderT t m (Event t a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (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 a. k a -> EventTrigger t a -> IO (IO ()))
-> StaticDomBuilderT t m (EventSelector t k)
newFanEventWithTrigger f :: forall a. k a -> EventTrigger t a -> IO (IO ())
f = m (EventSelector t k) -> StaticDomBuilderT t m (EventSelector t k)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (EventSelector t k)
-> StaticDomBuilderT t m (EventSelector t k))
-> m (EventSelector t k)
-> StaticDomBuilderT t 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)
newFanEventWithTrigger forall a. k a -> EventTrigger t a -> IO (IO ())
f
instance PerformEvent t m => PerformEvent t (StaticDomBuilderT t m) where
type Performable (StaticDomBuilderT t m) = Performable m
{-# INLINABLE performEvent_ #-}
performEvent_ :: Event t (Performable (StaticDomBuilderT t m) ())
-> StaticDomBuilderT t m ()
performEvent_ e :: Event t (Performable (StaticDomBuilderT t m) ())
e = m () -> StaticDomBuilderT t m ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m () -> StaticDomBuilderT t m ())
-> m () -> StaticDomBuilderT t m ()
forall a b. (a -> b) -> a -> b
$ Event t (Performable m ()) -> m ()
forall t (m :: * -> *).
PerformEvent t m =>
Event t (Performable m ()) -> m ()
performEvent_ Event t (Performable m ())
Event t (Performable (StaticDomBuilderT t m) ())
e
{-# INLINABLE performEvent #-}
performEvent :: Event t (Performable (StaticDomBuilderT t m) a)
-> StaticDomBuilderT t m (Event t a)
performEvent e :: Event t (Performable (StaticDomBuilderT t m) a)
e = m (Event t a) -> StaticDomBuilderT t m (Event t a)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Event t a) -> StaticDomBuilderT t m (Event t a))
-> m (Event t a) -> StaticDomBuilderT t m (Event t a)
forall a b. (a -> b) -> a -> b
$ 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)
Event t (Performable (StaticDomBuilderT t m) a)
e
instance MonadSample t m => MonadSample t (StaticDomBuilderT t m) where
{-# INLINABLE sample #-}
sample :: Behavior t a -> StaticDomBuilderT t m a
sample = m a -> StaticDomBuilderT t m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m a -> StaticDomBuilderT t m a)
-> (Behavior t a -> m a) -> Behavior t a -> StaticDomBuilderT t m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 (StaticDomBuilderT t m) where
{-# INLINABLE hold #-}
hold :: a -> Event t a -> StaticDomBuilderT t m (Behavior t a)
hold v0 :: a
v0 v' :: Event t a
v' = m (Behavior t a) -> StaticDomBuilderT t m (Behavior t a)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Behavior t a) -> StaticDomBuilderT t m (Behavior t a))
-> m (Behavior t a) -> StaticDomBuilderT t m (Behavior t a)
forall a b. (a -> b) -> a -> b
$ 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 Event t a
v'
{-# INLINABLE holdDyn #-}
holdDyn :: a -> Event t a -> StaticDomBuilderT t m (Dynamic t a)
holdDyn v0 :: a
v0 v' :: Event t a
v' = m (Dynamic t a) -> StaticDomBuilderT t m (Dynamic t a)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Dynamic t a) -> StaticDomBuilderT t m (Dynamic t a))
-> m (Dynamic t a) -> StaticDomBuilderT t m (Dynamic t a)
forall a b. (a -> b) -> a -> b
$ 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 Event t a
v'
{-# INLINABLE holdIncremental #-}
holdIncremental :: PatchTarget p
-> Event t p -> StaticDomBuilderT t m (Incremental t p)
holdIncremental v0 :: PatchTarget p
v0 v' :: Event t p
v' = m (Incremental t p) -> StaticDomBuilderT t m (Incremental t p)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Incremental t p) -> StaticDomBuilderT t m (Incremental t p))
-> m (Incremental t p) -> StaticDomBuilderT t m (Incremental t p)
forall a b. (a -> b) -> a -> b
$ 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 Event t p
v'
{-# INLINABLE buildDynamic #-}
buildDynamic :: PushM t a -> Event t a -> StaticDomBuilderT t m (Dynamic t a)
buildDynamic a0 :: PushM t a
a0 = m (Dynamic t a) -> StaticDomBuilderT t m (Dynamic t a)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Dynamic t a) -> StaticDomBuilderT t m (Dynamic t a))
-> (Event t a -> m (Dynamic t a))
-> Event t a
-> StaticDomBuilderT t 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 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 :: Event t a -> StaticDomBuilderT t m (Event t a)
headE = m (Event t a) -> StaticDomBuilderT t m (Event t a)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Event t a) -> StaticDomBuilderT t m (Event t a))
-> (Event t a -> m (Event t a))
-> Event t a
-> StaticDomBuilderT t m (Event t a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 (Monad m, Ref m ~ Ref IO, Reflex t) => TriggerEvent t (StaticDomBuilderT t m) where
{-# INLINABLE newTriggerEvent #-}
newTriggerEvent :: StaticDomBuilderT t m (Event t a, a -> IO ())
newTriggerEvent = (Event t a, a -> IO ())
-> StaticDomBuilderT t m (Event t a, a -> IO ())
forall (m :: * -> *) a. Monad m => a -> m a
return (Event t a
forall k (t :: k) a. Reflex t => Event t a
never, IO () -> a -> IO ()
forall a b. a -> b -> a
const (IO () -> a -> IO ()) -> IO () -> a -> IO ()
forall a b. (a -> b) -> a -> b
$ () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ())
{-# INLINABLE newTriggerEventWithOnComplete #-}
newTriggerEventWithOnComplete :: StaticDomBuilderT t m (Event t a, a -> IO () -> IO ())
newTriggerEventWithOnComplete = (Event t a, a -> IO () -> IO ())
-> StaticDomBuilderT t m (Event t a, a -> IO () -> IO ())
forall (m :: * -> *) a. Monad m => a -> m a
return (Event t a
forall k (t :: k) a. Reflex t => Event t a
never, \_ _ -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ())
{-# INLINABLE newEventWithLazyTriggerWithOnComplete #-}
newEventWithLazyTriggerWithOnComplete :: ((a -> IO () -> IO ()) -> IO (IO ()))
-> StaticDomBuilderT t m (Event t a)
newEventWithLazyTriggerWithOnComplete _ = Event t a -> StaticDomBuilderT t m (Event t a)
forall (m :: * -> *) a. Monad m => a -> m a
return Event t a
forall k (t :: k) a. Reflex t => Event t a
never
instance MonadRef m => MonadRef (StaticDomBuilderT t m) where
type Ref (StaticDomBuilderT t m) = Ref m
newRef :: a -> StaticDomBuilderT t m (Ref (StaticDomBuilderT t m) a)
newRef = m (Ref m a) -> StaticDomBuilderT t m (Ref m a)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Ref m a) -> StaticDomBuilderT t m (Ref m a))
-> (a -> m (Ref m a)) -> a -> StaticDomBuilderT t m (Ref m a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> m (Ref m a)
forall (m :: * -> *) a. MonadRef m => a -> m (Ref m a)
newRef
readRef :: Ref (StaticDomBuilderT t m) a -> StaticDomBuilderT t m a
readRef = m a -> StaticDomBuilderT t m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m a -> StaticDomBuilderT t m a)
-> (Ref m a -> m a) -> Ref m a -> StaticDomBuilderT t m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ref m a -> m a
forall (m :: * -> *) a. MonadRef m => Ref m a -> m a
readRef
writeRef :: Ref (StaticDomBuilderT t m) a -> a -> StaticDomBuilderT t m ()
writeRef r :: Ref (StaticDomBuilderT t m) a
r = m () -> StaticDomBuilderT t m ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m () -> StaticDomBuilderT t m ())
-> (a -> m ()) -> a -> StaticDomBuilderT t m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ref m a -> a -> m ()
forall (m :: * -> *) a. MonadRef m => Ref m a -> a -> m ()
writeRef Ref m a
Ref (StaticDomBuilderT t m) a
r
instance MonadAtomicRef m => MonadAtomicRef (StaticDomBuilderT t m) where
atomicModifyRef :: Ref (StaticDomBuilderT t m) a
-> (a -> (a, b)) -> StaticDomBuilderT t m b
atomicModifyRef r :: Ref (StaticDomBuilderT t m) a
r = m b -> StaticDomBuilderT t m b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m b -> StaticDomBuilderT t m b)
-> ((a -> (a, b)) -> m b)
-> (a -> (a, b))
-> StaticDomBuilderT t m b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 (StaticDomBuilderT t m) a
r
type SupportsStaticDomBuilder t m = (Reflex t, MonadIO m, MonadHold t m, MonadFix m, PerformEvent t m, MonadReflexCreateTrigger t m, MonadRef m, Ref m ~ Ref IO, Adjustable t m)
data StaticDomSpace
data StaticDomEvent (a :: k)
data StaticDomHandler (a :: k) (b :: k) = StaticDomHandler
data StaticEventSpec (er :: EventTag -> *) = StaticEventSpec deriving ((forall x. StaticEventSpec er -> Rep (StaticEventSpec er) x)
-> (forall x. Rep (StaticEventSpec er) x -> StaticEventSpec er)
-> Generic (StaticEventSpec er)
forall x. Rep (StaticEventSpec er) x -> StaticEventSpec er
forall x. StaticEventSpec er -> Rep (StaticEventSpec er) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (er :: EventTag -> *) x.
Rep (StaticEventSpec er) x -> StaticEventSpec er
forall (er :: EventTag -> *) x.
StaticEventSpec er -> Rep (StaticEventSpec er) x
$cto :: forall (er :: EventTag -> *) x.
Rep (StaticEventSpec er) x -> StaticEventSpec er
$cfrom :: forall (er :: EventTag -> *) x.
StaticEventSpec er -> Rep (StaticEventSpec er) x
Generic)
instance Default (StaticEventSpec er)
instance DomSpace StaticDomSpace where
type EventSpec StaticDomSpace = StaticEventSpec
type RawDocument StaticDomSpace = ()
type RawTextNode StaticDomSpace = ()
type StaticDomSpace = ()
type RawElement StaticDomSpace = ()
type RawInputElement StaticDomSpace = ()
type RawTextAreaElement StaticDomSpace = ()
type RawSelectElement StaticDomSpace = ()
addEventSpecFlags :: proxy StaticDomSpace
-> EventName en
-> (Maybe (er en) -> EventFlags)
-> EventSpec StaticDomSpace er
-> EventSpec StaticDomSpace er
addEventSpecFlags _ _ _ _ = EventSpec StaticDomSpace er
forall (er :: EventTag -> *). StaticEventSpec er
StaticEventSpec
instance (SupportsStaticDomBuilder t m, Monad m) => HasDocument (StaticDomBuilderT t m) where
askDocument :: StaticDomBuilderT
t m (RawDocument (DomBuilderSpace (StaticDomBuilderT t m)))
askDocument = () -> StaticDomBuilderT t m ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
instance (Reflex t, Adjustable t m, MonadHold t m, SupportsStaticDomBuilder t m) => Adjustable t (StaticDomBuilderT t m) where
runWithReplace :: StaticDomBuilderT t m a
-> Event t (StaticDomBuilderT t m b)
-> StaticDomBuilderT t m (a, Event t b)
runWithReplace a0 :: StaticDomBuilderT t m a
a0 a' :: Event t (StaticDomBuilderT t m b)
a' = do
StaticDomBuilderEnv t
e <- ReaderT
(StaticDomBuilderEnv t)
(StateT [Behavior t Builder] m)
(StaticDomBuilderEnv t)
-> StaticDomBuilderT t m (StaticDomBuilderEnv t)
forall k (t :: k) (m :: * -> *) a.
ReaderT (StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) a
-> StaticDomBuilderT t m a
StaticDomBuilderT ReaderT
(StaticDomBuilderEnv t)
(StateT [Behavior t Builder] m)
(StaticDomBuilderEnv t)
forall (m :: * -> *) r. Monad m => ReaderT r m r
ask
Text
key <- StaticDomBuilderEnv t -> StaticDomBuilderT t m Text
forall t (m :: * -> *).
(DomBuilder t m, MonadIO m) =>
StaticDomBuilderEnv t -> m Text
replaceStart StaticDomBuilderEnv t
e
(result0 :: (a, Behavior t Builder)
result0, result' :: Event t (b, Behavior t Builder)
result') <- m ((a, Behavior t Builder), Event t (b, Behavior t Builder))
-> StaticDomBuilderT
t m ((a, Behavior t Builder), Event t (b, Behavior t Builder))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m ((a, Behavior t Builder), Event t (b, Behavior t Builder))
-> StaticDomBuilderT
t m ((a, Behavior t Builder), Event t (b, Behavior t Builder)))
-> m ((a, Behavior t Builder), Event t (b, Behavior t Builder))
-> StaticDomBuilderT
t m ((a, Behavior t Builder), Event t (b, Behavior t Builder))
forall a b. (a -> b) -> a -> b
$ m (a, Behavior t Builder)
-> Event t (m (b, Behavior t Builder))
-> m ((a, Behavior t Builder), Event t (b, Behavior t Builder))
forall t (m :: * -> *) a b.
Adjustable t m =>
m a -> Event t (m b) -> m (a, Event t b)
runWithReplace (StaticDomBuilderT t m a
-> StaticDomBuilderEnv t -> m (a, Behavior t Builder)
forall k (m :: * -> *) (t :: k) a.
(Monad m, Reflex t) =>
StaticDomBuilderT t m a
-> StaticDomBuilderEnv t -> m (a, Behavior t Builder)
runStaticDomBuilderT StaticDomBuilderT t m a
a0 StaticDomBuilderEnv t
e) ((StaticDomBuilderT t m b
-> StaticDomBuilderEnv t -> m (b, Behavior t Builder))
-> StaticDomBuilderEnv t
-> StaticDomBuilderT t m b
-> m (b, Behavior t Builder)
forall a b c. (a -> b -> c) -> b -> a -> c
flip StaticDomBuilderT t m b
-> StaticDomBuilderEnv t -> m (b, Behavior t Builder)
forall k (m :: * -> *) (t :: k) a.
(Monad m, Reflex t) =>
StaticDomBuilderT t m a
-> StaticDomBuilderEnv t -> m (a, Behavior t Builder)
runStaticDomBuilderT StaticDomBuilderEnv t
e (StaticDomBuilderT t m b -> m (b, Behavior t Builder))
-> Event t (StaticDomBuilderT t m b)
-> Event t (m (b, Behavior t Builder))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Event t (StaticDomBuilderT t m b)
a')
Behavior t (Behavior t Builder)
o <- Behavior t Builder
-> Event t (Behavior t Builder)
-> StaticDomBuilderT t m (Behavior t (Behavior t Builder))
forall k (t :: k) (m :: * -> *) a.
MonadHold t m =>
a -> Event t a -> m (Behavior t a)
hold ((a, Behavior t Builder) -> Behavior t Builder
forall a b. (a, b) -> b
snd (a, Behavior t Builder)
result0) (Event t (Behavior t Builder)
-> StaticDomBuilderT t m (Behavior t (Behavior t Builder)))
-> Event t (Behavior t Builder)
-> StaticDomBuilderT t m (Behavior t (Behavior t Builder))
forall a b. (a -> b) -> a -> b
$ ((b, Behavior t Builder) -> Behavior t Builder)
-> Event t (b, Behavior t Builder) -> Event t (Behavior t Builder)
forall k (t :: k) a b.
Reflex t =>
(a -> b) -> Event t a -> Event t b
fmapCheap (b, Behavior t Builder) -> Behavior t Builder
forall a b. (a, b) -> b
snd Event t (b, Behavior t Builder)
result'
ReaderT (StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) ()
-> StaticDomBuilderT t m ()
forall k (t :: k) (m :: * -> *) a.
ReaderT (StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) a
-> StaticDomBuilderT t m a
StaticDomBuilderT (ReaderT (StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) ()
-> StaticDomBuilderT t m ())
-> ReaderT
(StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) ()
-> StaticDomBuilderT t m ()
forall a b. (a -> b) -> a -> b
$ ([Behavior t Builder] -> [Behavior t Builder])
-> ReaderT
(StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (([Behavior t Builder] -> [Behavior t Builder])
-> ReaderT
(StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) ())
-> ([Behavior t Builder] -> [Behavior t Builder])
-> ReaderT
(StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) ()
forall a b. (a -> b) -> a -> b
$ (:) (Behavior t Builder
-> [Behavior t Builder] -> [Behavior t Builder])
-> Behavior t Builder
-> [Behavior t Builder]
-> [Behavior t Builder]
forall a b. (a -> b) -> a -> b
$ Behavior t (Behavior t Builder) -> Behavior t Builder
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join Behavior t (Behavior t Builder)
o
Text -> StaticDomBuilderT t m ()
forall t (m :: * -> *). DomBuilder t m => Text -> m ()
replaceEnd Text
key
(a, Event t b) -> StaticDomBuilderT t m (a, Event t b)
forall (m :: * -> *) a. Monad m => a -> m a
return ((a, Behavior t Builder) -> a
forall a b. (a, b) -> a
fst (a, Behavior t Builder)
result0, ((b, Behavior t Builder) -> b)
-> Event t (b, Behavior t Builder) -> Event t b
forall k (t :: k) a b.
Reflex t =>
(a -> b) -> Event t a -> Event t b
fmapCheap (b, Behavior t Builder) -> b
forall a b. (a, b) -> a
fst Event t (b, Behavior t Builder)
result')
traverseIntMapWithKeyWithAdjust :: (Int -> v -> StaticDomBuilderT t m v')
-> IntMap v
-> Event t (PatchIntMap v)
-> StaticDomBuilderT t m (IntMap v', Event t (PatchIntMap v'))
traverseIntMapWithKeyWithAdjust = (forall x.
(Int -> v -> m x)
-> IntMap v
-> Event t (PatchIntMap v)
-> m (IntMap x, Event t (PatchIntMap x)))
-> (Int -> v -> StaticDomBuilderT t m v')
-> IntMap v
-> Event t (PatchIntMap v)
-> StaticDomBuilderT t m (IntMap v', Event t (PatchIntMap v'))
forall t (m :: * -> *) (p :: * -> *) a b.
(Adjustable t m, MonadHold t m, Patch (p a), Functor p,
Patch (p (Behavior t Builder)),
PatchTarget (p (Behavior t Builder)) ~ IntMap (Behavior t Builder),
Ref m ~ IORef, MonadIO m, MonadFix m, PerformEvent t m,
MonadReflexCreateTrigger t m, MonadRef m) =>
(forall x.
(Int -> a -> m x)
-> IntMap a -> Event t (p a) -> m (IntMap x, Event t (p x)))
-> (Int -> a -> StaticDomBuilderT t m b)
-> IntMap a
-> Event t (p a)
-> StaticDomBuilderT t m (IntMap b, Event t (p b))
hoistIntMapWithKeyWithAdjust forall x.
(Int -> v -> m x)
-> IntMap v
-> Event t (PatchIntMap v)
-> m (IntMap x, Event t (PatchIntMap x))
forall t (m :: * -> *) v v'.
Adjustable t m =>
(Int -> v -> m v')
-> IntMap v
-> Event t (PatchIntMap v)
-> m (IntMap v', Event t (PatchIntMap v'))
traverseIntMapWithKeyWithAdjust
traverseDMapWithKeyWithAdjust :: (forall a. k a -> v a -> StaticDomBuilderT t m (v' a))
-> DMap k v
-> Event t (PatchDMap k v)
-> StaticDomBuilderT t m (DMap k v', Event t (PatchDMap k v'))
traverseDMapWithKeyWithAdjust = (forall (vv :: * -> *) (vv' :: * -> *).
(forall a. k a -> vv a -> m (vv' a))
-> DMap k vv
-> Event t (PatchDMap k vv)
-> m (DMap k vv', Event t (PatchDMap k vv')))
-> (forall (vv :: * -> *) (vv' :: * -> *).
(forall a. vv a -> vv' a) -> PatchDMap k vv -> PatchDMap k vv')
-> (forall a. k a -> v a -> StaticDomBuilderT t m (v' a))
-> DMap k v
-> Event t (PatchDMap k v)
-> StaticDomBuilderT t m (DMap k v', Event t (PatchDMap k v'))
forall (k :: * -> *) (v :: * -> *) (v' :: * -> *) t (m :: * -> *)
(p :: (* -> *) -> (* -> *) -> *).
(Adjustable t m, MonadHold t m,
PatchTarget (p k (Constant (Behavior t Builder)))
~ DMap k (Constant (Behavior t Builder)),
Patch (p k (Constant (Behavior t Builder))), Ref m ~ IORef,
MonadIO m, MonadFix m, PerformEvent t m,
MonadReflexCreateTrigger t m, MonadRef m) =>
(forall (vv :: * -> *) (vv' :: * -> *).
(forall a. k a -> vv a -> m (vv' a))
-> DMap k vv
-> Event t (p k vv)
-> m (DMap k vv', Event t (p k vv')))
-> (forall (vv :: * -> *) (vv' :: * -> *).
(forall a. vv a -> vv' a) -> p k vv -> p k vv')
-> (forall a. k a -> v a -> StaticDomBuilderT t m (v' a))
-> DMap k v
-> Event t (p k v)
-> StaticDomBuilderT t m (DMap k v', Event t (p k v'))
hoistDMapWithKeyWithAdjust 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 (vv :: * -> *) (vv' :: * -> *).
(forall a. k a -> vv a -> m (vv' a))
-> DMap k vv
-> Event t (PatchDMap k vv)
-> m (DMap k vv', Event t (PatchDMap k vv'))
traverseDMapWithKeyWithAdjust forall k1 (v :: k1 -> *) (v' :: k1 -> *) (k2 :: k1 -> *).
(forall (a :: k1). v a -> v' a)
-> PatchDMap k2 v -> PatchDMap k2 v'
forall (vv :: * -> *) (vv' :: * -> *).
(forall a. vv a -> vv' a) -> PatchDMap k vv -> PatchDMap k vv'
mapPatchDMap
traverseDMapWithKeyWithAdjustWithMove :: (forall a. k a -> v a -> StaticDomBuilderT t m (v' a))
-> DMap k v
-> Event t (PatchDMapWithMove k v)
-> StaticDomBuilderT
t m (DMap k v', Event t (PatchDMapWithMove k v'))
traverseDMapWithKeyWithAdjustWithMove = (forall (vv :: * -> *) (vv' :: * -> *).
(forall a. k a -> vv a -> m (vv' a))
-> DMap k vv
-> Event t (PatchDMapWithMove k vv)
-> m (DMap k vv', Event t (PatchDMapWithMove k vv')))
-> (forall (vv :: * -> *) (vv' :: * -> *).
(forall a. vv a -> vv' a)
-> PatchDMapWithMove k vv -> PatchDMapWithMove k vv')
-> (forall a. k a -> v a -> StaticDomBuilderT t m (v' a))
-> DMap k v
-> Event t (PatchDMapWithMove k v)
-> StaticDomBuilderT
t m (DMap k v', Event t (PatchDMapWithMove k v'))
forall (k :: * -> *) (v :: * -> *) (v' :: * -> *) t (m :: * -> *)
(p :: (* -> *) -> (* -> *) -> *).
(Adjustable t m, MonadHold t m,
PatchTarget (p k (Constant (Behavior t Builder)))
~ DMap k (Constant (Behavior t Builder)),
Patch (p k (Constant (Behavior t Builder))), Ref m ~ IORef,
MonadIO m, MonadFix m, PerformEvent t m,
MonadReflexCreateTrigger t m, MonadRef m) =>
(forall (vv :: * -> *) (vv' :: * -> *).
(forall a. k a -> vv a -> m (vv' a))
-> DMap k vv
-> Event t (p k vv)
-> m (DMap k vv', Event t (p k vv')))
-> (forall (vv :: * -> *) (vv' :: * -> *).
(forall a. vv a -> vv' a) -> p k vv -> p k vv')
-> (forall a. k a -> v a -> StaticDomBuilderT t m (v' a))
-> DMap k v
-> Event t (p k v)
-> StaticDomBuilderT t m (DMap k v', Event t (p k v'))
hoistDMapWithKeyWithAdjust 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 (vv :: * -> *) (vv' :: * -> *).
(forall a. k a -> vv a -> m (vv' a))
-> DMap k vv
-> Event t (PatchDMapWithMove k vv)
-> m (DMap k vv', Event t (PatchDMapWithMove k vv'))
traverseDMapWithKeyWithAdjustWithMove forall k1 (k2 :: k1 -> *) (v :: k1 -> *) (v' :: k1 -> *).
(forall (a :: k1). v a -> v' a)
-> PatchDMapWithMove k2 v -> PatchDMapWithMove k2 v'
forall (vv :: * -> *) (vv' :: * -> *).
(forall a. vv a -> vv' a)
-> PatchDMapWithMove k vv -> PatchDMapWithMove k vv'
mapPatchDMapWithMove
replaceStart :: (DomBuilder t m, MonadIO m) => StaticDomBuilderEnv t -> m Text
replaceStart :: StaticDomBuilderEnv t -> m Text
replaceStart env :: StaticDomBuilderEnv t
env = do
String
str <- Int -> String
forall a. Show a => a -> String
show (Int -> String) -> m Int -> m String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO Int -> m Int
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (Ref IO Int -> (Int -> (Int, Int)) -> IO Int
forall (m :: * -> *) a b.
MonadAtomicRef m =>
Ref m a -> (a -> (a, b)) -> m b
atomicModifyRef (StaticDomBuilderEnv t -> IORef Int
forall k (t :: k). StaticDomBuilderEnv t -> IORef Int
_staticDomBuilderEnv_nextRunWithReplaceKey StaticDomBuilderEnv t
env) ((Int -> (Int, Int)) -> IO Int) -> (Int -> (Int, Int)) -> IO Int
forall a b. (a -> b) -> a -> b
$ \k :: Int
k -> (Int -> Int
forall a. Enum a => a -> a
succ Int
k, Int
k))
let key :: Text
key = "-" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack String
str
CommentNode (DomBuilderSpace m) t
_ <- CommentNodeConfig t -> m (CommentNode (DomBuilderSpace m) t)
forall t (m :: * -> *).
DomBuilder t m =>
CommentNodeConfig t -> m (CommentNode (DomBuilderSpace m) t)
commentNode (CommentNodeConfig t -> m (CommentNode (DomBuilderSpace m) t))
-> CommentNodeConfig t -> m (CommentNode (DomBuilderSpace m) t)
forall a b. (a -> b) -> a -> b
$ CommentNodeConfig t
forall a. Default a => a
def { _commentNodeConfig_initialContents :: Text
_commentNodeConfig_initialContents = "replace-start" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
key }
Text -> m Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure Text
key
replaceEnd :: DomBuilder t m => Text -> m ()
replaceEnd :: Text -> m ()
replaceEnd key :: Text
key = m (CommentNode (DomBuilderSpace m) t) -> m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (m (CommentNode (DomBuilderSpace m) t) -> m ())
-> m (CommentNode (DomBuilderSpace m) t) -> m ()
forall a b. (a -> b) -> a -> b
$ CommentNodeConfig t -> m (CommentNode (DomBuilderSpace m) t)
forall t (m :: * -> *).
DomBuilder t m =>
CommentNodeConfig t -> m (CommentNode (DomBuilderSpace m) t)
commentNode (CommentNodeConfig t -> m (CommentNode (DomBuilderSpace m) t))
-> CommentNodeConfig t -> m (CommentNode (DomBuilderSpace m) t)
forall a b. (a -> b) -> a -> b
$ CommentNodeConfig t
forall a. Default a => a
def { _commentNodeConfig_initialContents :: Text
_commentNodeConfig_initialContents = "replace-end" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
key }
hoistIntMapWithKeyWithAdjust :: forall t m p a b.
( Adjustable t m
, MonadHold t m
, Patch (p a)
, Functor p
, Patch (p (Behavior t Builder))
, PatchTarget (p (Behavior t Builder)) ~ IntMap (Behavior t Builder)
, Ref m ~ IORef, MonadIO m, MonadFix m, PerformEvent t m, MonadReflexCreateTrigger t m, MonadRef m
)
=> (forall x. (IntMap.Key -> a -> m x)
-> IntMap a
-> Event t (p a)
-> m (IntMap x, Event t (p x))
)
-> (IntMap.Key -> a -> StaticDomBuilderT t m b)
-> IntMap a
-> Event t (p a)
-> StaticDomBuilderT t m (IntMap b, Event t (p b))
hoistIntMapWithKeyWithAdjust :: (forall x.
(Int -> a -> m x)
-> IntMap a -> Event t (p a) -> m (IntMap x, Event t (p x)))
-> (Int -> a -> StaticDomBuilderT t m b)
-> IntMap a
-> Event t (p a)
-> StaticDomBuilderT t m (IntMap b, Event t (p b))
hoistIntMapWithKeyWithAdjust base :: forall x.
(Int -> a -> m x)
-> IntMap a -> Event t (p a) -> m (IntMap x, Event t (p x))
base f :: Int -> a -> StaticDomBuilderT t m b
f im0 :: IntMap a
im0 im' :: Event t (p a)
im' = do
StaticDomBuilderEnv t
e <- ReaderT
(StaticDomBuilderEnv t)
(StateT [Behavior t Builder] m)
(StaticDomBuilderEnv t)
-> StaticDomBuilderT t m (StaticDomBuilderEnv t)
forall k (t :: k) (m :: * -> *) a.
ReaderT (StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) a
-> StaticDomBuilderT t m a
StaticDomBuilderT ReaderT
(StaticDomBuilderEnv t)
(StateT [Behavior t Builder] m)
(StaticDomBuilderEnv t)
forall (m :: * -> *) r. Monad m => ReaderT r m r
ask
(children0 :: IntMap (b, Behavior t Builder)
children0, children' :: Event t (p (b, Behavior t Builder))
children') <- m (IntMap (b, Behavior t Builder),
Event t (p (b, Behavior t Builder)))
-> StaticDomBuilderT
t
m
(IntMap (b, Behavior t Builder),
Event t (p (b, Behavior t Builder)))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (IntMap (b, Behavior t Builder),
Event t (p (b, Behavior t Builder)))
-> StaticDomBuilderT
t
m
(IntMap (b, Behavior t Builder),
Event t (p (b, Behavior t Builder))))
-> m (IntMap (b, Behavior t Builder),
Event t (p (b, Behavior t Builder)))
-> StaticDomBuilderT
t
m
(IntMap (b, Behavior t Builder),
Event t (p (b, Behavior t Builder)))
forall a b. (a -> b) -> a -> b
$ (Int -> a -> m (b, Behavior t Builder))
-> IntMap a
-> Event t (p a)
-> m (IntMap (b, Behavior t Builder),
Event t (p (b, Behavior t Builder)))
forall x.
(Int -> a -> m x)
-> IntMap a -> Event t (p a) -> m (IntMap x, Event t (p x))
base (\k :: Int
k v :: a
v -> StaticDomBuilderT t m b
-> StaticDomBuilderEnv t -> m (b, Behavior t Builder)
forall k (m :: * -> *) (t :: k) a.
(Monad m, Reflex t) =>
StaticDomBuilderT t m a
-> StaticDomBuilderEnv t -> m (a, Behavior t Builder)
runStaticDomBuilderT (Int -> a -> StaticDomBuilderT t m b
f Int
k a
v) StaticDomBuilderEnv t
e) IntMap a
im0 Event t (p a)
im'
let result0 :: IntMap b
result0 = ((b, Behavior t Builder) -> b)
-> IntMap (b, Behavior t Builder) -> IntMap b
forall a b. (a -> b) -> IntMap a -> IntMap b
IntMap.map (b, Behavior t Builder) -> b
forall a b. (a, b) -> a
fst IntMap (b, Behavior t Builder)
children0
result' :: Event t (p b)
result' = ((p (b, Behavior t Builder) -> p b)
-> Event t (p (b, Behavior t Builder)) -> Event t (p b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((p (b, Behavior t Builder) -> p b)
-> Event t (p (b, Behavior t Builder)) -> Event t (p b))
-> (((b, Behavior t Builder) -> b)
-> p (b, Behavior t Builder) -> p b)
-> ((b, Behavior t Builder) -> b)
-> Event t (p (b, Behavior t Builder))
-> Event t (p b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((b, Behavior t Builder) -> b) -> p (b, Behavior t Builder) -> p b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap) (b, Behavior t Builder) -> b
forall a b. (a, b) -> a
fst Event t (p (b, Behavior t Builder))
children'
outputs0 :: IntMap (Behavior t Builder)
outputs0 :: IntMap (Behavior t Builder)
outputs0 = ((b, Behavior t Builder) -> Behavior t Builder)
-> IntMap (b, Behavior t Builder) -> IntMap (Behavior t Builder)
forall a b. (a -> b) -> IntMap a -> IntMap b
IntMap.map (b, Behavior t Builder) -> Behavior t Builder
forall a b. (a, b) -> b
snd IntMap (b, Behavior t Builder)
children0
outputs' :: Event t (p (Behavior t Builder))
outputs' :: Event t (p (Behavior t Builder))
outputs' = ((p (b, Behavior t Builder) -> p (Behavior t Builder))
-> Event t (p (b, Behavior t Builder))
-> Event t (p (Behavior t Builder))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((p (b, Behavior t Builder) -> p (Behavior t Builder))
-> Event t (p (b, Behavior t Builder))
-> Event t (p (Behavior t Builder)))
-> (((b, Behavior t Builder) -> Behavior t Builder)
-> p (b, Behavior t Builder) -> p (Behavior t Builder))
-> ((b, Behavior t Builder) -> Behavior t Builder)
-> Event t (p (b, Behavior t Builder))
-> Event t (p (Behavior t Builder))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((b, Behavior t Builder) -> Behavior t Builder)
-> p (b, Behavior t Builder) -> p (Behavior t Builder)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap) (b, Behavior t Builder) -> Behavior t Builder
forall a b. (a, b) -> b
snd Event t (p (b, Behavior t Builder))
children'
Incremental t (p (Behavior t Builder))
outputs <- PatchTarget (p (Behavior t Builder))
-> Event t (p (Behavior t Builder))
-> StaticDomBuilderT t m (Incremental t (p (Behavior t Builder)))
forall k (t :: k) (m :: * -> *) p.
(MonadHold t m, Patch p) =>
PatchTarget p -> Event t p -> m (Incremental t p)
holdIncremental IntMap (Behavior t Builder)
PatchTarget (p (Behavior t Builder))
outputs0 Event t (p (Behavior t Builder))
outputs'
ReaderT (StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) ()
-> StaticDomBuilderT t m ()
forall k (t :: k) (m :: * -> *) a.
ReaderT (StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) a
-> StaticDomBuilderT t m a
StaticDomBuilderT (ReaderT (StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) ()
-> StaticDomBuilderT t m ())
-> ReaderT
(StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) ()
-> StaticDomBuilderT t m ()
forall a b. (a -> b) -> a -> b
$ ([Behavior t Builder] -> [Behavior t Builder])
-> ReaderT
(StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (([Behavior t Builder] -> [Behavior t Builder])
-> ReaderT
(StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) ())
-> ([Behavior t Builder] -> [Behavior t Builder])
-> ReaderT
(StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) ()
forall a b. (a -> b) -> a -> b
$ (:) (Behavior t Builder
-> [Behavior t Builder] -> [Behavior t Builder])
-> Behavior t Builder
-> [Behavior t Builder]
-> [Behavior t Builder]
forall a b. (a -> b) -> a -> b
$ PullM t Builder -> Behavior t Builder
forall k (t :: k) a. Reflex t => PullM t a -> Behavior t a
pull (PullM t Builder -> Behavior t Builder)
-> PullM t Builder -> Behavior t Builder
forall a b. (a -> b) -> a -> b
$ do
IntMap (Behavior t Builder)
os <- Behavior t (IntMap (Behavior t Builder))
-> PullM t (IntMap (Behavior t Builder))
forall k (t :: k) (m :: * -> *) a.
MonadSample t m =>
Behavior t a -> m a
sample (Behavior t (IntMap (Behavior t Builder))
-> PullM t (IntMap (Behavior t Builder)))
-> Behavior t (IntMap (Behavior t Builder))
-> PullM t (IntMap (Behavior t Builder))
forall a b. (a -> b) -> a -> b
$ Incremental t (p (Behavior t Builder))
-> Behavior t (PatchTarget (p (Behavior t Builder)))
forall k (t :: k) p.
(Reflex t, Patch p) =>
Incremental t p -> Behavior t (PatchTarget p)
currentIncremental Incremental t (p (Behavior t Builder))
outputs
([Builder] -> Builder) -> PullM t [Builder] -> PullM t Builder
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Builder] -> Builder
forall a. Monoid a => [a] -> a
mconcat (PullM t [Builder] -> PullM t Builder)
-> PullM t [Builder] -> PullM t Builder
forall a b. (a -> b) -> a -> b
$ [(Int, Behavior t Builder)]
-> ((Int, Behavior t Builder) -> PullM t Builder)
-> PullM t [Builder]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM (IntMap (Behavior t Builder) -> [(Int, Behavior t Builder)]
forall a. IntMap a -> [(Int, a)]
IntMap.toList IntMap (Behavior t Builder)
os) (((Int, Behavior t Builder) -> PullM t Builder)
-> PullM t [Builder])
-> ((Int, Behavior t Builder) -> PullM t Builder)
-> PullM t [Builder]
forall a b. (a -> b) -> a -> b
$ \(_, o :: Behavior t Builder
o) -> do
Behavior t Builder -> PullM t Builder
forall k (t :: k) (m :: * -> *) a.
MonadSample t m =>
Behavior t a -> m a
sample Behavior t Builder
o
(IntMap b, Event t (p b))
-> StaticDomBuilderT t m (IntMap b, Event t (p b))
forall (m :: * -> *) a. Monad m => a -> m a
return (IntMap b
result0, Event t (p b)
result')
hoistDMapWithKeyWithAdjust :: forall (k :: * -> *) v v' t m p.
( Adjustable t m
, MonadHold t m
, PatchTarget (p k (Constant (Behavior t Builder))) ~ DMap k (Constant (Behavior t Builder))
, Patch (p k (Constant (Behavior t Builder)))
, Ref m ~ IORef, MonadIO m, MonadFix m, PerformEvent t m, MonadReflexCreateTrigger t m, MonadRef m
)
=> (forall vv vv'.
(forall a. k a -> vv a -> m (vv' a))
-> DMap k vv
-> Event t (p k vv)
-> m (DMap k vv', Event t (p k vv'))
)
-> (forall vv vv'. (forall a. vv a -> vv' a) -> p k vv -> p k vv')
-> (forall a. k a -> v a -> StaticDomBuilderT t m (v' a))
-> DMap k v
-> Event t (p k v)
-> StaticDomBuilderT t m (DMap k v', Event t (p k v'))
hoistDMapWithKeyWithAdjust :: (forall (vv :: * -> *) (vv' :: * -> *).
(forall a. k a -> vv a -> m (vv' a))
-> DMap k vv
-> Event t (p k vv)
-> m (DMap k vv', Event t (p k vv')))
-> (forall (vv :: * -> *) (vv' :: * -> *).
(forall a. vv a -> vv' a) -> p k vv -> p k vv')
-> (forall a. k a -> v a -> StaticDomBuilderT t m (v' a))
-> DMap k v
-> Event t (p k v)
-> StaticDomBuilderT t m (DMap k v', Event t (p k v'))
hoistDMapWithKeyWithAdjust base :: forall (vv :: * -> *) (vv' :: * -> *).
(forall a. k a -> vv a -> m (vv' a))
-> DMap k vv
-> Event t (p k vv)
-> m (DMap k vv', Event t (p k vv'))
base mapPatch :: forall (vv :: * -> *) (vv' :: * -> *).
(forall a. vv a -> vv' a) -> p k vv -> p k vv'
mapPatch f :: forall a. k a -> v a -> StaticDomBuilderT t m (v' a)
f dm0 :: DMap k v
dm0 dm' :: Event t (p k v)
dm' = do
StaticDomBuilderEnv t
e <- ReaderT
(StaticDomBuilderEnv t)
(StateT [Behavior t Builder] m)
(StaticDomBuilderEnv t)
-> StaticDomBuilderT t m (StaticDomBuilderEnv t)
forall k (t :: k) (m :: * -> *) a.
ReaderT (StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) a
-> StaticDomBuilderT t m a
StaticDomBuilderT ReaderT
(StaticDomBuilderEnv t)
(StateT [Behavior t Builder] m)
(StaticDomBuilderEnv t)
forall (m :: * -> *) r. Monad m => ReaderT r m r
ask
(children0 :: DMap k (Compose ((,) (Behavior t Builder)) v')
children0, children' :: Event t (p k (Compose ((,) (Behavior t Builder)) v'))
children') <- m (DMap k (Compose ((,) (Behavior t Builder)) v'),
Event t (p k (Compose ((,) (Behavior t Builder)) v')))
-> StaticDomBuilderT
t
m
(DMap k (Compose ((,) (Behavior t Builder)) v'),
Event t (p k (Compose ((,) (Behavior t Builder)) v')))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (DMap k (Compose ((,) (Behavior t Builder)) v'),
Event t (p k (Compose ((,) (Behavior t Builder)) v')))
-> StaticDomBuilderT
t
m
(DMap k (Compose ((,) (Behavior t Builder)) v'),
Event t (p k (Compose ((,) (Behavior t Builder)) v'))))
-> m (DMap k (Compose ((,) (Behavior t Builder)) v'),
Event t (p k (Compose ((,) (Behavior t Builder)) v')))
-> StaticDomBuilderT
t
m
(DMap k (Compose ((,) (Behavior t Builder)) v'),
Event t (p k (Compose ((,) (Behavior t Builder)) v')))
forall a b. (a -> b) -> a -> b
$ (forall a.
k a -> v a -> m (Compose ((,) (Behavior t Builder)) v' a))
-> DMap k v
-> Event t (p k v)
-> m (DMap k (Compose ((,) (Behavior t Builder)) v'),
Event t (p k (Compose ((,) (Behavior t Builder)) v')))
forall (vv :: * -> *) (vv' :: * -> *).
(forall a. k a -> vv a -> m (vv' a))
-> DMap k vv
-> Event t (p k vv)
-> m (DMap k vv', Event t (p k vv'))
base (\k :: k a
k v :: v a
v -> ((v' a, Behavior t Builder)
-> Compose ((,) (Behavior t Builder)) v' a)
-> m (v' a, Behavior t Builder)
-> m (Compose ((,) (Behavior t Builder)) v' a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Behavior t Builder, v' a)
-> Compose ((,) (Behavior t Builder)) v' a
forall k k1 (f :: k -> *) (g :: k1 -> k) (a :: k1).
f (g a) -> Compose f g a
Compose ((Behavior t Builder, v' a)
-> Compose ((,) (Behavior t Builder)) v' a)
-> ((v' a, Behavior t Builder) -> (Behavior t Builder, v' a))
-> (v' a, Behavior t Builder)
-> Compose ((,) (Behavior t Builder)) v' a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (v' a, Behavior t Builder) -> (Behavior t Builder, v' a)
forall a b. (a, b) -> (b, a)
swap) (StaticDomBuilderT t m (v' a)
-> StaticDomBuilderEnv t -> m (v' a, Behavior t Builder)
forall k (m :: * -> *) (t :: k) a.
(Monad m, Reflex t) =>
StaticDomBuilderT t m a
-> StaticDomBuilderEnv t -> m (a, Behavior t Builder)
runStaticDomBuilderT (k a -> v a -> StaticDomBuilderT t m (v' a)
forall a. k a -> v a -> StaticDomBuilderT t m (v' a)
f k a
k v a
v) StaticDomBuilderEnv t
e)) DMap k v
dm0 Event t (p k v)
dm'
let result0 :: DMap k v'
result0 = (forall v. Compose ((,) (Behavior t Builder)) v' v -> v' v)
-> DMap k (Compose ((,) (Behavior t Builder)) v') -> DMap k v'
forall k1 (f :: k1 -> *) (g :: k1 -> *) (k2 :: k1 -> *).
(forall (v :: k1). f v -> g v) -> DMap k2 f -> DMap k2 g
DMap.map ((Behavior t Builder, v' v) -> v' v
forall a b. (a, b) -> b
snd ((Behavior t Builder, v' v) -> v' v)
-> (Compose ((,) (Behavior t Builder)) v' v
-> (Behavior t Builder, v' v))
-> Compose ((,) (Behavior t Builder)) v' v
-> v' v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Compose ((,) (Behavior t Builder)) v' v
-> (Behavior t Builder, v' v)
forall k1 (f :: k1 -> *) k2 (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose) DMap k (Compose ((,) (Behavior t Builder)) v')
children0
result' :: Event t (p k v')
result' = Event t (p k (Compose ((,) (Behavior t Builder)) v'))
-> (p k (Compose ((,) (Behavior t Builder)) v') -> p k v')
-> Event t (p k v')
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
ffor Event t (p k (Compose ((,) (Behavior t Builder)) v'))
children' ((p k (Compose ((,) (Behavior t Builder)) v') -> p k v')
-> Event t (p k v'))
-> (p k (Compose ((,) (Behavior t Builder)) v') -> p k v')
-> Event t (p k v')
forall a b. (a -> b) -> a -> b
$ (forall v. Compose ((,) (Behavior t Builder)) v' v -> v' v)
-> p k (Compose ((,) (Behavior t Builder)) v') -> p k v'
forall (vv :: * -> *) (vv' :: * -> *).
(forall a. vv a -> vv' a) -> p k vv -> p k vv'
mapPatch ((forall v. Compose ((,) (Behavior t Builder)) v' v -> v' v)
-> p k (Compose ((,) (Behavior t Builder)) v') -> p k v')
-> (forall v. Compose ((,) (Behavior t Builder)) v' v -> v' v)
-> p k (Compose ((,) (Behavior t Builder)) v')
-> p k v'
forall a b. (a -> b) -> a -> b
$ (Behavior t Builder, v' a) -> v' a
forall a b. (a, b) -> b
snd ((Behavior t Builder, v' a) -> v' a)
-> (Compose ((,) (Behavior t Builder)) v' a
-> (Behavior t Builder, v' a))
-> Compose ((,) (Behavior t Builder)) v' a
-> v' a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Compose ((,) (Behavior t Builder)) v' a
-> (Behavior t Builder, v' a)
forall k1 (f :: k1 -> *) k2 (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose
outputs0 :: DMap k (Constant (Behavior t Builder))
outputs0 :: DMap k (Constant (Behavior t Builder))
outputs0 = (forall v.
Compose ((,) (Behavior t Builder)) v' v
-> Constant (Behavior t Builder) v)
-> DMap k (Compose ((,) (Behavior t Builder)) v')
-> DMap k (Constant (Behavior t Builder))
forall k1 (f :: k1 -> *) (g :: k1 -> *) (k2 :: k1 -> *).
(forall (v :: k1). f v -> g v) -> DMap k2 f -> DMap k2 g
DMap.map (Behavior t Builder -> Constant (Behavior t Builder) v
forall k a (b :: k). a -> Constant a b
Constant (Behavior t Builder -> Constant (Behavior t Builder) v)
-> (Compose ((,) (Behavior t Builder)) v' v -> Behavior t Builder)
-> Compose ((,) (Behavior t Builder)) v' v
-> Constant (Behavior t Builder) v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Behavior t Builder, v' v) -> Behavior t Builder
forall a b. (a, b) -> a
fst ((Behavior t Builder, v' v) -> Behavior t Builder)
-> (Compose ((,) (Behavior t Builder)) v' v
-> (Behavior t Builder, v' v))
-> Compose ((,) (Behavior t Builder)) v' v
-> Behavior t Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Compose ((,) (Behavior t Builder)) v' v
-> (Behavior t Builder, v' v)
forall k1 (f :: k1 -> *) k2 (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose) DMap k (Compose ((,) (Behavior t Builder)) v')
children0
outputs' :: Event t (p k (Constant (Behavior t Builder)))
outputs' :: Event t (p k (Constant (Behavior t Builder)))
outputs' = Event t (p k (Compose ((,) (Behavior t Builder)) v'))
-> (p k (Compose ((,) (Behavior t Builder)) v')
-> p k (Constant (Behavior t Builder)))
-> Event t (p k (Constant (Behavior t Builder)))
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
ffor Event t (p k (Compose ((,) (Behavior t Builder)) v'))
children' ((p k (Compose ((,) (Behavior t Builder)) v')
-> p k (Constant (Behavior t Builder)))
-> Event t (p k (Constant (Behavior t Builder))))
-> (p k (Compose ((,) (Behavior t Builder)) v')
-> p k (Constant (Behavior t Builder)))
-> Event t (p k (Constant (Behavior t Builder)))
forall a b. (a -> b) -> a -> b
$ (forall v.
Compose ((,) (Behavior t Builder)) v' v
-> Constant (Behavior t Builder) v)
-> p k (Compose ((,) (Behavior t Builder)) v')
-> p k (Constant (Behavior t Builder))
forall (vv :: * -> *) (vv' :: * -> *).
(forall a. vv a -> vv' a) -> p k vv -> p k vv'
mapPatch ((forall v.
Compose ((,) (Behavior t Builder)) v' v
-> Constant (Behavior t Builder) v)
-> p k (Compose ((,) (Behavior t Builder)) v')
-> p k (Constant (Behavior t Builder)))
-> (forall v.
Compose ((,) (Behavior t Builder)) v' v
-> Constant (Behavior t Builder) v)
-> p k (Compose ((,) (Behavior t Builder)) v')
-> p k (Constant (Behavior t Builder))
forall a b. (a -> b) -> a -> b
$ Behavior t Builder -> Constant (Behavior t Builder) a
forall k a (b :: k). a -> Constant a b
Constant (Behavior t Builder -> Constant (Behavior t Builder) a)
-> (Compose ((,) (Behavior t Builder)) v' a -> Behavior t Builder)
-> Compose ((,) (Behavior t Builder)) v' a
-> Constant (Behavior t Builder) a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Behavior t Builder, v' a) -> Behavior t Builder
forall a b. (a, b) -> a
fst ((Behavior t Builder, v' a) -> Behavior t Builder)
-> (Compose ((,) (Behavior t Builder)) v' a
-> (Behavior t Builder, v' a))
-> Compose ((,) (Behavior t Builder)) v' a
-> Behavior t Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Compose ((,) (Behavior t Builder)) v' a
-> (Behavior t Builder, v' a)
forall k1 (f :: k1 -> *) k2 (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose
Incremental t (p k (Constant (Behavior t Builder)))
outputs <- PatchTarget (p k (Constant (Behavior t Builder)))
-> Event t (p k (Constant (Behavior t Builder)))
-> StaticDomBuilderT
t m (Incremental t (p k (Constant (Behavior t Builder))))
forall k (t :: k) (m :: * -> *) p.
(MonadHold t m, Patch p) =>
PatchTarget p -> Event t p -> m (Incremental t p)
holdIncremental DMap k (Constant (Behavior t Builder))
PatchTarget (p k (Constant (Behavior t Builder)))
outputs0 Event t (p k (Constant (Behavior t Builder)))
outputs'
ReaderT (StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) ()
-> StaticDomBuilderT t m ()
forall k (t :: k) (m :: * -> *) a.
ReaderT (StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) a
-> StaticDomBuilderT t m a
StaticDomBuilderT (ReaderT (StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) ()
-> StaticDomBuilderT t m ())
-> ReaderT
(StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) ()
-> StaticDomBuilderT t m ()
forall a b. (a -> b) -> a -> b
$ ([Behavior t Builder] -> [Behavior t Builder])
-> ReaderT
(StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (([Behavior t Builder] -> [Behavior t Builder])
-> ReaderT
(StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) ())
-> ([Behavior t Builder] -> [Behavior t Builder])
-> ReaderT
(StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) ()
forall a b. (a -> b) -> a -> b
$ (:) (Behavior t Builder
-> [Behavior t Builder] -> [Behavior t Builder])
-> Behavior t Builder
-> [Behavior t Builder]
-> [Behavior t Builder]
forall a b. (a -> b) -> a -> b
$ PullM t Builder -> Behavior t Builder
forall k (t :: k) a. Reflex t => PullM t a -> Behavior t a
pull (PullM t Builder -> Behavior t Builder)
-> PullM t Builder -> Behavior t Builder
forall a b. (a -> b) -> a -> b
$ do
DMap k (Constant (Behavior t Builder))
os <- Behavior t (DMap k (Constant (Behavior t Builder)))
-> PullM t (DMap k (Constant (Behavior t Builder)))
forall k (t :: k) (m :: * -> *) a.
MonadSample t m =>
Behavior t a -> m a
sample (Behavior t (DMap k (Constant (Behavior t Builder)))
-> PullM t (DMap k (Constant (Behavior t Builder))))
-> Behavior t (DMap k (Constant (Behavior t Builder)))
-> PullM t (DMap k (Constant (Behavior t Builder)))
forall a b. (a -> b) -> a -> b
$ Incremental t (p k (Constant (Behavior t Builder)))
-> Behavior t (PatchTarget (p k (Constant (Behavior t Builder))))
forall k (t :: k) p.
(Reflex t, Patch p) =>
Incremental t p -> Behavior t (PatchTarget p)
currentIncremental Incremental t (p k (Constant (Behavior t Builder)))
outputs
([Builder] -> Builder) -> PullM t [Builder] -> PullM t Builder
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Builder] -> Builder
forall a. Monoid a => [a] -> a
mconcat (PullM t [Builder] -> PullM t Builder)
-> PullM t [Builder] -> PullM t Builder
forall a b. (a -> b) -> a -> b
$ [DSum k (Constant (Behavior t Builder))]
-> (DSum k (Constant (Behavior t Builder)) -> PullM t Builder)
-> PullM t [Builder]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM (DMap k (Constant (Behavior t Builder))
-> [DSum k (Constant (Behavior t Builder))]
forall k1 (k2 :: k1 -> *) (f :: k1 -> *). DMap k2 f -> [DSum k2 f]
DMap.toList DMap k (Constant (Behavior t Builder))
os) ((DSum k (Constant (Behavior t Builder)) -> PullM t Builder)
-> PullM t [Builder])
-> (DSum k (Constant (Behavior t Builder)) -> PullM t Builder)
-> PullM t [Builder]
forall a b. (a -> b) -> a -> b
$ \(_ :=> Constant o) -> do
Behavior t Builder -> PullM t Builder
forall k (t :: k) (m :: * -> *) a.
MonadSample t m =>
Behavior t a -> m a
sample Behavior t Builder
o
(DMap k v', Event t (p k v'))
-> StaticDomBuilderT t m (DMap k v', Event t (p k v'))
forall (m :: * -> *) a. Monad m => a -> m a
return (DMap k v'
result0, Event t (p k v')
result')
instance SupportsStaticDomBuilder t m => NotReady t (StaticDomBuilderT t m) where
notReadyUntil :: Event t a -> StaticDomBuilderT t m ()
notReadyUntil _ = () -> StaticDomBuilderT t m ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
notReady :: StaticDomBuilderT t m ()
notReady = () -> StaticDomBuilderT t m ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
instance SupportsStaticDomBuilder t m => DomBuilder t (StaticDomBuilderT t m) where
type DomBuilderSpace (StaticDomBuilderT t m) = StaticDomSpace
{-# INLINABLE textNode #-}
textNode :: TextNodeConfig t
-> StaticDomBuilderT
t m (TextNode (DomBuilderSpace (StaticDomBuilderT t m)) t)
textNode (TextNodeConfig initialContents :: Text
initialContents mSetContents :: Maybe (Event t Text)
mSetContents) = ReaderT
(StaticDomBuilderEnv t)
(StateT [Behavior t Builder] m)
(TextNode StaticDomSpace t)
-> StaticDomBuilderT
t m (TextNode (DomBuilderSpace (StaticDomBuilderT t m)) t)
forall k (t :: k) (m :: * -> *) a.
ReaderT (StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) a
-> StaticDomBuilderT t m a
StaticDomBuilderT (ReaderT
(StaticDomBuilderEnv t)
(StateT [Behavior t Builder] m)
(TextNode StaticDomSpace t)
-> StaticDomBuilderT
t m (TextNode (DomBuilderSpace (StaticDomBuilderT t m)) t))
-> ReaderT
(StaticDomBuilderEnv t)
(StateT [Behavior t Builder] m)
(TextNode StaticDomSpace t)
-> StaticDomBuilderT
t m (TextNode (DomBuilderSpace (StaticDomBuilderT t m)) t)
forall a b. (a -> b) -> a -> b
$ do
Bool
shouldEscape <- (StaticDomBuilderEnv t -> Bool)
-> ReaderT
(StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) Bool
forall (m :: * -> *) r a. Monad m => (r -> a) -> ReaderT r m a
asks StaticDomBuilderEnv t -> Bool
forall k (t :: k). StaticDomBuilderEnv t -> Bool
_staticDomBuilderEnv_shouldEscape
let escape :: Text -> Builder
escape = if Bool
shouldEscape then Text -> Builder
fromHtmlEscapedText else ByteString -> Builder
byteString (ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
encodeUtf8
([Behavior t Builder] -> [Behavior t Builder])
-> ReaderT
(StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (([Behavior t Builder] -> [Behavior t Builder])
-> ReaderT
(StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) ())
-> (Behavior t Builder
-> [Behavior t Builder] -> [Behavior t Builder])
-> Behavior t Builder
-> ReaderT
(StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (:) (Behavior t Builder
-> ReaderT
(StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) ())
-> ReaderT
(StaticDomBuilderEnv t)
(StateT [Behavior t Builder] m)
(Behavior t Builder)
-> ReaderT
(StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< case Maybe (Event t Text)
mSetContents of
Nothing -> Behavior t Builder
-> ReaderT
(StaticDomBuilderEnv t)
(StateT [Behavior t Builder] m)
(Behavior t Builder)
forall (m :: * -> *) a. Monad m => a -> m a
return (Builder -> Behavior t Builder
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> Builder
escape Text
initialContents))
Just setContents :: Event t Text
setContents -> Builder
-> Event t Builder
-> ReaderT
(StaticDomBuilderEnv t)
(StateT [Behavior t Builder] m)
(Behavior t Builder)
forall k (t :: k) (m :: * -> *) a.
MonadHold t m =>
a -> Event t a -> m (Behavior t a)
hold (Text -> Builder
escape Text
initialContents) (Event t Builder
-> ReaderT
(StaticDomBuilderEnv t)
(StateT [Behavior t Builder] m)
(Behavior t Builder))
-> Event t Builder
-> ReaderT
(StaticDomBuilderEnv t)
(StateT [Behavior t Builder] m)
(Behavior t Builder)
forall a b. (a -> b) -> a -> b
$ (Text -> Builder) -> Event t Text -> Event t Builder
forall k (t :: k) a b.
Reflex t =>
(a -> b) -> Event t a -> Event t b
fmapCheap Text -> Builder
escape Event t Text
setContents
TextNode StaticDomSpace t
-> ReaderT
(StaticDomBuilderEnv t)
(StateT [Behavior t Builder] m)
(TextNode StaticDomSpace t)
forall (m :: * -> *) a. Monad m => a -> m a
return (TextNode StaticDomSpace t
-> ReaderT
(StaticDomBuilderEnv t)
(StateT [Behavior t Builder] m)
(TextNode StaticDomSpace t))
-> TextNode StaticDomSpace t
-> ReaderT
(StaticDomBuilderEnv t)
(StateT [Behavior t Builder] m)
(TextNode StaticDomSpace t)
forall a b. (a -> b) -> a -> b
$ RawTextNode StaticDomSpace -> TextNode StaticDomSpace t
forall k k (d :: k) (t :: k). RawTextNode d -> TextNode d t
TextNode ()
{-# INLINABLE commentNode #-}
commentNode :: CommentNodeConfig t
-> StaticDomBuilderT
t m (CommentNode (DomBuilderSpace (StaticDomBuilderT t m)) t)
commentNode (CommentNodeConfig initialContents :: Text
initialContents mSetContents :: Maybe (Event t Text)
mSetContents) = ReaderT
(StaticDomBuilderEnv t)
(StateT [Behavior t Builder] m)
(CommentNode StaticDomSpace t)
-> StaticDomBuilderT
t m (CommentNode (DomBuilderSpace (StaticDomBuilderT t m)) t)
forall k (t :: k) (m :: * -> *) a.
ReaderT (StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) a
-> StaticDomBuilderT t m a
StaticDomBuilderT (ReaderT
(StaticDomBuilderEnv t)
(StateT [Behavior t Builder] m)
(CommentNode StaticDomSpace t)
-> StaticDomBuilderT
t m (CommentNode (DomBuilderSpace (StaticDomBuilderT t m)) t))
-> ReaderT
(StaticDomBuilderEnv t)
(StateT [Behavior t Builder] m)
(CommentNode StaticDomSpace t)
-> StaticDomBuilderT
t m (CommentNode (DomBuilderSpace (StaticDomBuilderT t m)) t)
forall a b. (a -> b) -> a -> b
$ do
Bool
shouldEscape <- (StaticDomBuilderEnv t -> Bool)
-> ReaderT
(StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) Bool
forall (m :: * -> *) r a. Monad m => (r -> a) -> ReaderT r m a
asks StaticDomBuilderEnv t -> Bool
forall k (t :: k). StaticDomBuilderEnv t -> Bool
_staticDomBuilderEnv_shouldEscape
let escape :: Text -> Builder
escape = if Bool
shouldEscape then Text -> Builder
fromHtmlEscapedText else ByteString -> Builder
byteString (ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
encodeUtf8
([Behavior t Builder] -> [Behavior t Builder])
-> ReaderT
(StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (([Behavior t Builder] -> [Behavior t Builder])
-> ReaderT
(StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) ())
-> (Behavior t Builder
-> [Behavior t Builder] -> [Behavior t Builder])
-> Behavior t Builder
-> ReaderT
(StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (:) (Behavior t Builder
-> ReaderT
(StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) ())
-> ReaderT
(StaticDomBuilderEnv t)
(StateT [Behavior t Builder] m)
(Behavior t Builder)
-> ReaderT
(StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< (\c :: Behavior t Builder
c -> "<!--" Behavior t Builder -> Behavior t Builder -> Behavior t Builder
forall a. Semigroup a => a -> a -> a
<> Behavior t Builder
c Behavior t Builder -> Behavior t Builder -> Behavior t Builder
forall a. Semigroup a => a -> a -> a
<> "-->") (Behavior t Builder -> Behavior t Builder)
-> ReaderT
(StaticDomBuilderEnv t)
(StateT [Behavior t Builder] m)
(Behavior t Builder)
-> ReaderT
(StaticDomBuilderEnv t)
(StateT [Behavior t Builder] m)
(Behavior t Builder)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> case Maybe (Event t Text)
mSetContents of
Nothing -> Behavior t Builder
-> ReaderT
(StaticDomBuilderEnv t)
(StateT [Behavior t Builder] m)
(Behavior t Builder)
forall (m :: * -> *) a. Monad m => a -> m a
return (Builder -> Behavior t Builder
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> Builder
escape Text
initialContents))
Just setContents :: Event t Text
setContents -> Builder
-> Event t Builder
-> ReaderT
(StaticDomBuilderEnv t)
(StateT [Behavior t Builder] m)
(Behavior t Builder)
forall k (t :: k) (m :: * -> *) a.
MonadHold t m =>
a -> Event t a -> m (Behavior t a)
hold (Text -> Builder
escape Text
initialContents) (Event t Builder
-> ReaderT
(StaticDomBuilderEnv t)
(StateT [Behavior t Builder] m)
(Behavior t Builder))
-> Event t Builder
-> ReaderT
(StaticDomBuilderEnv t)
(StateT [Behavior t Builder] m)
(Behavior t Builder)
forall a b. (a -> b) -> a -> b
$ (Text -> Builder) -> Event t Text -> Event t Builder
forall k (t :: k) a b.
Reflex t =>
(a -> b) -> Event t a -> Event t b
fmapCheap Text -> Builder
escape Event t Text
setContents
CommentNode StaticDomSpace t
-> ReaderT
(StaticDomBuilderEnv t)
(StateT [Behavior t Builder] m)
(CommentNode StaticDomSpace t)
forall (m :: * -> *) a. Monad m => a -> m a
return (CommentNode StaticDomSpace t
-> ReaderT
(StaticDomBuilderEnv t)
(StateT [Behavior t Builder] m)
(CommentNode StaticDomSpace t))
-> CommentNode StaticDomSpace t
-> ReaderT
(StaticDomBuilderEnv t)
(StateT [Behavior t Builder] m)
(CommentNode StaticDomSpace t)
forall a b. (a -> b) -> a -> b
$ RawCommentNode StaticDomSpace -> CommentNode StaticDomSpace t
forall k k (d :: k) (t :: k). RawCommentNode d -> CommentNode d t
CommentNode ()
{-# INLINABLE element #-}
element :: Text
-> ElementConfig er t (DomBuilderSpace (StaticDomBuilderT t m))
-> StaticDomBuilderT t m a
-> StaticDomBuilderT
t m (Element er (DomBuilderSpace (StaticDomBuilderT t m)) t, a)
element elementTag :: Text
elementTag cfg :: ElementConfig er t (DomBuilderSpace (StaticDomBuilderT t m))
cfg child :: StaticDomBuilderT t m a
child = do
let voidElements :: Set Text
voidElements = [Text] -> Set Text
forall a. Ord a => [a] -> Set a
Set.fromList ["area", "base", "br", "col", "command", "embed", "hr", "img", "input", "keygen", "link", "meta", "param", "source", "track", "wbr"]
let noEscapeElements :: Set Text
noEscapeElements = [Text] -> Set Text
forall a. Ord a => [a] -> Set a
Set.fromList ["style", "script"]
let toAttr :: AttributeName -> Text -> Builder
toAttr (AttributeName _mns :: Maybe Text
_mns k :: Text
k) v :: Text
v = ByteString -> Builder
byteString (Text -> ByteString
encodeUtf8 Text
k) Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> ByteString -> Builder
byteString "=\"" Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Text -> Builder
fromHtmlEscapedText Text
v Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> ByteString -> Builder
byteString "\""
EventSelector t (WrapArg er EventName)
es <- (forall a.
WrapArg er EventName a -> EventTrigger t a -> IO (IO ()))
-> StaticDomBuilderT t m (EventSelector t (WrapArg er EventName))
forall t (m :: * -> *) (k :: * -> *).
(MonadReflexCreateTrigger t m, GCompare k) =>
(forall a. k a -> EventTrigger t a -> IO (IO ()))
-> m (EventSelector t k)
newFanEventWithTrigger ((forall a.
WrapArg er EventName a -> EventTrigger t a -> IO (IO ()))
-> StaticDomBuilderT t m (EventSelector t (WrapArg er EventName)))
-> (forall a.
WrapArg er EventName a -> EventTrigger t a -> IO (IO ()))
-> StaticDomBuilderT t m (EventSelector t (WrapArg er EventName))
forall a b. (a -> b) -> a -> b
$ \_ _ -> IO () -> IO (IO ())
forall (m :: * -> *) a. Monad m => a -> m a
return (() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ())
ReaderT
(StaticDomBuilderEnv t)
(StateT [Behavior t Builder] m)
(Element er StaticDomSpace t, a)
-> StaticDomBuilderT t m (Element er StaticDomSpace t, a)
forall k (t :: k) (m :: * -> *) a.
ReaderT (StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) a
-> StaticDomBuilderT t m a
StaticDomBuilderT (ReaderT
(StaticDomBuilderEnv t)
(StateT [Behavior t Builder] m)
(Element er StaticDomSpace t, a)
-> StaticDomBuilderT t m (Element er StaticDomSpace t, a))
-> ReaderT
(StaticDomBuilderEnv t)
(StateT [Behavior t Builder] m)
(Element er StaticDomSpace t, a)
-> StaticDomBuilderT t m (Element er StaticDomSpace t, a)
forall a b. (a -> b) -> a -> b
$ do
let shouldEscape :: Bool
shouldEscape = Text
elementTag Text -> Set Text -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.notMember` Set Text
noEscapeElements
IORef Int
nextRunWithReplaceKey <- (StaticDomBuilderEnv t -> IORef Int)
-> ReaderT
(StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) (IORef Int)
forall (m :: * -> *) r a. Monad m => (r -> a) -> ReaderT r m a
asks StaticDomBuilderEnv t -> IORef Int
forall k (t :: k). StaticDomBuilderEnv t -> IORef Int
_staticDomBuilderEnv_nextRunWithReplaceKey
(result :: a
result, innerHtml :: Behavior t Builder
innerHtml) <- StateT [Behavior t Builder] m (a, Behavior t Builder)
-> ReaderT
(StaticDomBuilderEnv t)
(StateT [Behavior t Builder] m)
(a, Behavior t Builder)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (StateT [Behavior t Builder] m (a, Behavior t Builder)
-> ReaderT
(StaticDomBuilderEnv t)
(StateT [Behavior t Builder] m)
(a, Behavior t Builder))
-> StateT [Behavior t Builder] m (a, Behavior t Builder)
-> ReaderT
(StaticDomBuilderEnv t)
(StateT [Behavior t Builder] m)
(a, Behavior t Builder)
forall a b. (a -> b) -> a -> b
$ m (a, Behavior t Builder)
-> StateT [Behavior t Builder] m (a, Behavior t Builder)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (a, Behavior t Builder)
-> StateT [Behavior t Builder] m (a, Behavior t Builder))
-> m (a, Behavior t Builder)
-> StateT [Behavior t Builder] m (a, Behavior t Builder)
forall a b. (a -> b) -> a -> b
$ StaticDomBuilderT t m a
-> StaticDomBuilderEnv t -> m (a, Behavior t Builder)
forall k (m :: * -> *) (t :: k) a.
(Monad m, Reflex t) =>
StaticDomBuilderT t m a
-> StaticDomBuilderEnv t -> m (a, Behavior t Builder)
runStaticDomBuilderT StaticDomBuilderT t m a
child (StaticDomBuilderEnv t -> m (a, Behavior t Builder))
-> StaticDomBuilderEnv t -> m (a, Behavior t Builder)
forall a b. (a -> b) -> a -> b
$ Bool
-> Maybe (Behavior t Text) -> IORef Int -> StaticDomBuilderEnv t
forall k (t :: k).
Bool
-> Maybe (Behavior t Text) -> IORef Int -> StaticDomBuilderEnv t
StaticDomBuilderEnv Bool
shouldEscape Maybe (Behavior t Text)
forall a. Maybe a
Nothing IORef Int
nextRunWithReplaceKey
Dynamic t (Map AttributeName Text)
attrs0 <- (Map AttributeName (Maybe Text)
-> Map AttributeName Text -> Map AttributeName Text)
-> Map AttributeName Text
-> Event t (Map AttributeName (Maybe Text))
-> ReaderT
(StaticDomBuilderEnv t)
(StateT [Behavior t Builder] m)
(Dynamic t (Map AttributeName Text))
forall k (t :: k) (m :: * -> *) a b.
(Reflex t, MonadHold t m, MonadFix m) =>
(a -> b -> b) -> b -> Event t a -> m (Dynamic t b)
foldDyn Map AttributeName (Maybe Text)
-> Map AttributeName Text -> Map AttributeName Text
forall k v. Ord k => Map k (Maybe v) -> Map k v -> Map k v
applyMap (ElementConfig er t (DomBuilderSpace (StaticDomBuilderT t m))
ElementConfig er t StaticDomSpace
cfg ElementConfig er t StaticDomSpace
-> Getting
(Map AttributeName Text)
(ElementConfig er t StaticDomSpace)
(Map AttributeName Text)
-> Map AttributeName Text
forall s a. s -> Getting a s a -> a
^. Getting
(Map AttributeName Text)
(ElementConfig er t StaticDomSpace)
(Map AttributeName Text)
forall a. InitialAttributes a => Lens' a (Map AttributeName Text)
initialAttributes) (ElementConfig er t (DomBuilderSpace (StaticDomBuilderT t m))
ElementConfig er t StaticDomSpace
cfg ElementConfig er t StaticDomSpace
-> Getting
(Event t (Map AttributeName (Maybe Text)))
(ElementConfig er t StaticDomSpace)
(Event t (Map AttributeName (Maybe Text)))
-> Event t (Map AttributeName (Maybe Text))
forall s a. s -> Getting a s a -> a
^. Getting
(Event t (Map AttributeName (Maybe Text)))
(ElementConfig er t StaticDomSpace)
(Event t (Map AttributeName (Maybe Text)))
forall k (t :: k) a.
(ModifyAttributes t a, Reflex t) =>
Lens' a (Event t (Map AttributeName (Maybe Text)))
modifyAttributes)
Maybe (Behavior t Text)
selectValue <- (StaticDomBuilderEnv t -> Maybe (Behavior t Text))
-> ReaderT
(StaticDomBuilderEnv t)
(StateT [Behavior t Builder] m)
(Maybe (Behavior t Text))
forall (m :: * -> *) r a. Monad m => (r -> a) -> ReaderT r m a
asks StaticDomBuilderEnv t -> Maybe (Behavior t Text)
forall k (t :: k). StaticDomBuilderEnv t -> Maybe (Behavior t Text)
_staticDomBuilderEnv_selectValue
let addSelectedAttr :: Map k a -> a -> Map k a
addSelectedAttr attrs :: Map k a
attrs sel :: a
sel = case k -> Map k a -> Maybe a
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup "value" Map k a
attrs of
Just v :: a
v | a
v a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
sel -> Map k a
attrs Map k a -> Map k a -> Map k a
forall a. Semigroup a => a -> a -> a
<> k -> a -> Map k a
forall k a. k -> a -> Map k a
Map.singleton "selected" ""
_ -> k -> Map k a -> Map k a
forall k a. Ord k => k -> Map k a -> Map k a
Map.delete "selected" Map k a
attrs
let attrs1 :: Behavior t (Map AttributeName Text)
attrs1 = case (Text
elementTag, Maybe (Behavior t Text)
selectValue) of
("option", Just sv :: Behavior t Text
sv) -> PullM t (Map AttributeName Text)
-> Behavior t (Map AttributeName Text)
forall k (t :: k) a. Reflex t => PullM t a -> Behavior t a
pull (PullM t (Map AttributeName Text)
-> Behavior t (Map AttributeName Text))
-> PullM t (Map AttributeName Text)
-> Behavior t (Map AttributeName Text)
forall a b. (a -> b) -> a -> b
$ Map AttributeName Text -> Text -> Map AttributeName Text
forall k a.
(Ord k, IsString k, IsString a, Eq a) =>
Map k a -> a -> Map k a
addSelectedAttr (Map AttributeName Text -> Text -> Map AttributeName Text)
-> PullM t (Map AttributeName Text)
-> PullM t (Text -> Map AttributeName Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Behavior t (Map AttributeName Text)
-> PullM t (Map AttributeName Text)
forall k (t :: k) (m :: * -> *) a.
MonadSample t m =>
Behavior t a -> m a
sample (Dynamic t (Map AttributeName Text)
-> Behavior t (Map AttributeName Text)
forall k (t :: k) a. Reflex t => Dynamic t a -> Behavior t a
current Dynamic t (Map AttributeName Text)
attrs0) PullM t (Text -> Map AttributeName Text)
-> PullM t Text -> PullM t (Map AttributeName Text)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Behavior t Text -> PullM t Text
forall k (t :: k) (m :: * -> *) a.
MonadSample t m =>
Behavior t a -> m a
sample Behavior t Text
sv
_ -> Dynamic t (Map AttributeName Text)
-> Behavior t (Map AttributeName Text)
forall k (t :: k) a. Reflex t => Dynamic t a -> Behavior t a
current Dynamic t (Map AttributeName Text)
attrs0
let attrs2 :: Behavior t Builder
attrs2 = Behavior t (Map AttributeName Text)
-> (Map AttributeName Text -> Builder) -> Behavior t Builder
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
ffor Behavior t (Map AttributeName Text)
attrs1 ((Map AttributeName Text -> Builder) -> Behavior t Builder)
-> (Map AttributeName Text -> Builder) -> Behavior t Builder
forall a b. (a -> b) -> a -> b
$ [Builder] -> Builder
forall a. Monoid a => [a] -> a
mconcat ([Builder] -> Builder)
-> (Map AttributeName Text -> [Builder])
-> Map AttributeName Text
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((AttributeName, Text) -> Builder)
-> [(AttributeName, Text)] -> [Builder]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(k :: AttributeName
k, v :: Text
v) -> " " Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> AttributeName -> Text -> Builder
toAttr AttributeName
k Text
v) ([(AttributeName, Text)] -> [Builder])
-> (Map AttributeName Text -> [(AttributeName, Text)])
-> Map AttributeName Text
-> [Builder]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Map AttributeName Text -> [(AttributeName, Text)]
forall k a. Map k a -> [(k, a)]
Map.toList
let tagBS :: ByteString
tagBS = Text -> ByteString
encodeUtf8 Text
elementTag
if Text -> Set Text -> Bool
forall a. Ord a => a -> Set a -> Bool
Set.member Text
elementTag Set Text
voidElements
then ([Behavior t Builder] -> [Behavior t Builder])
-> ReaderT
(StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (([Behavior t Builder] -> [Behavior t Builder])
-> ReaderT
(StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) ())
-> ([Behavior t Builder] -> [Behavior t Builder])
-> ReaderT
(StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) ()
forall a b. (a -> b) -> a -> b
$ (:) (Behavior t Builder
-> [Behavior t Builder] -> [Behavior t Builder])
-> Behavior t Builder
-> [Behavior t Builder]
-> [Behavior t Builder]
forall a b. (a -> b) -> a -> b
$ [Behavior t Builder] -> Behavior t Builder
forall a. Monoid a => [a] -> a
mconcat [Builder -> Behavior t Builder
forall k (t :: k) a. Reflex t => a -> Behavior t a
constant ("<" Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> ByteString -> Builder
byteString ByteString
tagBS), Behavior t Builder
attrs2, Builder -> Behavior t Builder
forall k (t :: k) a. Reflex t => a -> Behavior t a
constant (ByteString -> Builder
byteString " />")]
else do
let open :: Behavior t Builder
open = [Behavior t Builder] -> Behavior t Builder
forall a. Monoid a => [a] -> a
mconcat [Builder -> Behavior t Builder
forall k (t :: k) a. Reflex t => a -> Behavior t a
constant ("<" Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> ByteString -> Builder
byteString ByteString
tagBS), Behavior t Builder
attrs2, Builder -> Behavior t Builder
forall k (t :: k) a. Reflex t => a -> Behavior t a
constant (ByteString -> Builder
byteString ">")]
let close :: Behavior t Builder
close = Builder -> Behavior t Builder
forall k (t :: k) a. Reflex t => a -> Behavior t a
constant (Builder -> Behavior t Builder) -> Builder -> Behavior t Builder
forall a b. (a -> b) -> a -> b
$ ByteString -> Builder
byteString (ByteString -> Builder) -> ByteString -> Builder
forall a b. (a -> b) -> a -> b
$ "</" ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
tagBS ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ">"
([Behavior t Builder] -> [Behavior t Builder])
-> ReaderT
(StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (([Behavior t Builder] -> [Behavior t Builder])
-> ReaderT
(StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) ())
-> ([Behavior t Builder] -> [Behavior t Builder])
-> ReaderT
(StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) ()
forall a b. (a -> b) -> a -> b
$ (:) (Behavior t Builder
-> [Behavior t Builder] -> [Behavior t Builder])
-> Behavior t Builder
-> [Behavior t Builder]
-> [Behavior t Builder]
forall a b. (a -> b) -> a -> b
$ [Behavior t Builder] -> Behavior t Builder
forall a. Monoid a => [a] -> a
mconcat [Behavior t Builder
open, Behavior t Builder
innerHtml, Behavior t Builder
close]
let e :: Element er StaticDomSpace t
e = Element :: forall k k (er :: EventTag -> *) (d :: k) (t :: k).
EventSelector t (WrapArg er EventName)
-> RawElement d -> Element er d t
Element
{ _element_events :: EventSelector t (WrapArg er EventName)
_element_events = EventSelector t (WrapArg er EventName)
es
, _element_raw :: RawElement StaticDomSpace
_element_raw = ()
}
(Element er StaticDomSpace t, a)
-> ReaderT
(StaticDomBuilderEnv t)
(StateT [Behavior t Builder] m)
(Element er StaticDomSpace t, a)
forall (m :: * -> *) a. Monad m => a -> m a
return (Element er StaticDomSpace t
e, a
result)
{-# INLINABLE inputElement #-}
inputElement :: InputElementConfig er t (DomBuilderSpace (StaticDomBuilderT t m))
-> StaticDomBuilderT
t m (InputElement er (DomBuilderSpace (StaticDomBuilderT t m)) t)
inputElement cfg :: InputElementConfig er t (DomBuilderSpace (StaticDomBuilderT t m))
cfg = do
(e :: Element er StaticDomSpace t
e, _result :: ()
_result) <- Text
-> ElementConfig er t (DomBuilderSpace (StaticDomBuilderT t m))
-> StaticDomBuilderT t m ()
-> StaticDomBuilderT
t m (Element er (DomBuilderSpace (StaticDomBuilderT t m)) t, ())
forall t (m :: * -> *) (er :: EventTag -> *) a.
DomBuilder t m =>
Text
-> ElementConfig er t (DomBuilderSpace m)
-> m a
-> m (Element er (DomBuilderSpace m) t, a)
element "input" (InputElementConfig er t (DomBuilderSpace (StaticDomBuilderT t m))
InputElementConfig er t StaticDomSpace
cfg InputElementConfig er t StaticDomSpace
-> Getting
(ElementConfig er t StaticDomSpace)
(InputElementConfig er t StaticDomSpace)
(ElementConfig er t StaticDomSpace)
-> ElementConfig er t StaticDomSpace
forall s a. s -> Getting a s a -> a
^. Getting
(ElementConfig er t StaticDomSpace)
(InputElementConfig er t StaticDomSpace)
(ElementConfig er t StaticDomSpace)
forall k1 k2 k3 (er1 :: EventTag -> *) (t :: k1) (s1 :: k2)
(er2 :: EventTag -> *) (s2 :: k3).
Lens
(InputElementConfig er1 t s1)
(InputElementConfig er2 t s2)
(ElementConfig er1 t s1)
(ElementConfig er2 t s2)
inputElementConfig_elementConfig) (StaticDomBuilderT t m ()
-> StaticDomBuilderT t m (Element er StaticDomSpace t, ()))
-> StaticDomBuilderT t m ()
-> StaticDomBuilderT t m (Element er StaticDomSpace t, ())
forall a b. (a -> b) -> a -> b
$ () -> StaticDomBuilderT t m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
let v0 :: Dynamic t Text
v0 = Text -> Dynamic t Text
forall k (t :: k) a. Reflex t => a -> Dynamic t a
constDyn (Text -> Dynamic t Text) -> Text -> Dynamic t Text
forall a b. (a -> b) -> a -> b
$ InputElementConfig er t (DomBuilderSpace (StaticDomBuilderT t m))
InputElementConfig er t StaticDomSpace
cfg InputElementConfig er t StaticDomSpace
-> Getting Text (InputElementConfig er t StaticDomSpace) Text
-> Text
forall s a. s -> Getting a s a -> a
^. Getting Text (InputElementConfig er t StaticDomSpace) Text
forall k1 k2 (er1 :: EventTag -> *) (t :: k1) (s1 :: k2).
Lens' (InputElementConfig er1 t s1) Text
inputElementConfig_initialValue
let c0 :: Dynamic t Bool
c0 = Bool -> Dynamic t Bool
forall k (t :: k) a. Reflex t => a -> Dynamic t a
constDyn (Bool -> Dynamic t Bool) -> Bool -> Dynamic t Bool
forall a b. (a -> b) -> a -> b
$ InputElementConfig er t (DomBuilderSpace (StaticDomBuilderT t m))
InputElementConfig er t StaticDomSpace
cfg InputElementConfig er t StaticDomSpace
-> Getting Bool (InputElementConfig er t StaticDomSpace) Bool
-> Bool
forall s a. s -> Getting a s a -> a
^. Getting Bool (InputElementConfig er t StaticDomSpace) Bool
forall k1 k2 (er1 :: EventTag -> *) (t :: k1) (s1 :: k2).
Lens' (InputElementConfig er1 t s1) Bool
inputElementConfig_initialChecked
let hasFocus :: Dynamic t Bool
hasFocus = Bool -> Dynamic t Bool
forall k (t :: k) a. Reflex t => a -> Dynamic t a
constDyn Bool
False
InputElement er StaticDomSpace t
-> StaticDomBuilderT t m (InputElement er StaticDomSpace t)
forall (m :: * -> *) a. Monad m => a -> m a
return (InputElement er StaticDomSpace t
-> StaticDomBuilderT t m (InputElement er StaticDomSpace t))
-> InputElement er StaticDomSpace t
-> StaticDomBuilderT t m (InputElement er StaticDomSpace t)
forall a b. (a -> b) -> a -> b
$ InputElement :: forall k k (er :: EventTag -> *) (d :: k) (t :: k).
Dynamic t Text
-> Dynamic t Bool
-> Event t Bool
-> Event t Text
-> Dynamic t Bool
-> Element er d t
-> RawInputElement d
-> Dynamic t [File]
-> InputElement er d t
InputElement
{ _inputElement_value :: Dynamic t Text
_inputElement_value = Dynamic t Text
v0
, _inputElement_checked :: Dynamic t Bool
_inputElement_checked = Dynamic t Bool
c0
, _inputElement_checkedChange :: Event t Bool
_inputElement_checkedChange = Event t Bool
forall k (t :: k) a. Reflex t => Event t a
never
, _inputElement_input :: Event t Text
_inputElement_input = Event t Text
forall k (t :: k) a. Reflex t => Event t a
never
, _inputElement_hasFocus :: Dynamic t Bool
_inputElement_hasFocus = Dynamic t Bool
hasFocus
, _inputElement_element :: Element er StaticDomSpace t
_inputElement_element = Element er StaticDomSpace t
e
, _inputElement_raw :: RawInputElement StaticDomSpace
_inputElement_raw = ()
, _inputElement_files :: Dynamic t [File]
_inputElement_files = [File] -> Dynamic t [File]
forall k (t :: k) a. Reflex t => a -> Dynamic t a
constDyn [File]
forall a. Monoid a => a
mempty
}
{-# INLINABLE textAreaElement #-}
textAreaElement :: TextAreaElementConfig
er t (DomBuilderSpace (StaticDomBuilderT t m))
-> StaticDomBuilderT
t
m
(TextAreaElement er (DomBuilderSpace (StaticDomBuilderT t m)) t)
textAreaElement cfg :: TextAreaElementConfig
er t (DomBuilderSpace (StaticDomBuilderT t m))
cfg = do
(e :: Element er StaticDomSpace t
e, _domElement :: ()
_domElement) <- Text
-> ElementConfig er t (DomBuilderSpace (StaticDomBuilderT t m))
-> StaticDomBuilderT t m ()
-> StaticDomBuilderT
t m (Element er (DomBuilderSpace (StaticDomBuilderT t m)) t, ())
forall t (m :: * -> *) (er :: EventTag -> *) a.
DomBuilder t m =>
Text
-> ElementConfig er t (DomBuilderSpace m)
-> m a
-> m (Element er (DomBuilderSpace m) t, a)
element "textarea" (TextAreaElementConfig
er t (DomBuilderSpace (StaticDomBuilderT t m))
TextAreaElementConfig er t StaticDomSpace
cfg TextAreaElementConfig er t StaticDomSpace
-> Getting
(ElementConfig er t StaticDomSpace)
(TextAreaElementConfig er t StaticDomSpace)
(ElementConfig er t StaticDomSpace)
-> ElementConfig er t StaticDomSpace
forall s a. s -> Getting a s a -> a
^. Getting
(ElementConfig er t StaticDomSpace)
(TextAreaElementConfig er t StaticDomSpace)
(ElementConfig er t StaticDomSpace)
forall k1 k2 k3 (er1 :: EventTag -> *) (t :: k1) (m1 :: k2)
(er2 :: EventTag -> *) (m2 :: k3).
Lens
(TextAreaElementConfig er1 t m1)
(TextAreaElementConfig er2 t m2)
(ElementConfig er1 t m1)
(ElementConfig er2 t m2)
textAreaElementConfig_elementConfig) (StaticDomBuilderT t m ()
-> StaticDomBuilderT t m (Element er StaticDomSpace t, ()))
-> StaticDomBuilderT t m ()
-> StaticDomBuilderT t m (Element er StaticDomSpace t, ())
forall a b. (a -> b) -> a -> b
$ () -> StaticDomBuilderT t m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
let v0 :: Dynamic t Text
v0 = Text -> Dynamic t Text
forall k (t :: k) a. Reflex t => a -> Dynamic t a
constDyn (Text -> Dynamic t Text) -> Text -> Dynamic t Text
forall a b. (a -> b) -> a -> b
$ TextAreaElementConfig
er t (DomBuilderSpace (StaticDomBuilderT t m))
TextAreaElementConfig er t StaticDomSpace
cfg TextAreaElementConfig er t StaticDomSpace
-> Getting Text (TextAreaElementConfig er t StaticDomSpace) Text
-> Text
forall s a. s -> Getting a s a -> a
^. Getting Text (TextAreaElementConfig er t StaticDomSpace) Text
forall k1 k2 (er1 :: EventTag -> *) (t :: k1) (m1 :: k2).
Lens' (TextAreaElementConfig er1 t m1) Text
textAreaElementConfig_initialValue
let hasFocus :: Dynamic t Bool
hasFocus = Bool -> Dynamic t Bool
forall k (t :: k) a. Reflex t => a -> Dynamic t a
constDyn Bool
False
TextAreaElement er StaticDomSpace t
-> StaticDomBuilderT t m (TextAreaElement er StaticDomSpace t)
forall (m :: * -> *) a. Monad m => a -> m a
return (TextAreaElement er StaticDomSpace t
-> StaticDomBuilderT t m (TextAreaElement er StaticDomSpace t))
-> TextAreaElement er StaticDomSpace t
-> StaticDomBuilderT t m (TextAreaElement er StaticDomSpace t)
forall a b. (a -> b) -> a -> b
$ TextAreaElement :: forall k k (er :: EventTag -> *) (d :: k) (t :: k).
Dynamic t Text
-> Event t Text
-> Dynamic t Bool
-> Element er d t
-> RawTextAreaElement d
-> TextAreaElement er d t
TextAreaElement
{ _textAreaElement_value :: Dynamic t Text
_textAreaElement_value = Dynamic t Text
v0
, _textAreaElement_input :: Event t Text
_textAreaElement_input = Event t Text
forall k (t :: k) a. Reflex t => Event t a
never
, _textAreaElement_hasFocus :: Dynamic t Bool
_textAreaElement_hasFocus = Dynamic t Bool
hasFocus
, _textAreaElement_element :: Element er StaticDomSpace t
_textAreaElement_element = Element er StaticDomSpace t
e
, _textAreaElement_raw :: RawTextAreaElement StaticDomSpace
_textAreaElement_raw = ()
}
selectElement :: SelectElementConfig er t (DomBuilderSpace (StaticDomBuilderT t m))
-> StaticDomBuilderT t m a
-> StaticDomBuilderT
t
m
(SelectElement er (DomBuilderSpace (StaticDomBuilderT t m)) t, a)
selectElement cfg :: SelectElementConfig er t (DomBuilderSpace (StaticDomBuilderT t m))
cfg child :: StaticDomBuilderT t m a
child = do
Dynamic t Text
v <- Text -> Event t Text -> StaticDomBuilderT t m (Dynamic t Text)
forall k (t :: k) (m :: * -> *) a.
MonadHold t m =>
a -> Event t a -> m (Dynamic t a)
holdDyn (SelectElementConfig er t (DomBuilderSpace (StaticDomBuilderT t m))
SelectElementConfig er t StaticDomSpace
cfg SelectElementConfig er t StaticDomSpace
-> Getting Text (SelectElementConfig er t StaticDomSpace) Text
-> Text
forall s a. s -> Getting a s a -> a
^. Getting Text (SelectElementConfig er t StaticDomSpace) Text
forall k1 k2 (er :: EventTag -> *) (t :: k1) (m :: k2).
Lens' (SelectElementConfig er t m) Text
selectElementConfig_initialValue) (SelectElementConfig er t (DomBuilderSpace (StaticDomBuilderT t m))
SelectElementConfig er t StaticDomSpace
cfg SelectElementConfig er t StaticDomSpace
-> Getting
(Event t Text)
(SelectElementConfig er t StaticDomSpace)
(Event t Text)
-> Event t Text
forall s a. s -> Getting a s a -> a
^. Getting
(Event t Text)
(SelectElementConfig er t StaticDomSpace)
(Event t Text)
forall k1 k2 (t :: k1) (er :: EventTag -> *) (m :: k2).
Reflex t =>
Lens' (SelectElementConfig er t m) (Event t Text)
selectElementConfig_setValue)
(e :: Element er StaticDomSpace t
e, result :: a
result) <- Text
-> ElementConfig er t (DomBuilderSpace (StaticDomBuilderT t m))
-> StaticDomBuilderT t m a
-> StaticDomBuilderT
t m (Element er (DomBuilderSpace (StaticDomBuilderT t m)) t, a)
forall t (m :: * -> *) (er :: EventTag -> *) a.
DomBuilder t m =>
Text
-> ElementConfig er t (DomBuilderSpace m)
-> m a
-> m (Element er (DomBuilderSpace m) t, a)
element "select" (SelectElementConfig er t StaticDomSpace
-> ElementConfig er t StaticDomSpace
forall (er :: EventTag -> *) k1 (t :: k1) k2 (m :: k2).
SelectElementConfig er t m -> ElementConfig er t m
_selectElementConfig_elementConfig SelectElementConfig er t (DomBuilderSpace (StaticDomBuilderT t m))
SelectElementConfig er t StaticDomSpace
cfg) (StaticDomBuilderT t m a
-> StaticDomBuilderT t m (Element er StaticDomSpace t, a))
-> StaticDomBuilderT t m a
-> StaticDomBuilderT t m (Element er StaticDomSpace t, a)
forall a b. (a -> b) -> a -> b
$ do
(a :: a
a, innerHtml :: Behavior t Builder
innerHtml) <- ReaderT
(StaticDomBuilderEnv t)
(StateT [Behavior t Builder] m)
(a, Behavior t Builder)
-> StaticDomBuilderT t m (a, Behavior t Builder)
forall k (t :: k) (m :: * -> *) a.
ReaderT (StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) a
-> StaticDomBuilderT t m a
StaticDomBuilderT (ReaderT
(StaticDomBuilderEnv t)
(StateT [Behavior t Builder] m)
(a, Behavior t Builder)
-> StaticDomBuilderT t m (a, Behavior t Builder))
-> ReaderT
(StaticDomBuilderEnv t)
(StateT [Behavior t Builder] m)
(a, Behavior t Builder)
-> StaticDomBuilderT t m (a, Behavior t Builder)
forall a b. (a -> b) -> a -> b
$ do
IORef Int
nextRunWithReplaceKey <- (StaticDomBuilderEnv t -> IORef Int)
-> ReaderT
(StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) (IORef Int)
forall (m :: * -> *) r a. Monad m => (r -> a) -> ReaderT r m a
asks StaticDomBuilderEnv t -> IORef Int
forall k (t :: k). StaticDomBuilderEnv t -> IORef Int
_staticDomBuilderEnv_nextRunWithReplaceKey
StateT [Behavior t Builder] m (a, Behavior t Builder)
-> ReaderT
(StaticDomBuilderEnv t)
(StateT [Behavior t Builder] m)
(a, Behavior t Builder)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (StateT [Behavior t Builder] m (a, Behavior t Builder)
-> ReaderT
(StaticDomBuilderEnv t)
(StateT [Behavior t Builder] m)
(a, Behavior t Builder))
-> StateT [Behavior t Builder] m (a, Behavior t Builder)
-> ReaderT
(StaticDomBuilderEnv t)
(StateT [Behavior t Builder] m)
(a, Behavior t Builder)
forall a b. (a -> b) -> a -> b
$ m (a, Behavior t Builder)
-> StateT [Behavior t Builder] m (a, Behavior t Builder)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (a, Behavior t Builder)
-> StateT [Behavior t Builder] m (a, Behavior t Builder))
-> m (a, Behavior t Builder)
-> StateT [Behavior t Builder] m (a, Behavior t Builder)
forall a b. (a -> b) -> a -> b
$ StaticDomBuilderT t m a
-> StaticDomBuilderEnv t -> m (a, Behavior t Builder)
forall k (m :: * -> *) (t :: k) a.
(Monad m, Reflex t) =>
StaticDomBuilderT t m a
-> StaticDomBuilderEnv t -> m (a, Behavior t Builder)
runStaticDomBuilderT StaticDomBuilderT t m a
child (StaticDomBuilderEnv t -> m (a, Behavior t Builder))
-> StaticDomBuilderEnv t -> m (a, Behavior t Builder)
forall a b. (a -> b) -> a -> b
$ Bool
-> Maybe (Behavior t Text) -> IORef Int -> StaticDomBuilderEnv t
forall k (t :: k).
Bool
-> Maybe (Behavior t Text) -> IORef Int -> StaticDomBuilderEnv t
StaticDomBuilderEnv Bool
False (Behavior t Text -> Maybe (Behavior t Text)
forall a. a -> Maybe a
Just (Behavior t Text -> Maybe (Behavior t Text))
-> Behavior t Text -> Maybe (Behavior t Text)
forall a b. (a -> b) -> a -> b
$ Dynamic t Text -> Behavior t Text
forall k (t :: k) a. Reflex t => Dynamic t a -> Behavior t a
current Dynamic t Text
v) IORef Int
nextRunWithReplaceKey
ReaderT (StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) ()
-> StaticDomBuilderT t m ()
forall k (t :: k) (m :: * -> *) a.
ReaderT (StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) a
-> StaticDomBuilderT t m a
StaticDomBuilderT (ReaderT (StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) ()
-> StaticDomBuilderT t m ())
-> ReaderT
(StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) ()
-> StaticDomBuilderT t m ()
forall a b. (a -> b) -> a -> b
$ StateT [Behavior t Builder] m ()
-> ReaderT
(StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (StateT [Behavior t Builder] m ()
-> ReaderT
(StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) ())
-> StateT [Behavior t Builder] m ()
-> ReaderT
(StaticDomBuilderEnv t) (StateT [Behavior t Builder] m) ()
forall a b. (a -> b) -> a -> b
$ ([Behavior t Builder] -> [Behavior t Builder])
-> StateT [Behavior t Builder] m ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (([Behavior t Builder] -> [Behavior t Builder])
-> StateT [Behavior t Builder] m ())
-> ([Behavior t Builder] -> [Behavior t Builder])
-> StateT [Behavior t Builder] m ()
forall a b. (a -> b) -> a -> b
$ (:) Behavior t Builder
innerHtml
a -> StaticDomBuilderT t m a
forall (m :: * -> *) a. Monad m => a -> m a
return a
a
let wrapped :: SelectElement er StaticDomSpace t
wrapped = SelectElement :: forall k k (er :: EventTag -> *) (d :: k) (t :: k).
Element er d t
-> Dynamic t Text
-> Event t Text
-> Dynamic t Bool
-> RawSelectElement d
-> SelectElement er d t
SelectElement
{ _selectElement_value :: Dynamic t Text
_selectElement_value = Dynamic t Text
v
, _selectElement_change :: Event t Text
_selectElement_change = Event t Text
forall k (t :: k) a. Reflex t => Event t a
never
, _selectElement_hasFocus :: Dynamic t Bool
_selectElement_hasFocus = Bool -> Dynamic t Bool
forall k (t :: k) a. Reflex t => a -> Dynamic t a
constDyn Bool
False
, _selectElement_element :: Element er StaticDomSpace t
_selectElement_element = Element er StaticDomSpace t
e
, _selectElement_raw :: RawSelectElement StaticDomSpace
_selectElement_raw = ()
}
(SelectElement er StaticDomSpace t, a)
-> StaticDomBuilderT t m (SelectElement er StaticDomSpace t, a)
forall (m :: * -> *) a. Monad m => a -> m a
return (SelectElement er StaticDomSpace t
wrapped, a
result)
placeRawElement :: RawElement (DomBuilderSpace (StaticDomBuilderT t m))
-> StaticDomBuilderT t m ()
placeRawElement () = () -> StaticDomBuilderT t m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
wrapRawElement :: RawElement (DomBuilderSpace (StaticDomBuilderT t m))
-> RawElementConfig er t (DomBuilderSpace (StaticDomBuilderT t m))
-> StaticDomBuilderT
t m (Element er (DomBuilderSpace (StaticDomBuilderT t m)) t)
wrapRawElement () _ = Element er StaticDomSpace t
-> StaticDomBuilderT
t m (Element er (DomBuilderSpace (StaticDomBuilderT t m)) t)
forall (m :: * -> *) a. Monad m => a -> m a
return (Element er StaticDomSpace t
-> StaticDomBuilderT
t m (Element er (DomBuilderSpace (StaticDomBuilderT t m)) t))
-> Element er StaticDomSpace t
-> StaticDomBuilderT
t m (Element er (DomBuilderSpace (StaticDomBuilderT t m)) t)
forall a b. (a -> b) -> a -> b
$ EventSelector t (WrapArg er EventName)
-> RawElement StaticDomSpace -> Element er StaticDomSpace t
forall k k (er :: EventTag -> *) (d :: k) (t :: k).
EventSelector t (WrapArg er EventName)
-> RawElement d -> Element er d t
Element ((forall a. WrapArg er EventName a -> Event t a)
-> EventSelector t (WrapArg er EventName)
forall k (t :: k) (k1 :: * -> *).
(forall a. k1 a -> Event t a) -> EventSelector t k1
EventSelector ((forall a. WrapArg er EventName a -> Event t a)
-> EventSelector t (WrapArg er EventName))
-> (forall a. WrapArg er EventName a -> Event t a)
-> EventSelector t (WrapArg er EventName)
forall a b. (a -> b) -> a -> b
$ Event t a -> WrapArg er EventName a -> Event t a
forall a b. a -> b -> a
const Event t a
forall k (t :: k) a. Reflex t => Event t a
never) ()
type StaticWidget x = PostBuildT DomTimeline (StaticDomBuilderT DomTimeline (PerformEventT DomTimeline DomHost))
{-# INLINE renderStatic #-}
renderStatic :: StaticWidget x a -> IO (a, ByteString)
renderStatic :: StaticWidget x a -> IO (a, ByteString)
renderStatic w :: StaticWidget x a
w = do
DomHost (a, ByteString) -> IO (a, ByteString)
forall a. DomHost a -> IO a
runDomHost (DomHost (a, ByteString) -> IO (a, ByteString))
-> DomHost (a, ByteString) -> IO (a, ByteString)
forall a b. (a -> b) -> a -> b
$ do
(postBuild :: Event DomTimeline ()
postBuild, postBuildTriggerRef :: IORef (Maybe (RootTrigger Global ()))
postBuildTriggerRef) <- SpiderHost
Global
(Event DomTimeline (), IORef (Maybe (RootTrigger Global ())))
forall t (m :: * -> *) a.
(MonadReflexCreateTrigger t m, MonadRef m, Ref m ~ Ref IO) =>
m (Event t a, Ref m (Maybe (EventTrigger t a)))
newEventWithTriggerRef
IORef Int
nextRunWithReplaceKey <- Int -> SpiderHost Global (Ref (SpiderHost Global) Int)
forall (m :: * -> *) a. MonadRef m => a -> m (Ref m a)
newRef 0
let env0 :: StaticDomBuilderEnv DomTimeline
env0 = Bool
-> Maybe (Behavior DomTimeline Text)
-> IORef Int
-> StaticDomBuilderEnv DomTimeline
forall k (t :: k).
Bool
-> Maybe (Behavior t Text) -> IORef Int -> StaticDomBuilderEnv t
StaticDomBuilderEnv Bool
True Maybe (Behavior DomTimeline Text)
forall a. Maybe a
Nothing IORef Int
nextRunWithReplaceKey
((res :: a
res, bs :: Behavior DomTimeline Builder
bs), FireCommand fire :: forall a.
[DSum (EventTrigger DomTimeline) Identity]
-> ReadPhase (SpiderHost Global) a -> DomHost [a]
fire) <- PerformEventT
DomTimeline (SpiderHost Global) (a, Behavior DomTimeline Builder)
-> DomHost
((a, Behavior DomTimeline Builder),
FireCommand DomTimeline (SpiderHost Global))
forall t (m :: * -> *) a.
(Monad m, MonadSubscribeEvent t m, MonadReflexHost t m, MonadRef m,
Ref m ~ Ref IO) =>
PerformEventT t m a -> m (a, FireCommand t m)
hostPerformEventT (PerformEventT
DomTimeline (SpiderHost Global) (a, Behavior DomTimeline Builder)
-> DomHost
((a, Behavior DomTimeline Builder),
FireCommand DomTimeline (SpiderHost Global)))
-> PerformEventT
DomTimeline (SpiderHost Global) (a, Behavior DomTimeline Builder)
-> DomHost
((a, Behavior DomTimeline Builder),
FireCommand DomTimeline (SpiderHost Global))
forall a b. (a -> b) -> a -> b
$ StaticDomBuilderT
DomTimeline (PerformEventT DomTimeline (SpiderHost Global)) a
-> StaticDomBuilderEnv DomTimeline
-> PerformEventT
DomTimeline (SpiderHost Global) (a, Behavior DomTimeline Builder)
forall k (m :: * -> *) (t :: k) a.
(Monad m, Reflex t) =>
StaticDomBuilderT t m a
-> StaticDomBuilderEnv t -> m (a, Behavior t Builder)
runStaticDomBuilderT (StaticWidget x a
-> Event DomTimeline ()
-> StaticDomBuilderT
DomTimeline (PerformEventT DomTimeline (SpiderHost Global)) a
forall t (m :: * -> *) a. PostBuildT t m a -> Event t () -> m a
runPostBuildT StaticWidget x a
w Event DomTimeline ()
postBuild) StaticDomBuilderEnv DomTimeline
env0
Maybe (RootTrigger Global ())
mPostBuildTrigger <- Ref (SpiderHost Global) (Maybe (RootTrigger Global ()))
-> SpiderHost Global (Maybe (RootTrigger Global ()))
forall (m :: * -> *) a. MonadRef m => Ref m a -> m a
readRef IORef (Maybe (RootTrigger Global ()))
Ref (SpiderHost Global) (Maybe (RootTrigger Global ()))
postBuildTriggerRef
Maybe (RootTrigger Global ())
-> (RootTrigger Global () -> SpiderHost Global [()])
-> SpiderHost Global ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ Maybe (RootTrigger Global ())
mPostBuildTrigger ((RootTrigger Global () -> SpiderHost Global [()])
-> SpiderHost Global ())
-> (RootTrigger Global () -> SpiderHost Global [()])
-> SpiderHost Global ()
forall a b. (a -> b) -> a -> b
$ \postBuildTrigger :: RootTrigger Global ()
postBuildTrigger -> [DSum (EventTrigger DomTimeline) Identity]
-> ReadPhase (SpiderHost Global) () -> SpiderHost Global [()]
forall a.
[DSum (EventTrigger DomTimeline) Identity]
-> ReadPhase (SpiderHost Global) a -> DomHost [a]
fire [RootTrigger Global ()
postBuildTrigger RootTrigger Global ()
-> Identity () -> DSum (RootTrigger Global) Identity
forall k (tag :: k -> *) (f :: k -> *) (a :: k).
tag a -> f a -> DSum tag f
:=> () -> Identity ()
forall a. a -> Identity a
Identity ()] (ReadPhase (SpiderHost Global) () -> SpiderHost Global [()])
-> ReadPhase (SpiderHost Global) () -> SpiderHost Global [()]
forall a b. (a -> b) -> a -> b
$ () -> ReadPhase Global ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
Builder
bs' <- Behavior DomTimeline Builder -> SpiderHost Global Builder
forall k (t :: k) (m :: * -> *) a.
MonadSample t m =>
Behavior t a -> m a
sample Behavior DomTimeline Builder
bs
(a, ByteString) -> DomHost (a, ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (a
res, ByteString -> ByteString
LBS.toStrict (ByteString -> ByteString) -> ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ Builder -> ByteString
toLazyByteString Builder
bs')