{-# LANGUAGE EmptyDataDecls #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE RankNTypes #-}
module Reflex.Profiled where
import Control.Monad
import Control.Monad.Exception
import Control.Monad.Fix
import Control.Monad.Primitive
import Control.Monad.Reader
import Control.Monad.Ref
import Control.Monad.State.Strict (StateT, execStateT, modify)
import Data.Bifunctor
import Data.Coerce
import Data.Dependent.Map (DMap, GCompare)
import Data.FastMutableIntMap
import Data.IORef
import Data.List
import Data.Map (Map)
import qualified Data.Map.Strict as Map
import Data.Monoid ((<>))
import Data.Ord
import Data.Profunctor.Unsafe ((#.))
import qualified Data.Semigroup as S
import Data.Type.Coercion
import Foreign.Ptr
import GHC.Foreign
import GHC.IO.Encoding
import GHC.Stack
import Reflex.Adjustable.Class
import Reflex.BehaviorWriter.Class
import Reflex.Class
import Reflex.DynamicWriter.Class
import Reflex.EventWriter.Class
import Reflex.Host.Class
import Reflex.NotReady.Class
import Reflex.PerformEvent.Class
import Reflex.PostBuild.Class
import Reflex.Query.Class
import Reflex.Requester.Class
import Reflex.TriggerEvent.Class
import System.IO.Unsafe
data ProfiledTimeline t
{-# NOINLINE profilingData #-}
profilingData :: IORef (Map (Ptr CostCentreStack) Int)
profilingData :: IORef (Map (Ptr CostCentreStack) Int)
profilingData = IO (IORef (Map (Ptr CostCentreStack) Int))
-> IORef (Map (Ptr CostCentreStack) Int)
forall a. IO a -> a
unsafePerformIO (IO (IORef (Map (Ptr CostCentreStack) Int))
-> IORef (Map (Ptr CostCentreStack) Int))
-> IO (IORef (Map (Ptr CostCentreStack) Int))
-> IORef (Map (Ptr CostCentreStack) Int)
forall a b. (a -> b) -> a -> b
$ Map (Ptr CostCentreStack) Int
-> IO (IORef (Map (Ptr CostCentreStack) Int))
forall a. a -> IO (IORef a)
newIORef Map (Ptr CostCentreStack) Int
forall k a. Map k a
Map.empty
data CostCentreTree = CostCentreTree
{ CostCentreTree -> Int
_costCentreTree_ownEntries :: !Int
, CostCentreTree -> Int
_costCentreTree_cumulativeEntries :: !Int
, CostCentreTree -> Map (Ptr CostCentre) CostCentreTree
_costCentreTree_children :: !(Map (Ptr CostCentre) CostCentreTree)
}
deriving (Int -> CostCentreTree -> ShowS
[CostCentreTree] -> ShowS
CostCentreTree -> String
(Int -> CostCentreTree -> ShowS)
-> (CostCentreTree -> String)
-> ([CostCentreTree] -> ShowS)
-> Show CostCentreTree
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CostCentreTree] -> ShowS
$cshowList :: [CostCentreTree] -> ShowS
show :: CostCentreTree -> String
$cshow :: CostCentreTree -> String
showsPrec :: Int -> CostCentreTree -> ShowS
$cshowsPrec :: Int -> CostCentreTree -> ShowS
Show, CostCentreTree -> CostCentreTree -> Bool
(CostCentreTree -> CostCentreTree -> Bool)
-> (CostCentreTree -> CostCentreTree -> Bool) -> Eq CostCentreTree
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CostCentreTree -> CostCentreTree -> Bool
$c/= :: CostCentreTree -> CostCentreTree -> Bool
== :: CostCentreTree -> CostCentreTree -> Bool
$c== :: CostCentreTree -> CostCentreTree -> Bool
Eq, Eq CostCentreTree
Eq CostCentreTree =>
(CostCentreTree -> CostCentreTree -> Ordering)
-> (CostCentreTree -> CostCentreTree -> Bool)
-> (CostCentreTree -> CostCentreTree -> Bool)
-> (CostCentreTree -> CostCentreTree -> Bool)
-> (CostCentreTree -> CostCentreTree -> Bool)
-> (CostCentreTree -> CostCentreTree -> CostCentreTree)
-> (CostCentreTree -> CostCentreTree -> CostCentreTree)
-> Ord CostCentreTree
CostCentreTree -> CostCentreTree -> Bool
CostCentreTree -> CostCentreTree -> Ordering
CostCentreTree -> CostCentreTree -> CostCentreTree
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CostCentreTree -> CostCentreTree -> CostCentreTree
$cmin :: CostCentreTree -> CostCentreTree -> CostCentreTree
max :: CostCentreTree -> CostCentreTree -> CostCentreTree
$cmax :: CostCentreTree -> CostCentreTree -> CostCentreTree
>= :: CostCentreTree -> CostCentreTree -> Bool
$c>= :: CostCentreTree -> CostCentreTree -> Bool
> :: CostCentreTree -> CostCentreTree -> Bool
$c> :: CostCentreTree -> CostCentreTree -> Bool
<= :: CostCentreTree -> CostCentreTree -> Bool
$c<= :: CostCentreTree -> CostCentreTree -> Bool
< :: CostCentreTree -> CostCentreTree -> Bool
$c< :: CostCentreTree -> CostCentreTree -> Bool
compare :: CostCentreTree -> CostCentreTree -> Ordering
$ccompare :: CostCentreTree -> CostCentreTree -> Ordering
$cp1Ord :: Eq CostCentreTree
Ord)
instance S.Semigroup CostCentreTree where
(CostCentreTree oa :: Int
oa ea :: Int
ea ca :: Map (Ptr CostCentre) CostCentreTree
ca) <> :: CostCentreTree -> CostCentreTree -> CostCentreTree
<> (CostCentreTree ob :: Int
ob eb :: Int
eb cb :: Map (Ptr CostCentre) CostCentreTree
cb) =
Int -> Int -> Map (Ptr CostCentre) CostCentreTree -> CostCentreTree
CostCentreTree (Int
oa Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
ob) (Int
ea Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
eb) (Map (Ptr CostCentre) CostCentreTree -> CostCentreTree)
-> Map (Ptr CostCentre) CostCentreTree -> CostCentreTree
forall a b. (a -> b) -> a -> b
$ (CostCentreTree -> CostCentreTree -> CostCentreTree)
-> Map (Ptr CostCentre) CostCentreTree
-> Map (Ptr CostCentre) CostCentreTree
-> Map (Ptr CostCentre) CostCentreTree
forall k a. Ord k => (a -> a -> a) -> Map k a -> Map k a -> Map k a
Map.unionWith CostCentreTree -> CostCentreTree -> CostCentreTree
forall a. Semigroup a => a -> a -> a
(S.<>) Map (Ptr CostCentre) CostCentreTree
ca Map (Ptr CostCentre) CostCentreTree
cb
instance Monoid CostCentreTree where
mempty :: CostCentreTree
mempty = Int -> Int -> Map (Ptr CostCentre) CostCentreTree -> CostCentreTree
CostCentreTree 0 0 Map (Ptr CostCentre) CostCentreTree
forall a. Monoid a => a
mempty
mappend :: CostCentreTree -> CostCentreTree -> CostCentreTree
mappend = CostCentreTree -> CostCentreTree -> CostCentreTree
forall a. Semigroup a => a -> a -> a
(S.<>)
getCostCentreStack :: Ptr CostCentreStack -> IO [Ptr CostCentre]
getCostCentreStack :: Ptr CostCentreStack -> IO [Ptr CostCentre]
getCostCentreStack = [Ptr CostCentre] -> Ptr CostCentreStack -> IO [Ptr CostCentre]
go []
where go :: [Ptr CostCentre] -> Ptr CostCentreStack -> IO [Ptr CostCentre]
go l :: [Ptr CostCentre]
l ccs :: Ptr CostCentreStack
ccs = if Ptr CostCentreStack
ccs Ptr CostCentreStack -> Ptr CostCentreStack -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr CostCentreStack
forall a. Ptr a
nullPtr
then [Ptr CostCentre] -> IO [Ptr CostCentre]
forall (m :: * -> *) a. Monad m => a -> m a
return [Ptr CostCentre]
l
else do
Ptr CostCentre
cc <- Ptr CostCentreStack -> IO (Ptr CostCentre)
ccsCC Ptr CostCentreStack
ccs
Ptr CostCentreStack
parent <- Ptr CostCentreStack -> IO (Ptr CostCentreStack)
ccsParent Ptr CostCentreStack
ccs
[Ptr CostCentre] -> Ptr CostCentreStack -> IO [Ptr CostCentre]
go (Ptr CostCentre
cc Ptr CostCentre -> [Ptr CostCentre] -> [Ptr CostCentre]
forall a. a -> [a] -> [a]
: [Ptr CostCentre]
l) Ptr CostCentreStack
parent
toCostCentreTree :: Ptr CostCentreStack -> Int -> IO CostCentreTree
toCostCentreTree :: Ptr CostCentreStack -> Int -> IO CostCentreTree
toCostCentreTree ccs :: Ptr CostCentreStack
ccs n :: Int
n =
(Ptr CostCentre -> CostCentreTree -> CostCentreTree)
-> CostCentreTree -> [Ptr CostCentre] -> CostCentreTree
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (\cc :: Ptr CostCentre
cc child :: CostCentreTree
child -> Int -> Int -> Map (Ptr CostCentre) CostCentreTree -> CostCentreTree
CostCentreTree 0 Int
n (Map (Ptr CostCentre) CostCentreTree -> CostCentreTree)
-> Map (Ptr CostCentre) CostCentreTree -> CostCentreTree
forall a b. (a -> b) -> a -> b
$ Ptr CostCentre
-> CostCentreTree -> Map (Ptr CostCentre) CostCentreTree
forall k a. k -> a -> Map k a
Map.singleton Ptr CostCentre
cc CostCentreTree
child) (Int -> Int -> Map (Ptr CostCentre) CostCentreTree -> CostCentreTree
CostCentreTree Int
n Int
n Map (Ptr CostCentre) CostCentreTree
forall a. Monoid a => a
mempty)
([Ptr CostCentre] -> CostCentreTree)
-> IO [Ptr CostCentre] -> IO CostCentreTree
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CostCentreStack -> IO [Ptr CostCentre]
getCostCentreStack Ptr CostCentreStack
ccs
getCostCentreTree :: IO CostCentreTree
getCostCentreTree :: IO CostCentreTree
getCostCentreTree = do
Map (Ptr CostCentreStack) Int
vals <- IORef (Map (Ptr CostCentreStack) Int)
-> IO (Map (Ptr CostCentreStack) Int)
forall a. IORef a -> IO a
readIORef IORef (Map (Ptr CostCentreStack) Int)
profilingData
[CostCentreTree] -> CostCentreTree
forall a. Monoid a => [a] -> a
mconcat ([CostCentreTree] -> CostCentreTree)
-> IO [CostCentreTree] -> IO CostCentreTree
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((Ptr CostCentreStack, Int) -> IO CostCentreTree)
-> [(Ptr CostCentreStack, Int)] -> IO [CostCentreTree]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((Ptr CostCentreStack -> Int -> IO CostCentreTree)
-> (Ptr CostCentreStack, Int) -> IO CostCentreTree
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Ptr CostCentreStack -> Int -> IO CostCentreTree
toCostCentreTree) (Map (Ptr CostCentreStack) Int -> [(Ptr CostCentreStack, Int)]
forall k a. Map k a -> [(k, a)]
Map.toList Map (Ptr CostCentreStack) Int
vals)
formatCostCentreTree :: CostCentreTree -> IO String
formatCostCentreTree :: CostCentreTree -> IO String
formatCostCentreTree cct0 :: CostCentreTree
cct0 = [String] -> String
unlines ([String] -> String)
-> ([String] -> [String]) -> [String] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> [String]
forall a. [a] -> [a]
reverse ([String] -> String) -> IO [String] -> IO String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StateT [String] IO () -> [String] -> IO [String]
forall (m :: * -> *) s a. Monad m => StateT s m a -> s -> m s
execStateT (Int -> CostCentreTree -> StateT [String] IO ()
go 0 CostCentreTree
cct0) []
where go :: Int -> CostCentreTree -> StateT [String] IO ()
go :: Int -> CostCentreTree -> StateT [String] IO ()
go depth :: Int
depth cct :: CostCentreTree
cct = do
let children :: [(Ptr CostCentre, CostCentreTree)]
children = ((Ptr CostCentre, CostCentreTree) -> Down Int)
-> [(Ptr CostCentre, CostCentreTree)]
-> [(Ptr CostCentre, CostCentreTree)]
forall b a. Ord b => (a -> b) -> [a] -> [a]
sortOn (Int -> Down Int
forall a. a -> Down a
Down (Int -> Down Int)
-> ((Ptr CostCentre, CostCentreTree) -> Int)
-> (Ptr CostCentre, CostCentreTree)
-> Down Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CostCentreTree -> Int
_costCentreTree_cumulativeEntries (CostCentreTree -> Int)
-> ((Ptr CostCentre, CostCentreTree) -> CostCentreTree)
-> (Ptr CostCentre, CostCentreTree)
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Ptr CostCentre, CostCentreTree) -> CostCentreTree
forall a b. (a, b) -> b
snd) ([(Ptr CostCentre, CostCentreTree)]
-> [(Ptr CostCentre, CostCentreTree)])
-> [(Ptr CostCentre, CostCentreTree)]
-> [(Ptr CostCentre, CostCentreTree)]
forall a b. (a -> b) -> a -> b
$ Map (Ptr CostCentre) CostCentreTree
-> [(Ptr CostCentre, CostCentreTree)]
forall k a. Map k a -> [(k, a)]
Map.toList (Map (Ptr CostCentre) CostCentreTree
-> [(Ptr CostCentre, CostCentreTree)])
-> Map (Ptr CostCentre) CostCentreTree
-> [(Ptr CostCentre, CostCentreTree)]
forall a b. (a -> b) -> a -> b
$ CostCentreTree -> Map (Ptr CostCentre) CostCentreTree
_costCentreTree_children CostCentreTree
cct
indent :: String
indent = [String] -> String
forall a. Monoid a => [a] -> a
mconcat ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ Int -> String -> [String]
forall a. Int -> a -> [a]
replicate Int
depth " "
[(Ptr CostCentre, CostCentreTree)]
-> ((Ptr CostCentre, CostCentreTree) -> StateT [String] IO ())
-> StateT [String] IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [(Ptr CostCentre, CostCentreTree)]
children (((Ptr CostCentre, CostCentreTree) -> StateT [String] IO ())
-> StateT [String] IO ())
-> ((Ptr CostCentre, CostCentreTree) -> StateT [String] IO ())
-> StateT [String] IO ()
forall a b. (a -> b) -> a -> b
$ \(cc :: Ptr CostCentre
cc, childCct :: CostCentreTree
childCct) -> do
String
lbl <- IO String -> StateT [String] IO String
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> StateT [String] IO String)
-> IO String -> StateT [String] IO String
forall a b. (a -> b) -> a -> b
$ TextEncoding -> CString -> IO String
peekCString TextEncoding
utf8 (CString -> IO String) -> IO CString -> IO String
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr CostCentre -> IO CString
ccLabel Ptr CostCentre
cc
String
mdl <- IO String -> StateT [String] IO String
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> StateT [String] IO String)
-> IO String -> StateT [String] IO String
forall a b. (a -> b) -> a -> b
$ TextEncoding -> CString -> IO String
peekCString TextEncoding
utf8 (CString -> IO String) -> IO CString -> IO String
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr CostCentre -> IO CString
ccModule Ptr CostCentre
cc
String
loc <- IO String -> StateT [String] IO String
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> StateT [String] IO String)
-> IO String -> StateT [String] IO String
forall a b. (a -> b) -> a -> b
$ TextEncoding -> CString -> IO String
peekCString TextEncoding
utf8 (CString -> IO String) -> IO CString -> IO String
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr CostCentre -> IO CString
ccSrcSpan Ptr CostCentre
cc
let description :: String
description = String
mdl String -> ShowS
forall a. Semigroup a => a -> a -> a
<> "." String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
lbl String -> ShowS
forall a. Semigroup a => a -> a -> a
<> " (" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
loc String -> ShowS
forall a. Semigroup a => a -> a -> a
<> ")"
([String] -> [String]) -> StateT [String] IO ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (([String] -> [String]) -> StateT [String] IO ())
-> ([String] -> [String]) -> StateT [String] IO ()
forall a b. (a -> b) -> a -> b
$ (:) (String -> [String] -> [String]) -> String -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ String
indent String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
description String -> ShowS
forall a. Semigroup a => a -> a -> a
<> "\t" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Int -> String
forall a. Show a => a -> String
show (CostCentreTree -> Int
_costCentreTree_cumulativeEntries CostCentreTree
childCct) String -> ShowS
forall a. Semigroup a => a -> a -> a
<> "\t" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Int -> String
forall a. Show a => a -> String
show (CostCentreTree -> Int
_costCentreTree_ownEntries CostCentreTree
childCct)
Int -> CostCentreTree -> StateT [String] IO ()
go (Int -> Int
forall a. Enum a => a -> a
succ Int
depth) CostCentreTree
childCct
showProfilingData :: IO ()
showProfilingData :: IO ()
showProfilingData = do
String -> IO ()
putStr (String -> IO ()) -> IO String -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< CostCentreTree -> IO String
formatCostCentreTree (CostCentreTree -> IO String) -> IO CostCentreTree -> IO String
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IO CostCentreTree
getCostCentreTree
writeProfilingData :: FilePath -> IO ()
writeProfilingData :: String -> IO ()
writeProfilingData p :: String
p = do
String -> String -> IO ()
writeFile String
p (String -> IO ()) -> IO String -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< CostCentreTree -> IO String
formatCostCentreTree (CostCentreTree -> IO String) -> IO CostCentreTree -> IO String
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IO CostCentreTree
getCostCentreTree
newtype ProfiledM m a = ProfiledM { ProfiledM m a -> m a
runProfiledM :: m a }
deriving (a -> ProfiledM m b -> ProfiledM m a
(a -> b) -> ProfiledM m a -> ProfiledM m b
(forall a b. (a -> b) -> ProfiledM m a -> ProfiledM m b)
-> (forall a b. a -> ProfiledM m b -> ProfiledM m a)
-> Functor (ProfiledM m)
forall a b. a -> ProfiledM m b -> ProfiledM m a
forall a b. (a -> b) -> ProfiledM m a -> ProfiledM m b
forall (m :: * -> *) a b.
Functor m =>
a -> ProfiledM m b -> ProfiledM m a
forall (m :: * -> *) a b.
Functor m =>
(a -> b) -> ProfiledM m a -> ProfiledM m b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> ProfiledM m b -> ProfiledM m a
$c<$ :: forall (m :: * -> *) a b.
Functor m =>
a -> ProfiledM m b -> ProfiledM m a
fmap :: (a -> b) -> ProfiledM m a -> ProfiledM m b
$cfmap :: forall (m :: * -> *) a b.
Functor m =>
(a -> b) -> ProfiledM m a -> ProfiledM m b
Functor, Functor (ProfiledM m)
a -> ProfiledM m a
Functor (ProfiledM m) =>
(forall a. a -> ProfiledM m a)
-> (forall a b.
ProfiledM m (a -> b) -> ProfiledM m a -> ProfiledM m b)
-> (forall a b c.
(a -> b -> c) -> ProfiledM m a -> ProfiledM m b -> ProfiledM m c)
-> (forall a b. ProfiledM m a -> ProfiledM m b -> ProfiledM m b)
-> (forall a b. ProfiledM m a -> ProfiledM m b -> ProfiledM m a)
-> Applicative (ProfiledM m)
ProfiledM m a -> ProfiledM m b -> ProfiledM m b
ProfiledM m a -> ProfiledM m b -> ProfiledM m a
ProfiledM m (a -> b) -> ProfiledM m a -> ProfiledM m b
(a -> b -> c) -> ProfiledM m a -> ProfiledM m b -> ProfiledM m c
forall a. a -> ProfiledM m a
forall a b. ProfiledM m a -> ProfiledM m b -> ProfiledM m a
forall a b. ProfiledM m a -> ProfiledM m b -> ProfiledM m b
forall a b. ProfiledM m (a -> b) -> ProfiledM m a -> ProfiledM m b
forall a b c.
(a -> b -> c) -> ProfiledM m a -> ProfiledM m b -> ProfiledM 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
forall (m :: * -> *). Applicative m => Functor (ProfiledM m)
forall (m :: * -> *) a. Applicative m => a -> ProfiledM m a
forall (m :: * -> *) a b.
Applicative m =>
ProfiledM m a -> ProfiledM m b -> ProfiledM m a
forall (m :: * -> *) a b.
Applicative m =>
ProfiledM m a -> ProfiledM m b -> ProfiledM m b
forall (m :: * -> *) a b.
Applicative m =>
ProfiledM m (a -> b) -> ProfiledM m a -> ProfiledM m b
forall (m :: * -> *) a b c.
Applicative m =>
(a -> b -> c) -> ProfiledM m a -> ProfiledM m b -> ProfiledM m c
<* :: ProfiledM m a -> ProfiledM m b -> ProfiledM m a
$c<* :: forall (m :: * -> *) a b.
Applicative m =>
ProfiledM m a -> ProfiledM m b -> ProfiledM m a
*> :: ProfiledM m a -> ProfiledM m b -> ProfiledM m b
$c*> :: forall (m :: * -> *) a b.
Applicative m =>
ProfiledM m a -> ProfiledM m b -> ProfiledM m b
liftA2 :: (a -> b -> c) -> ProfiledM m a -> ProfiledM m b -> ProfiledM m c
$cliftA2 :: forall (m :: * -> *) a b c.
Applicative m =>
(a -> b -> c) -> ProfiledM m a -> ProfiledM m b -> ProfiledM m c
<*> :: ProfiledM m (a -> b) -> ProfiledM m a -> ProfiledM m b
$c<*> :: forall (m :: * -> *) a b.
Applicative m =>
ProfiledM m (a -> b) -> ProfiledM m a -> ProfiledM m b
pure :: a -> ProfiledM m a
$cpure :: forall (m :: * -> *) a. Applicative m => a -> ProfiledM m a
$cp1Applicative :: forall (m :: * -> *). Applicative m => Functor (ProfiledM m)
Applicative, Applicative (ProfiledM m)
a -> ProfiledM m a
Applicative (ProfiledM m) =>
(forall a b.
ProfiledM m a -> (a -> ProfiledM m b) -> ProfiledM m b)
-> (forall a b. ProfiledM m a -> ProfiledM m b -> ProfiledM m b)
-> (forall a. a -> ProfiledM m a)
-> Monad (ProfiledM m)
ProfiledM m a -> (a -> ProfiledM m b) -> ProfiledM m b
ProfiledM m a -> ProfiledM m b -> ProfiledM m b
forall a. a -> ProfiledM m a
forall a b. ProfiledM m a -> ProfiledM m b -> ProfiledM m b
forall a b. ProfiledM m a -> (a -> ProfiledM m b) -> ProfiledM m b
forall (m :: * -> *). Monad m => Applicative (ProfiledM m)
forall (m :: * -> *) a. Monad m => a -> ProfiledM m a
forall (m :: * -> *) a b.
Monad m =>
ProfiledM m a -> ProfiledM m b -> ProfiledM m b
forall (m :: * -> *) a b.
Monad m =>
ProfiledM m a -> (a -> ProfiledM m b) -> ProfiledM 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 -> ProfiledM m a
$creturn :: forall (m :: * -> *) a. Monad m => a -> ProfiledM m a
>> :: ProfiledM m a -> ProfiledM m b -> ProfiledM m b
$c>> :: forall (m :: * -> *) a b.
Monad m =>
ProfiledM m a -> ProfiledM m b -> ProfiledM m b
>>= :: ProfiledM m a -> (a -> ProfiledM m b) -> ProfiledM m b
$c>>= :: forall (m :: * -> *) a b.
Monad m =>
ProfiledM m a -> (a -> ProfiledM m b) -> ProfiledM m b
$cp1Monad :: forall (m :: * -> *). Monad m => Applicative (ProfiledM m)
Monad, Monad (ProfiledM m)
Monad (ProfiledM m) =>
(forall a. (a -> ProfiledM m a) -> ProfiledM m a)
-> MonadFix (ProfiledM m)
(a -> ProfiledM m a) -> ProfiledM m a
forall a. (a -> ProfiledM m a) -> ProfiledM m a
forall (m :: * -> *).
Monad m =>
(forall a. (a -> m a) -> m a) -> MonadFix m
forall (m :: * -> *). MonadFix m => Monad (ProfiledM m)
forall (m :: * -> *) a.
MonadFix m =>
(a -> ProfiledM m a) -> ProfiledM m a
mfix :: (a -> ProfiledM m a) -> ProfiledM m a
$cmfix :: forall (m :: * -> *) a.
MonadFix m =>
(a -> ProfiledM m a) -> ProfiledM m a
$cp1MonadFix :: forall (m :: * -> *). MonadFix m => Monad (ProfiledM m)
MonadFix, Monad (ProfiledM m)
e -> ProfiledM m a
Monad (ProfiledM m) =>
(forall e a. Exception e => e -> ProfiledM m a)
-> (forall e a.
Exception e =>
ProfiledM m a -> (e -> ProfiledM m a) -> ProfiledM m a)
-> (forall a b. ProfiledM m a -> ProfiledM m b -> ProfiledM m a)
-> MonadException (ProfiledM m)
ProfiledM m a -> (e -> ProfiledM m a) -> ProfiledM m a
ProfiledM m a -> ProfiledM m b -> ProfiledM m a
forall e a. Exception e => e -> ProfiledM m a
forall e a.
Exception e =>
ProfiledM m a -> (e -> ProfiledM m a) -> ProfiledM m a
forall a b. ProfiledM m a -> ProfiledM m b -> ProfiledM 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
forall (m :: * -> *). MonadException m => Monad (ProfiledM m)
forall (m :: * -> *) e a.
(MonadException m, Exception e) =>
e -> ProfiledM m a
forall (m :: * -> *) e a.
(MonadException m, Exception e) =>
ProfiledM m a -> (e -> ProfiledM m a) -> ProfiledM m a
forall (m :: * -> *) a b.
MonadException m =>
ProfiledM m a -> ProfiledM m b -> ProfiledM m a
finally :: ProfiledM m a -> ProfiledM m b -> ProfiledM m a
$cfinally :: forall (m :: * -> *) a b.
MonadException m =>
ProfiledM m a -> ProfiledM m b -> ProfiledM m a
catch :: ProfiledM m a -> (e -> ProfiledM m a) -> ProfiledM m a
$ccatch :: forall (m :: * -> *) e a.
(MonadException m, Exception e) =>
ProfiledM m a -> (e -> ProfiledM m a) -> ProfiledM m a
throw :: e -> ProfiledM m a
$cthrow :: forall (m :: * -> *) e a.
(MonadException m, Exception e) =>
e -> ProfiledM m a
$cp1MonadException :: forall (m :: * -> *). MonadException m => Monad (ProfiledM m)
MonadException, MonadIO (ProfiledM m)
MonadException (ProfiledM m)
(MonadIO (ProfiledM m), MonadException (ProfiledM m)) =>
(forall b.
((forall a. ProfiledM m a -> ProfiledM m a) -> ProfiledM m b)
-> ProfiledM m b)
-> MonadAsyncException (ProfiledM m)
((forall a. ProfiledM m a -> ProfiledM m a) -> ProfiledM m b)
-> ProfiledM m b
forall b.
((forall a. ProfiledM m a -> ProfiledM m a) -> ProfiledM m b)
-> ProfiledM m b
forall (m :: * -> *).
(MonadIO m, MonadException m) =>
(forall b. ((forall a. m a -> m a) -> m b) -> m b)
-> MonadAsyncException m
forall (m :: * -> *).
MonadAsyncException m =>
MonadIO (ProfiledM m)
forall (m :: * -> *).
MonadAsyncException m =>
MonadException (ProfiledM m)
forall (m :: * -> *) b.
MonadAsyncException m =>
((forall a. ProfiledM m a -> ProfiledM m a) -> ProfiledM m b)
-> ProfiledM m b
mask :: ((forall a. ProfiledM m a -> ProfiledM m a) -> ProfiledM m b)
-> ProfiledM m b
$cmask :: forall (m :: * -> *) b.
MonadAsyncException m =>
((forall a. ProfiledM m a -> ProfiledM m a) -> ProfiledM m b)
-> ProfiledM m b
$cp2MonadAsyncException :: forall (m :: * -> *).
MonadAsyncException m =>
MonadException (ProfiledM m)
$cp1MonadAsyncException :: forall (m :: * -> *).
MonadAsyncException m =>
MonadIO (ProfiledM m)
MonadAsyncException)
profileEvent :: Reflex t => Event t a -> Event t a
profileEvent :: Event t a -> Event t a
profileEvent e :: Event t a
e = IO (Event t a) -> Event t a
forall a. IO a -> a
unsafePerformIO (IO (Event t a) -> Event t a) -> IO (Event t a) -> Event t a
forall a b. (a -> b) -> a -> b
$ do
Ptr CostCentreStack
stack <- Event t a -> IO (Ptr CostCentreStack)
forall dummy. dummy -> IO (Ptr CostCentreStack)
getCurrentCCS Event t a
e
let f :: a -> PushM t (Maybe a)
f x :: a
x = IO (PushM t (Maybe a)) -> PushM t (Maybe a)
forall a. IO a -> a
unsafePerformIO (IO (PushM t (Maybe a)) -> PushM t (Maybe a))
-> IO (PushM t (Maybe a)) -> PushM t (Maybe a)
forall a b. (a -> b) -> a -> b
$ do
IORef (Map (Ptr CostCentreStack) Int)
-> (Map (Ptr CostCentreStack) Int -> Map (Ptr CostCentreStack) Int)
-> IO ()
forall a. IORef a -> (a -> a) -> IO ()
modifyIORef' IORef (Map (Ptr CostCentreStack) Int)
profilingData ((Map (Ptr CostCentreStack) Int -> Map (Ptr CostCentreStack) Int)
-> IO ())
-> (Map (Ptr CostCentreStack) Int -> Map (Ptr CostCentreStack) Int)
-> IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> Int -> Int)
-> Ptr CostCentreStack
-> Int
-> Map (Ptr CostCentreStack) Int
-> Map (Ptr CostCentreStack) Int
forall k a. Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a
Map.insertWith Int -> Int -> Int
forall a. Num a => a -> a -> a
(+) Ptr CostCentreStack
stack 1
PushM t (Maybe a) -> IO (PushM t (Maybe a))
forall (m :: * -> *) a. Monad m => a -> m a
return (PushM t (Maybe a) -> IO (PushM t (Maybe a)))
-> PushM t (Maybe a) -> IO (PushM t (Maybe a))
forall a b. (a -> b) -> a -> b
$ Maybe a -> PushM t (Maybe a)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe a -> PushM t (Maybe a)) -> Maybe a -> PushM t (Maybe a)
forall a b. (a -> b) -> a -> b
$ a -> Maybe a
forall a. a -> Maybe a
Just a
x
Event t a -> IO (Event t a)
forall (m :: * -> *) a. Monad m => a -> m a
return (Event t a -> IO (Event t a)) -> Event t a -> IO (Event t a)
forall a b. (a -> b) -> a -> b
$ (a -> PushM t (Maybe a)) -> Event t a -> Event t a
forall k (t :: k) a b.
Reflex t =>
(a -> PushM t (Maybe b)) -> Event t a -> Event t b
pushCheap a -> PushM t (Maybe a)
f Event t a
e
instance Reflex t => Reflex (ProfiledTimeline t) where
newtype Behavior (ProfiledTimeline t) a = Behavior_Profiled { Behavior (ProfiledTimeline t) a -> Behavior t a
unBehavior_Profiled :: Behavior t a }
newtype Event (ProfiledTimeline t) a = Event_Profiled { Event (ProfiledTimeline t) a -> Event t a
unEvent_Profiled :: Event t a }
newtype Dynamic (ProfiledTimeline t) a = Dynamic_Profiled { Dynamic (ProfiledTimeline t) a -> Dynamic t a
unDynamic_Profiled :: Dynamic t a }
newtype Incremental (ProfiledTimeline t) p = Incremental_Profiled { Incremental (ProfiledTimeline t) p -> Incremental t p
unIncremental_Profiled :: Incremental t p }
type PushM (ProfiledTimeline t) = ProfiledM (PushM t)
type PullM (ProfiledTimeline t) = ProfiledM (PullM t)
never :: Event (ProfiledTimeline t) a
never = Event t a -> Event (ProfiledTimeline t) a
forall k (t :: k) a. Event t a -> Event (ProfiledTimeline t) a
Event_Profiled Event t a
forall k (t :: k) a. Reflex t => Event t a
never
constant :: a -> Behavior (ProfiledTimeline t) a
constant = Behavior t a -> Behavior (ProfiledTimeline t) a
forall k (t :: k) a.
Behavior t a -> Behavior (ProfiledTimeline t) a
Behavior_Profiled (Behavior t a -> Behavior (ProfiledTimeline t) a)
-> (a -> Behavior t a) -> a -> Behavior (ProfiledTimeline t) a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Behavior t a
forall k (t :: k) a. Reflex t => a -> Behavior t a
constant
push :: (a -> PushM (ProfiledTimeline t) (Maybe b))
-> Event (ProfiledTimeline t) a -> Event (ProfiledTimeline t) b
push f :: a -> PushM (ProfiledTimeline t) (Maybe b)
f (Event_Profiled e) = Event t b -> Event (ProfiledTimeline t) b
forall a b. Coercible a b => a -> b
coerce (Event t b -> Event (ProfiledTimeline t) b)
-> Event t b -> Event (ProfiledTimeline t) b
forall a b. (a -> b) -> a -> b
$ (a -> PushM t (Maybe b)) -> Event t a -> Event t b
forall k (t :: k) a b.
Reflex t =>
(a -> PushM t (Maybe b)) -> Event t a -> Event t b
push ((a -> ProfiledM (PushM t) (Maybe b)) -> a -> PushM t (Maybe b)
forall a b. Coercible a b => a -> b
coerce a -> PushM (ProfiledTimeline t) (Maybe b)
a -> ProfiledM (PushM t) (Maybe b)
f) (Event t a -> Event t b) -> Event t a -> Event t b
forall a b. (a -> b) -> a -> b
$ Event t a -> Event t a
forall k (t :: k) a. Reflex t => Event t a -> Event t a
profileEvent Event t a
e
pushCheap :: (a -> PushM (ProfiledTimeline t) (Maybe b))
-> Event (ProfiledTimeline t) a -> Event (ProfiledTimeline t) b
pushCheap f :: a -> PushM (ProfiledTimeline t) (Maybe b)
f (Event_Profiled e) = Event t b -> Event (ProfiledTimeline t) b
forall a b. Coercible a b => a -> b
coerce (Event t b -> Event (ProfiledTimeline t) b)
-> Event t b -> Event (ProfiledTimeline t) b
forall a b. (a -> b) -> a -> b
$ (a -> PushM t (Maybe b)) -> Event t a -> Event t b
forall k (t :: k) a b.
Reflex t =>
(a -> PushM t (Maybe b)) -> Event t a -> Event t b
pushCheap ((a -> ProfiledM (PushM t) (Maybe b)) -> a -> PushM t (Maybe b)
forall a b. Coercible a b => a -> b
coerce a -> PushM (ProfiledTimeline t) (Maybe b)
a -> ProfiledM (PushM t) (Maybe b)
f) (Event t a -> Event t b) -> Event t a -> Event t b
forall a b. (a -> b) -> a -> b
$ Event t a -> Event t a
forall k (t :: k) a. Reflex t => Event t a -> Event t a
profileEvent Event t a
e
pull :: PullM (ProfiledTimeline t) a -> Behavior (ProfiledTimeline t) a
pull = Behavior t a -> Behavior (ProfiledTimeline t) a
forall k (t :: k) a.
Behavior t a -> Behavior (ProfiledTimeline t) a
Behavior_Profiled (Behavior t a -> Behavior (ProfiledTimeline t) a)
-> (ProfiledM (PullM t) a -> Behavior t a)
-> ProfiledM (PullM t) a
-> Behavior (ProfiledTimeline t) a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PullM t a -> Behavior t a
forall k (t :: k) a. Reflex t => PullM t a -> Behavior t a
pull (PullM t a -> Behavior t a)
-> (ProfiledM (PullM t) a -> PullM t a)
-> ProfiledM (PullM t) a
-> Behavior t a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProfiledM (PullM t) a -> PullM t a
forall a b. Coercible a b => a -> b
coerce
fanG :: Event (ProfiledTimeline t) (DMap k v)
-> EventSelectorG (ProfiledTimeline t) k v
fanG (Event_Profiled e) = (forall (a :: k). k a -> Event (ProfiledTimeline t) (v a))
-> EventSelectorG (ProfiledTimeline t) k v
forall k k (t :: k) (k :: k -> *) (v :: k -> *).
(forall (a :: k). k a -> Event t (v a)) -> EventSelectorG t k v
EventSelectorG ((forall (a :: k). k a -> Event (ProfiledTimeline t) (v a))
-> EventSelectorG (ProfiledTimeline t) k v)
-> (forall (a :: k). k a -> Event (ProfiledTimeline t) (v a))
-> EventSelectorG (ProfiledTimeline t) k v
forall a b. (a -> b) -> a -> b
$ (k a -> Event t (v a)) -> k a -> Event (ProfiledTimeline t) (v a)
forall a b. Coercible a b => a -> b
coerce ((k a -> Event t (v a)) -> k a -> Event (ProfiledTimeline t) (v a))
-> (k a -> Event t (v a))
-> k a
-> Event (ProfiledTimeline t) (v a)
forall a b. (a -> b) -> a -> b
$ EventSelectorG t k v -> forall (a :: k). k a -> Event t (v a)
forall k (t :: k) k (k :: k -> *) (v :: k -> *).
EventSelectorG t k v -> forall (a :: k). k a -> Event t (v a)
selectG (Event t (DMap k v) -> EventSelectorG t k v
forall k (t :: k) k (k :: k -> *) (v :: k -> *).
(Reflex t, GCompare k) =>
Event t (DMap k v) -> EventSelectorG t k v
fanG (Event t (DMap k v) -> EventSelectorG t k v)
-> Event t (DMap k v) -> EventSelectorG t k v
forall a b. (a -> b) -> a -> b
$ Event t (DMap k v) -> Event t (DMap k v)
forall k (t :: k) a. Reflex t => Event t a -> Event t a
profileEvent Event t (DMap k v)
e)
mergeG :: forall (k :: z -> *) q v. GCompare k
=> (forall a. q a -> Event (ProfiledTimeline t) (v a))
-> DMap k q -> Event (ProfiledTimeline t) (DMap k v)
mergeG :: (forall (a :: z). q a -> Event (ProfiledTimeline t) (v a))
-> DMap k q -> Event (ProfiledTimeline t) (DMap k v)
mergeG nt :: forall (a :: z). q a -> Event (ProfiledTimeline t) (v a)
nt = Event t (DMap k v) -> Event (ProfiledTimeline t) (DMap k v)
forall k (t :: k) a. Event t a -> Event (ProfiledTimeline t) a
Event_Profiled (Event t (DMap k v) -> Event (ProfiledTimeline t) (DMap k v))
-> (DMap k q -> Event t (DMap k v))
-> DMap k q
-> Event (ProfiledTimeline t) (DMap k v)
forall (p :: * -> * -> *) a b c (q :: * -> * -> *).
(Profunctor p, Coercible c b) =>
q b c -> p a b -> p a c
#. (forall (a :: z). q a -> Event t (v a))
-> DMap k q -> Event t (DMap k v)
forall k (t :: k) k (k :: k -> *) (q :: k -> *) (v :: k -> *).
(Reflex t, GCompare k) =>
(forall (a :: k). q a -> Event t (v a))
-> DMap k q -> Event t (DMap k v)
mergeG ((q a -> Event (ProfiledTimeline t) (v a)) -> q a -> Event t (v a)
forall a b. Coercible a b => a -> b
coerce q a -> Event (ProfiledTimeline t) (v a)
forall (a :: z). q a -> Event (ProfiledTimeline t) (v a)
nt)
switch :: Behavior (ProfiledTimeline t) (Event (ProfiledTimeline t) a)
-> Event (ProfiledTimeline t) a
switch (Behavior_Profiled b) = Event t a -> Event (ProfiledTimeline t) a
forall a b. Coercible a b => a -> b
coerce (Event t a -> Event (ProfiledTimeline t) a)
-> Event t a -> Event (ProfiledTimeline t) a
forall a b. (a -> b) -> a -> b
$ Event t a -> Event t a
forall k (t :: k) a. Reflex t => Event t a -> Event t a
profileEvent (Event t a -> Event t a) -> Event t a -> Event t a
forall a b. (a -> b) -> a -> b
$ Behavior t (Event t a) -> Event t a
forall k (t :: k) a.
Reflex t =>
Behavior t (Event t a) -> Event t a
switch (Behavior t (Event (ProfiledTimeline t) a) -> Behavior t (Event t a)
forall k (t :: k) a b.
(Reflex t, Coercible a b) =>
Behavior t a -> Behavior t b
coerceBehavior Behavior t (Event (ProfiledTimeline t) a)
b)
coincidence :: Event (ProfiledTimeline t) (Event (ProfiledTimeline t) a)
-> Event (ProfiledTimeline t) a
coincidence (Event_Profiled e) = Event t a -> Event (ProfiledTimeline t) a
forall a b. Coercible a b => a -> b
coerce (Event t a -> Event (ProfiledTimeline t) a)
-> Event t a -> Event (ProfiledTimeline t) a
forall a b. (a -> b) -> a -> b
$ Event t a -> Event t a
forall k (t :: k) a. Reflex t => Event t a -> Event t a
profileEvent (Event t a -> Event t a) -> Event t a -> Event t a
forall a b. (a -> b) -> a -> b
$ Event t (Event t a) -> Event t a
forall k (t :: k) a. Reflex t => Event t (Event t a) -> Event t a
coincidence (Event t (Event (ProfiledTimeline t) a) -> Event t (Event t a)
forall k (t :: k) a b.
(Reflex t, Coercible a b) =>
Event t a -> Event t b
coerceEvent Event t (Event (ProfiledTimeline t) a)
e)
current :: Dynamic (ProfiledTimeline t) a -> Behavior (ProfiledTimeline t) a
current (Dynamic_Profiled d) = Behavior t a -> Behavior (ProfiledTimeline t) a
forall a b. Coercible a b => a -> b
coerce (Behavior t a -> Behavior (ProfiledTimeline t) a)
-> Behavior t a -> Behavior (ProfiledTimeline t) a
forall a b. (a -> b) -> a -> b
$ Dynamic t a -> Behavior t a
forall k (t :: k) a. Reflex t => Dynamic t a -> Behavior t a
current Dynamic t a
d
updated :: Dynamic (ProfiledTimeline t) a -> Event (ProfiledTimeline t) a
updated (Dynamic_Profiled d) = Event t a -> Event (ProfiledTimeline t) a
forall a b. Coercible a b => a -> b
coerce (Event t a -> Event (ProfiledTimeline t) a)
-> Event t a -> Event (ProfiledTimeline t) a
forall a b. (a -> b) -> a -> b
$ Event t a -> Event t a
forall k (t :: k) a. Reflex t => Event t a -> Event t a
profileEvent (Event t a -> Event t a) -> Event t a -> Event t a
forall a b. (a -> b) -> a -> b
$ Dynamic t a -> Event t a
forall k (t :: k) a. Reflex t => Dynamic t a -> Event t a
updated Dynamic t a
d
unsafeBuildDynamic :: PullM (ProfiledTimeline t) a
-> Event (ProfiledTimeline t) a -> Dynamic (ProfiledTimeline t) a
unsafeBuildDynamic (ProfiledM a0) (Event_Profiled a') = Dynamic t a -> Dynamic (ProfiledTimeline t) a
forall a b. Coercible a b => a -> b
coerce (Dynamic t a -> Dynamic (ProfiledTimeline t) a)
-> Dynamic t a -> Dynamic (ProfiledTimeline t) a
forall a b. (a -> b) -> a -> b
$ PullM t a -> Event t a -> Dynamic t a
forall k (t :: k) a.
Reflex t =>
PullM t a -> Event t a -> Dynamic t a
unsafeBuildDynamic PullM t a
a0 Event t a
a'
unsafeBuildIncremental :: PullM (ProfiledTimeline t) (PatchTarget p)
-> Event (ProfiledTimeline t) p
-> Incremental (ProfiledTimeline t) p
unsafeBuildIncremental (ProfiledM a0) (Event_Profiled a') = Incremental t p -> Incremental (ProfiledTimeline t) p
forall a b. Coercible a b => a -> b
coerce (Incremental t p -> Incremental (ProfiledTimeline t) p)
-> Incremental t p -> Incremental (ProfiledTimeline t) p
forall a b. (a -> b) -> a -> b
$ PullM t (PatchTarget p) -> Event t p -> Incremental t p
forall k (t :: k) p.
(Reflex t, Patch p) =>
PullM t (PatchTarget p) -> Event t p -> Incremental t p
unsafeBuildIncremental PullM t (PatchTarget p)
a0 Event t p
a'
mergeIncrementalG :: (forall (a :: k). q a -> Event (ProfiledTimeline t) (v a))
-> Incremental (ProfiledTimeline t) (PatchDMap k q)
-> Event (ProfiledTimeline t) (DMap k v)
mergeIncrementalG nt :: forall (a :: k). q a -> Event (ProfiledTimeline t) (v a)
nt res :: Incremental (ProfiledTimeline t) (PatchDMap k q)
res = Event t (DMap k v) -> Event (ProfiledTimeline t) (DMap k v)
forall k (t :: k) a. Event t a -> Event (ProfiledTimeline t) a
Event_Profiled (Event t (DMap k v) -> Event (ProfiledTimeline t) (DMap k v))
-> Event t (DMap k v) -> Event (ProfiledTimeline t) (DMap k v)
forall a b. (a -> b) -> a -> b
$ (forall (a :: k). q a -> Event t (v a))
-> Incremental t (PatchDMap k q) -> Event t (DMap k v)
forall k (t :: k) k (k :: k -> *) (q :: k -> *) (v :: k -> *).
(Reflex t, GCompare k) =>
(forall (a :: k). q a -> Event t (v a))
-> Incremental t (PatchDMap k q) -> Event t (DMap k v)
mergeIncrementalG ((q a -> Event (ProfiledTimeline t) (v a)) -> q a -> Event t (v a)
forall a b. Coercible a b => a -> b
coerce q a -> Event (ProfiledTimeline t) (v a)
forall (a :: k). q a -> Event (ProfiledTimeline t) (v a)
nt) (Incremental (ProfiledTimeline t) (PatchDMap k q)
-> Incremental t (PatchDMap k q)
forall a b. Coercible a b => a -> b
coerce Incremental (ProfiledTimeline t) (PatchDMap k q)
res)
mergeIncrementalWithMoveG :: (forall (a :: k). q a -> Event (ProfiledTimeline t) (v a))
-> Incremental (ProfiledTimeline t) (PatchDMapWithMove k q)
-> Event (ProfiledTimeline t) (DMap k v)
mergeIncrementalWithMoveG nt :: forall (a :: k). q a -> Event (ProfiledTimeline t) (v a)
nt res :: Incremental (ProfiledTimeline t) (PatchDMapWithMove k q)
res = Event t (DMap k v) -> Event (ProfiledTimeline t) (DMap k v)
forall k (t :: k) a. Event t a -> Event (ProfiledTimeline t) a
Event_Profiled (Event t (DMap k v) -> Event (ProfiledTimeline t) (DMap k v))
-> Event t (DMap k v) -> Event (ProfiledTimeline t) (DMap k v)
forall a b. (a -> b) -> a -> b
$ (forall (a :: k). q a -> Event t (v a))
-> Incremental t (PatchDMapWithMove k q) -> Event t (DMap k v)
forall k (t :: k) k (k :: k -> *) (q :: k -> *) (v :: k -> *).
(Reflex t, GCompare k) =>
(forall (a :: k). q a -> Event t (v a))
-> Incremental t (PatchDMapWithMove k q) -> Event t (DMap k v)
mergeIncrementalWithMoveG ((q a -> Event (ProfiledTimeline t) (v a)) -> q a -> Event t (v a)
forall a b. Coercible a b => a -> b
coerce q a -> Event (ProfiledTimeline t) (v a)
forall (a :: k). q a -> Event (ProfiledTimeline t) (v a)
nt) (Incremental (ProfiledTimeline t) (PatchDMapWithMove k q)
-> Incremental t (PatchDMapWithMove k q)
forall a b. Coercible a b => a -> b
coerce Incremental (ProfiledTimeline t) (PatchDMapWithMove k q)
res)
currentIncremental :: Incremental (ProfiledTimeline t) p
-> Behavior (ProfiledTimeline t) (PatchTarget p)
currentIncremental (Incremental_Profiled i) = Behavior t (PatchTarget p)
-> Behavior (ProfiledTimeline t) (PatchTarget p)
forall a b. Coercible a b => a -> b
coerce (Behavior t (PatchTarget p)
-> Behavior (ProfiledTimeline t) (PatchTarget p))
-> Behavior t (PatchTarget p)
-> Behavior (ProfiledTimeline t) (PatchTarget p)
forall a b. (a -> b) -> a -> b
$ Incremental t p -> Behavior t (PatchTarget p)
forall k (t :: k) p.
(Reflex t, Patch p) =>
Incremental t p -> Behavior t (PatchTarget p)
currentIncremental Incremental t p
i
updatedIncremental :: Incremental (ProfiledTimeline t) p -> Event (ProfiledTimeline t) p
updatedIncremental (Incremental_Profiled i) = Event t p -> Event (ProfiledTimeline t) p
forall a b. Coercible a b => a -> b
coerce (Event t p -> Event (ProfiledTimeline t) p)
-> Event t p -> Event (ProfiledTimeline t) p
forall a b. (a -> b) -> a -> b
$ Event t p -> Event t p
forall k (t :: k) a. Reflex t => Event t a -> Event t a
profileEvent (Event t p -> Event t p) -> Event t p -> Event t p
forall a b. (a -> b) -> a -> b
$ Incremental t p -> Event t p
forall k (t :: k) p.
(Reflex t, Patch p) =>
Incremental t p -> Event t p
updatedIncremental Incremental t p
i
incrementalToDynamic :: Incremental (ProfiledTimeline t) p
-> Dynamic (ProfiledTimeline t) (PatchTarget p)
incrementalToDynamic (Incremental_Profiled i) = Dynamic t (PatchTarget p)
-> Dynamic (ProfiledTimeline t) (PatchTarget p)
forall a b. Coercible a b => a -> b
coerce (Dynamic t (PatchTarget p)
-> Dynamic (ProfiledTimeline t) (PatchTarget p))
-> Dynamic t (PatchTarget p)
-> Dynamic (ProfiledTimeline t) (PatchTarget p)
forall a b. (a -> b) -> a -> b
$ Incremental t p -> Dynamic t (PatchTarget p)
forall k (t :: k) p.
(Reflex t, Patch p) =>
Incremental t p -> Dynamic t (PatchTarget p)
incrementalToDynamic Incremental t p
i
behaviorCoercion :: Coercion a b
-> Coercion
(Behavior (ProfiledTimeline t) a) (Behavior (ProfiledTimeline t) b)
behaviorCoercion c :: Coercion a b
c =
Coercion (Behavior (ProfiledTimeline t) a) (Behavior t a)
forall k (a :: k) (b :: k). Coercible a b => Coercion a b
Coercion Coercion (Behavior (ProfiledTimeline t) a) (Behavior t a)
-> Coercion (Behavior t a) (Behavior t b)
-> Coercion (Behavior (ProfiledTimeline t) a) (Behavior t b)
forall k (a :: k) (b :: k) (c :: k).
Coercion a b -> Coercion b c -> Coercion a c
`trans` Coercion a b -> Coercion (Behavior t a) (Behavior t b)
forall k (t :: k) a b.
Reflex t =>
Coercion a b -> Coercion (Behavior t a) (Behavior t b)
behaviorCoercion @t Coercion a b
c Coercion (Behavior (ProfiledTimeline t) a) (Behavior t b)
-> Coercion (Behavior t b) (Behavior (ProfiledTimeline t) b)
-> Coercion
(Behavior (ProfiledTimeline t) a) (Behavior (ProfiledTimeline t) b)
forall k (a :: k) (b :: k) (c :: k).
Coercion a b -> Coercion b c -> Coercion a c
`trans` Coercion (Behavior t b) (Behavior (ProfiledTimeline t) b)
forall k (a :: k) (b :: k). Coercible a b => Coercion a b
Coercion
eventCoercion :: Coercion a b
-> Coercion
(Event (ProfiledTimeline t) a) (Event (ProfiledTimeline t) b)
eventCoercion c :: Coercion a b
c =
Coercion (Event (ProfiledTimeline t) a) (Event t a)
forall k (a :: k) (b :: k). Coercible a b => Coercion a b
Coercion Coercion (Event (ProfiledTimeline t) a) (Event t a)
-> Coercion (Event t a) (Event t b)
-> Coercion (Event (ProfiledTimeline t) a) (Event t b)
forall k (a :: k) (b :: k) (c :: k).
Coercion a b -> Coercion b c -> Coercion a c
`trans` Coercion a b -> Coercion (Event t a) (Event t b)
forall k (t :: k) a b.
Reflex t =>
Coercion a b -> Coercion (Event t a) (Event t b)
eventCoercion @t Coercion a b
c Coercion (Event (ProfiledTimeline t) a) (Event t b)
-> Coercion (Event t b) (Event (ProfiledTimeline t) b)
-> Coercion
(Event (ProfiledTimeline t) a) (Event (ProfiledTimeline t) b)
forall k (a :: k) (b :: k) (c :: k).
Coercion a b -> Coercion b c -> Coercion a c
`trans` Coercion (Event t b) (Event (ProfiledTimeline t) b)
forall k (a :: k) (b :: k). Coercible a b => Coercion a b
Coercion
dynamicCoercion :: Coercion a b
-> Coercion
(Dynamic (ProfiledTimeline t) a) (Dynamic (ProfiledTimeline t) b)
dynamicCoercion c :: Coercion a b
c =
Coercion (Dynamic (ProfiledTimeline t) a) (Dynamic t a)
forall k (a :: k) (b :: k). Coercible a b => Coercion a b
Coercion Coercion (Dynamic (ProfiledTimeline t) a) (Dynamic t a)
-> Coercion (Dynamic t a) (Dynamic t b)
-> Coercion (Dynamic (ProfiledTimeline t) a) (Dynamic t b)
forall k (a :: k) (b :: k) (c :: k).
Coercion a b -> Coercion b c -> Coercion a c
`trans` Coercion a b -> Coercion (Dynamic t a) (Dynamic t b)
forall k (t :: k) a b.
Reflex t =>
Coercion a b -> Coercion (Dynamic t a) (Dynamic t b)
dynamicCoercion @t Coercion a b
c Coercion (Dynamic (ProfiledTimeline t) a) (Dynamic t b)
-> Coercion (Dynamic t b) (Dynamic (ProfiledTimeline t) b)
-> Coercion
(Dynamic (ProfiledTimeline t) a) (Dynamic (ProfiledTimeline t) b)
forall k (a :: k) (b :: k) (c :: k).
Coercion a b -> Coercion b c -> Coercion a c
`trans` Coercion (Dynamic t b) (Dynamic (ProfiledTimeline t) b)
forall k (a :: k) (b :: k). Coercible a b => Coercion a b
Coercion
incrementalCoercion :: Coercion (PatchTarget a) (PatchTarget b)
-> Coercion a b
-> Coercion
(Incremental (ProfiledTimeline t) a)
(Incremental (ProfiledTimeline t) b)
incrementalCoercion c :: Coercion (PatchTarget a) (PatchTarget b)
c d :: Coercion a b
d =
Coercion (Incremental (ProfiledTimeline t) a) (Incremental t a)
forall k (a :: k) (b :: k). Coercible a b => Coercion a b
Coercion Coercion (Incremental (ProfiledTimeline t) a) (Incremental t a)
-> Coercion (Incremental t a) (Incremental t b)
-> Coercion (Incremental (ProfiledTimeline t) a) (Incremental t b)
forall k (a :: k) (b :: k) (c :: k).
Coercion a b -> Coercion b c -> Coercion a c
`trans` Coercion (PatchTarget a) (PatchTarget b)
-> Coercion a b -> Coercion (Incremental t a) (Incremental t b)
forall k (t :: k) a b.
Reflex t =>
Coercion (PatchTarget a) (PatchTarget b)
-> Coercion a b -> Coercion (Incremental t a) (Incremental t b)
incrementalCoercion @t Coercion (PatchTarget a) (PatchTarget b)
c Coercion a b
d Coercion (Incremental (ProfiledTimeline t) a) (Incremental t b)
-> Coercion (Incremental t b) (Incremental (ProfiledTimeline t) b)
-> Coercion
(Incremental (ProfiledTimeline t) a)
(Incremental (ProfiledTimeline t) b)
forall k (a :: k) (b :: k) (c :: k).
Coercion a b -> Coercion b c -> Coercion a c
`trans` Coercion (Incremental t b) (Incremental (ProfiledTimeline t) b)
forall k (a :: k) (b :: k). Coercible a b => Coercion a b
Coercion
mergeIntIncremental :: Incremental
(ProfiledTimeline t) (PatchIntMap (Event (ProfiledTimeline t) a))
-> Event (ProfiledTimeline t) (IntMap a)
mergeIntIncremental = Event t (IntMap a) -> Event (ProfiledTimeline t) (IntMap a)
forall k (t :: k) a. Event t a -> Event (ProfiledTimeline t) a
Event_Profiled (Event t (IntMap a) -> Event (ProfiledTimeline t) (IntMap a))
-> (Incremental
(ProfiledTimeline t) (PatchIntMap (Event (ProfiledTimeline t) a))
-> Event t (IntMap a))
-> Incremental
(ProfiledTimeline t) (PatchIntMap (Event (ProfiledTimeline t) a))
-> Event (ProfiledTimeline t) (IntMap a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Incremental t (PatchIntMap (Event t a)) -> Event t (IntMap a)
forall k (t :: k) a.
Reflex t =>
Incremental t (PatchIntMap (Event t a)) -> Event t (IntMap a)
mergeIntIncremental (Incremental t (PatchIntMap (Event t a)) -> Event t (IntMap a))
-> (Incremental
(ProfiledTimeline t) (PatchIntMap (Event (ProfiledTimeline t) a))
-> Incremental t (PatchIntMap (Event t a)))
-> Incremental
(ProfiledTimeline t) (PatchIntMap (Event (ProfiledTimeline t) a))
-> Event t (IntMap a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Coercion
(Incremental
(ProfiledTimeline t) (PatchIntMap (Event (ProfiledTimeline t) a)))
(Incremental t (PatchIntMap (Event t a)))
-> Incremental
(ProfiledTimeline t) (PatchIntMap (Event (ProfiledTimeline t) a))
-> Incremental t (PatchIntMap (Event t a))
forall a b. Coercion a b -> a -> b
coerceWith (Coercion
(Incremental
(ProfiledTimeline t) (PatchIntMap (Event (ProfiledTimeline t) a)))
(Incremental t (PatchIntMap (Event (ProfiledTimeline t) a)))
forall k (a :: k) (b :: k). Coercible a b => Coercion a b
Coercion Coercion
(Incremental
(ProfiledTimeline t) (PatchIntMap (Event (ProfiledTimeline t) a)))
(Incremental t (PatchIntMap (Event (ProfiledTimeline t) a)))
-> Coercion
(Incremental t (PatchIntMap (Event (ProfiledTimeline t) a)))
(Incremental t (PatchIntMap (Event t a)))
-> Coercion
(Incremental
(ProfiledTimeline t) (PatchIntMap (Event (ProfiledTimeline t) a)))
(Incremental t (PatchIntMap (Event t a)))
forall k (a :: k) (b :: k) (c :: k).
Coercion a b -> Coercion b c -> Coercion a c
`trans` Coercion
(PatchTarget (PatchIntMap (Event (ProfiledTimeline t) a)))
(PatchTarget (PatchIntMap (Event t a)))
-> Coercion
(PatchIntMap (Event (ProfiledTimeline t) a))
(PatchIntMap (Event t a))
-> Coercion
(Incremental t (PatchIntMap (Event (ProfiledTimeline t) a)))
(Incremental t (PatchIntMap (Event t a)))
forall k (t :: k) a b.
Reflex t =>
Coercion (PatchTarget a) (PatchTarget b)
-> Coercion a b -> Coercion (Incremental t a) (Incremental t b)
incrementalCoercion Coercion
(PatchTarget (PatchIntMap (Event (ProfiledTimeline t) a)))
(PatchTarget (PatchIntMap (Event t a)))
forall k (a :: k) (b :: k). Coercible a b => Coercion a b
Coercion Coercion
(PatchIntMap (Event (ProfiledTimeline t) a))
(PatchIntMap (Event t a))
forall k (a :: k) (b :: k). Coercible a b => Coercion a b
Coercion Coercion
(Incremental
(ProfiledTimeline t) (PatchIntMap (Event (ProfiledTimeline t) a)))
(Incremental t (PatchIntMap (Event t a)))
-> Coercion
(Incremental t (PatchIntMap (Event t a)))
(Incremental t (PatchIntMap (Event t a)))
-> Coercion
(Incremental
(ProfiledTimeline t) (PatchIntMap (Event (ProfiledTimeline t) a)))
(Incremental t (PatchIntMap (Event t a)))
forall k (a :: k) (b :: k) (c :: k).
Coercion a b -> Coercion b c -> Coercion a c
`trans` Coercion
(Incremental t (PatchIntMap (Event t a)))
(Incremental t (PatchIntMap (Event t a)))
forall k (a :: k) (b :: k). Coercible a b => Coercion a b
Coercion)
fanInt :: Event (ProfiledTimeline t) (IntMap a)
-> EventSelectorInt (ProfiledTimeline t) a
fanInt (Event_Profiled e) = EventSelectorInt t a -> EventSelectorInt (ProfiledTimeline t) a
forall a b. Coercible a b => a -> b
coerce (EventSelectorInt t a -> EventSelectorInt (ProfiledTimeline t) a)
-> EventSelectorInt t a -> EventSelectorInt (ProfiledTimeline t) a
forall a b. (a -> b) -> a -> b
$ Event t (IntMap a) -> EventSelectorInt t a
forall k (t :: k) a.
Reflex t =>
Event t (IntMap a) -> EventSelectorInt t a
fanInt (Event t (IntMap a) -> EventSelectorInt t a)
-> Event t (IntMap a) -> EventSelectorInt t a
forall a b. (a -> b) -> a -> b
$ Event t (IntMap a) -> Event t (IntMap a)
forall k (t :: k) a. Reflex t => Event t a -> Event t a
profileEvent Event t (IntMap a)
e
deriving instance Functor (Dynamic t) => Functor (Dynamic (ProfiledTimeline t))
deriving instance Applicative (Dynamic t) => Applicative (Dynamic (ProfiledTimeline t))
deriving instance Monad (Dynamic t) => Monad (Dynamic (ProfiledTimeline t))
instance MonadHold t m => MonadHold (ProfiledTimeline t) (ProfiledM m) where
hold :: a
-> Event (ProfiledTimeline t) a
-> ProfiledM m (Behavior (ProfiledTimeline t) a)
hold v0 :: a
v0 (Event_Profiled v') = m (Behavior (ProfiledTimeline t) a)
-> ProfiledM m (Behavior (ProfiledTimeline t) a)
forall k (m :: k -> *) (a :: k). m a -> ProfiledM m a
ProfiledM (m (Behavior (ProfiledTimeline t) a)
-> ProfiledM m (Behavior (ProfiledTimeline t) a))
-> m (Behavior (ProfiledTimeline t) a)
-> ProfiledM m (Behavior (ProfiledTimeline t) a)
forall a b. (a -> b) -> a -> b
$ Behavior t a -> Behavior (ProfiledTimeline t) a
forall k (t :: k) a.
Behavior t a -> Behavior (ProfiledTimeline t) a
Behavior_Profiled (Behavior t a -> Behavior (ProfiledTimeline t) a)
-> m (Behavior t a) -> m (Behavior (ProfiledTimeline t) a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f 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'
holdDyn :: a
-> Event (ProfiledTimeline t) a
-> ProfiledM m (Dynamic (ProfiledTimeline t) a)
holdDyn v0 :: a
v0 (Event_Profiled v') = m (Dynamic (ProfiledTimeline t) a)
-> ProfiledM m (Dynamic (ProfiledTimeline t) a)
forall k (m :: k -> *) (a :: k). m a -> ProfiledM m a
ProfiledM (m (Dynamic (ProfiledTimeline t) a)
-> ProfiledM m (Dynamic (ProfiledTimeline t) a))
-> m (Dynamic (ProfiledTimeline t) a)
-> ProfiledM m (Dynamic (ProfiledTimeline t) a)
forall a b. (a -> b) -> a -> b
$ Dynamic t a -> Dynamic (ProfiledTimeline t) a
forall k (t :: k) a. Dynamic t a -> Dynamic (ProfiledTimeline t) a
Dynamic_Profiled (Dynamic t a -> Dynamic (ProfiledTimeline t) a)
-> m (Dynamic t a) -> m (Dynamic (ProfiledTimeline t) a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f 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'
holdIncremental :: PatchTarget p
-> Event (ProfiledTimeline t) p
-> ProfiledM m (Incremental (ProfiledTimeline t) p)
holdIncremental v0 :: PatchTarget p
v0 (Event_Profiled v') = m (Incremental (ProfiledTimeline t) p)
-> ProfiledM m (Incremental (ProfiledTimeline t) p)
forall k (m :: k -> *) (a :: k). m a -> ProfiledM m a
ProfiledM (m (Incremental (ProfiledTimeline t) p)
-> ProfiledM m (Incremental (ProfiledTimeline t) p))
-> m (Incremental (ProfiledTimeline t) p)
-> ProfiledM m (Incremental (ProfiledTimeline t) p)
forall a b. (a -> b) -> a -> b
$ Incremental t p -> Incremental (ProfiledTimeline t) p
forall k (t :: k) p.
Incremental t p -> Incremental (ProfiledTimeline t) p
Incremental_Profiled (Incremental t p -> Incremental (ProfiledTimeline t) p)
-> m (Incremental t p) -> m (Incremental (ProfiledTimeline t) p)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f 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'
buildDynamic :: PushM (ProfiledTimeline t) a
-> Event (ProfiledTimeline t) a
-> ProfiledM m (Dynamic (ProfiledTimeline t) a)
buildDynamic (ProfiledM v0) (Event_Profiled v') = m (Dynamic (ProfiledTimeline t) a)
-> ProfiledM m (Dynamic (ProfiledTimeline t) a)
forall k (m :: k -> *) (a :: k). m a -> ProfiledM m a
ProfiledM (m (Dynamic (ProfiledTimeline t) a)
-> ProfiledM m (Dynamic (ProfiledTimeline t) a))
-> m (Dynamic (ProfiledTimeline t) a)
-> ProfiledM m (Dynamic (ProfiledTimeline t) a)
forall a b. (a -> b) -> a -> b
$ Dynamic t a -> Dynamic (ProfiledTimeline t) a
forall k (t :: k) a. Dynamic t a -> Dynamic (ProfiledTimeline t) a
Dynamic_Profiled (Dynamic t a -> Dynamic (ProfiledTimeline t) a)
-> m (Dynamic t a) -> m (Dynamic (ProfiledTimeline t) a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> 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
v0 Event t a
v'
headE :: Event (ProfiledTimeline t) a
-> ProfiledM m (Event (ProfiledTimeline t) a)
headE (Event_Profiled e) = m (Event (ProfiledTimeline t) a)
-> ProfiledM m (Event (ProfiledTimeline t) a)
forall k (m :: k -> *) (a :: k). m a -> ProfiledM m a
ProfiledM (m (Event (ProfiledTimeline t) a)
-> ProfiledM m (Event (ProfiledTimeline t) a))
-> m (Event (ProfiledTimeline t) a)
-> ProfiledM m (Event (ProfiledTimeline t) a)
forall a b. (a -> b) -> a -> b
$ Event t a -> Event (ProfiledTimeline t) a
forall k (t :: k) a. Event t a -> Event (ProfiledTimeline t) a
Event_Profiled (Event t a -> Event (ProfiledTimeline t) a)
-> m (Event t a) -> m (Event (ProfiledTimeline t) a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Event t a -> m (Event t a)
forall k (t :: k) (m :: * -> *) a.
MonadHold t m =>
Event t a -> m (Event t a)
headE Event t a
e
instance MonadSample t m => MonadSample (ProfiledTimeline t) (ProfiledM m) where
sample :: Behavior (ProfiledTimeline t) a -> ProfiledM m a
sample (Behavior_Profiled b) = m a -> ProfiledM m a
forall k (m :: k -> *) (a :: k). m a -> ProfiledM m a
ProfiledM (m a -> ProfiledM m a) -> m a -> ProfiledM m a
forall a b. (a -> b) -> a -> b
$ Behavior t a -> m a
forall k (t :: k) (m :: * -> *) a.
MonadSample t m =>
Behavior t a -> m a
sample Behavior t a
b
instance Adjustable t m => Adjustable (ProfiledTimeline t) (ProfiledM m) where
runWithReplace :: ProfiledM m a
-> Event (ProfiledTimeline t) (ProfiledM m b)
-> ProfiledM m (a, Event (ProfiledTimeline t) b)
runWithReplace a0 :: ProfiledM m a
a0 a' :: Event (ProfiledTimeline t) (ProfiledM m b)
a' = (((a, Event t b) -> (a, Event (ProfiledTimeline t) b))
-> ProfiledM m (a, Event t b)
-> ProfiledM m (a, Event (ProfiledTimeline t) b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (((a, Event t b) -> (a, Event (ProfiledTimeline t) b))
-> ProfiledM m (a, Event t b)
-> ProfiledM m (a, Event (ProfiledTimeline t) b))
-> ((Event t b -> Event (ProfiledTimeline t) b)
-> (a, Event t b) -> (a, Event (ProfiledTimeline t) b))
-> (Event t b -> Event (ProfiledTimeline t) b)
-> ProfiledM m (a, Event t b)
-> ProfiledM m (a, Event (ProfiledTimeline t) b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Event t b -> Event (ProfiledTimeline t) b)
-> (a, Event t b) -> (a, Event (ProfiledTimeline t) b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap) Event t b -> Event (ProfiledTimeline t) b
forall a b. Coercible a b => a -> b
coerce (ProfiledM m (a, Event t b)
-> ProfiledM m (a, Event (ProfiledTimeline t) b))
-> (m (a, Event t b) -> ProfiledM m (a, Event t b))
-> m (a, Event t b)
-> ProfiledM m (a, Event (ProfiledTimeline t) b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. m (a, Event t b) -> ProfiledM m (a, Event t b)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (a, Event t b) -> ProfiledM m (a, Event (ProfiledTimeline t) b))
-> m (a, Event t b)
-> ProfiledM m (a, Event (ProfiledTimeline t) b)
forall a b. (a -> b) -> a -> b
$
m a -> Event t (m b) -> m (a, Event t b)
forall t (m :: * -> *) a b.
Adjustable t m =>
m a -> Event t (m b) -> m (a, Event t b)
runWithReplace (ProfiledM m a -> m a
forall a b. Coercible a b => a -> b
coerce ProfiledM m a
a0) (Event (ProfiledTimeline t) (m b) -> Event t (m b)
forall a b. Coercible a b => a -> b
coerce (Event (ProfiledTimeline t) (m b) -> Event t (m b))
-> Event (ProfiledTimeline t) (m b) -> Event t (m b)
forall a b. (a -> b) -> a -> b
$ ProfiledM m b -> m b
forall a b. Coercible a b => a -> b
coerce (ProfiledM m b -> m b)
-> Event (ProfiledTimeline t) (ProfiledM m b)
-> Event (ProfiledTimeline t) (m b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Event (ProfiledTimeline t) (ProfiledM m b)
a')
traverseIntMapWithKeyWithAdjust :: (Int -> v -> ProfiledM m v')
-> IntMap v
-> Event (ProfiledTimeline t) (PatchIntMap v)
-> ProfiledM
m (IntMap v', Event (ProfiledTimeline t) (PatchIntMap v'))
traverseIntMapWithKeyWithAdjust f :: Int -> v -> ProfiledM m v'
f dm0 :: IntMap v
dm0 dm' :: Event (ProfiledTimeline t) (PatchIntMap v)
dm' = (((IntMap v', Event t (PatchIntMap v'))
-> (IntMap v', Event (ProfiledTimeline t) (PatchIntMap v')))
-> ProfiledM m (IntMap v', Event t (PatchIntMap v'))
-> ProfiledM
m (IntMap v', Event (ProfiledTimeline t) (PatchIntMap v'))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (((IntMap v', Event t (PatchIntMap v'))
-> (IntMap v', Event (ProfiledTimeline t) (PatchIntMap v')))
-> ProfiledM m (IntMap v', Event t (PatchIntMap v'))
-> ProfiledM
m (IntMap v', Event (ProfiledTimeline t) (PatchIntMap v')))
-> ((Event t (PatchIntMap v')
-> Event (ProfiledTimeline t) (PatchIntMap v'))
-> (IntMap v', Event t (PatchIntMap v'))
-> (IntMap v', Event (ProfiledTimeline t) (PatchIntMap v')))
-> (Event t (PatchIntMap v')
-> Event (ProfiledTimeline t) (PatchIntMap v'))
-> ProfiledM m (IntMap v', Event t (PatchIntMap v'))
-> ProfiledM
m (IntMap v', Event (ProfiledTimeline t) (PatchIntMap v'))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Event t (PatchIntMap v')
-> Event (ProfiledTimeline t) (PatchIntMap v'))
-> (IntMap v', Event t (PatchIntMap v'))
-> (IntMap v', Event (ProfiledTimeline t) (PatchIntMap v'))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap) Event t (PatchIntMap v')
-> Event (ProfiledTimeline t) (PatchIntMap v')
forall a b. Coercible a b => a -> b
coerce (ProfiledM m (IntMap v', Event t (PatchIntMap v'))
-> ProfiledM
m (IntMap v', Event (ProfiledTimeline t) (PatchIntMap v')))
-> (m (IntMap v', Event t (PatchIntMap v'))
-> ProfiledM m (IntMap v', Event t (PatchIntMap v')))
-> m (IntMap v', Event t (PatchIntMap v'))
-> ProfiledM
m (IntMap v', Event (ProfiledTimeline t) (PatchIntMap v'))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. m (IntMap v', Event t (PatchIntMap v'))
-> ProfiledM m (IntMap v', Event t (PatchIntMap v'))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (IntMap v', Event t (PatchIntMap v'))
-> ProfiledM
m (IntMap v', Event (ProfiledTimeline t) (PatchIntMap v')))
-> m (IntMap v', Event t (PatchIntMap v'))
-> ProfiledM
m (IntMap v', Event (ProfiledTimeline t) (PatchIntMap v'))
forall a b. (a -> b) -> a -> b
$
(Int -> v -> m v')
-> IntMap v
-> Event t (PatchIntMap v)
-> m (IntMap v', Event t (PatchIntMap v'))
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 (\k :: Int
k v :: v
v -> ProfiledM m v' -> m v'
forall a b. Coercible a b => a -> b
coerce (ProfiledM m v' -> m v') -> ProfiledM m v' -> m v'
forall a b. (a -> b) -> a -> b
$ Int -> v -> ProfiledM m v'
f Int
k v
v) IntMap v
dm0 (Event (ProfiledTimeline t) (PatchIntMap v)
-> Event t (PatchIntMap v)
forall a b. Coercible a b => a -> b
coerce Event (ProfiledTimeline t) (PatchIntMap v)
dm')
traverseDMapWithKeyWithAdjust :: (forall a. k a -> v a -> ProfiledM m (v' a))
-> DMap k v
-> Event (ProfiledTimeline t) (PatchDMap k v)
-> ProfiledM
m (DMap k v', Event (ProfiledTimeline t) (PatchDMap k v'))
traverseDMapWithKeyWithAdjust f :: forall a. k a -> v a -> ProfiledM m (v' a)
f dm0 :: DMap k v
dm0 dm' :: Event (ProfiledTimeline t) (PatchDMap k v)
dm' = (((DMap k v', Event t (PatchDMap k v'))
-> (DMap k v', Event (ProfiledTimeline t) (PatchDMap k v')))
-> ProfiledM m (DMap k v', Event t (PatchDMap k v'))
-> ProfiledM
m (DMap k v', Event (ProfiledTimeline t) (PatchDMap k v'))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (((DMap k v', Event t (PatchDMap k v'))
-> (DMap k v', Event (ProfiledTimeline t) (PatchDMap k v')))
-> ProfiledM m (DMap k v', Event t (PatchDMap k v'))
-> ProfiledM
m (DMap k v', Event (ProfiledTimeline t) (PatchDMap k v')))
-> ((Event t (PatchDMap k v')
-> Event (ProfiledTimeline t) (PatchDMap k v'))
-> (DMap k v', Event t (PatchDMap k v'))
-> (DMap k v', Event (ProfiledTimeline t) (PatchDMap k v')))
-> (Event t (PatchDMap k v')
-> Event (ProfiledTimeline t) (PatchDMap k v'))
-> ProfiledM m (DMap k v', Event t (PatchDMap k v'))
-> ProfiledM
m (DMap k v', Event (ProfiledTimeline t) (PatchDMap k v'))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Event t (PatchDMap k v')
-> Event (ProfiledTimeline t) (PatchDMap k v'))
-> (DMap k v', Event t (PatchDMap k v'))
-> (DMap k v', Event (ProfiledTimeline t) (PatchDMap k v'))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap) Event t (PatchDMap k v')
-> Event (ProfiledTimeline t) (PatchDMap k v')
forall a b. Coercible a b => a -> b
coerce (ProfiledM m (DMap k v', Event t (PatchDMap k v'))
-> ProfiledM
m (DMap k v', Event (ProfiledTimeline t) (PatchDMap k v')))
-> (m (DMap k v', Event t (PatchDMap k v'))
-> ProfiledM m (DMap k v', Event t (PatchDMap k v')))
-> m (DMap k v', Event t (PatchDMap k v'))
-> ProfiledM
m (DMap k v', Event (ProfiledTimeline t) (PatchDMap k v'))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. m (DMap k v', Event t (PatchDMap k v'))
-> ProfiledM m (DMap k v', Event t (PatchDMap k v'))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (DMap k v', Event t (PatchDMap k v'))
-> ProfiledM
m (DMap k v', Event (ProfiledTimeline t) (PatchDMap k v')))
-> m (DMap k v', Event t (PatchDMap k v'))
-> ProfiledM
m (DMap k v', Event (ProfiledTimeline t) (PatchDMap k v'))
forall a b. (a -> b) -> a -> b
$
(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 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'))
traverseDMapWithKeyWithAdjust (\k :: k a
k v :: v a
v -> ProfiledM m (v' a) -> m (v' a)
forall a b. Coercible a b => a -> b
coerce (ProfiledM m (v' a) -> m (v' a)) -> ProfiledM m (v' a) -> m (v' a)
forall a b. (a -> b) -> a -> b
$ k a -> v a -> ProfiledM m (v' a)
forall a. k a -> v a -> ProfiledM m (v' a)
f k a
k v a
v) DMap k v
dm0 (Event (ProfiledTimeline t) (PatchDMap k v)
-> Event t (PatchDMap k v)
forall a b. Coercible a b => a -> b
coerce Event (ProfiledTimeline t) (PatchDMap k v)
dm')
traverseDMapWithKeyWithAdjustWithMove :: (forall a. k a -> v a -> ProfiledM m (v' a))
-> DMap k v
-> Event (ProfiledTimeline t) (PatchDMapWithMove k v)
-> ProfiledM
m (DMap k v', Event (ProfiledTimeline t) (PatchDMapWithMove k v'))
traverseDMapWithKeyWithAdjustWithMove f :: forall a. k a -> v a -> ProfiledM m (v' a)
f dm0 :: DMap k v
dm0 dm' :: Event (ProfiledTimeline t) (PatchDMapWithMove k v)
dm' = (((DMap k v', Event t (PatchDMapWithMove k v'))
-> (DMap k v',
Event (ProfiledTimeline t) (PatchDMapWithMove k v')))
-> ProfiledM m (DMap k v', Event t (PatchDMapWithMove k v'))
-> ProfiledM
m (DMap k v', Event (ProfiledTimeline t) (PatchDMapWithMove k v'))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (((DMap k v', Event t (PatchDMapWithMove k v'))
-> (DMap k v',
Event (ProfiledTimeline t) (PatchDMapWithMove k v')))
-> ProfiledM m (DMap k v', Event t (PatchDMapWithMove k v'))
-> ProfiledM
m (DMap k v', Event (ProfiledTimeline t) (PatchDMapWithMove k v')))
-> ((Event t (PatchDMapWithMove k v')
-> Event (ProfiledTimeline t) (PatchDMapWithMove k v'))
-> (DMap k v', Event t (PatchDMapWithMove k v'))
-> (DMap k v',
Event (ProfiledTimeline t) (PatchDMapWithMove k v')))
-> (Event t (PatchDMapWithMove k v')
-> Event (ProfiledTimeline t) (PatchDMapWithMove k v'))
-> ProfiledM m (DMap k v', Event t (PatchDMapWithMove k v'))
-> ProfiledM
m (DMap k v', Event (ProfiledTimeline t) (PatchDMapWithMove k v'))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Event t (PatchDMapWithMove k v')
-> Event (ProfiledTimeline t) (PatchDMapWithMove k v'))
-> (DMap k v', Event t (PatchDMapWithMove k v'))
-> (DMap k v', Event (ProfiledTimeline t) (PatchDMapWithMove k v'))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap) Event t (PatchDMapWithMove k v')
-> Event (ProfiledTimeline t) (PatchDMapWithMove k v')
forall a b. Coercible a b => a -> b
coerce (ProfiledM m (DMap k v', Event t (PatchDMapWithMove k v'))
-> ProfiledM
m (DMap k v', Event (ProfiledTimeline t) (PatchDMapWithMove k v')))
-> (m (DMap k v', Event t (PatchDMapWithMove k v'))
-> ProfiledM m (DMap k v', Event t (PatchDMapWithMove k v')))
-> m (DMap k v', Event t (PatchDMapWithMove k v'))
-> ProfiledM
m (DMap k v', Event (ProfiledTimeline t) (PatchDMapWithMove k v'))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. m (DMap k v', Event t (PatchDMapWithMove k v'))
-> ProfiledM m (DMap k v', Event t (PatchDMapWithMove k v'))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (DMap k v', Event t (PatchDMapWithMove k v'))
-> ProfiledM
m (DMap k v', Event (ProfiledTimeline t) (PatchDMapWithMove k v')))
-> m (DMap k v', Event t (PatchDMapWithMove k v'))
-> ProfiledM
m (DMap k v', Event (ProfiledTimeline t) (PatchDMapWithMove k v'))
forall a b. (a -> b) -> a -> b
$
(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 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'))
traverseDMapWithKeyWithAdjustWithMove (\k :: k a
k v :: v a
v -> ProfiledM m (v' a) -> m (v' a)
forall a b. Coercible a b => a -> b
coerce (ProfiledM m (v' a) -> m (v' a)) -> ProfiledM m (v' a) -> m (v' a)
forall a b. (a -> b) -> a -> b
$ k a -> v a -> ProfiledM m (v' a)
forall a. k a -> v a -> ProfiledM m (v' a)
f k a
k v a
v) DMap k v
dm0 (Event (ProfiledTimeline t) (PatchDMapWithMove k v)
-> Event t (PatchDMapWithMove k v)
forall a b. Coercible a b => a -> b
coerce Event (ProfiledTimeline t) (PatchDMapWithMove k v)
dm')
instance MonadTrans ProfiledM where
lift :: m a -> ProfiledM m a
lift = m a -> ProfiledM m a
forall k (m :: k -> *) (a :: k). m a -> ProfiledM m a
ProfiledM
instance MonadIO m => MonadIO (ProfiledM m) where
liftIO :: IO a -> ProfiledM m a
liftIO = m a -> ProfiledM m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m a -> ProfiledM m a) -> (IO a -> m a) -> IO a -> ProfiledM m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO
instance PerformEvent t m => PerformEvent (ProfiledTimeline t) (ProfiledM m) where
type Performable (ProfiledM m) = Performable m
performEvent_ :: Event (ProfiledTimeline t) (Performable (ProfiledM m) ())
-> ProfiledM m ()
performEvent_ = m () -> ProfiledM m ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m () -> ProfiledM m ())
-> (Event (ProfiledTimeline t) (Performable m ()) -> m ())
-> Event (ProfiledTimeline t) (Performable m ())
-> ProfiledM m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Event t (Performable m ()) -> m ()
forall t (m :: * -> *).
PerformEvent t m =>
Event t (Performable m ()) -> m ()
performEvent_ (Event t (Performable m ()) -> m ())
-> (Event (ProfiledTimeline t) (Performable m ())
-> Event t (Performable m ()))
-> Event (ProfiledTimeline t) (Performable m ())
-> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Event (ProfiledTimeline t) (Performable m ())
-> Event t (Performable m ())
forall a b. Coercible a b => a -> b
coerce
performEvent :: Event (ProfiledTimeline t) (Performable (ProfiledM m) a)
-> ProfiledM m (Event (ProfiledTimeline t) a)
performEvent = m (Event (ProfiledTimeline t) a)
-> ProfiledM m (Event (ProfiledTimeline t) a)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Event (ProfiledTimeline t) a)
-> ProfiledM m (Event (ProfiledTimeline t) a))
-> (Event (ProfiledTimeline t) (Performable m a)
-> m (Event (ProfiledTimeline t) a))
-> Event (ProfiledTimeline t) (Performable m a)
-> ProfiledM m (Event (ProfiledTimeline t) a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Event t a -> Event (ProfiledTimeline t) a)
-> m (Event t a) -> m (Event (ProfiledTimeline t) a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Event t a -> Event (ProfiledTimeline t) a
forall a b. Coercible a b => a -> b
coerce (m (Event t a) -> m (Event (ProfiledTimeline t) a))
-> (Event (ProfiledTimeline t) (Performable m a) -> m (Event t a))
-> Event (ProfiledTimeline t) (Performable m a)
-> m (Event (ProfiledTimeline t) a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Event t (Performable m a) -> m (Event t a)
forall t (m :: * -> *) a.
PerformEvent t m =>
Event t (Performable m a) -> m (Event t a)
performEvent (Event t (Performable m a) -> m (Event t a))
-> (Event (ProfiledTimeline t) (Performable m a)
-> Event t (Performable m a))
-> Event (ProfiledTimeline t) (Performable m a)
-> m (Event t a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Event (ProfiledTimeline t) (Performable m a)
-> Event t (Performable m a)
forall a b. Coercible a b => a -> b
coerce
instance TriggerEvent t m => TriggerEvent (ProfiledTimeline t) (ProfiledM m) where
newTriggerEvent :: ProfiledM m (Event (ProfiledTimeline t) a, a -> IO ())
newTriggerEvent = (Event t a -> Event (ProfiledTimeline t) a)
-> (Event t a, a -> IO ())
-> (Event (ProfiledTimeline t) a, a -> IO ())
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first Event t a -> Event (ProfiledTimeline t) a
forall a b. Coercible a b => a -> b
coerce ((Event t a, a -> IO ())
-> (Event (ProfiledTimeline t) a, a -> IO ()))
-> ProfiledM m (Event t a, a -> IO ())
-> ProfiledM m (Event (ProfiledTimeline t) a, a -> IO ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m (Event t a, a -> IO ()) -> ProfiledM m (Event t a, a -> IO ())
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift m (Event t a, a -> IO ())
forall t (m :: * -> *) a.
TriggerEvent t m =>
m (Event t a, a -> IO ())
newTriggerEvent
newTriggerEventWithOnComplete :: ProfiledM m (Event (ProfiledTimeline t) a, a -> IO () -> IO ())
newTriggerEventWithOnComplete = (Event t a -> Event (ProfiledTimeline t) a)
-> (Event t a, a -> IO () -> IO ())
-> (Event (ProfiledTimeline t) a, a -> IO () -> IO ())
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first Event t a -> Event (ProfiledTimeline t) a
forall a b. Coercible a b => a -> b
coerce ((Event t a, a -> IO () -> IO ())
-> (Event (ProfiledTimeline t) a, a -> IO () -> IO ()))
-> ProfiledM m (Event t a, a -> IO () -> IO ())
-> ProfiledM m (Event (ProfiledTimeline t) a, a -> IO () -> IO ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m (Event t a, a -> IO () -> IO ())
-> ProfiledM m (Event t a, a -> IO () -> IO ())
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift m (Event t a, a -> IO () -> IO ())
forall t (m :: * -> *) a.
TriggerEvent t m =>
m (Event t a, a -> IO () -> IO ())
newTriggerEventWithOnComplete
newEventWithLazyTriggerWithOnComplete :: ((a -> IO () -> IO ()) -> IO (IO ()))
-> ProfiledM m (Event (ProfiledTimeline t) a)
newEventWithLazyTriggerWithOnComplete f :: (a -> IO () -> IO ()) -> IO (IO ())
f = Event t a -> Event (ProfiledTimeline t) a
forall a b. Coercible a b => a -> b
coerce (Event t a -> Event (ProfiledTimeline t) a)
-> ProfiledM m (Event t a)
-> ProfiledM m (Event (ProfiledTimeline t) a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m (Event t a) -> ProfiledM m (Event t a)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (((a -> IO () -> IO ()) -> IO (IO ())) -> m (Event t a)
forall t (m :: * -> *) a.
TriggerEvent t m =>
((a -> IO () -> IO ()) -> IO (IO ())) -> m (Event t a)
newEventWithLazyTriggerWithOnComplete (a -> IO () -> IO ()) -> IO (IO ())
f)
instance PostBuild t m => PostBuild (ProfiledTimeline t) (ProfiledM m) where
getPostBuild :: ProfiledM m (Event (ProfiledTimeline t) ())
getPostBuild = Event t () -> Event (ProfiledTimeline t) ()
forall a b. Coercible a b => a -> b
coerce (Event t () -> Event (ProfiledTimeline t) ())
-> ProfiledM m (Event t ())
-> ProfiledM m (Event (ProfiledTimeline t) ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m (Event t ()) -> ProfiledM 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 NotReady t m => NotReady (ProfiledTimeline t) (ProfiledM m) where
notReady :: ProfiledM m ()
notReady = m () -> ProfiledM m ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift m ()
forall t (m :: * -> *). NotReady t m => m ()
notReady
notReadyUntil :: Event (ProfiledTimeline t) a -> ProfiledM m ()
notReadyUntil = m () -> ProfiledM m ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m () -> ProfiledM m ())
-> (Event (ProfiledTimeline t) a -> m ())
-> Event (ProfiledTimeline t) a
-> ProfiledM m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Event t a -> m ()
forall t (m :: * -> *) a. NotReady t m => Event t a -> m ()
notReadyUntil (Event t a -> m ())
-> (Event (ProfiledTimeline t) a -> Event t a)
-> Event (ProfiledTimeline t) a
-> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Event (ProfiledTimeline t) a -> Event t a
forall a b. Coercible a b => a -> b
coerce
instance BehaviorWriter t w m => BehaviorWriter (ProfiledTimeline t) w (ProfiledM m) where
tellBehavior :: Behavior (ProfiledTimeline t) w -> ProfiledM m ()
tellBehavior = m () -> ProfiledM m ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m () -> ProfiledM m ())
-> (Behavior (ProfiledTimeline t) w -> m ())
-> Behavior (ProfiledTimeline t) w
-> ProfiledM m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Behavior t w -> m ()
forall t w (m :: * -> *).
BehaviorWriter t w m =>
Behavior t w -> m ()
tellBehavior (Behavior t w -> m ())
-> (Behavior (ProfiledTimeline t) w -> Behavior t w)
-> Behavior (ProfiledTimeline t) w
-> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Behavior (ProfiledTimeline t) w -> Behavior t w
forall a b. Coercible a b => a -> b
coerce
instance DynamicWriter t w m => DynamicWriter (ProfiledTimeline t) w (ProfiledM m) where
tellDyn :: Dynamic (ProfiledTimeline t) w -> ProfiledM m ()
tellDyn = m () -> ProfiledM m ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m () -> ProfiledM m ())
-> (Dynamic (ProfiledTimeline t) w -> m ())
-> Dynamic (ProfiledTimeline t) w
-> ProfiledM m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Dynamic t w -> m ()
forall t w (m :: * -> *).
DynamicWriter t w m =>
Dynamic t w -> m ()
tellDyn (Dynamic t w -> m ())
-> (Dynamic (ProfiledTimeline t) w -> Dynamic t w)
-> Dynamic (ProfiledTimeline t) w
-> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Dynamic (ProfiledTimeline t) w -> Dynamic t w
forall a b. Coercible a b => a -> b
coerce
instance EventWriter t w m => EventWriter (ProfiledTimeline t) w (ProfiledM m) where
tellEvent :: Event (ProfiledTimeline t) w -> ProfiledM m ()
tellEvent = m () -> ProfiledM m ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m () -> ProfiledM m ())
-> (Event (ProfiledTimeline t) w -> m ())
-> Event (ProfiledTimeline t) w
-> ProfiledM m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Event t w -> m ()
forall t w (m :: * -> *). EventWriter t w m => Event t w -> m ()
tellEvent (Event t w -> m ())
-> (Event (ProfiledTimeline t) w -> Event t w)
-> Event (ProfiledTimeline t) w
-> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Event (ProfiledTimeline t) w -> Event t w
forall a b. Coercible a b => a -> b
coerce
instance MonadQuery t q m => MonadQuery (ProfiledTimeline t) q (ProfiledM m) where
tellQueryIncremental :: Incremental (ProfiledTimeline t) (AdditivePatch q)
-> ProfiledM m ()
tellQueryIncremental = m () -> ProfiledM m ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m () -> ProfiledM m ())
-> (Incremental (ProfiledTimeline t) (AdditivePatch q) -> m ())
-> Incremental (ProfiledTimeline t) (AdditivePatch q)
-> ProfiledM m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Incremental t (AdditivePatch q) -> m ()
forall t q (m :: * -> *).
MonadQuery t q m =>
Incremental t (AdditivePatch q) -> m ()
tellQueryIncremental (Incremental t (AdditivePatch q) -> m ())
-> (Incremental (ProfiledTimeline t) (AdditivePatch q)
-> Incremental t (AdditivePatch q))
-> Incremental (ProfiledTimeline t) (AdditivePatch q)
-> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Incremental (ProfiledTimeline t) (AdditivePatch q)
-> Incremental t (AdditivePatch q)
forall a b. Coercible a b => a -> b
coerce
askQueryResult :: ProfiledM m (Dynamic (ProfiledTimeline t) (QueryResult q))
askQueryResult = Dynamic t (QueryResult q)
-> Dynamic (ProfiledTimeline t) (QueryResult q)
forall a b. Coercible a b => a -> b
coerce (Dynamic t (QueryResult q)
-> Dynamic (ProfiledTimeline t) (QueryResult q))
-> ProfiledM m (Dynamic t (QueryResult q))
-> ProfiledM m (Dynamic (ProfiledTimeline t) (QueryResult q))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m (Dynamic t (QueryResult q))
-> ProfiledM m (Dynamic t (QueryResult q))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift m (Dynamic t (QueryResult q))
forall t q (m :: * -> *).
MonadQuery t q m =>
m (Dynamic t (QueryResult q))
askQueryResult
queryIncremental :: Incremental (ProfiledTimeline t) (AdditivePatch q)
-> ProfiledM m (Dynamic (ProfiledTimeline t) (QueryResult q))
queryIncremental = (Dynamic t (QueryResult q)
-> Dynamic (ProfiledTimeline t) (QueryResult q))
-> ProfiledM m (Dynamic t (QueryResult q))
-> ProfiledM m (Dynamic (ProfiledTimeline t) (QueryResult q))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Dynamic t (QueryResult q)
-> Dynamic (ProfiledTimeline t) (QueryResult q)
forall a b. Coercible a b => a -> b
coerce (ProfiledM m (Dynamic t (QueryResult q))
-> ProfiledM m (Dynamic (ProfiledTimeline t) (QueryResult q)))
-> (Incremental (ProfiledTimeline t) (AdditivePatch q)
-> ProfiledM m (Dynamic t (QueryResult q)))
-> Incremental (ProfiledTimeline t) (AdditivePatch q)
-> ProfiledM m (Dynamic (ProfiledTimeline t) (QueryResult q))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. m (Dynamic t (QueryResult q))
-> ProfiledM m (Dynamic t (QueryResult q))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Dynamic t (QueryResult q))
-> ProfiledM m (Dynamic t (QueryResult q)))
-> (Incremental (ProfiledTimeline t) (AdditivePatch q)
-> m (Dynamic t (QueryResult q)))
-> Incremental (ProfiledTimeline t) (AdditivePatch q)
-> ProfiledM m (Dynamic t (QueryResult q))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Incremental t (AdditivePatch q) -> m (Dynamic t (QueryResult q))
forall t q (m :: * -> *).
MonadQuery t q m =>
Incremental t (AdditivePatch q) -> m (Dynamic t (QueryResult q))
queryIncremental (Incremental t (AdditivePatch q) -> m (Dynamic t (QueryResult q)))
-> (Incremental (ProfiledTimeline t) (AdditivePatch q)
-> Incremental t (AdditivePatch q))
-> Incremental (ProfiledTimeline t) (AdditivePatch q)
-> m (Dynamic t (QueryResult q))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Incremental (ProfiledTimeline t) (AdditivePatch q)
-> Incremental t (AdditivePatch q)
forall a b. Coercible a b => a -> b
coerce
instance Requester t m => Requester (ProfiledTimeline t) (ProfiledM m) where
type Request (ProfiledM m) = Request m
type Response (ProfiledM m) = Response m
requesting :: Event (ProfiledTimeline t) (Request (ProfiledM m) a)
-> ProfiledM
m (Event (ProfiledTimeline t) (Response (ProfiledM m) a))
requesting = (Event t (Response m a)
-> Event (ProfiledTimeline t) (Response m a))
-> ProfiledM m (Event t (Response m a))
-> ProfiledM m (Event (ProfiledTimeline t) (Response m a))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Event t (Response m a) -> Event (ProfiledTimeline t) (Response m a)
forall a b. Coercible a b => a -> b
coerce (ProfiledM m (Event t (Response m a))
-> ProfiledM m (Event (ProfiledTimeline t) (Response m a)))
-> (Event (ProfiledTimeline t) (Request m a)
-> ProfiledM m (Event t (Response m a)))
-> Event (ProfiledTimeline t) (Request m a)
-> ProfiledM m (Event (ProfiledTimeline t) (Response m a))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. m (Event t (Response m a)) -> ProfiledM m (Event t (Response m a))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Event t (Response m a))
-> ProfiledM m (Event t (Response m a)))
-> (Event (ProfiledTimeline t) (Request m a)
-> m (Event t (Response m a)))
-> Event (ProfiledTimeline t) (Request m a)
-> ProfiledM m (Event t (Response m a))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Event t (Request m a) -> m (Event t (Response m a))
forall t (m :: * -> *) a.
Requester t m =>
Event t (Request m a) -> m (Event t (Response m a))
requesting (Event t (Request m a) -> m (Event t (Response m a)))
-> (Event (ProfiledTimeline t) (Request m a)
-> Event t (Request m a))
-> Event (ProfiledTimeline t) (Request m a)
-> m (Event t (Response m a))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Event (ProfiledTimeline t) (Request m a) -> Event t (Request m a)
forall a b. Coercible a b => a -> b
coerce
requesting_ :: Event (ProfiledTimeline t) (Request (ProfiledM m) a)
-> ProfiledM m ()
requesting_ = m () -> ProfiledM m ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m () -> ProfiledM m ())
-> (Event (ProfiledTimeline t) (Request m a) -> m ())
-> Event (ProfiledTimeline t) (Request m a)
-> ProfiledM m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Event t (Request m a) -> m ()
forall t (m :: * -> *) a.
Requester t m =>
Event t (Request m a) -> m ()
requesting_ (Event t (Request m a) -> m ())
-> (Event (ProfiledTimeline t) (Request m a)
-> Event t (Request m a))
-> Event (ProfiledTimeline t) (Request m a)
-> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Event (ProfiledTimeline t) (Request m a) -> Event t (Request m a)
forall a b. Coercible a b => a -> b
coerce
instance MonadRef m => MonadRef (ProfiledM m) where
type Ref (ProfiledM m) = Ref m
newRef :: a -> ProfiledM m (Ref (ProfiledM m) a)
newRef = m (Ref m a) -> ProfiledM m (Ref m a)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Ref m a) -> ProfiledM m (Ref m a))
-> (a -> m (Ref m a)) -> a -> ProfiledM 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 (ProfiledM m) a -> ProfiledM m a
readRef = m a -> ProfiledM m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m a -> ProfiledM m a)
-> (Ref m a -> m a) -> Ref m a -> ProfiledM 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 (ProfiledM m) a -> a -> ProfiledM m ()
writeRef r :: Ref (ProfiledM m) a
r = m () -> ProfiledM m ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m () -> ProfiledM m ()) -> (a -> m ()) -> a -> ProfiledM 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 (ProfiledM m) a
r
instance MonadReflexCreateTrigger t m => MonadReflexCreateTrigger (ProfiledTimeline t) (ProfiledM m) where
newEventWithTrigger :: (EventTrigger (ProfiledTimeline t) a -> IO (IO ()))
-> ProfiledM m (Event (ProfiledTimeline t) a)
newEventWithTrigger = m (Event (ProfiledTimeline t) a)
-> ProfiledM m (Event (ProfiledTimeline t) a)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Event (ProfiledTimeline t) a)
-> ProfiledM m (Event (ProfiledTimeline t) a))
-> ((EventTrigger t a -> IO (IO ()))
-> m (Event (ProfiledTimeline t) a))
-> (EventTrigger t a -> IO (IO ()))
-> ProfiledM m (Event (ProfiledTimeline t) a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Event t a -> Event (ProfiledTimeline t) a)
-> m (Event t a) -> m (Event (ProfiledTimeline t) a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Event t a -> Event (ProfiledTimeline t) a
forall a b. Coercible a b => a -> b
coerce (m (Event t a) -> m (Event (ProfiledTimeline t) a))
-> ((EventTrigger t a -> IO (IO ())) -> m (Event t a))
-> (EventTrigger t a -> IO (IO ()))
-> m (Event (ProfiledTimeline 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
newFanEventWithTrigger :: (forall a.
k a -> EventTrigger (ProfiledTimeline t) a -> IO (IO ()))
-> ProfiledM m (EventSelector (ProfiledTimeline t) k)
newFanEventWithTrigger f :: forall a. k a -> EventTrigger (ProfiledTimeline t) a -> IO (IO ())
f = do
EventSelector t k
es <- m (EventSelector t k) -> ProfiledM m (EventSelector t k)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (EventSelector t k) -> ProfiledM m (EventSelector t k))
-> m (EventSelector t k) -> ProfiledM 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 ())
forall a. k a -> EventTrigger (ProfiledTimeline t) a -> IO (IO ())
f
EventSelector (ProfiledTimeline t) k
-> ProfiledM m (EventSelector (ProfiledTimeline t) k)
forall (m :: * -> *) a. Monad m => a -> m a
return (EventSelector (ProfiledTimeline t) k
-> ProfiledM m (EventSelector (ProfiledTimeline t) k))
-> EventSelector (ProfiledTimeline t) k
-> ProfiledM m (EventSelector (ProfiledTimeline t) k)
forall a b. (a -> b) -> a -> b
$ (forall a. k a -> Event (ProfiledTimeline t) a)
-> EventSelector (ProfiledTimeline t) k
forall k (t :: k) (k :: * -> *).
(forall a. k a -> Event t a) -> EventSelector t k
EventSelector ((forall a. k a -> Event (ProfiledTimeline t) a)
-> EventSelector (ProfiledTimeline t) k)
-> (forall a. k a -> Event (ProfiledTimeline t) a)
-> EventSelector (ProfiledTimeline t) k
forall a b. (a -> b) -> a -> b
$ \k :: k a
k -> Event t a -> Event (ProfiledTimeline t) a
forall a b. Coercible a b => a -> b
coerce (Event t a -> Event (ProfiledTimeline t) a)
-> Event t a -> Event (ProfiledTimeline t) a
forall a b. (a -> b) -> a -> b
$ EventSelector t k -> k a -> Event t a
forall k (t :: k) (k :: * -> *).
EventSelector t k -> forall a. k a -> Event t a
select EventSelector t k
es k a
k
instance MonadReader r m => MonadReader r (ProfiledM m) where
ask :: ProfiledM m r
ask = m r -> ProfiledM m r
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift m r
forall r (m :: * -> *). MonadReader r m => m r
ask
local :: (r -> r) -> ProfiledM m a -> ProfiledM m a
local f :: r -> r
f (ProfiledM a :: m a
a) = m a -> ProfiledM m a
forall k (m :: k -> *) (a :: k). m a -> ProfiledM m a
ProfiledM (m a -> ProfiledM m a) -> m a -> ProfiledM m a
forall a b. (a -> b) -> a -> b
$ (r -> r) -> m a -> m a
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local r -> r
f m a
a
reader :: (r -> a) -> ProfiledM m a
reader = m a -> ProfiledM m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m a -> ProfiledM m a)
-> ((r -> a) -> m a) -> (r -> a) -> ProfiledM m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (r -> a) -> m a
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
reader
instance ReflexHost t => ReflexHost (ProfiledTimeline t) where
type EventTrigger (ProfiledTimeline t) = EventTrigger t
type EventHandle (ProfiledTimeline t) = EventHandle t
type HostFrame (ProfiledTimeline t) = ProfiledM (HostFrame t)
instance MonadSubscribeEvent t m => MonadSubscribeEvent (ProfiledTimeline t) (ProfiledM m) where
subscribeEvent :: Event (ProfiledTimeline t) a
-> ProfiledM m (EventHandle (ProfiledTimeline t) a)
subscribeEvent = m (EventHandle t a) -> ProfiledM m (EventHandle t a)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (EventHandle t a) -> ProfiledM m (EventHandle t a))
-> (Event (ProfiledTimeline t) a -> m (EventHandle t a))
-> Event (ProfiledTimeline t) a
-> ProfiledM m (EventHandle t a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Event t a -> m (EventHandle t a)
forall t (m :: * -> *) a.
MonadSubscribeEvent t m =>
Event t a -> m (EventHandle t a)
subscribeEvent (Event t a -> m (EventHandle t a))
-> (Event (ProfiledTimeline t) a -> Event t a)
-> Event (ProfiledTimeline t) a
-> m (EventHandle t a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Event (ProfiledTimeline t) a -> Event t a
forall a b. Coercible a b => a -> b
coerce
instance PrimMonad m => PrimMonad (ProfiledM m) where
type PrimState (ProfiledM m) = PrimState m
primitive :: (State# (PrimState (ProfiledM m))
-> (# State# (PrimState (ProfiledM m)), a #))
-> ProfiledM m a
primitive = m a -> ProfiledM m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m a -> ProfiledM m a)
-> ((State# (PrimState m) -> (# State# (PrimState m), a #)) -> m a)
-> (State# (PrimState m) -> (# State# (PrimState m), a #))
-> ProfiledM 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 MonadReflexHost t m => MonadReflexHost (ProfiledTimeline t) (ProfiledM m) where
type ReadPhase (ProfiledM m) = ProfiledM (ReadPhase m)
fireEventsAndRead :: [DSum (EventTrigger (ProfiledTimeline t)) Identity]
-> ReadPhase (ProfiledM m) a -> ProfiledM m a
fireEventsAndRead ts :: [DSum (EventTrigger (ProfiledTimeline t)) Identity]
ts r :: ReadPhase (ProfiledM m) a
r = m a -> ProfiledM m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m a -> ProfiledM m a) -> m a -> ProfiledM m a
forall a b. (a -> b) -> a -> b
$ [DSum (EventTrigger t) Identity] -> ReadPhase m a -> m a
forall t (m :: * -> *) a.
MonadReflexHost t m =>
[DSum (EventTrigger t) Identity] -> ReadPhase m a -> m a
fireEventsAndRead [DSum (EventTrigger t) Identity]
[DSum (EventTrigger (ProfiledTimeline t)) Identity]
ts (ReadPhase m a -> m a) -> ReadPhase m a -> m a
forall a b. (a -> b) -> a -> b
$ ProfiledM (ReadPhase m) a -> ReadPhase m a
forall a b. Coercible a b => a -> b
coerce ReadPhase (ProfiledM m) a
ProfiledM (ReadPhase m) a
r
runHostFrame :: HostFrame (ProfiledTimeline t) a -> ProfiledM m a
runHostFrame = m a -> ProfiledM m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m a -> ProfiledM m a)
-> (ProfiledM (HostFrame t) a -> m a)
-> ProfiledM (HostFrame t) a
-> ProfiledM m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HostFrame t a -> m a
forall t (m :: * -> *) a.
MonadReflexHost t m =>
HostFrame t a -> m a
runHostFrame (HostFrame t a -> m a)
-> (ProfiledM (HostFrame t) a -> HostFrame t a)
-> ProfiledM (HostFrame t) a
-> m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProfiledM (HostFrame t) a -> HostFrame t a
forall a b. Coercible a b => a -> b
coerce
instance MonadReadEvent t m => MonadReadEvent (ProfiledTimeline t) (ProfiledM m) where
readEvent :: EventHandle (ProfiledTimeline t) a
-> ProfiledM m (Maybe (ProfiledM m a))
readEvent = m (Maybe (ProfiledM m a)) -> ProfiledM m (Maybe (ProfiledM m a))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Maybe (ProfiledM m a)) -> ProfiledM m (Maybe (ProfiledM m a)))
-> (EventHandle t a -> m (Maybe (ProfiledM m a)))
-> EventHandle t a
-> ProfiledM m (Maybe (ProfiledM m a))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe (m a) -> Maybe (ProfiledM m a))
-> m (Maybe (m a)) -> m (Maybe (ProfiledM m a))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Maybe (m a) -> Maybe (ProfiledM m a)
forall a b. Coercible a b => a -> b
coerce (m (Maybe (m a)) -> m (Maybe (ProfiledM m a)))
-> (EventHandle t a -> m (Maybe (m a)))
-> EventHandle t a
-> m (Maybe (ProfiledM m a))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EventHandle t a -> m (Maybe (m a))
forall t (m :: * -> *) a.
MonadReadEvent t m =>
EventHandle t a -> m (Maybe (m a))
readEvent