[commit: ghc] master: Better document TypeRep patterns (f9bf621)
git at git.haskell.org
git at git.haskell.org
Wed Sep 13 20:54:45 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/f9bf621caf2fc17d829dee0ee48b204144927e72/ghc
>---------------------------------------------------------------
commit f9bf621caf2fc17d829dee0ee48b204144927e72
Author: Ben Gamari <bgamari.foss at gmail.com>
Date: Wed Sep 13 12:23:47 2017 -0400
Better document TypeRep patterns
As pointed out in #14199 these are rather non-trivial; extra
documentation is in order.
[skip ci]
Test Plan: Read it
Reviewers: dfeuer, austin, hvr
Subscribers: rwbarton, thomie
GHC Trac Issues: #14199
Differential Revision: https://phabricator.haskell.org/D3943
>---------------------------------------------------------------
f9bf621caf2fc17d829dee0ee48b204144927e72
libraries/base/Data/Typeable/Internal.hs | 28 +++++++++++++++++++++++++++-
1 file changed, 27 insertions(+), 1 deletion(-)
diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs
index cf3ea07..f094d96 100644
--- a/libraries/base/Data/Typeable/Internal.hs
+++ b/libraries/base/Data/Typeable/Internal.hs
@@ -221,6 +221,13 @@ instance Ord SomeTypeRep where
SomeTypeRep a `compare` SomeTypeRep b =
typeRepFingerprint a `compare` typeRepFingerprint b
+-- | The function type constructor.
+--
+-- For instance,
+-- @
+-- typeRep \@(Int -> Char) === Fun (typeRep \@Int) (typeRep \@Char)
+-- @
+--
pattern Fun :: forall k (fun :: k). ()
=> forall (r1 :: RuntimeRep) (r2 :: RuntimeRep)
(arg :: TYPE r1) (res :: TYPE r2).
@@ -265,7 +272,14 @@ mkTrApp a b = TrApp fpr a b
fpr_b = typeRepFingerprint b
fpr = fingerprintFingerprints [fpr_a, fpr_b]
--- | Pattern match on a type application
+-- | A type application.
+--
+-- For instance,
+-- @
+-- typeRep \@(Maybe Int) === App (typeRep \@Maybe) (typeRep \@Int)
+-- @
+-- Note that this will never match a function type (e.g. @Int -> Char@).
+--
pattern App :: forall k2 (t :: k2). ()
=> forall k1 (a :: k1 -> k2) (b :: k1). (t ~ a b)
=> TypeRep a -> TypeRep b -> TypeRep t
@@ -287,6 +301,18 @@ pattern Con con <- TrTyCon _ con _
-- | Pattern match on a type constructor including its instantiated kind
-- variables.
+--
+-- For instance,
+-- @
+-- App (Con' proxyTyCon ks) intRep = typeRep @(Proxy \@Int)
+-- @
+-- will bring into scope,
+-- @
+-- proxyTyCon :: TyCon
+-- ks == [someTypeRep @Type] :: [SomeTypeRep]
+-- intRep == typeRep @Int
+-- @
+--
pattern Con' :: forall k (a :: k). TyCon -> [SomeTypeRep] -> TypeRep a
pattern Con' con ks <- TrTyCon _ con ks
More information about the ghc-commits
mailing list