@@ -207,7 +207,7 @@ import Prelude ()
207
207
import Control.Applicative ((<$>) , (<**>) , Alternative ,
208
208
liftA3 )
209
209
import qualified Control.Applicative as Applicative
210
- import Control.DeepSeq (NFData (rnf ))
210
+ import Control.DeepSeq (NFData (rnf ), NFData1 ( liftRnf ) )
211
211
import Control.Monad (MonadPlus (.. ))
212
212
import Data.Monoid (Monoid (.. ))
213
213
import Data.Functor (Functor (.. ))
@@ -504,6 +504,10 @@ instance Traversable Seq where
504
504
instance NFData a => NFData (Seq a ) where
505
505
rnf (Seq xs) = rnf xs
506
506
507
+ -- | @since 0.7.1
508
+ instance NFData1 Seq where
509
+ liftRnf rnfx (Seq xs) = liftRnf (liftRnf rnfx) xs
510
+
507
511
instance Monad Seq where
508
512
return = pure
509
513
xs >>= f = foldl' add empty xs
@@ -1170,6 +1174,12 @@ instance NFData a => NFData (FingerTree a) where
1170
1174
rnf (Single x) = rnf x
1171
1175
rnf (Deep _ pr m sf) = rnf pr `seq` rnf sf `seq` rnf m
1172
1176
1177
+ -- | @since 0.7.1
1178
+ instance NFData1 FingerTree where
1179
+ liftRnf _ EmptyT = ()
1180
+ liftRnf rnfx (Single x) = rnfx x
1181
+ liftRnf rnfx (Deep _ pr m sf) = liftRnf rnfx pr `seq` liftRnf (liftRnf rnfx) m `seq` liftRnf rnfx sf
1182
+
1173
1183
{-# INLINE deep #-}
1174
1184
deep :: Sized a => Digit a -> FingerTree (Node a ) -> Digit a -> FingerTree a
1175
1185
deep pr m sf = Deep (size pr + size m + size sf) pr m sf
@@ -1272,6 +1282,13 @@ instance NFData a => NFData (Digit a) where
1272
1282
rnf (Three a b c) = rnf a `seq` rnf b `seq` rnf c
1273
1283
rnf (Four a b c d) = rnf a `seq` rnf b `seq` rnf c `seq` rnf d
1274
1284
1285
+ -- | @since 0.7.1
1286
+ instance NFData1 Digit where
1287
+ liftRnf rnfx (One a) = rnfx a
1288
+ liftRnf rnfx (Two a b) = rnfx a `seq` rnfx b
1289
+ liftRnf rnfx (Three a b c) = rnfx a `seq` rnfx b `seq` rnfx c
1290
+ liftRnf rnfx (Four a b c d) = rnfx a `seq` rnfx b `seq` rnfx c `seq` rnfx d
1291
+
1275
1292
instance Sized a => Sized (Digit a ) where
1276
1293
{-# INLINE size #-}
1277
1294
size = foldl1 (+) . fmap size
@@ -1350,6 +1367,11 @@ instance NFData a => NFData (Node a) where
1350
1367
rnf (Node2 _ a b) = rnf a `seq` rnf b
1351
1368
rnf (Node3 _ a b c) = rnf a `seq` rnf b `seq` rnf c
1352
1369
1370
+ -- | @since 0.7.1
1371
+ instance NFData1 Node where
1372
+ liftRnf rnfx (Node2 _ a b) = rnfx a `seq` rnfx b
1373
+ liftRnf rnfx (Node3 _ a b c) = rnfx a `seq` rnfx b `seq` rnfx c
1374
+
1353
1375
instance Sized (Node a ) where
1354
1376
size (Node2 v _ _) = v
1355
1377
size (Node3 v _ _ _) = v
@@ -1410,6 +1432,10 @@ instance Traversable Elem where
1410
1432
instance NFData a => NFData (Elem a ) where
1411
1433
rnf (Elem x) = rnf x
1412
1434
1435
+ -- | @since 0.7.1
1436
+ instance NFData1 Elem where
1437
+ liftRnf rnfx (Elem x) = rnfx x
1438
+
1413
1439
-------------------------------------------------------
1414
1440
-- Applicative construction
1415
1441
-------------------------------------------------------
0 commit comments