[commit: ghc] wip/hasfield: Test interaction between HasField and DuplicateRecordFields (2b91d14)
git at git.haskell.org
git at git.haskell.org
Mon May 16 08:07:34 UTC 2016
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/hasfield
Link : http://ghc.haskell.org/trac/ghc/changeset/2b91d149005bede1ea22c74d1d86d9897adb51ad/ghc
>---------------------------------------------------------------
commit 2b91d149005bede1ea22c74d1d86d9897adb51ad
Author: Adam Gundry <adam at well-typed.com>
Date: Wed Dec 23 12:00:01 2015 +0000
Test interaction between HasField and DuplicateRecordFields
>---------------------------------------------------------------
2b91d149005bede1ea22c74d1d86d9897adb51ad
testsuite/tests/overloadedrecflds/should_run/all.T | 1 +
.../tests/overloadedrecflds/should_run/hasfieldrun02.hs | 15 +++++++++++++++
...overloadedrecfldsrun06.stdout => hasfieldrun02.stdout} | 0
3 files changed, 16 insertions(+)
diff --git a/testsuite/tests/overloadedrecflds/should_run/all.T b/testsuite/tests/overloadedrecflds/should_run/all.T
index 1e0787e..c6fc8ad 100644
--- a/testsuite/tests/overloadedrecflds/should_run/all.T
+++ b/testsuite/tests/overloadedrecflds/should_run/all.T
@@ -16,3 +16,4 @@ test('overloadedlabelsrun04',
extra_clean(['OverloadedLabelsRun04_A.hi', 'OverloadedLabelsRun04_A.o']),
multimod_compile_and_run, ['overloadedlabelsrun04', ''])
test('hasfieldrun01', normal, compile_and_run, [''])
+test('hasfieldrun02', normal, compile_and_run, [''])
diff --git a/testsuite/tests/overloadedrecflds/should_run/hasfieldrun02.hs b/testsuite/tests/overloadedrecflds/should_run/hasfieldrun02.hs
new file mode 100644
index 0000000..cb255f1
--- /dev/null
+++ b/testsuite/tests/overloadedrecflds/should_run/hasfieldrun02.hs
@@ -0,0 +1,15 @@
+{-# LANGUAGE DuplicateRecordFields, OverloadedLabels,
+ ExistentialQuantification,
+ FlexibleInstances, MultiParamTypeClasses #-}
+
+import GHC.OverloadedLabels (IsLabel(..))
+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 = getField
+
+main = do print (#foo (MkS 42))
+ print (#foo (MkT True False))
diff --git a/testsuite/tests/overloadedrecflds/should_run/overloadedrecfldsrun06.stdout b/testsuite/tests/overloadedrecflds/should_run/hasfieldrun02.stdout
similarity index 100%
copy from testsuite/tests/overloadedrecflds/should_run/overloadedrecfldsrun06.stdout
copy to testsuite/tests/overloadedrecflds/should_run/hasfieldrun02.stdout
More information about the ghc-commits
mailing list