[commit: packages/base] master: Add a couple of `/Since: 4.7.0.0/` annotations (cad7219)
git at git.haskell.org
git at git.haskell.org
Fri Nov 1 09:31:36 UTC 2013
Repository : ssh://git@git.haskell.org/base
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/cad7219d7a149c8bb3e8eeb0467c437f59715506/base
>---------------------------------------------------------------
commit cad7219d7a149c8bb3e8eeb0467c437f59715506
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date: Fri Nov 1 10:07:44 2013 +0100
Add a couple of `/Since: 4.7.0.0/` annotations
Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org>
>---------------------------------------------------------------
cad7219d7a149c8bb3e8eeb0467c437f59715506
Data/Typeable.hs | 2 ++
GHC/TypeLits.hs | 12 ++++++++++++
System/Mem.hs | 4 ++++
3 files changed, 18 insertions(+)
diff --git a/Data/Typeable.hs b/Data/Typeable.hs
index 15aeccb..2f122b9 100644
--- a/Data/Typeable.hs
+++ b/Data/Typeable.hs
@@ -105,6 +105,8 @@ cast x = if typeRep (Proxy :: Proxy a) == typeRep (Proxy :: Proxy b)
else Nothing
-- | Extract a witness of equality of two types
+--
+-- /Since: 4.7.0.0/
eqT :: forall a b. (Typeable a, Typeable b) => Maybe (a :~: b)
eqT = if typeRep (Proxy :: Proxy a) == typeRep (Proxy :: Proxy b)
then Just $ unsafeCoerce Refl
diff --git a/GHC/TypeLits.hs b/GHC/TypeLits.hs
index 41607c3..f3ba70e 100644
--- a/GHC/TypeLits.hs
+++ b/GHC/TypeLits.hs
@@ -53,18 +53,24 @@ data Symbol
-- | This class gives the integer associated with a type-level natural.
-- There are instances of the class for every concrete literal: 0, 1, 2, etc.
+--
+-- /Since: 4.7.0.0/
class KnownNat (n :: Nat) where
natSing :: SNat n
-- | This class gives the integer associated with a type-level symbol.
-- There are instances of the class for every concrete literal: "hello", etc.
+--
+-- /Since: 4.7.0.0/
class KnownSymbol (n :: Symbol) where
symbolSing :: SSymbol n
+-- | /Since: 4.7.0.0/
natVal :: forall n proxy. KnownNat n => proxy n -> Integer
natVal _ = case natSing :: SNat n of
SNat x -> x
+-- | /Since: 4.7.0.0/
symbolVal :: forall n proxy. KnownSymbol n => proxy n -> String
symbolVal _ = case symbolSing :: SSymbol n of
SSymbol x -> x
@@ -73,17 +79,23 @@ symbolVal _ = case symbolSing :: SSymbol n of
-- | This type represents unknown type-level natural numbers.
data SomeNat = forall n. KnownNat n => SomeNat (Proxy n)
+ -- ^ /Since: 4.7.0.0/
-- | This type represents unknown type-level symbols.
data SomeSymbol = forall n. KnownSymbol n => SomeSymbol (Proxy n)
+ -- ^ /Since: 4.7.0.0/
-- | Convert an integer into an unknown type-level natural.
+--
+-- /Since: 4.7.0.0/
someNatVal :: Integer -> Maybe SomeNat
someNatVal n
| n >= 0 = Just (withSNat SomeNat (SNat n) Proxy)
| otherwise = Nothing
-- | Convert a string into an unknown type-level symbol.
+--
+-- /Since: 4.7.0.0/
someSymbolVal :: String -> SomeSymbol
someSymbolVal n = withSSymbol SomeSymbol (SSymbol n) Proxy
diff --git a/System/Mem.hs b/System/Mem.hs
index d46e67e..3674dcb 100644
--- a/System/Mem.hs
+++ b/System/Mem.hs
@@ -26,7 +26,11 @@ performGC :: IO ()
performGC = performMajorGC
-- | Triggers an immediate garbage collection.
+--
+-- /Since: 4.7.0.0/
foreign import ccall "performMajorGC" performMajorGC :: IO ()
-- | Triggers an immediate minor garbage collection.
+--
+-- /Since: 4.7.0.0/
foreign import ccall "performGC" performMinorGC :: IO ()
More information about the ghc-commits
mailing list