summaryrefslogtreecommitdiff
path: root/testsuite/tests/parser/should_fail/RecordDotSyntaxFail13.hs
diff options
context:
space:
mode:
authorShayne Fletcher <shayne@shaynefletcher.org>2021-02-21 11:48:17 -0500
committerBen Gamari <ben@smart-cactus.org>2021-03-06 19:27:04 -0500
commitcf65cf16c89414273c4f6b2d090d4b2fffb90759 (patch)
tree57d893535444c2face265c12ade95f0ef3f0ceba /testsuite/tests/parser/should_fail/RecordDotSyntaxFail13.hs
parent9e0c0c3a7b6cad8c08e5de7e2a27cf2cb2d2368f (diff)
downloadhaskell-cf65cf16c89414273c4f6b2d090d4b2fffb90759.tar.gz
Implement record dot syntaxwip/joachim/bump-haddock
Diffstat (limited to 'testsuite/tests/parser/should_fail/RecordDotSyntaxFail13.hs')
-rw-r--r--testsuite/tests/parser/should_fail/RecordDotSyntaxFail13.hs26
1 files changed, 26 insertions, 0 deletions
diff --git a/testsuite/tests/parser/should_fail/RecordDotSyntaxFail13.hs b/testsuite/tests/parser/should_fail/RecordDotSyntaxFail13.hs
new file mode 100644
index 0000000000..7050145b9d
--- /dev/null
+++ b/testsuite/tests/parser/should_fail/RecordDotSyntaxFail13.hs
@@ -0,0 +1,26 @@
+{-# LANGUAGE AllowAmbiguousTypes, FunctionalDependencies, ScopedTypeVariables, PolyKinds, TypeApplications, DataKinds #-}
+{-# LANGUAGE OverloadedRecordDot, OverloadedRecordUpdate #-}
+{-# LANGUAGE RecordWildCards, NamedFieldPuns #-}
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE UndecidableInstances #-}
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE RebindableSyntax #-}
+import Prelude
+
+class HasField x r a | x r -> a where
+ hasField :: r -> (a -> r, a)
+
+getField :: forall x r a . HasField x r a => r -> a
+getField = snd . hasField @x -- Note: a.x = is getField @"x" a.
+
+setField :: forall x r a . HasField x r a => r -> a -> r
+setField = fst . hasField @x -- Note : a{x = b} is setField @"x" a b.
+
+-- 'Foo' has 'foo' field of type 'Int'
+data Foo = Foo { foo :: Int } deriving (Show, Eq)
+instance HasField "foo" Foo Int where
+ hasField r = (\x -> case r of Foo { .. } -> Foo { foo = x, .. }, foo r)
+main = do
+ let a = Foo {foo = 12};
+ -- let foo = 13;
+ print $ a {foo}