summaryrefslogtreecommitdiff
path: root/testsuite/tests/parser/should_fail/RecordDotSyntaxFail3.hs
diff options
context:
space:
mode:
Diffstat (limited to 'testsuite/tests/parser/should_fail/RecordDotSyntaxFail3.hs')
-rw-r--r--testsuite/tests/parser/should_fail/RecordDotSyntaxFail3.hs24
1 files changed, 24 insertions, 0 deletions
diff --git a/testsuite/tests/parser/should_fail/RecordDotSyntaxFail3.hs b/testsuite/tests/parser/should_fail/RecordDotSyntaxFail3.hs
new file mode 100644
index 0000000000..ae1a1fa797
--- /dev/null
+++ b/testsuite/tests/parser/should_fail/RecordDotSyntaxFail3.hs
@@ -0,0 +1,24 @@
+{-# LANGUAGE AllowAmbiguousTypes, FunctionalDependencies, ScopedTypeVariables, PolyKinds, TypeApplications, DataKinds #-}
+{-# LANGUAGE NamedFieldPuns #-}
+{-# LANGUAGE RecordWildCards #-}
+{-# LANGUAGE OverloadedRecordDot #-}
+
+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.
+
+-- 'Corge' has a '&&&' field of type 'Int'
+data Corge = Corge { (&&&) :: Int } deriving (Show, Eq)
+instance HasField "&&&" Corge Int where
+ hasField r = (\x -> case r of Corge { .. } -> Corge { (&&&) = x, .. }, (&&&) r)
+
+main = do
+ let b = Corge { (&&&) = 12 };
+ print $ (b.(&&&))
+ -- Syntax error: Dot notation is not available for fields with
+ -- operator names