You signed in with another tab or window. Reload to refresh your session.You signed out in another tab or window. Reload to refresh your session.You switched accounts on another tab or window. Reload to refresh your session.Dismiss alert
Copy file name to clipboardExpand all lines: src/Data/Map/Misc.hs
+24-9Lines changed: 24 additions & 9 deletions
Original file line number
Diff line number
Diff line change
@@ -1,4 +1,5 @@
1
1
{-# LANGUAGE LambdaCase #-}
2
+
--|Additional functions for manipulating 'Map's.
2
3
moduleData.Map.Misc
3
4
(
4
5
-- * Working with Maps
@@ -10,20 +11,28 @@ module Data.Map.Misc
10
11
) where
11
12
12
13
importData.Align
13
-
importData.Either
14
14
importData.Map (Map)
15
15
importqualifiedData.MapasMap
16
16
importData.Maybe
17
17
importData.Set (Set)
18
18
importqualifiedData.SetasSet
19
19
importData.These
20
20
21
+
--|Produce a @'Map' k (Maybe v)@ by comparing two @'Map' k v@s, @old@ and @new@ respectively. @Just@ represents an association present in @new@ and @Nothing@
22
+
-- represents an association only present in @old@ but no longer present in @new@.
23
+
--
24
+
-- Similar to 'diffMap' but doesn't require 'Eq' on the values, thus can't tell if a value has changed or not.
--|Produce a @'Map' k (Maybe v)@ by comparing two @'Map' k v@s, @old@ and @new respectively. @Just@ represents an association present in @new@ and either not
32
+
-- present in @old@ or where the value has changed. @Nothing@ represents an association only present in @old@ but no longer present in @new@.
33
+
--
34
+
-- See also 'diffMapNoEq' for a similar but weaker version which does not require 'Eq' on the values but thus can't indicated a value not changing between
Copy file name to clipboardExpand all lines: src/Reflex/FastWeak.hs
+46-5Lines changed: 46 additions & 5 deletions
Original file line number
Diff line number
Diff line change
@@ -5,6 +5,15 @@
5
5
{-# LANGUAGE ForeignFunctionInterface #-}
6
6
{-# LANGUAGE JavaScriptFFI #-}
7
7
#endif
8
+
9
+
--|Contains 'FastWeak', a weak pointer to some value, and 'FastWeakTicket' which ensures the value referred to by a 'FastWeak' stays live while the ticket is
10
+
-- held (live).
11
+
--
12
+
-- On GHC or GHCJS when not built with the @fast-weak@ cabal flag, 'FastWeak' is a wrapper around the simple version of 'System.Mem.Weak.Weak' where the key
13
+
-- and value are the same.
14
+
--
15
+
-- On GHCJS when built with the @fast-weak@ cabal flag, 'FastWeak' is implemented directly in JS using @h$FastWeak@ and @h$FastWeakTicket@ which are a
16
+
-- nonstandard part of the GHCJS RTS. __FIXME__
8
17
moduleReflex.FastWeak
9
18
( FastWeakTicket
10
19
, FastWeak
@@ -35,29 +44,52 @@ import System.Mem.Weak
35
44
36
45
37
46
#ifdef GHCJS_FAST_WEAK
47
+
--|A 'FastWeak' which has been promoted to a strong reference. 'getFastWeakTicketValue' can be used to get the referred to value without fear of @Nothing,
48
+
-- and 'getFastWeakTicketWeak' can be used to get the weak version.
49
+
--
50
+
-- Implemented by way of special support in the GHCJS RTS, @h$FastWeakTicket@.
38
51
newtypeFastWeakTicketa=FastWeakTicketJSVal
39
52
53
+
--|A reference to some value which can be garbage collected if there are only weak references to the value left.
54
+
--
55
+
-- 'getFastWeakValue' can be used to try and obtain a strong reference to the value.
56
+
--
57
+
-- The value in a @FastWeak@ can also be kept alive by obtaining a 'FastWeakTicket' using 'getFastWeakTicket' if the value hasn't been collected yet.
58
+
--
59
+
-- Implemented by way of special support in the GHCJS RTS, @h$FastWeak@.
40
60
newtypeFastWeaka=FastWeakJSVal
41
61
42
62
-- Just designed to mirror JSVal, so that we can unsafeCoerce between the two
43
63
dataVala=Val{unVal::a}
44
64
45
-
--| Coerce a JSVal that represents the heap object of a value of type 'a' into a value of type 'a'
65
+
--| Coerce a JSVal that represents the heap object of a value of type @a@ into a value of type @a@
46
66
unsafeFromRawJSVal::JSVal->a
47
67
unsafeFromRawJSVal v = unVal (unsafeCoerce v)
48
68
69
+
--| Coerce a heap object of type @a@ into a 'JSVal' which represents that object.
49
70
unsafeToRawJSVal::a->JSVal
50
71
unsafeToRawJSVal v = unsafeCoerce (Val v)
51
72
#else
73
+
--|A 'FastWeak' which has been promoted to a strong reference. 'getFastWeakTicketValue' can be used to get the referred to value without fear of @Nothing,
74
+
-- and 'getFastWeakTicketWeak' can be used to get the weak version.
52
75
dataFastWeakTicketa=FastWeakTicket
53
76
{_fastWeakTicket_val::!a
54
77
, _fastWeakTicket_weak:: {-# UNPACK #-} !(Weaka)
55
78
}
56
79
80
+
--|A reference to some value which can be garbage collected if there are only weak references to the value left.
81
+
--
82
+
-- 'getFastWeakValue' can be used to try and obtain a strong reference to the value.
83
+
--
84
+
-- The value in a @FastWeak@ can also be kept alive by obtaining a 'FastWeakTicket' using 'getFastWeakTicket' if the value hasn't been collected yet.
85
+
--
86
+
-- Synonymous with 'Weak'.
57
87
typeFastWeaka=Weaka
58
88
#endif
59
89
60
-
-- This needs to be in IO so we know that we've relinquished the ticket
90
+
--|Return the @a@ kept alive by the given 'FastWeakTicket'.
91
+
--
92
+
-- This needs to be in IO so we know that we've relinquished the ticket.
--|Try to create a 'FastWeakTicket' for the given 'FastWeak' which will ensure the referred to value remains alive. Returns @Just@ if the value hasn't been
121
+
-- collected and a ticket can therefore be obtained, @Nothing@ if it's been collected.
--I think it's fine if this is lazy - it'll retain the 'a', but so would the output; we just need to make sure it's forced before we start relying on the associated FastWeak to actually be weak
141
+
--|Create a 'FastWeakTicket' directly from a value, creating a 'FastWeak' in the process which can be obtained with 'getFastWeakTicketValue'.
107
142
mkFastWeakTicket::a->IO (FastWeakTicketa)
143
+
-- I think it's fine if this is lazy - it'll retain the 'a', but so would the output; we just need to make sure it's forced before we start relying on the
144
+
-- associated FastWeak to actually be weak
108
145
#ifdef GHCJS_FAST_WEAK
109
146
mkFastWeakTicket v = js_fastWeakTicket (unsafeToRawJSVal v)
110
147
@@ -119,11 +156,15 @@ mkFastWeakTicket v = do
119
156
}
120
157
#endif
121
158
159
+
--|Demote a 'FastWeakTicket' which ensures the value is alive to a 'FastWeak' which doesn't. Note that unless the ticket or another for the same 'FastWeak' is
160
+
-- held some other way the value might be collected immediately.
--|Apply the insertions or deletions to a given 'DMap'.
31
33
instanceGComparek=>Patch (PatchDMapkv) where
32
34
typePatchTarget (PatchDMapkv) =DMapkv
33
35
apply (PatchDMap diff) old =Just$! insertions `DMap.union` (old `DMap.difference` deletions) --TODO: return Nothing sometimes --Note: the strict application here is critical to ensuring that incremental merges don't hold onto all their prerequisite events forever; can we make this more robust?
@@ -37,32 +39,38 @@ instance GCompare k => Patch (PatchDMap k v) where
37
39
Nothing->Just$Constant()
38
40
Just _ ->Nothing
39
41
42
+
--| Map a function @v a -> v' a@ over any inserts/updates in the given @'PatchDMap' k v@ to produce a @'PatchDMap' k v'@.
--| Convert a weak @'PatchDMap' ('Const2' k a) v@ where the @a@ is known by way of the @Const2@ into a @'PatchMap' k v'@ using a rank 1 function @v a -> v'@.
, _nodeInfo_to =ComposeMaybe$Const2<$>MapWithMove._nodeInfo_to ni
363
364
}
364
365
366
+
--| Apply the insertions, deletions, and moves to a given 'DMap'.
365
367
instanceGComparek=>Patch (PatchDMapWithMovekv) where
366
368
typePatchTarget (PatchDMapWithMovekv) =DMapkv
367
369
apply (PatchDMapWithMove p) old =Just$! insertions `DMap.union` (old `DMap.difference` deletions) --TODO: return Nothing sometimes --Note: the strict application here is critical to ensuring that incremental merges don't hold onto all their prerequisite events forever; can we make this more robust?
@@ -377,8 +379,7 @@ instance GCompare k => Patch (PatchDMapWithMove k v) where
377
379
From_Delete->Just$Constant()
378
380
_ ->Nothing
379
381
380
-
--| Get the values that will be deleted or moved if the given patch is applied
381
-
-- to the given 'DMap'.
382
+
--| Get the values that will be replaced, deleted, or moved if the given patch is applied to the given 'DMap'.
Copy file name to clipboardExpand all lines: src/Reflex/Patch/IntMap.hs
+13-1Lines changed: 13 additions & 1 deletion
Original file line number
Diff line number
Diff line change
@@ -4,6 +4,7 @@
4
4
{-# LANGUAGE DeriveTraversable #-}
5
5
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
6
6
{-# LANGUAGE TypeFamilies #-}
7
+
--|Module containing 'PatchIntMap', a 'Patch' for 'IntMap' which allows for insert/update or delete of associations.
7
8
moduleReflex.Patch.IntMapwhere
8
9
9
10
importPreludehiding (lookup)
@@ -13,8 +14,11 @@ import Data.Maybe
13
14
importData.Semigroup
14
15
importReflex.Patch.Class
15
16
17
+
--|'Patch' for 'IntMap' which represents insertion or deletion of keys in the mapping. Internally represented by 'IntMap (Maybe a)', where @Just@ means
mapIntMapPatchWithKey f (PatchIntMap m) =PatchIntMap$IntMap.mapWithKey (\ k mv -> f k <$> mv) m
47
+
48
+
--|Map an effectful function @Int -> a -> f b@ over all @a@s in the given @'PatchIntMap' a@ (that is, all inserts/updates), producing a @f (PatchIntMap b)@.
0 commit comments