Skip to content
Snippets Groups Projects
Commit ee731a02 authored by sof's avatar sof
Browse files

[project @ 1999-07-05 17:02:42 by sof]

Two new Dark Corner regression tests:

- testing the derived Show&Read instances for constructors with
  a field label that is a varsym rather than a varid.
- check that the default fixity & assoc of an operator is 'infixl 9'.
parent df7cb092
No related merge requests found
......@@ -4,4 +4,6 @@ include $(TOP)/mk/should_run.mk
SRC_HC_OPTS += -dcore-lint
drvrun005_RUNTEST_OPTS += -fail
include $(TOP)/mk/target.mk
module Main where
data Hash = Hash{ (#) :: Int }
deriving (Show, Read)
main =
do print s
print (read s :: Hash)
where
s = show (Hash 3)
"Hash{(#)=3}"
Hash{(#)=3}
module Main where
{-
If a fixity declaration hasn't been supplied for
an operator, it is defaulted to being "infixl 9".
The derived Read instances for data types containing
left-assoc constructors produces code that causes
non-termination if you use 'read' to evaluate them
( (head (reads x)) is cool tho.)
==> The inferred assoc for :++ below left & the derived
Read instance should fail to terminate (with ghc-4.xx,
this is exemplified by having the stack overflow.)
-}
-- infixl 9 :++
data T = T1 | T :++ T deriving (Eq,Show, Read)
t :: T
t = read "T1"
main = print t
Stack space overflow: current size 1048576 bytes.
Use `+RTS -Ksize' to increase it.
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment