[commit: ghc] wip/hasfield: Add IsLabel (->) instance (d2df666)

git at git.haskell.org git at git.haskell.org
Sat Oct 8 16:15:27 UTC 2016


Repository : ssh://git@git.haskell.org/ghc

On branch  : wip/hasfield
Link       : http://ghc.haskell.org/trac/ghc/changeset/d2df6663d9874333e0593af4f95c11ba6de1f7b3/ghc

>---------------------------------------------------------------

commit d2df6663d9874333e0593af4f95c11ba6de1f7b3
Author: Adam Gundry <adam at well-typed.com>
Date:   Sat Oct 8 13:17:53 2016 +0100

    Add IsLabel (->) instance


>---------------------------------------------------------------

d2df6663d9874333e0593af4f95c11ba6de1f7b3
 libraries/base/GHC/OverloadedLabels.hs                      | 13 ++++++++++---
 .../tests/overloadedrecflds/should_run/hasfieldrun02.hs     |  6 +-----
 2 files changed, 11 insertions(+), 8 deletions(-)

diff --git a/libraries/base/GHC/OverloadedLabels.hs b/libraries/base/GHC/OverloadedLabels.hs
index 3a3449d..7dcfdc6 100644
--- a/libraries/base/GHC/OverloadedLabels.hs
+++ b/libraries/base/GHC/OverloadedLabels.hs
@@ -1,8 +1,11 @@
 {-# LANGUAGE AllowAmbiguousTypes
-           , NoImplicitPrelude
-           , MultiParamTypeClasses
-           , KindSignatures
            , DataKinds
+           , FlexibleInstances
+           , KindSignatures
+           , MultiParamTypeClasses
+           , NoImplicitPrelude
+           , ScopedTypeVariables
+           , TypeApplications
   #-}
 
 -----------------------------------------------------------------------------
@@ -42,6 +45,10 @@ module GHC.OverloadedLabels
        ) where
 
 import GHC.Base ( Symbol )
+import qualified GHC.Records
 
 class IsLabel (x :: Symbol) a where
   fromLabel :: a
+
+instance GHC.Records.HasField x r a => IsLabel x (r -> a) where
+  fromLabel = GHC.Records.fromLabel @x
diff --git a/testsuite/tests/overloadedrecflds/should_run/hasfieldrun02.hs b/testsuite/tests/overloadedrecflds/should_run/hasfieldrun02.hs
index ce0173a..121f35e 100644
--- a/testsuite/tests/overloadedrecflds/should_run/hasfieldrun02.hs
+++ b/testsuite/tests/overloadedrecflds/should_run/hasfieldrun02.hs
@@ -1,7 +1,6 @@
 {-# LANGUAGE DuplicateRecordFields, OverloadedLabels,
              ExistentialQuantification,
-             FlexibleInstances, MultiParamTypeClasses,
-             ScopedTypeVariables, TypeApplications #-}
+             FlexibleInstances, MultiParamTypeClasses #-}
 
 import GHC.OverloadedLabels (IsLabel(..))
 import GHC.Records (HasField(..))
@@ -9,8 +8,5 @@ import GHC.Records (HasField(..))
 data S = MkS { foo :: Int }
 data T x y z = forall b . MkT { foo :: y, bar :: b }
 
-instance HasField x r a => IsLabel x (r -> a) where
-  fromLabel = GHC.Records.fromLabel @x
-
 main = do print (#foo (MkS 42))
           print (#foo (MkT True False))



More information about the ghc-commits mailing list