Skip to content

Commit 13e76bb

Browse files
treeowloliver-batchelor
authored andcommitted
Generalize fan following DMap (#318)
Generalize fan to fanG allowing fanning DMaps with arbitrary targets (not just Identity)
1 parent 9afdfce commit 13e76bb

File tree

6 files changed

+67
-32
lines changed

6 files changed

+67
-32
lines changed

ChangeLog.md

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -2,12 +2,16 @@
22

33
## Unreleased
44

5+
* Generalize `fan` to `fanG` to take a `DMap` with non-`Identity`
6+
values.
7+
58
* Generalize merging functions:
69
`merge` to `mergeG`,
710
`mergeIncremental` to `mergeIncrementalG`,
811
`distributeDMapOverDynPure` to `distributeDMapOverDynPureG`,
912
`mergeIncrementalWithMove` to `mergeIncrementalWithMoveG`.
1013

14+
1115
## 0.6.2.0
1216

1317
* Fix `holdDyn` so that it is lazy in its event argument

src/Reflex/Class.hs

Lines changed: 31 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -41,6 +41,7 @@ module Reflex.Class
4141
, MonadHold (..)
4242
-- ** 'fan' related types
4343
, EventSelector (..)
44+
, EventSelectorG (..)
4445
, EventSelectorInt (..)
4546
-- * Convenience functions
4647
, constDyn
@@ -64,6 +65,7 @@ module Reflex.Class
6465
, alignEventWithMaybe
6566
-- ** Breaking up 'Event's
6667
, splitE
68+
, fan
6769
, fanEither
6870
, fanThese
6971
, fanMap
@@ -260,13 +262,16 @@ class ( MonadHold t (PushM t)
260262
-- | Merge a collection of events; the resulting 'Event' will only occur if at
261263
-- least one input event is occurring, and will contain all of the input keys
262264
-- that are occurring simultaneously
265+
266+
--TODO: Generalize to get rid of DMap use --TODO: Provide a type-level guarantee that the result is not empty
263267
mergeG :: GCompare k => (forall a. q a -> Event t (v a))
264268
-> 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
269+
266270
-- | Efficiently fan-out an event to many destinations. You should save the
267-
-- result in a @let@-binding, and then repeatedly 'select' on the result to
271+
-- result in a @let@-binding, and then repeatedly 'selectG' on the result to
268272
-- create child events
269-
fan :: GCompare k => Event t (DMap k Identity) -> EventSelector t k
273+
fanG :: GCompare k => Event t (DMap k v) -> EventSelectorG t k v
274+
270275
-- | Create an 'Event' that will occur whenever the currently-selected input
271276
-- 'Event' occurs
272277
switch :: Behavior t (Event t a) -> Event t a
@@ -310,6 +315,18 @@ class ( MonadHold t (PushM t)
310315
mergeIntIncremental :: Incremental t (PatchIntMap (Event t a)) -> Event t (IntMap a)
311316
fanInt :: Event t (IntMap a) -> EventSelectorInt t a
312317

318+
-- | Efficiently fan-out an event to many destinations. You should save the
319+
-- result in a @let@-binding, and then repeatedly 'select' on the result to
320+
-- create child events
321+
fan :: forall t k. (Reflex t, GCompare k)
322+
=> Event t (DMap k Identity) -> EventSelector t k
323+
--TODO: Can we help enforce the partial application discipline here? The combinator is worthless without it
324+
fan e = EventSelector (fixup (selectG (fanG e) :: k a -> Event t (Identity a)) :: forall a. k a -> Event t a)
325+
where
326+
fixup :: forall a. (k a -> Event t (Identity a)) -> k a -> Event t a
327+
fixup = case eventCoercion Coercion :: Coercion (Event t (Identity a)) (Event t a) of
328+
Coercion -> coerce
329+
313330
--TODO: Specialize this so that we can take advantage of knowing that there's no changing going on
314331
-- | Constructs a single 'Event' out of a map of events. The output event may fire with multiple
315332
-- keys simultaneously.
@@ -497,6 +514,17 @@ newtype EventSelector t k = EventSelector
497514
select :: forall a. k a -> Event t a
498515
}
499516

517+
newtype EventSelectorG t k v = EventSelectorG
518+
{ -- | Retrieve the 'Event' for the given key. The type of the 'Event' is
519+
-- determined by the type of the key, so this can be used to fan-out
520+
-- 'Event's whose sub-'Event's have different types.
521+
--
522+
-- Using 'EventSelector's and the 'fan' primitive is far more efficient than
523+
-- (but equivalent to) using 'mapMaybe' to select only the relevant
524+
-- occurrences of an 'Event'.
525+
selectG :: forall a. k a -> Event t (v a)
526+
}
527+
500528
-- | Efficiently select an 'Event' keyed on 'Int'. This is more efficient than manually
501529
-- filtering by key.
502530
newtype EventSelectorInt t a = EventSelectorInt { selectInt :: Int -> Event t a }

src/Reflex/Profiled.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -135,11 +135,11 @@ instance Reflex t => Reflex (ProfiledTimeline t) where
135135
push f (Event_Profiled e) = coerce $ push (coerce f) $ profileEvent e -- Profile before rather than after; this way fanout won't count against us
136136
pushCheap f (Event_Profiled e) = coerce $ pushCheap (coerce f) $ profileEvent e
137137
pull = Behavior_Profiled . pull . coerce
138+
fanG (Event_Profiled e) = EventSelectorG $ coerce $ selectG (fanG $ profileEvent e)
138139
mergeG :: forall (k :: z -> *) q v. GCompare k
139140
=> (forall a. q a -> Event (ProfiledTimeline t) (v a))
140141
-> DMap k q -> Event (ProfiledTimeline t) (DMap k v)
141142
mergeG nt = Event_Profiled #. mergeG (coerce nt)
142-
fan (Event_Profiled e) = EventSelector $ coerce $ select (fan $ profileEvent e)
143143
switch (Behavior_Profiled b) = coerce $ profileEvent $ switch (coerceBehavior b)
144144
coincidence (Event_Profiled e) = coerce $ profileEvent $ coincidence (coerceEvent e)
145145
current (Dynamic_Profiled d) = coerce $ current d

src/Reflex/Pure.hs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,7 @@
77
{-# LANGUAGE TypeFamilies #-}
88
{-# LANGUAGE RankNTypes #-}
99
{-# LANGUAGE PolyKinds #-}
10+
1011
#ifdef USE_REFLEX_OPTIMIZER
1112
{-# OPTIONS_GHC -fplugin=Reflex.Optimizer #-}
1213
#endif
@@ -92,8 +93,8 @@ instance (Enum t, HasTrie t, Ord t) => Reflex (Pure t) where
9293
then Nothing
9394
else Just currentOccurrences
9495

95-
fan :: GCompare k => Event (Pure t) (DMap k Identity) -> EventSelector (Pure t) k
96-
fan e = EventSelector $ \k -> Event $ \t -> unEvent e t >>= fmap runIdentity . DMap.lookup k
96+
-- fanG :: GCompare k => Event (Pure t) (DMap k v) -> EventSelectorG (Pure t) k v
97+
fanG e = EventSelectorG $ \k -> Event $ \t -> unEvent e t >>= DMap.lookup k
9798

9899
switch :: Behavior (Pure t) (Event (Pure t) a) -> Event (Pure t) a
99100
switch b = Event $ memo $ \t -> unEvent (unBehavior b t) t

src/Reflex/Spider/Internal.hs

Lines changed: 26 additions & 24 deletions
Original file line numberDiff line numberDiff line change
@@ -19,6 +19,7 @@
1919
{-# LANGUAGE UndecidableInstances #-}
2020
{-# LANGUAGE PolyKinds #-}
2121
{-# LANGUAGE InstanceSigs #-}
22+
2223
#ifdef USE_REFLEX_OPTIMIZER
2324
{-# OPTIONS_GHC -fplugin=Reflex.Optimizer #-}
2425
#endif
@@ -374,7 +375,7 @@ eventRoot !k !r = Event $ wrap eventSubscribedRoot $ liftIO . getRootSubscribed
374375
eventNever :: Event x a
375376
eventNever = Event $ \_ -> return (EventSubscription (return ()) eventSubscribedNever, Nothing)
376377

377-
eventFan :: (GCompare k, HasSpiderTimeline x) => k a -> Fan x k -> Event x a
378+
eventFan :: (GCompare k, HasSpiderTimeline x) => k a -> Fan x k v -> Event x (v a)
378379
eventFan !k !f = Event $ wrap eventSubscribedFan $ getFanSubscribed k f
379380

380381
eventSwitch :: HasSpiderTimeline x => Switch x a -> Event x a
@@ -426,14 +427,14 @@ newSubscriberHold h = return $ Subscriber
426427
, subscriberRecalculateHeight = \_ -> return ()
427428
}
428429

429-
newSubscriberFan :: forall x k. (HasSpiderTimeline x, GCompare k) => FanSubscribed x k -> IO (Subscriber x (DMap k Identity))
430+
newSubscriberFan :: forall x k v. (HasSpiderTimeline x, GCompare k) => FanSubscribed x k v -> IO (Subscriber x (DMap k v))
430431
newSubscriberFan subscribed = return $ Subscriber
431432
{ subscriberPropagate = \a -> {-# SCC "traverseFan" #-} do
432433
subs <- liftIO $ readIORef $ fanSubscribedSubscribers subscribed
433434
tracePropagate (Proxy :: Proxy x) $ "SubscriberFan" <> showNodeId subscribed <> ": " ++ show (DMap.size subs) ++ " keys subscribed, " ++ show (DMap.size a) ++ " keys firing"
434435
liftIO $ writeIORef (fanSubscribedOccurrence subscribed) $ Just a
435436
scheduleClear $ fanSubscribedOccurrence subscribed
436-
let f _ (Pair (Identity v) subsubs) = do
437+
let f _ (Pair v subsubs) = do
437438
propagate v $ _fanSubscribedChildren_list subsubs
438439
return $ Constant ()
439440
_ <- DMap.traverseWithKey f $ DMap.intersectionWithKey (\_ -> Pair) a subs --TODO: Would be nice to have DMap.traverse_
@@ -581,7 +582,7 @@ eventSubscribedNever = EventSubscribed
581582
#endif
582583
}
583584

584-
eventSubscribedFan :: FanSubscribed x k -> EventSubscribed x
585+
eventSubscribedFan :: FanSubscribed x k v -> EventSubscribed x
585586
eventSubscribedFan !subscribed = EventSubscribed
586587
{ eventSubscribedHeightRef = eventSubscribedHeightRef $ _eventSubscription_subscribed $ fanSubscribedParent subscribed
587588
, eventSubscribedRetained = toAny subscribed
@@ -990,7 +991,7 @@ data RootSubscribed x a = forall k. GCompare k => RootSubscribed
990991
#endif
991992
}
992993

993-
data Root x (k :: * -> *)
994+
data Root x k
994995
= Root { rootOccurrence :: !(IORef (DMap k Identity)) -- The currently-firing occurrence of this event
995996
, rootSubscribed :: !(IORef (DMap k (RootSubscribed x)))
996997
, rootInit :: !(forall a. k a -> RootTrigger x a -> IO (IO ()))
@@ -1060,25 +1061,25 @@ heightBagVerify b@(HeightBag s c) = if
10601061
heightBagVerify = id
10611062
#endif
10621063

1063-
data FanSubscribedChildren (x :: *) k a = FanSubscribedChildren
1064-
{ _fanSubscribedChildren_list :: !(WeakBag (Subscriber x a))
1065-
, _fanSubscribedChildren_self :: {-# NOUNPACK #-} !(k a, FanSubscribed x k)
1066-
, _fanSubscribedChildren_weakSelf :: !(IORef (Weak (k a, FanSubscribed x k)))
1064+
data FanSubscribedChildren x k v a = FanSubscribedChildren
1065+
{ _fanSubscribedChildren_list :: !(WeakBag (Subscriber x (v a)))
1066+
, _fanSubscribedChildren_self :: {-# NOUNPACK #-} !(k a, FanSubscribed x k v)
1067+
, _fanSubscribedChildren_weakSelf :: !(IORef (Weak (k a, FanSubscribed x k v)))
10671068
}
10681069

1069-
data FanSubscribed (x :: *) k
1070-
= FanSubscribed { fanSubscribedCachedSubscribed :: !(IORef (Maybe (FanSubscribed x k)))
1071-
, fanSubscribedOccurrence :: !(IORef (Maybe (DMap k Identity)))
1072-
, fanSubscribedSubscribers :: !(IORef (DMap k (FanSubscribedChildren x k))) -- This DMap should never be empty
1070+
data FanSubscribed x k v
1071+
= FanSubscribed { fanSubscribedCachedSubscribed :: !(IORef (Maybe (FanSubscribed x k v)))
1072+
, fanSubscribedOccurrence :: !(IORef (Maybe (DMap k v)))
1073+
, fanSubscribedSubscribers :: !(IORef (DMap k (FanSubscribedChildren x k v))) -- This DMap should never be empty
10731074
, fanSubscribedParent :: !(EventSubscription x)
10741075
#ifdef DEBUG_NODEIDS
10751076
, fanSubscribedNodeId :: Int
10761077
#endif
10771078
}
10781079

1079-
data Fan x k
1080-
= Fan { fanParent :: !(Event x (DMap k Identity))
1081-
, fanSubscribed :: !(IORef (Maybe (FanSubscribed x k)))
1080+
data Fan x k v
1081+
= Fan { fanParent :: !(Event x (DMap k v))
1082+
, fanSubscribed :: !(IORef (Maybe (FanSubscribed x k v)))
10821083
}
10831084

10841085
data SwitchSubscribed x a
@@ -1525,7 +1526,7 @@ fanInt p =
15251526
return (EventSubscription (FastWeakBag.remove t) $! EventSubscribed heightRef $! toAny (_fanInt_subscriptionRef self, t), IntMap.lookup k currentOcc)
15261527

15271528
{-# INLINABLE getFanSubscribed #-}
1528-
getFanSubscribed :: (HasSpiderTimeline x, GCompare k) => k a -> Fan x k -> Subscriber x a -> EventM x (WeakBagTicket, FanSubscribed x k, Maybe a)
1529+
getFanSubscribed :: (HasSpiderTimeline x, GCompare k) => k a -> Fan x k v -> Subscriber x (v a) -> EventM x (WeakBagTicket, FanSubscribed x k v, Maybe (v a))
15291530
getFanSubscribed k f sub = do
15301531
mSubscribed <- liftIO $ readIORef $ fanSubscribed f
15311532
case mSubscribed of
@@ -1559,7 +1560,7 @@ getFanSubscribed k f sub = do
15591560
liftIO $ writeIORef (fanSubscribed f) $ Just subscribed
15601561
return (slnForSub, subscribed, coerce $ DMap.lookup k =<< parentOcc)
15611562

1562-
cleanupFanSubscribed :: GCompare k => (k a, FanSubscribed x k) -> IO ()
1563+
cleanupFanSubscribed :: GCompare k => (k a, FanSubscribed x k v) -> IO ()
15631564
cleanupFanSubscribed (k, subscribed) = do
15641565
subscribers <- readIORef $ fanSubscribedSubscribers subscribed
15651566
let reducedSubscribers = DMap.delete k subscribers
@@ -1571,7 +1572,7 @@ cleanupFanSubscribed (k, subscribed) = do
15711572
else writeIORef (fanSubscribedSubscribers subscribed) $! reducedSubscribers
15721573

15731574
{-# INLINE subscribeFanSubscribed #-}
1574-
subscribeFanSubscribed :: GCompare k => k a -> FanSubscribed x k -> Subscriber x a -> IO WeakBagTicket
1575+
subscribeFanSubscribed :: GCompare k => k a -> FanSubscribed x k v -> Subscriber x (v a) -> IO WeakBagTicket
15751576
subscribeFanSubscribed k subscribed sub = do
15761577
subscribers <- readIORef $ fanSubscribedSubscribers subscribed
15771578
case DMap.lookup k subscribers of
@@ -2047,14 +2048,15 @@ mergeIntCheap d = Event $ \sub -> do
20472048
)
20482049

20492050
newtype EventSelector x k = EventSelector { select :: forall a. k a -> Event x a }
2051+
newtype EventSelectorG x k v = EventSelectorG { selectG :: forall a. k a -> Event x (v a) }
20502052

2051-
fan :: (HasSpiderTimeline x, GCompare k) => Event x (DMap k Identity) -> EventSelector x k
2052-
fan e =
2053+
fanG :: (HasSpiderTimeline x, GCompare k) => Event x (DMap k v) -> EventSelectorG x k v
2054+
fanG e =
20532055
let f = Fan
20542056
{ fanParent = e
20552057
, fanSubscribed = unsafeNewIORef e Nothing
20562058
}
2057-
in EventSelector $ \k -> eventFan k f
2059+
in EventSelectorG $ \k -> eventFan k f
20582060

20592061
runHoldInits :: HasSpiderTimeline x => IORef [SomeHoldInit x] -> IORef [SomeDynInit x] -> IORef [SomeMergeInit x] -> EventM x ()
20602062
runHoldInits holdInitRef dynInitRef mergeInitRef = do
@@ -2523,15 +2525,15 @@ instance HasSpiderTimeline x => R.Reflex (SpiderTimeline x) where
25232525
pushCheap f = SpiderEvent . pushCheap (coerce f) . unSpiderEvent
25242526
{-# INLINABLE pull #-}
25252527
pull = SpiderBehavior . pull . coerce
2528+
{-# INLINABLE fanG #-}
2529+
fanG e = R.EventSelectorG $ SpiderEvent . selectG (fanG (unSpiderEvent e))
25262530
{-# INLINABLE mergeG #-}
25272531
mergeG
25282532
:: forall (k :: k2 -> *) q (v :: k2 -> *). GCompare k
25292533
=> (forall a. q a -> R.Event (SpiderTimeline x) (v a))
25302534
-> DMap k q
25312535
-> R.Event (SpiderTimeline x) (DMap k v)
25322536
mergeG nt = SpiderEvent . mergeG (unSpiderEvent #. nt) . dynamicConst
2533-
{-# INLINABLE fan #-}
2534-
fan e = R.EventSelector $ SpiderEvent . select (fan (unSpiderEvent e))
25352537
{-# INLINABLE switch #-}
25362538
switch = SpiderEvent . switch . (coerce :: Behavior x (R.Event (SpiderTimeline x) a) -> Behavior x (Event x a)) . unSpiderBehavior
25372539
{-# INLINABLE coincidence #-}

test/GC.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -56,8 +56,8 @@ hostPerf ref = S.runSpiderHost $ do
5656
{ S.subscriberPropagate = S.subscriberPropagate sub
5757
}
5858
return (s, o))
59-
$ runIdentity <$> S.select
60-
(S.fan $ S.pushCheap (return . Just . mapKeyValuePairsMonotonic (\(t :=> e) -> WrapArg t :=> Identity e)) response)
59+
$ runIdentity . runIdentity <$> S.selectG
60+
(S.fanG $ S.pushCheap (return . Just . mapKeyValuePairsMonotonic (\(t :=> e) -> WrapArg t :=> Identity e)) response)
6161
(WrapArg Request)
6262
return $ alignWith (mergeThese (<>))
6363
(flip S.pushCheap eadd $ \_ -> return $ Just $ DMap.singleton Request $ do

0 commit comments

Comments
 (0)