diff --git a/ChangeLog.md b/ChangeLog.md index f0bb4c1..f92e90b 100644 --- a/ChangeLog.md +++ b/ChangeLog.md @@ -1,3 +1,8 @@ +# 1.0.3 + +- Make `GNFData` PolyKinded. +- Add `GNFData ((:~:) a)` and `GNFData TypeRep` instances + # 1.0.2 - Explicitly mark `Data.Some` as `Safe`. diff --git a/some.cabal b/some.cabal index 463ba8d..a1b2b24 100644 --- a/some.cabal +++ b/some.cabal @@ -1,5 +1,5 @@ name: some -version: 1.0.2 +version: 1.0.3 stability: provisional cabal-version: >=1.10 build-type: Simple @@ -60,11 +60,12 @@ library if flag(newtype-unsafe) cpp-options: -DSOME_NEWTYPE + -- main module + exposed-modules: Data.Some exposed-modules: Data.GADT.Compare Data.GADT.DeepSeq Data.GADT.Show - Data.Some Data.Some.Church Data.Some.GADT Data.Some.Newtype @@ -83,11 +84,14 @@ library , transformers >=0.3 && <0.6 , transformers-compat >=0.6 && <0.7 - if impl(ghc >= 9.0) + if impl(ghc >=9.0) -- these flags may abort compilation with GHC-8.10 -- https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3295 ghc-options: -Winferred-safe-imports -Wmissing-safe-haskell-mode + if impl(ghc >=9.1) + ghc-options: -Wmissing-kind-signatures + test-suite hkd-example default-language: Haskell2010 type: exitcode-stdio-1.0 diff --git a/src/Data/GADT/DeepSeq.hs b/src/Data/GADT/DeepSeq.hs index 344279a..0046985 100644 --- a/src/Data/GADT/DeepSeq.hs +++ b/src/Data/GADT/DeepSeq.hs @@ -1,5 +1,12 @@ {-# LANGUAGE CPP #-} -#if __GLASGOW_HASKELL__ >= 704 +{-# LANGUAGE GADTs #-} +#if __GLASGOW_HASKELL__ >= 706 +{-# LANGUAGE PolyKinds #-} +#endif +#if __GLASGOW_HASKELL__ >= 810 +{-# LANGUAGE StandaloneKindSignatures #-} +#endif +#if (__GLASGOW_HASKELL__ >= 704 && __GLASGOW_HASKELL__ < 707) || __GLASGOW_HASKELL__ >= 801 {-# LANGUAGE Safe #-} #elif __GLASGOW_HASKELL__ >= 702 {-# LANGUAGE Trustworthy #-} @@ -10,6 +17,19 @@ module Data.GADT.DeepSeq ( import Data.Functor.Product (Product (..)) import Data.Functor.Sum (Sum (..)) +import Data.Type.Equality ((:~:) (..)) + +#if MIN_VERSION_base(4,10,0) +import qualified Type.Reflection as TR +#endif + +#if __GLASGOW_HASKELL__ >= 810 +import Data.Kind (Type, Constraint) +#endif + +#if __GLASGOW_HASKELL__ >= 810 +type GNFData :: (k -> Type) -> Constraint +#endif class GNFData f where grnf :: f a -> () @@ -20,3 +40,13 @@ instance (GNFData a, GNFData b) => GNFData (Product a b) where instance (GNFData a, GNFData b) => GNFData (Sum a b) where grnf (InL x) = grnf x grnf (InR y) = grnf y + +-- | @since 1.0.3 +instance GNFData ((:~:) a) where + grnf Refl = () + +#if MIN_VERSION_base(4,10,0) +-- | @since 1.0.3 +instance GNFData TR.TypeRep where + grnf = TR.rnfTypeRep +#endif diff --git a/src/Data/GADT/Internal.hs b/src/Data/GADT/Internal.hs index a66f2e3..2743d44 100644 --- a/src/Data/GADT/Internal.hs +++ b/src/Data/GADT/Internal.hs @@ -7,15 +7,17 @@ #if __GLASGOW_HASKELL__ >= 706 {-# LANGUAGE PolyKinds #-} #endif -#if __GLASGOW_HASKELL__ >= 704 -#define GHC __GLASGOW_HASKELL__ -#if (GHC >= 704 && GHC <707) || GHC >= 801 +#if __GLASGOW_HASKELL__ >= 708 +{-# LANGUAGE RoleAnnotations #-} +#endif +#if __GLASGOW_HASKELL__ >= 810 +{-# LANGUAGE StandaloneKindSignatures #-} +#endif +#if (__GLASGOW_HASKELL__ >= 704 && __GLASGOW_HASKELL__ < 707) || __GLASGOW_HASKELL__ >= 801 {-# LANGUAGE Safe #-} -#else +#elif __GLASGOW_HASKELL__ >= 702 {-# LANGUAGE Trustworthy #-} #endif -#undef GHC -#endif module Data.GADT.Internal where import Control.Applicative (Applicative (..)) @@ -35,6 +37,10 @@ import Data.Type.Equality (testEquality) import qualified Type.Reflection as TR #endif +#if __GLASGOW_HASKELL__ >= 810 +import Data.Kind (Type, Constraint) +#endif + -- $setup -- >>> :set -XKindSignatures -XGADTs @@ -43,6 +49,9 @@ import qualified Type.Reflection as TR -- to write (or derive) an @instance Show (T a)@, and then simply say: -- -- > instance GShow t where gshowsPrec = showsPrec +#if __GLASGOW_HASKELL__ >= 810 +type GShow :: (k -> Type) -> Constraint +#endif class GShow t where gshowsPrec :: Int -> t a -> ShowS @@ -79,6 +88,9 @@ instance (GShow a, GShow b) => GShow (Product a b) where -- |@GReadS t@ is equivalent to @ReadS (forall b. (forall a. t a -> b) -> b)@, which is -- in turn equivalent to @ReadS (Exists t)@ (with @data Exists t where Exists :: t a -> Exists t@) +#if __GLASGOW_HASKELL__ >= 810 +type GReadS :: (k -> Type) -> Type +#endif type GReadS t = String -> [(Some t, String)] getGReadResult :: Some tag -> (forall a. tag a -> b) -> b @@ -90,6 +102,9 @@ mkGReadResult = mkSome -- |'Read'-like class for 1-type-parameter GADTs. Unlike 'GShow', this one cannot be -- mechanically derived from a 'Read' instance because 'greadsPrec' must choose the phantom -- type based on the 'String' being parsed. +#if __GLASGOW_HASKELL__ >= 810 +type GRead :: (k -> Type) -> Constraint +#endif class GRead t where greadsPrec :: Int -> GReadS t @@ -139,6 +154,9 @@ instance (GRead a, GRead b) => GRead (Sum a b) where -- |A class for type-contexts which contain enough information -- to (at least in some cases) decide the equality of types -- occurring within them. +#if __GLASGOW_HASKELL__ >= 810 +type GEq :: (k -> Type) -> Constraint +#endif class GEq f where -- |Produce a witness of type-equality, if one exists. -- @@ -219,6 +237,9 @@ instance GEq TR.TypeRep where -- |A type for the result of comparing GADT constructors; the type parameters -- of the GADT values being compared are included so that in the case where -- they are equal their parameter types can be unified. +#if __GLASGOW_HASKELL__ >= 810 +type GOrdering :: k -> k -> Type +#endif data GOrdering a b where GLT :: GOrdering a b GEQ :: GOrdering t t @@ -259,6 +280,9 @@ instance GRead (GOrdering a) where -- |Type class for comparable GADT-like structures. When 2 things are equal, -- must return a witness that their parameter types are equal as well ('GEQ'). +#if __GLASGOW_HASKELL__ >= 810 +type GCompare :: (k -> Type) -> Constraint +#endif class GEq f => GCompare f where gcompare :: f a -> f b -> GOrdering a b @@ -343,11 +367,18 @@ instance (GCompare a, GCompare b) => GCompare (Product a b) where -- >>> read "mkSome TagInt" :: Some Tag -- mkSome TagInt -- +#if __GLASGOW_HASKELL__ >= 810 +type Some :: (k -> Type) -> Type +#endif newtype Some tag = S { -- | Eliminator. withSome :: forall r. (forall a. tag a -> r) -> r } +#if __GLASGOW_HASKELL__ >= 708 +type role Some representational +#endif + -- | Constructor. mkSome :: tag a -> Some tag mkSome t = S (\f -> f t) diff --git a/src/Data/Some/GADT.hs b/src/Data/Some/GADT.hs index 1ad59d8..4647b3c 100644 --- a/src/Data/Some/GADT.hs +++ b/src/Data/Some/GADT.hs @@ -4,6 +4,12 @@ #if __GLASGOW_HASKELL__ >= 706 {-# LANGUAGE PolyKinds #-} #endif +#if __GLASGOW_HASKELL__ >= 708 +{-# LANGUAGE RoleAnnotations #-} +#endif +#if __GLASGOW_HASKELL__ >= 810 +{-# LANGUAGE StandaloneKindSignatures #-} +#endif #if __GLASGOW_HASKELL__ >= 704 {-# LANGUAGE Safe #-} #elif __GLASGOW_HASKELL__ >= 702 @@ -24,10 +30,15 @@ import Control.DeepSeq (NFData (..)) import Data.Monoid (Monoid (..)) import Data.Semigroup (Semigroup (..)) +#if __GLASGOW_HASKELL__ >= 810 +import Data.Kind (Type) +#endif + import Data.GADT.Compare import Data.GADT.DeepSeq import Data.GADT.Show + -- $setup -- >>> :set -XKindSignatures -XGADTs @@ -73,9 +84,16 @@ import Data.GADT.Show -- >>> read "mkSome TagInt" :: Some Tag -- Some TagInt -- +#if __GLASGOW_HASKELL__ >= 810 +type Some :: (k -> Type) -> Type +#endif data Some tag where Some :: tag a -> Some tag +#if __GLASGOW_HASKELL__ >= 708 +type role Some representational +#endif + -- | Constructor. mkSome :: tag a -> Some tag mkSome = Some diff --git a/src/Data/Some/Newtype.hs b/src/Data/Some/Newtype.hs index d8e1470..4ed5c72 100644 --- a/src/Data/Some/Newtype.hs +++ b/src/Data/Some/Newtype.hs @@ -4,9 +4,15 @@ #if __GLASGOW_HASKELL__ >= 801 {-# LANGUAGE PatternSynonyms #-} #endif +#if __GLASGOW_HASKELL__ >= 708 +{-# LANGUAGE RoleAnnotations #-} +#endif #if __GLASGOW_HASKELL__ >= 706 {-# LANGUAGE PolyKinds #-} #endif +#if __GLASGOW_HASKELL__ >= 810 +{-# LANGUAGE StandaloneKindSignatures #-} +#endif #if __GLASGOW_HASKELL__ >= 702 {-# LANGUAGE Trustworthy #-} #endif @@ -31,6 +37,10 @@ import Data.Semigroup (Semigroup (..)) import GHC.Exts (Any) import Unsafe.Coerce (unsafeCoerce) +#if __GLASGOW_HASKELL__ >= 810 +import Data.Kind (Type) +#endif + import Data.GADT.Compare import Data.GADT.DeepSeq import Data.GADT.Show @@ -80,7 +90,14 @@ import Data.GADT.Show -- >>> read "mkSome TagInt" :: Some Tag -- Some TagInt -- +#if __GLASGOW_HASKELL__ >= 810 +type Some :: (k -> Type) -> Type +#endif newtype Some tag = UnsafeSome (tag Any) + +#if __GLASGOW_HASKELL__ >= 708 +type role Some representational +#endif #if __GLASGOW_HASKELL__ >= 801 {-# COMPLETE Some #-}