Skip to content

Commit 7aba44f

Browse files
committed
Add Lift instances for other containers
Add `Lift` instances for `Data.Map.Map`, `Data.Set.Set`, `Data.IntSet.IntSet`, `Data.IntMap.IntMap`, `Data.Tree.Tree`, and `Data.Graph.SCC`.
1 parent 9efb1de commit 7aba44f

File tree

8 files changed

+47
-7
lines changed

8 files changed

+47
-7
lines changed

containers/changelog.md

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -9,8 +9,9 @@
99

1010
### New instances
1111

12-
* `Data.Sequence` now offers `Lift` instances for `Seq`, `ViewL`, and `ViewR`
13-
for use with Template Haskell.
12+
* Add `Lift` instances for use with Template Haskell. Specifically:
13+
`Seq`, `ViewL`, and `ViewR` (in `Data.Sequence`), `Map`, `Set`,
14+
`IntMap`, `IntSet`, `Tree`, and `SCC` (in `Data.Graph`).
1415

1516
## 0.6.5.1
1617

containers/src/Data/Graph.hs

Lines changed: 9 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -3,8 +3,13 @@
33
{-# LANGUAGE RankNTypes #-}
44
{-# LANGUAGE DeriveDataTypeable #-}
55
{-# LANGUAGE DeriveGeneric #-}
6+
{-# LANGUAGE DeriveLift #-}
67
{-# LANGUAGE StandaloneDeriving #-}
8+
# if __GLASGOW_HASKELL__ >= 802
79
{-# LANGUAGE Safe #-}
10+
# else
11+
{-# LANGUAGE Trustworthy #-}
12+
# endif
813
#endif
914

1015
#include "containers.h"
@@ -121,6 +126,7 @@ import Data.Semigroup (Semigroup (..))
121126
#ifdef __GLASGOW_HASKELL__
122127
import GHC.Generics (Generic, Generic1)
123128
import Data.Data (Data)
129+
import Language.Haskell.TH.Syntax (Lift)
124130
#endif
125131

126132
-- Make sure we don't use Integer by mistake.
@@ -155,6 +161,9 @@ deriving instance Generic1 SCC
155161

156162
-- | @since 0.5.9
157163
deriving instance Generic (SCC vertex)
164+
165+
-- | @since FIXME
166+
deriving instance Lift vertex => Lift (SCC vertex)
158167
#endif
159168

160169
-- | @since 0.5.9

containers/src/Data/IntMap/Internal.hs

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,7 @@
22
{-# LANGUAGE BangPatterns #-}
33
{-# LANGUAGE PatternGuards #-}
44
#ifdef __GLASGOW_HASKELL__
5+
{-# LANGUAGE DeriveLift #-}
56
{-# LANGUAGE MagicHash #-}
67
{-# LANGUAGE ScopedTypeVariables #-}
78
{-# LANGUAGE StandaloneDeriving #-}
@@ -319,6 +320,7 @@ import Data.Data (Data(..), Constr, mkConstr, constrIndex, Fixity(Prefix),
319320
import GHC.Exts (build)
320321
import qualified GHC.Exts as GHCExts
321322
import Text.Read
323+
import Language.Haskell.TH.Syntax (Lift)
322324
#endif
323325
import qualified Control.Category as Category
324326

@@ -369,6 +371,9 @@ type Mask = Int
369371
type IntSetPrefix = Int
370372
type IntSetBitMap = Word
371373

374+
-- | @since FIXME
375+
deriving instance Lift a => Lift (IntMap a)
376+
372377
bitmapOf :: Int -> IntSetBitMap
373378
bitmapOf x = shiftLL 1 (x .&. IntSet.suffixBitMask)
374379
{-# INLINE bitmapOf #-}

containers/src/Data/IntSet/Internal.hs

Lines changed: 10 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,9 @@
22
{-# LANGUAGE BangPatterns #-}
33
{-# LANGUAGE PatternGuards #-}
44
#ifdef __GLASGOW_HASKELL__
5+
{-# LANGUAGE DeriveLift #-}
56
{-# LANGUAGE MagicHash #-}
7+
{-# LANGUAGE StandaloneDeriving #-}
68
{-# LANGUAGE TypeFamilies #-}
79
#endif
810
#if !defined(TESTING) && defined(__GLASGOW_HASKELL__)
@@ -209,9 +211,10 @@ import Text.Read
209211

210212
#if __GLASGOW_HASKELL__
211213
import qualified GHC.Exts
212-
#if !(WORD_SIZE_IN_BITS==64)
214+
# if !(WORD_SIZE_IN_BITS==64)
213215
import qualified GHC.Int
214-
#endif
216+
# endif
217+
import Language.Haskell.TH.Syntax (Lift)
215218
#endif
216219

217220
import qualified Data.Foldable as Foldable
@@ -268,6 +271,11 @@ type Mask = Int
268271
type BitMap = Word
269272
type Key = Int
270273

274+
#ifdef __GLASGOW_HASKELL__
275+
-- | @since FIXME
276+
deriving instance Lift IntSet
277+
#endif
278+
271279
instance Monoid IntSet where
272280
mempty = empty
273281
mconcat = unions

containers/src/Data/Map/Internal.hs

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,9 @@
22
{-# LANGUAGE BangPatterns #-}
33
{-# LANGUAGE PatternGuards #-}
44
#if defined(__GLASGOW_HASKELL__)
5+
{-# LANGUAGE DeriveLift #-}
56
{-# LANGUAGE RoleAnnotations #-}
7+
{-# LANGUAGE StandaloneDeriving #-}
68
{-# LANGUAGE Trustworthy #-}
79
{-# LANGUAGE TypeFamilies #-}
810
#endif
@@ -393,6 +395,7 @@ import Utils.Containers.Internal.BitUtil (wordSize)
393395

394396
#if __GLASGOW_HASKELL__
395397
import GHC.Exts (build, lazy)
398+
import Language.Haskell.TH.Syntax (Lift)
396399
# ifdef USE_MAGIC_PROXY
397400
import GHC.Exts (Proxy#, proxy# )
398401
# endif
@@ -462,6 +465,11 @@ type Size = Int
462465
type role Map nominal representational
463466
#endif
464467

468+
#ifdef __GLASGOW_HASKELL__
469+
-- | @since FIXME
470+
deriving instance (Lift k, Lift a) => Lift (Map k a)
471+
#endif
472+
465473
instance (Ord k) => Monoid (Map k v) where
466474
mempty = empty
467475
mconcat = unions

containers/src/Data/Sequence/Internal.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -341,7 +341,7 @@ instance Sized (ForceBox a) where
341341
newtype Seq a = Seq (FingerTree (Elem a))
342342

343343
#ifdef __GLASGOW_HASKELL__
344-
-- | @since 0.7
344+
-- | @since FIXME
345345
instance TH.Lift a => TH.Lift (Seq a) where
346346
# if MIN_VERSION_template_haskell(2,16,0)
347347
liftTyped t = [|| coerceFT z ||]
@@ -2174,7 +2174,7 @@ deriving instance Generic1 ViewL
21742174
-- | @since 0.5.8
21752175
deriving instance Generic (ViewL a)
21762176

2177-
-- | @since 0.7
2177+
-- | @since FIXME
21782178
deriving instance TH.Lift a => TH.Lift (ViewL a)
21792179
#endif
21802180

@@ -2241,7 +2241,7 @@ deriving instance Generic1 ViewR
22412241
-- | @since 0.5.8
22422242
deriving instance Generic (ViewR a)
22432243

2244-
-- | @since 0.7
2244+
-- | @since FIXME
22452245
deriving instance TH.Lift a => TH.Lift (ViewR a)
22462246
#endif
22472247

containers/src/Data/Set/Internal.hs

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,9 @@
55
{-# LANGUAGE Trustworthy #-}
66
#endif
77
#ifdef __GLASGOW_HASKELL__
8+
{-# LANGUAGE DeriveLift #-}
89
{-# LANGUAGE RoleAnnotations #-}
10+
{-# LANGUAGE StandaloneDeriving #-}
911
{-# LANGUAGE TypeFamilies #-}
1012
#endif
1113

@@ -250,6 +252,7 @@ import qualified GHC.Exts as GHCExts
250252
import Text.Read ( readPrec, Read (..), Lexeme (..), parens, prec
251253
, lexP, readListPrecDefault )
252254
import Data.Data
255+
import Language.Haskell.TH.Syntax (Lift)
253256
#endif
254257

255258

@@ -280,6 +283,9 @@ type Size = Int
280283
type role Set nominal
281284
#endif
282285

286+
-- | @since FIXME
287+
deriving instance Lift a => Lift (Set a)
288+
283289
instance Ord a => Monoid (Set a) where
284290
mempty = empty
285291
mconcat = unions

containers/src/Data/Tree.hs

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,7 @@
33
#if __GLASGOW_HASKELL__
44
{-# LANGUAGE DeriveDataTypeable #-}
55
{-# LANGUAGE DeriveGeneric #-}
6+
{-# LANGUAGE DeriveLift #-}
67
{-# LANGUAGE Trustworthy #-}
78
#endif
89

@@ -62,6 +63,7 @@ import Control.DeepSeq (NFData(rnf))
6263
#ifdef __GLASGOW_HASKELL__
6364
import Data.Data (Data)
6465
import GHC.Generics (Generic, Generic1)
66+
import Language.Haskell.TH.Syntax (Lift)
6567
#endif
6668

6769
import Control.Monad.Zip (MonadZip (..))
@@ -88,6 +90,7 @@ data Tree a = Node {
8890
, Data
8991
, Generic -- ^ @since 0.5.8
9092
, Generic1 -- ^ @since 0.5.8
93+
, Lift -- ^ @since FIXME
9194
)
9295
#else
9396
deriving (Eq, Ord, Read, Show)

0 commit comments

Comments
 (0)