Skip to content

Commit 5e037c0

Browse files
treeowloliver-batchelor
authored andcommitted
Less unsafeCoerce (#322)
* Reduce the use of unsafeCoerce Remove most uses of `unsafeCoerce`. Most of the rest are taken care of in my `mergeG` pull request.
1 parent c477539 commit 5e037c0

File tree

7 files changed

+163
-53
lines changed

7 files changed

+163
-53
lines changed

reflex.cabal

+2
Original file line numberDiff line numberDiff line change
@@ -56,6 +56,7 @@ library
5656
mtl >= 2.1 && < 2.3,
5757
prim-uniq >= 0.1.0.1 && < 0.2,
5858
primitive >= 0.5 && < 0.7,
59+
profunctors,
5960
random == 1.1.*,
6061
ref-tf == 0.4.*,
6162
reflection == 2.1.*,
@@ -71,6 +72,7 @@ library
7172
witherable >= 0.2 && < 0.4
7273

7374
exposed-modules:
75+
Control.Monad.ReaderIO
7476
Data.AppendMap,
7577
Data.FastMutableIntMap,
7678
Data.FastWeakBag,

src/Control/Monad/ReaderIO.hs

+60
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,60 @@
1+
{-# language RoleAnnotations #-}
2+
{-# language MultiParamTypeClasses #-}
3+
{-# language FlexibleInstances #-}
4+
{-# language CPP #-}
5+
module Control.Monad.ReaderIO
6+
(
7+
ReaderIO (..)
8+
)
9+
where
10+
11+
import Control.Monad.Fix
12+
#if MIN_VERSION_base(4,10,0)
13+
import Control.Applicative
14+
#endif
15+
import Control.Monad
16+
import Control.Monad.Reader.Class
17+
import Control.Monad.IO.Class
18+
19+
-- | An approximate clone of @RIO@ from the @rio@ package, but not based on
20+
-- @ReaderT@. The trouble with @ReaderT@ is that its third type argument has a
21+
-- @nominal@ role, so we can't coerce through it when it's wrapped in some
22+
-- other @data@ type. Ugh.
23+
newtype ReaderIO e a = ReaderIO { runReaderIO :: e -> IO a }
24+
type role ReaderIO representational representational
25+
26+
instance Functor (ReaderIO e) where
27+
fmap = liftM
28+
{-# INLINE fmap #-}
29+
a <$ m = m >> pure a
30+
{-# INLINE (<$) #-}
31+
32+
instance Applicative (ReaderIO e) where
33+
pure a = ReaderIO $ \_ -> pure a
34+
{-# INLINE pure #-}
35+
(<*>) = ap
36+
{-# INLINE (<*>) #-}
37+
#if MIN_VERSION_base(4,10,0)
38+
liftA2 = liftM2
39+
{-# INLINE liftA2 #-}
40+
#endif
41+
(*>) = (>>)
42+
{-# INLINE (*>) #-}
43+
44+
instance Monad (ReaderIO e) where
45+
ReaderIO q >>= f = ReaderIO $ \e -> q e >>= \a -> runReaderIO (f a) e
46+
{-# INLINE (>>=) #-}
47+
48+
instance MonadFix (ReaderIO e) where
49+
mfix f = ReaderIO $ \e -> mfix $ \r -> runReaderIO (f r) e
50+
{-# INLINE mfix #-}
51+
52+
instance MonadIO (ReaderIO e) where
53+
liftIO m = ReaderIO $ \_ -> m
54+
{-# INLINE liftIO #-}
55+
56+
instance MonadReader e (ReaderIO e) where
57+
ask = ReaderIO pure
58+
{-# INLINE ask #-}
59+
local f (ReaderIO m) = ReaderIO (m . f)
60+
{-# INLINE local #-}

src/Reflex/Class.hs

+11
Original file line numberDiff line numberDiff line change
@@ -37,6 +37,7 @@ module Reflex.Class
3737
, coerceBehavior
3838
, coerceEvent
3939
, coerceDynamic
40+
, coerceIncremental
4041
, MonadSample (..)
4142
, MonadHold (..)
4243
-- ** 'fan' related types
@@ -312,6 +313,10 @@ class ( MonadHold t (PushM t)
312313
-- | Construct a 'Coercion' for a 'Dynamic' given an 'Coercion' for its
313314
-- occurrence type
314315
dynamicCoercion :: Coercion a b -> Coercion (Dynamic t a) (Dynamic t b)
316+
-- | Construct a 'Coercion' for an 'Incremental' given 'Coercion's for its
317+
-- patch target and patch types.
318+
incrementalCoercion
319+
:: Coercion (PatchTarget a) (PatchTarget b) -> Coercion a b -> Coercion (Incremental t a) (Incremental t b)
315320
mergeIntIncremental :: Incremental t (PatchIntMap (Event t a)) -> Event t (IntMap a)
316321
fanInt :: Event t (IntMap a) -> EventSelectorInt t a
317322

@@ -345,6 +350,12 @@ coerceEvent = coerceWith $ eventCoercion Coercion
345350
coerceDynamic :: (Reflex t, Coercible a b) => Dynamic t a -> Dynamic t b
346351
coerceDynamic = coerceWith $ dynamicCoercion Coercion
347352

353+
-- | Coerce an 'Incremental' between representationally-equivalent value types
354+
coerceIncremental
355+
:: (Reflex t, Coercible a b, Coercible (PatchTarget a) (PatchTarget b))
356+
=> Incremental t a -> Incremental t b
357+
coerceIncremental = coerceWith $ incrementalCoercion Coercion Coercion
358+
348359
-- | Construct a 'Dynamic' from a 'Behavior' and an 'Event'. The 'Behavior'
349360
-- __must__ change when and only when the 'Event' fires, such that the
350361
-- 'Behavior''s value is always equal to the most recent firing of the 'Event';

src/Reflex/Profiled.hs

+11-7
Original file line numberDiff line numberDiff line change
@@ -9,6 +9,7 @@
99
{-# LANGUAGE TypeFamilies #-}
1010
{-# LANGUAGE UndecidableInstances #-}
1111
{-# LANGUAGE PolyKinds #-}
12+
{-# LANGUAGE TypeApplications #-}
1213
{-# LANGUAGE RankNTypes #-}
1314
-- |
1415
-- Module:
@@ -151,13 +152,16 @@ instance Reflex t => Reflex (ProfiledTimeline t) where
151152
currentIncremental (Incremental_Profiled i) = coerce $ currentIncremental i
152153
updatedIncremental (Incremental_Profiled i) = coerce $ profileEvent $ updatedIncremental i
153154
incrementalToDynamic (Incremental_Profiled i) = coerce $ incrementalToDynamic i
154-
behaviorCoercion (c :: Coercion a b) = case behaviorCoercion c :: Coercion (Behavior t a) (Behavior t b) of
155-
Coercion -> unsafeCoerce (Coercion :: Coercion (Behavior (ProfiledTimeline t) a) (Behavior (ProfiledTimeline t) a)) --TODO: Figure out how to make this typecheck without the unsafeCoerce
156-
eventCoercion (c :: Coercion a b) = case eventCoercion c :: Coercion (Event t a) (Event t b) of
157-
Coercion -> unsafeCoerce (Coercion :: Coercion (Event (ProfiledTimeline t) a) (Event (ProfiledTimeline t) a)) --TODO: Figure out how to make this typecheck without the unsafeCoerce
158-
dynamicCoercion (c :: Coercion a b) = case dynamicCoercion c :: Coercion (Dynamic t a) (Dynamic t b) of
159-
Coercion -> unsafeCoerce (Coercion :: Coercion (Dynamic (ProfiledTimeline t) a) (Dynamic (ProfiledTimeline t) a)) --TODO: Figure out how to make this typecheck without the unsafeCoerce
160-
mergeIntIncremental = Event_Profiled . mergeIntIncremental . (unsafeCoerce :: Incremental (ProfiledTimeline t) (PatchIntMap (Event (ProfiledTimeline t) a)) -> Incremental t (PatchIntMap (Event t a)))
155+
behaviorCoercion c =
156+
Coercion `trans` behaviorCoercion @t c `trans` Coercion
157+
eventCoercion c =
158+
Coercion `trans` eventCoercion @t c `trans` Coercion
159+
dynamicCoercion c =
160+
Coercion `trans` dynamicCoercion @t c `trans` Coercion
161+
incrementalCoercion c d =
162+
Coercion `trans` incrementalCoercion @t c d `trans` Coercion
163+
mergeIntIncremental = Event_Profiled . mergeIntIncremental .
164+
coerceWith (Coercion `trans` incrementalCoercion Coercion Coercion `trans` Coercion)
161165
fanInt (Event_Profiled e) = coerce $ fanInt $ profileEvent e
162166

163167
deriving instance Functor (Dynamic t) => Functor (Dynamic (ProfiledTimeline t))

src/Reflex/Pure.hs

+1
Original file line numberDiff line numberDiff line change
@@ -133,6 +133,7 @@ instance (Enum t, HasTrie t, Ord t) => Reflex (Pure t) where
133133
behaviorCoercion Coercion = Coercion
134134
eventCoercion Coercion = Coercion
135135
dynamicCoercion Coercion = Coercion
136+
incrementalCoercion Coercion Coercion = Coercion
136137

137138
fanInt e = EventSelectorInt $ \k -> Event $ \t -> unEvent e t >>= IntMap.lookup k
138139

0 commit comments

Comments
 (0)