Skip to content
Snippets Groups Projects
Commit 59ba62ad authored by Ryan Scott's avatar Ryan Scott
Browse files

Migrate patches to more recent Hackage versions

These packages all have more recent Hackage versions that require
patching to support GHC HEAD.
parent ebb6a19b
No related branches found
No related tags found
No related merge requests found
diff --git a/active.cabal b/active.cabal
index 20ae73c..06fad98 100644
--- a/active.cabal
+++ b/active.cabal
@@ -23,8 +23,8 @@ library
build-depends: base >= 4.0 && < 4.11,
vector >= 0.10,
semigroups >= 0.1 && < 0.19,
- semigroupoids >= 1.2 && < 5.3,
- lens >= 4.0 && < 4.16,
+ semigroupoids >= 1.2 && < 5.4,
+ lens >= 4.0 && < 4.19,
linear >= 1.14 && < 1.21
hs-source-dirs: src
default-language: Haskell2010
@@ -35,8 +35,8 @@ test-suite active-tests
build-depends: base >= 4.0 && < 4.10,
vector >= 0.10,
semigroups >= 0.1 && < 0.19,
- semigroupoids >= 1.2 && < 5.3,
- lens >= 4.0 && < 4.16,
+ semigroupoids >= 1.2 && < 5.4,
+ lens >= 4.0 && < 4.19,
linear >= 1.14 && < 1.21,
QuickCheck >= 2.9 && < 2.10
other-modules: Data.Active
diff --git a/src/Data/Active.hs b/src/Data/Active.hs
index c5e1b3f..4db447b 100644
--- a/src/Data/Active.hs
......
diff --git a/src/Data/DoubleWord/TH.hs b/src/Data/DoubleWord/TH.hs
index 1b4dc07..458d1b1 100644
index 780f44b..5634f19 100644
--- a/src/Data/DoubleWord/TH.hs
+++ b/src/Data/DoubleWord/TH.hs
@@ -22,9 +22,19 @@ import Data.Hashable (Hashable(..), hashWithSalt)
import Data.Hashable (Hashable(..), combine)
#endif
@@ -24,10 +24,17 @@ import Data.Hashable (Hashable(..), combine)
#if !MIN_VERSION_base(4,12,0)
import Control.Applicative ((<$>), (<*>))
#endif
-import Language.Haskell.TH hiding (unpacked, match)
+import Language.Haskell.TH hiding (unpacked, match, tupE)
import Data.BinaryWord (BinaryWord(..))
import Data.DoubleWord.Base
+#if MIN_VERSION_template_haskell(2,15,0)
+import Data.List (foldl')
+#endif
+
+tupE :: [Exp] -> Exp
+#if MIN_VERSION_template_haskell(2,16,0)
+tupE = TupE . map Just
+#else
+tupE = TupE
+#endif
+
-- | Declare signed and unsigned binary word types built from
-- the specified low and high halves. The high halves /must/ have
@@ -549,26 +559,26 @@ mkDoubleWord' signed tp cn otp ocn hiS hiT loS loT ad = (<$> mkRules) $ (++) $
-- less or equal bit-length than the lover half. For each data type
@@ -551,26 +558,26 @@ mkDoubleWord' signed tp cn otp ocn hiS hiT loS loT ad = (<$> mkRules) $ (++) $
appV 'quotRem
[ appV 'unsignedWord [appVN 'negate [x]]
, appV 'unsignedWord [appVN 'negate [y]] ]]
......@@ -54,7 +52,7 @@ index 1b4dc07..458d1b1 100644
, appVN 'signedWord [r] ])))
else
funHiLo2XY' 'quotRem
@@ -576,25 +586,25 @@ mkDoubleWord' signed tp cn otp ocn hiS hiT loS loT ad = (<$> mkRules) $ (++) $
@@ -578,25 +585,25 @@ mkDoubleWord' signed tp cn otp ocn hiS hiT loS loT ad = (<$> mkRules) $ (++) $
, appVN '(==) [lo', 'allZeroes] ])
(appV 'error [litS "divide by zero"])
(CaseE (appVN 'compare [hi, hi'])
......@@ -86,7 +84,7 @@ index 1b4dc07..458d1b1 100644
[ appW [zeroE, appVN 'fromIntegral [t2]]
, appW [appVN 'fromIntegral [t1], VarE lo]
] ))
@@ -606,16 +616,16 @@ mkDoubleWord' signed tp cn otp ocn hiS hiT loS loT ad = (<$> mkRules) $ (++) $
@@ -608,16 +615,16 @@ mkDoubleWord' signed tp cn otp ocn hiS hiT loS loT ad = (<$> mkRules) $ (++) $
, appVN '(==) [lo', 'maxBound] ])
, CondE (appVN '(==) [t2, 'allZeroes])
(CondE (appVN '(==) [t1, 'maxBound])
......@@ -106,7 +104,7 @@ index 1b4dc07..458d1b1 100644
[ appV '(+)
[appWN ['allZeroes, z], litI 2]
, oneE ])
@@ -624,11 +634,11 @@ mkDoubleWord' signed tp cn otp ocn hiS hiT loS loT ad = (<$> mkRules) $ (++) $
@@ -626,11 +633,11 @@ mkDoubleWord' signed tp cn otp ocn hiS hiT loS loT ad = (<$> mkRules) $ (++) $
[ VarE t1
, appVN 'xor ['maxBound, 'lsb]
])
......@@ -120,7 +118,7 @@ index 1b4dc07..458d1b1 100644
[ appV '(+)
[appWN ['allZeroes, z], oneE]
, appW [ zeroE
@@ -640,12 +650,12 @@ mkDoubleWord' signed tp cn otp ocn hiS hiT loS loT ad = (<$> mkRules) $ (++) $
@@ -642,12 +649,12 @@ mkDoubleWord' signed tp cn otp ocn hiS hiT loS loT ad = (<$> mkRules) $ (++) $
, Match (ConP 'GT [])
(GuardedB $ return
( NormalG (appVN '(==) [hi', 'allZeroes])
......@@ -136,7 +134,7 @@ index 1b4dc07..458d1b1 100644
, appVN 'shiftR [r2, t2] ]))
[ val t1 $ appVN 'leadingZeroes [hi]
, val t2 $ appVN 'leadingZeroes [hi']
@@ -671,24 +681,24 @@ mkDoubleWord' signed tp cn otp ocn hiS hiT loS loT ad = (<$> mkRules) $ (++) $
@@ -673,24 +680,24 @@ mkDoubleWord' signed tp cn otp ocn hiS hiT loS loT ad = (<$> mkRules) $ (++) $
CondE (appVN '(>) [t5, t6])
(CondE (appV '(==) [appVN 'loWord [t8], zeroE])
(CondE (appVN '(>=) [t7, t5])
......@@ -166,7 +164,7 @@ index 1b4dc07..458d1b1 100644
]
]))
[ FunD div1 $ return $
@@ -699,7 +709,7 @@ mkDoubleWord' signed tp cn otp ocn hiS hiT loS loT ad = (<$> mkRules) $ (++) $
@@ -701,7 +708,7 @@ mkDoubleWord' signed tp cn otp ocn hiS hiT loS loT ad = (<$> mkRules) $ (++) $
Clause [VarP h, VarP l, VarP c]
(NormalB
(CondE (appVN '(==) [z, 'allZeroes])
......@@ -175,7 +173,7 @@ index 1b4dc07..458d1b1 100644
[ VarE c
, appV '(+)
[ appW [ appVN 'fromIntegral [t8]
@@ -729,17 +739,17 @@ mkDoubleWord' signed tp cn otp ocn hiS hiT loS loT ad = (<$> mkRules) $ (++) $
@@ -731,17 +738,17 @@ mkDoubleWord' signed tp cn otp ocn hiS hiT loS loT ad = (<$> mkRules) $ (++) $
Clause [VarP hhh, VarP hll, VarP by]
(NormalB (appV go [ VarE hhh
, VarE hll
......@@ -197,7 +195,7 @@ index 1b4dc07..458d1b1 100644
]
, VarE t9 ])
(appV go
@@ -747,7 +757,7 @@ mkDoubleWord' signed tp cn otp ocn hiS hiT loS loT ad = (<$> mkRules) $ (++) $
@@ -749,7 +756,7 @@ mkDoubleWord' signed tp cn otp ocn hiS hiT loS loT ad = (<$> mkRules) $ (++) $
, VarE t5
, appV addT
[ VarE c
......@@ -206,7 +204,7 @@ index 1b4dc07..458d1b1 100644
]
])))
[ vals [t4, t3] $
@@ -761,7 +771,7 @@ mkDoubleWord' signed tp cn otp ocn hiS hiT loS loT ad = (<$> mkRules) $ (++) $
@@ -763,7 +770,7 @@ mkDoubleWord' signed tp cn otp ocn hiS hiT loS loT ad = (<$> mkRules) $ (++) $
Clause [ TupP [VarP lhh, VarP lhl]
, TupP [VarP llh, VarP lll]
]
......@@ -215,7 +213,7 @@ index 1b4dc07..458d1b1 100644
[ VarE t4
, appVN '(+) [lhh, llh]
]
@@ -811,7 +821,7 @@ mkDoubleWord' signed tp cn otp ocn hiS hiT loS loT ad = (<$> mkRules) $ (++) $
@@ -813,7 +820,7 @@ mkDoubleWord' signed tp cn otp ocn hiS hiT loS loT ad = (<$> mkRules) $ (++) $
appV 'quotRem
[ appV 'unsignedWord [appVN 'negate [x]]
, appV 'unsignedWord [appVN 'negate [y]] ]]
......@@ -224,7 +222,7 @@ index 1b4dc07..458d1b1 100644
, appV 'signedWord [appVN 'negate [r]] ]))
(LetE [ vals [q, r] $
appV 'quotRem
@@ -821,8 +831,8 @@ mkDoubleWord' signed tp cn otp ocn hiS hiT loS loT ad = (<$> mkRules) $ (++) $
@@ -823,8 +830,8 @@ mkDoubleWord' signed tp cn otp ocn hiS hiT loS loT ad = (<$> mkRules) $ (++) $
, val r1 $ appV 'signedWord [appVN 'negate [r]]
]
(CondE (appVN '(==) [r, 'allZeroes])
......@@ -235,7 +233,7 @@ index 1b4dc07..458d1b1 100644
, appVN '(+) [r1, y] ]))))
(CondE (appVN 'testMsb [y])
(LetE [ vals [q, r] $
@@ -833,14 +843,14 @@ mkDoubleWord' signed tp cn otp ocn hiS hiT loS loT ad = (<$> mkRules) $ (++) $
@@ -835,14 +842,14 @@ mkDoubleWord' signed tp cn otp ocn hiS hiT loS loT ad = (<$> mkRules) $ (++) $
, val r1 $ appVN 'signedWord [r]
]
(CondE (appVN '(==) [r, 'allZeroes])
......@@ -253,7 +251,7 @@ index 1b4dc07..458d1b1 100644
, appVN 'signedWord [r] ])))
else
fun 'divMod $ VarE 'quotRem
@@ -856,7 +866,7 @@ mkDoubleWord' signed tp cn otp ocn hiS hiT loS loT ad = (<$> mkRules) $ (++) $
@@ -858,7 +865,7 @@ mkDoubleWord' signed tp cn otp ocn hiS hiT loS loT ad = (<$> mkRules) $ (++) $
-}
[ funXY 'readsPrec $
appV 'fmap [ LamE [TupP [VarP q, VarP r]]
......@@ -262,7 +260,7 @@ index 1b4dc07..458d1b1 100644
, appVN 'readsPrec [x, y] ]
]
, inst ''Hashable [tp]
@@ -1145,7 +1155,7 @@ mkDoubleWord' signed tp cn otp ocn hiS hiT loS loT ad = (<$> mkRules) $ (++) $
@@ -1147,7 +1154,7 @@ mkDoubleWord' signed tp cn otp ocn hiS hiT loS loT ad = (<$> mkRules) $ (++) $
-}
, if signed
then
......@@ -271,7 +269,7 @@ index 1b4dc07..458d1b1 100644
[ val t1 $ CondE (appVN 'testMsb [x])
(VarE 'maxBound) (VarE 'minBound)
, val t2 $ CondE (appVN 'testMsb [y])
@@ -1158,7 +1168,7 @@ mkDoubleWord' signed tp cn otp ocn hiS hiT loS loT ad = (<$> mkRules) $ (++) $
@@ -1160,7 +1167,7 @@ mkDoubleWord' signed tp cn otp ocn hiS hiT loS loT ad = (<$> mkRules) $ (++) $
]
else
funHiLo2' 'unwrappedAdd
......@@ -280,7 +278,7 @@ index 1b4dc07..458d1b1 100644
[ vals [t1, x] $ appVN 'unwrappedAdd [lo, lo']
, vals [t3, t2] $
appV 'unwrappedAdd [VarE hi, appVN 'fromIntegral [t1]]
@@ -1200,7 +1210,7 @@ mkDoubleWord' signed tp cn otp ocn hiS hiT loS loT ad = (<$> mkRules) $ (++) $
@@ -1202,7 +1209,7 @@ mkDoubleWord' signed tp cn otp ocn hiS hiT loS loT ad = (<$> mkRules) $ (++) $
-}
, if signed
then
......@@ -289,7 +287,7 @@ index 1b4dc07..458d1b1 100644
[ val t1 $
appV '(+) [ appW [ appVN 'complement [hi']
, appVN 'complement [lo'] ]
@@ -1224,7 +1234,7 @@ mkDoubleWord' signed tp cn otp ocn hiS hiT loS loT ad = (<$> mkRules) $ (++) $
@@ -1226,7 +1233,7 @@ mkDoubleWord' signed tp cn otp ocn hiS hiT loS loT ad = (<$> mkRules) $ (++) $
]
else
funHiLo2' 'unwrappedMul
......@@ -298,136 +296,3 @@ index 1b4dc07..458d1b1 100644
[ appV '(+)
[ VarE hhh
, appV '(+)
@@ -1378,8 +1388,12 @@ mkDoubleWord' signed tp cn otp ocn hiS hiT loS loT ad = (<$> mkRules) $ (++) $
hi' = mkName "hi'"
lo' = mkName "lo'"
tpT = ConT tp
+
+ tySynInst :: Name -> [Type] -> Type -> Dec
tySynInst n ps t =
-#if MIN_VERSION_template_haskell(2,9,0)
+#if MIN_VERSION_template_haskell(2,15,0)
+ TySynInstD (TySynEqn Nothing (foldl' AppT (ConT n) ps) t)
+#elif MIN_VERSION_template_haskell(2,9,0)
TySynInstD n (TySynEqn ps t)
#else
TySynInstD n ps t
@@ -1448,11 +1462,19 @@ mkDoubleWord' signed tp cn otp ocn hiS hiT loS loT ad = (<$> mkRules) $ (++) $
#endif
singE e = appC '(:) [e, ConE '[]]
mkRules = do
- let idRule = RuleP ("fromIntegral/" ++ show tp ++ "->" ++ show tp) []
+ let idRule = RuleP ("fromIntegral/" ++ show tp ++ "->" ++ show tp)
+#if MIN_VERSION_template_haskell(2,15,0)
+ Nothing
+#endif
+ []
(VarE 'fromIntegral)
(SigE (VarE 'id) (AppT (AppT ArrowT tpT) tpT))
AllPhases
- signRule = RuleP ("fromIntegral/" ++ show tp ++ "->" ++ show otp) []
+ signRule = RuleP ("fromIntegral/" ++ show tp ++ "->" ++ show otp)
+#if MIN_VERSION_template_haskell(2,15,0)
+ Nothing
+#endif
+ []
(VarE 'fromIntegral)
(SigE (VarE (if signed then 'unsignedWord
else 'signedWord))
@@ -1464,11 +1486,17 @@ mkDoubleWord' signed tp cn otp ocn hiS hiT loS loT ad = (<$> mkRules) $ (++) $
(VarE 'signExtendLo)
mkRules' rules t narrowE extE signExtE = do
let narrowRule = RuleP ("fromIntegral/" ++ show tp ++ "->" ++ showT t)
+#if MIN_VERSION_template_haskell(2,15,0)
+ Nothing
+#endif
[]
(VarE 'fromIntegral)
(SigE narrowE (AppT (AppT ArrowT tpT) t))
AllPhases
extRule = RuleP ("fromIntegral/" ++ showT t ++ "->" ++ show tp)
+#if MIN_VERSION_template_haskell(2,15,0)
+ Nothing
+#endif
[]
(VarE 'fromIntegral)
(SigE extE (AppT (AppT ArrowT t) tpT))
@@ -1476,18 +1504,26 @@ mkDoubleWord' signed tp cn otp ocn hiS hiT loS loT ad = (<$> mkRules) $ (++) $
signedRules ← do
insts ← reifyInstances ''SignedWord [t]
case insts of
-#if MIN_VERSION_template_haskell(2,9,0)
+#if MIN_VERSION_template_haskell(2,15,0)
+ [TySynInstD (TySynEqn _ _ signT)] -> return $
+#elif MIN_VERSION_template_haskell(2,9,0)
[TySynInstD _ (TySynEqn _ signT)] → return $
#else
[TySynInstD _ _ signT] → return $
#endif
[ RuleP ("fromIntegral/" ++ show tp ++ "->" ++ showT signT)
+#if MIN_VERSION_template_haskell(2,15,0)
+ Nothing
+#endif
[]
(VarE 'fromIntegral)
(SigE (AppE (appVN '(.) ['signedWord]) narrowE)
(AppT (AppT ArrowT tpT) signT))
AllPhases
, RuleP ("fromIntegral/" ++ showT signT ++ "->" ++ show tp)
+#if MIN_VERSION_template_haskell(2,15,0)
+ Nothing
+#endif
[]
(VarE 'fromIntegral)
(SigE signExtE (AppT (AppT ArrowT signT) tpT))
@@ -1501,6 +1537,9 @@ mkDoubleWord' signed tp cn otp ocn hiS hiT loS loT ad = (<$> mkRules) $ (++) $
sSmallT = ConT sSmallName in
[ RuleP ("fromIntegral/" ++
show tp ++ "->" ++ show uSmallName)
+#if MIN_VERSION_template_haskell(2,15,0)
+ Nothing
+#endif
[]
(VarE 'fromIntegral)
(SigE (appV '(.) [VarE 'fromIntegral, narrowE])
@@ -1508,6 +1547,9 @@ mkDoubleWord' signed tp cn otp ocn hiS hiT loS loT ad = (<$> mkRules) $ (++) $
AllPhases
, RuleP ("fromIntegral/" ++
show uSmallName ++ "->" ++ show tp)
+#if MIN_VERSION_template_haskell(2,15,0)
+ Nothing
+#endif
[]
(VarE 'fromIntegral)
(SigE (appV '(.) [extE, VarE 'fromIntegral])
@@ -1515,6 +1557,9 @@ mkDoubleWord' signed tp cn otp ocn hiS hiT loS loT ad = (<$> mkRules) $ (++) $
AllPhases
, RuleP ("fromIntegral/" ++
show tp ++ "->" ++ show sSmallName)
+#if MIN_VERSION_template_haskell(2,15,0)
+ Nothing
+#endif
[]
(VarE 'fromIntegral)
(SigE (appV '(.) [VarE 'fromIntegral, narrowE])
@@ -1522,6 +1567,9 @@ mkDoubleWord' signed tp cn otp ocn hiS hiT loS loT ad = (<$> mkRules) $ (++) $
AllPhases
, RuleP ("fromIntegral/" ++
show sSmallName ++ "->" ++ show tp)
+#if MIN_VERSION_template_haskell(2,15,0)
+ Nothing
+#endif
[]
(VarE 'fromIntegral)
(SigE (appV '(.) [signExtE, VarE 'fromIntegral])
@@ -1532,7 +1580,9 @@ mkDoubleWord' signed tp cn otp ocn hiS hiT loS loT ad = (<$> mkRules) $ (++) $
_ → do
insts ← reifyInstances ''LoWord [t]
case insts of
-#if MIN_VERSION_template_haskell(2,9,0)
+#if MIN_VERSION_template_haskell(2,15,0)
+ [TySynInstD (TySynEqn _ _ t')] ->
+#elif MIN_VERSION_template_haskell(2,9,0)
[TySynInstD _ (TySynEqn _ t')] →
#else
[TySynInstD _ _ t'] →
diff --git a/src/Language/Haskell/Meta/Syntax/Translate.hs b/src/Language/Haskell/Meta/Syntax/Translate.hs
index 1719f29..ecf3012 100644
index 104eb92..660a634 100644
--- a/src/Language/Haskell/Meta/Syntax/Translate.hs
+++ b/src/Language/Haskell/Meta/Syntax/Translate.hs
@@ -83,11 +83,23 @@ instance ToExp TH.Lit where
......@@ -53,10 +53,10 @@ index 1719f29..ecf3012 100644
toExp (Exts.List _ xs) = TH.ListE (fmap toExp xs)
toExp (Exts.Paren _ e) = TH.ParensE (toExp e)
diff --git a/src/Language/Haskell/Meta/Utils.hs b/src/Language/Haskell/Meta/Utils.hs
index e0b1477..40b5d98 100644
index 5aee5e8..9aaf269 100644
--- a/src/Language/Haskell/Meta/Utils.hs
+++ b/src/Language/Haskell/Meta/Utils.hs
@@ -350,7 +350,13 @@ fromDataConI (DataConI dConN ty _tyConN) =
@@ -330,7 +330,13 @@ fromDataConI (DataConI dConN ty _tyConN) =
in replicateM n (newName "a")
>>= \ns -> return (Just (LamE
[ConP dConN (fmap VarP ns)]
......
File moved
diff --git a/src/TH/ReifySimple.hs b/src/TH/ReifySimple.hs
index d179829..4bd6430 100644
--- a/src/TH/ReifySimple.hs
+++ b/src/TH/ReifySimple.hs
@@ -60,7 +60,7 @@ import Data.Generics.Aliases (extT)
import qualified Data.Map as M
import Data.Typeable (Typeable)
import GHC.Generics (Generic)
-import Language.Haskell.TH
+import Language.Haskell.TH hiding (reifyType)
import Language.Haskell.TH.Instances ()
import TH.Utilities
@@ -233,18 +233,24 @@ infoToDataFamily info = case info of
Just $ DataFamily name (map tyVarBndrName tvs) (map go insts)
_ -> Nothing
where
-#if MIN_VERSION_template_haskell(2,11,0)
- go (NewtypeInstD preds name params _kind con _deriving) =
+#if MIN_VERSION_template_haskell(2,15,0)
+ go (NewtypeInstD preds _ lhs _kind con _deriving)
+ | ConT name:params <- unAppsT lhs
+#elif MIN_VERSION_template_haskell(2,11,0)
+ go (NewtypeInstD preds name params _kind con _deriving)
#else
- go (NewtypeInstD preds name params con _deriving) =
+ go (NewtypeInstD preds name params con _deriving)
#endif
- DataInst name preds params (conToDataCons con)
-#if MIN_VERSION_template_haskell(2,11,0)
- go (DataInstD preds name params _kind cons _deriving) =
+ = DataInst name preds params (conToDataCons con)
+#if MIN_VERSION_template_haskell(2,15,0)
+ go (DataInstD preds _ lhs _kind cons _deriving)
+ | ConT name:params <- unAppsT lhs
+#elif MIN_VERSION_template_haskell(2,11,0)
+ go (DataInstD preds name params _kind cons _deriving)
#else
- go (DataInstD preds name params cons _deriving) =
+ go (DataInstD preds name params cons _deriving)
#endif
- DataInst name preds params (concatMap conToDataCons cons)
+ = DataInst name preds params (concatMap conToDataCons cons)
go info' = error $
"Unexpected instance in FamilyI in infoToDataInsts:\n" ++ pprint info'
@@ -263,8 +269,23 @@ infoToTypeFamily info = case info of
#endif
_ -> Nothing
where
+#if MIN_VERSION_template_haskell(2,15,0)
+ goEqn _ (TySynEqn _ lhs ty)
+ | ConT name:params <- unAppsT lhs
+ = TypeInst name params ty
+ | otherwise
+ = error $ "Unexpected type family instance head: " ++ pprint lhs
+#else
goEqn name (TySynEqn params ty) = TypeInst name params ty
+#endif
+
+#if MIN_VERSION_template_haskell(2,15,0)
+ go (TySynInstD (TySynEqn _ lhs ty))
+ | ConT name:params <- unAppsT lhs
+ = TypeInst name params ty
+#else
go (TySynInstD name (TySynEqn params ty)) = TypeInst name params ty
+#endif
go info' = error $
"Unexpected instance in FamilyI in infoToTypeInsts:\n" ++ pprint info'
diff --git a/src/TH/ReifySimple.hs b/src/TH/ReifySimple.hs
index 70b929e..78509ce 100644
--- a/src/TH/ReifySimple.hs
+++ b/src/TH/ReifySimple.hs
@@ -61,6 +61,9 @@ import qualified Data.Map as M
import Data.Typeable (Typeable)
import GHC.Generics (Generic)
import Language.Haskell.TH
+#if MIN_VERSION_template_haskell(2,16,0)
+ hiding (reifyType)
+#endif
import Language.Haskell.TH.Instances ()
import TH.Utilities
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment