Skip to content

Commit 8d8ceec

Browse files
committed
Generalize merge
1 parent 7ef47af commit 8d8ceec

File tree

7 files changed

+141
-72
lines changed

7 files changed

+141
-72
lines changed

ChangeLog.md

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,10 @@
33
## Unreleased
44

55
* Fix `holdDyn` so that it is lazy in its event argument
6+
* Generalize `merge` to `mergeG`, `mergeIncremental` to
7+
`mergeIncrementalG`, and `mergeIncrementalWithMove`
8+
to `mergeIncrementalWithMoveG`. These produce `DMap`s
9+
whose values needn't be `Identity`.
610

711
## 0.6.1.0
812

reflex.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -48,6 +48,7 @@ library
4848
data-default >= 0.5 && < 0.8,
4949
dependent-map >= 0.2.4 && < 0.3,
5050
exception-transformers == 0.4.*,
51+
profunctors,
5152
lens >= 4.7 && < 5,
5253
monad-control >= 1.0.1 && < 1.1,
5354
monoidal-containers == 0.4.*,

src/Reflex/Class.hs

Lines changed: 31 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -17,6 +17,7 @@
1717
{-# LANGUAGE TypeFamilies #-}
1818
{-# LANGUAGE TypeOperators #-}
1919
{-# LANGUAGE UndecidableInstances #-}
20+
{-# LANGUAGE Trustworthy #-}
2021
#ifdef USE_REFLEX_OPTIMIZER
2122
{-# OPTIONS_GHC -fplugin=Reflex.Optimizer #-}
2223
#endif
@@ -46,6 +47,9 @@ module Reflex.Class
4647
, pushAlways
4748
-- ** Combining 'Event's
4849
, leftmost
50+
, merge
51+
, mergeIncremental
52+
, mergeIncrementalWithMove
4953
, mergeMap
5054
, mergeIntMap
5155
, mergeMapIncremental
@@ -256,7 +260,9 @@ class ( MonadHold t (PushM t)
256260
-- | Merge a collection of events; the resulting 'Event' will only occur if at
257261
-- least one input event is occurring, and will contain all of the input keys
258262
-- that are occurring simultaneously
259-
merge :: GCompare k => DMap k (Event t) -> Event t (DMap k Identity) --TODO: Generalize to get rid of DMap use --TODO: Provide a type-level guarantee that the result is not empty
263+
mergeG :: GCompare k => (forall a. q a -> Event t (v a))
264+
-> DMap k q -> Event t (DMap k v)
265+
--TODO: Generalize to get rid of DMap use --TODO: Provide a type-level guarantee that the result is not empty
260266
-- | Efficiently fan-out an event to many destinations. You should save the
261267
-- result in a @let@-binding, and then repeatedly 'select' on the result to
262268
-- create child events
@@ -278,9 +284,14 @@ class ( MonadHold t (PushM t)
278284
-- that value.
279285
unsafeBuildIncremental :: Patch p => PullM t (PatchTarget p) -> Event t p -> Incremental t p
280286
-- | Create a merge whose parents can change over time
281-
mergeIncremental :: GCompare k => Incremental t (PatchDMap k (Event t)) -> Event t (DMap k Identity)
287+
mergeIncrementalG :: GCompare k
288+
=> (forall a. q a -> Event t (v a))
289+
-> Incremental t (PatchDMap k q)
290+
-> Event t (DMap k v)
282291
-- | Experimental: Create a merge whose parents can change over time; changing the key of an Event is more efficient than with mergeIncremental
283-
mergeIncrementalWithMove :: GCompare k => Incremental t (PatchDMapWithMove k (Event t)) -> Event t (DMap k Identity)
292+
mergeIncrementalWithMoveG :: GCompare k
293+
=> (forall a. q a -> Event t (v a))
294+
-> Incremental t (PatchDMapWithMove k q) -> Event t (DMap k v)
284295
-- | Extract the 'Behavior' component of an 'Incremental'
285296
currentIncremental :: Patch p => Incremental t p -> Behavior t (PatchTarget p)
286297
-- | Extract the 'Event' component of an 'Incremental'
@@ -1558,6 +1569,23 @@ fmapCheap f = pushCheap $ return . Just . f
15581569
tagCheap :: Reflex t => Behavior t b -> Event t a -> Event t b
15591570
tagCheap b = pushAlwaysCheap $ \_ -> sample b
15601571

1572+
-- | Merge a collection of events; the resulting 'Event' will only occur if at
1573+
-- least one input event is occurring, and will contain all of the input keys
1574+
-- that are occurring simultaneously
1575+
merge :: (Reflex t, GCompare k) => DMap k (Event t) -> Event t (DMap k Identity)
1576+
merge = mergeG coerceEvent
1577+
{-# INLINE merge #-}
1578+
1579+
-- | Create a merge whose parents can change over time
1580+
mergeIncremental :: (Reflex t, GCompare k)
1581+
=> Incremental t (PatchDMap k (Event t)) -> Event t (DMap k Identity)
1582+
mergeIncremental = mergeIncrementalG coerceEvent
1583+
1584+
-- | Experimental: Create a merge whose parents can change over time; changing the key of an Event is more efficient than with mergeIncremental
1585+
mergeIncrementalWithMove :: (Reflex t, GCompare k)
1586+
=> Incremental t (PatchDMapWithMove k (Event t)) -> Event t (DMap k Identity)
1587+
mergeIncrementalWithMove = mergeIncrementalWithMoveG coerceEvent
1588+
15611589
-- | A "cheap" version of 'mergeWithCheap'. See the performance note on 'pushCheap'.
15621590
{-# INLINE mergeWithCheap #-}
15631591
mergeWithCheap :: Reflex t => (a -> a -> a) -> [Event t a] -> Event t a

src/Reflex/Profiled.hs

Lines changed: 9 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -8,6 +8,8 @@
88
{-# LANGUAGE StandaloneDeriving #-}
99
{-# LANGUAGE TypeFamilies #-}
1010
{-# LANGUAGE UndecidableInstances #-}
11+
{-# LANGUAGE PolyKinds #-}
12+
{-# LANGUAGE RankNTypes #-}
1113
-- |
1214
-- Module:
1315
-- Reflex.Profiled
@@ -16,7 +18,6 @@
1618
-- profiling/cost-center information.
1719
module Reflex.Profiled where
1820

19-
import Control.Lens hiding (children)
2021
import Control.Monad
2122
import Control.Monad.Exception
2223
import Control.Monad.Fix
@@ -33,6 +34,7 @@ import Data.Map (Map)
3334
import qualified Data.Map.Strict as Map
3435
import Data.Monoid ((<>))
3536
import Data.Ord
37+
import Data.Profunctor.Unsafe ((#.))
3638
import qualified Data.Semigroup as S
3739
import Data.Type.Coercion
3840
import Foreign.Ptr
@@ -133,17 +135,19 @@ instance Reflex t => Reflex (ProfiledTimeline t) where
133135
push f (Event_Profiled e) = coerce $ push (coerce f) $ profileEvent e -- Profile before rather than after; this way fanout won't count against us
134136
pushCheap f (Event_Profiled e) = coerce $ pushCheap (coerce f) $ profileEvent e
135137
pull = Behavior_Profiled . pull . coerce
136-
merge :: forall k. GCompare k => DMap k (Event (ProfiledTimeline t)) -> Event (ProfiledTimeline t) (DMap k Identity)
137-
merge = Event_Profiled . merge . (unsafeCoerce :: DMap k (Event (ProfiledTimeline t)) -> DMap k (Event t))
138+
mergeG :: forall (k :: z -> *) q v. GCompare k
139+
=> (forall a. q a -> Event (ProfiledTimeline t) (v a))
140+
-> DMap k q -> Event (ProfiledTimeline t) (DMap k v)
141+
mergeG nt = Event_Profiled #. mergeG (coerce nt)
138142
fan (Event_Profiled e) = EventSelector $ coerce $ select (fan $ profileEvent e)
139143
switch (Behavior_Profiled b) = coerce $ profileEvent $ switch (coerceBehavior b)
140144
coincidence (Event_Profiled e) = coerce $ profileEvent $ coincidence (coerceEvent e)
141145
current (Dynamic_Profiled d) = coerce $ current d
142146
updated (Dynamic_Profiled d) = coerce $ profileEvent $ updated d
143147
unsafeBuildDynamic (ProfiledM a0) (Event_Profiled a') = coerce $ unsafeBuildDynamic a0 a'
144148
unsafeBuildIncremental (ProfiledM a0) (Event_Profiled a') = coerce $ unsafeBuildIncremental a0 a'
145-
mergeIncremental = Event_Profiled . mergeIncremental . (unsafeCoerce :: Incremental (ProfiledTimeline t) (PatchDMap k (Event (ProfiledTimeline t))) -> Incremental t (PatchDMap k (Event t)))
146-
mergeIncrementalWithMove = Event_Profiled . mergeIncrementalWithMove . (unsafeCoerce :: Incremental (ProfiledTimeline t) (PatchDMapWithMove k (Event (ProfiledTimeline t))) -> Incremental t (PatchDMapWithMove k (Event t)))
149+
mergeIncrementalG nt = (Event_Profiled . coerce) #. mergeIncrementalG nt
150+
mergeIncrementalWithMoveG nt = (Event_Profiled . coerce) #. mergeIncrementalWithMoveG nt
147151
currentIncremental (Incremental_Profiled i) = coerce $ currentIncremental i
148152
updatedIncremental (Incremental_Profiled i) = coerce $ profileEvent $ updatedIncremental i
149153
incrementalToDynamic (Incremental_Profiled i) = coerce $ incrementalToDynamic i

src/Reflex/Pure.hs

Lines changed: 16 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,8 @@
55
{-# LANGUAGE MultiParamTypeClasses #-}
66
{-# LANGUAGE ScopedTypeVariables #-}
77
{-# LANGUAGE TypeFamilies #-}
8+
{-# LANGUAGE RankNTypes #-}
9+
{-# LANGUAGE PolyKinds #-}
810
#ifdef USE_REFLEX_OPTIMIZER
911
{-# OPTIONS_GHC -fplugin=Reflex.Optimizer #-}
1012
#endif
@@ -43,10 +45,11 @@ import Data.MemoTrie
4345
import Data.Monoid
4446
import Data.Type.Coercion
4547
import Reflex.Class
48+
import Data.Kind (Type)
4649

4750
-- | A completely pure-functional 'Reflex' timeline, identifying moments in time
4851
-- with the type @/t/@.
49-
data Pure t
52+
data Pure (t :: Type)
5053

5154
-- | The 'Enum' instance of @/t/@ must be dense: for all @/x :: t/@, there must not exist
5255
-- any @/y :: t/@ such that @/'pred' x < y < x/@. The 'HasTrie' instance will be used
@@ -79,11 +82,12 @@ instance (Enum t, HasTrie t, Ord t) => Reflex (Pure t) where
7982
-- [UNUSED_CONSTRAINT]: The following type signature for merge will produce a
8083
-- warning because the GCompare instance is not used; however, removing the
8184
-- GCompare instance produces a different warning, due to that constraint
82-
-- being present in the original class definition
85+
-- being present in the original class definition.
8386

84-
--merge :: GCompare k => DMap k (Event (Pure t)) -> Event (Pure t) (DMap k Identity)
85-
merge events = Event $ memo $ \t ->
86-
let currentOccurrences = DMap.mapMaybeWithKey (\_ (Event a) -> Identity <$> a t) events
87+
--mergeG :: GCompare k => (forall a. q a -> Event (Pure t) (v a))
88+
-- -> DMap k q -> Event (Pure t) (DMap k v)
89+
mergeG nt events = Event $ memo $ \t ->
90+
let currentOccurrences = DMap.mapMaybeWithKey (\_ q -> case nt q of Event a -> a t) events
8791
in if DMap.null currentOccurrences
8892
then Nothing
8993
else Just currentOccurrences
@@ -112,8 +116,8 @@ instance (Enum t, HasTrie t, Ord t) => Reflex (Pure t) where
112116
--a) -> Incremental (Pure t) p a
113117
unsafeBuildIncremental readV0 p = Incremental $ \t -> (readV0 t, unEvent p t)
114118

115-
mergeIncremental = mergeIncrementalImpl
116-
mergeIncrementalWithMove = mergeIncrementalImpl
119+
mergeIncrementalG = mergeIncrementalImpl
120+
mergeIncrementalWithMoveG = mergeIncrementalImpl
117121

118122
currentIncremental i = Behavior $ \t -> fst $ unIncremental i t
119123

@@ -133,9 +137,11 @@ instance (Enum t, HasTrie t, Ord t) => Reflex (Pure t) where
133137

134138
mergeIntIncremental = mergeIntIncrementalImpl
135139

136-
mergeIncrementalImpl :: (PatchTarget p ~ DMap k (Event (Pure t)), GCompare k) => Incremental (Pure t) p -> Event (Pure t) (DMap k Identity)
137-
mergeIncrementalImpl i = Event $ \t ->
138-
let results = DMap.mapMaybeWithKey (\_ (Event e) -> Identity <$> e t) $ fst $ unIncremental i t
140+
mergeIncrementalImpl :: (PatchTarget p ~ DMap k q, GCompare k)
141+
=> (forall a. q a -> Event (Pure t) (v a))
142+
-> Incremental (Pure t) p -> Event (Pure t) (DMap k v)
143+
mergeIncrementalImpl nt i = Event $ \t ->
144+
let results = DMap.mapMaybeWithKey (\_ q -> case nt q of Event e -> e t) $ fst $ unIncremental i t
139145
in if DMap.null results
140146
then Nothing
141147
else Just results

0 commit comments

Comments
 (0)