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

[project @ 1997-07-31 00:05:10 by sof]

Moved to main compiler regression test directory
parent 29b46083
No related branches found
No related tags found
No related merge requests found
Showing
with 0 additions and 283 deletions
TOP = ../../..
include $(TOP)/mk/boilerplate.mk
SUBDIRS = should_fail should_succeed stress
include $(TOP)/mk/target.mk
--!!! trying to have a polymorphic type sig where inappropriate
--
module Digraph where
data MaybeErr val err = Succeeded val | Failed err deriving ()
type Edge vertex = (vertex, vertex)
type Cycle vertex = [vertex]
stronglyConnComp :: Eq vertex => [Edge vertex] -> [vertex] -> [[vertex]]
stronglyConnComp es vs
= snd (span_tree (new_range reversed_edges)
([],[])
( snd (dfs (new_range es) ([],[]) vs) )
)
where
-- *********** the offending type signature **************
reversed_edges :: Eq v => [Edge v]
reversed_edges = map swap es
-- WRONGOLA: swap :: Eq v => Edge v -> Edge v
swap (x,y) = (y, x)
-- WRONGOLA?: new_range :: Eq v => [Edge v] -> v -> [v]
new_range [] w = []
new_range ((x,y):xys) w
= if x==w
then (y : (new_range xys w))
else (new_range xys w)
{- WRONGOLA?:
span_tree :: Eq v => (v -> [v])
-> ([v], [[v]])
-> [v]
-> ([v], [[v]])
-}
span_tree r (vs,ns) [] = (vs,ns)
span_tree r (vs,ns) (x:xs)
| x `elem` vs = span_tree r (vs,ns) xs
| otherwise = span_tree r (vs',(x:ns'):ns) xs
where
(vs',ns') = dfs r (x:vs,[]) (r x)
dfs :: Eq v => (v -> [v])
-> ([v], [v])
-> [v]
-> ([v], [v])
dfs r (vs,ns) [] = (vs,ns)
dfs r (vs,ns) (x:xs) | x `elem` vs = dfs r (vs,ns) xs
| otherwise = dfs r (vs',(x:ns')++ns) xs
where
(vs',ns') = dfs r (x:vs,[]) (r x)
Digraph.hs:19: A type signature is more polymorphic than the inferred type
Some type variables in the inferred type can't be forall'd, namely:
`v{-a13W-}'
Possible cause: the RHS mentions something subject to the monomorphism restriction
When checking signature for `reversed_edges'
In an equation for function `stronglyConnComp':
`stronglyConnComp es vs = PrelTup.snd
(span_tree
(new_range
reversed_edges)
(PrelBase.[], (PrelBase.[]))
(PrelTup.snd
(dfs (new_range
es)
(PrelBase.[], (PrelBase.[]))
vs)))
where
span_tree
r (vs, ns) PrelBase.[]
= (vs, (ns))
span_tree
r (vs, ns) (x PrelBase.: xs)
| [x PrelList.elem vs] =
span_tree
r (vs, (ns)) xs
| [PrelBase.otherwise] =
span_tree
r
(vs', ((x PrelBase.: ns') PrelBase.: ns))
xs
where
(vs', ns')
= dfs r
(x PrelBase.: vs, (PrelBase.[]))
(r x)
new_range
PrelBase.[] w
= PrelBase.[]
new_range
((x, y) PrelBase.: xys) w
= if x PrelBase.== w then
(y
PrelBase.: (new_range
xys w))
else
(new_range
xys w)
swap
(x, y) = (y, (x))
reversed_edges ::
_forall_ [v] {PrelBase.Eq v} => [Edge v]
reversed_edges
= PrelBase.map
swap es'
Compilation had errors
TOP = ../../../..
include $(TOP)/mk/boilerplate.mk
HS_SRCS = $(wildcard *.hs)
SRC_RUNTEST_OPTS += -o1 $*.stdout -o2 $*.stderr -x 1
HC_OPTS += -noC -ddump-tc -dppr-user
%.o : %.hs
%.o : %.hs
$(RUNTEST) $(HC) $(RUNTEST_OPTS) -- $(HC_OPTS) -c $< -o $@ -osuf $(subst .,,$(suffix $@))
all :: $(HS_OBJS)
# Not all of them fail, allthough they're advertised as doing so..
tcfail021_RUNTEST_OPTS = -x 0
tcfail041_RUNTEST_OPTS = -x 0
tcfail045_HC_OPTS = -fglasgow-exts
tcfail059_HC_OPTS = -hi
tcfail059_RUNTEST_OPTS = -x 0
tcfail060_HC_OPTS = -hi
tcfail060_RUNTEST_OPTS = -x 0
tcfail061_HC_OPTS = -hi
tcfail062_HC_OPTS = -hi
tcfail063_HC_OPTS = -hi
tcfail064_HC_OPTS = -hi
tcfail065_HC_OPTS = -hi
tcfail066_HC_OPTS = -hi
tcfail066_RUNTEST_OPTS = -x 0
tcfail067_HC_OPTS = -hi
tcfail068_HC_OPTS = -fglasgow-exts
include $(TOP)/mk/target.mk
--!!! This should fail with a type error: the instance method
--!!! has a function type when it should have the type [a].
module Test where
class A a where
op :: a
instance (A a, A a) => A [a] where
op [] = []
tcfail001.hs:9:warning:
Duplicate class assertion `[(`A',
`a'),
(`A',
`a')]' in context:
[(`A',
`a'),
(`A',
`a')]
tcfail001.hs:9: Couldn't match the type
`PrelBase.[]' against `GHC.-> [t{-anj-}]'
Expected: `[a{-ani-}]'
Inferred: `[t{-anj-}] -> [t{-ank-}]'
In an equation for function `op':
`op PrelBase.[]
= PrelBase.[]'
Compilation had errors
module ShouldFail where
c (x:y) = x
c z = z
tcfail002.hs:4: Cannot construct the infinite type (occur check)
`t{-amM-}' = `[t{-amM-}]'
Expected: `[t{-amM-}] -> t{-amM-}'
Inferred: `[t{-amM-}] -> [t{-amM-}]'
In an equation for function `c':
`c z = z'
Compilation had errors
module ShouldFail where
(d:e) = [1,'a']
tcfail003.hs:3: No instance for:
`PrelBase.Num PrelBase.Char'
tcfail003.hs:3:
at an overloaded literal: 1
Compilation had errors
module ShouldFail where
(f,g) = (1,2,3)
tcfail004.hs:3: Couldn't match the type
`PrelTup.(,)' against `PrelTup.(,,) t{-aXz-}'
Expected: `(t{-aXt-}, t{-aXw-})'
Inferred: `(t{-aXz-}, t{-aXC-}, t{-aXF-})'
In a pattern binding:
(`f', `g')
= `(1, 2, 3)'
Compilation had errors
module ShouldFail where
(h:i) = (1,'a')
tcfail005.hs:3: Couldn't match the type
`PrelBase.[]' against `PrelTup.(,) t{-aWN-}'
Expected: `[t{-aWJ-}]'
Inferred: `(t{-aWN-}, PrelBase.Char)'
In a pattern binding:
(`h' `PrelBase.:' `i')
= `(1, ('a'))'
Compilation had errors
module ShouldFail where
(j,k) = case (if True then True else False) of
True -> (True,1)
False -> (1,True)
tcfail006.hs:4: No instance for:
`PrelBase.Num PrelBase.Bool'
tcfail006.hs:4:
at an overloaded literal: 1
Compilation had errors
module ShouldFail where
n x | True = x+1
| False = True
tcfail007.hs:4: No instance for:
`PrelBase.Num PrelBase.Bool'
tcfail007.hs:4:
at a use of an overloaded identifier: `PrelBase.+'
Compilation had errors
module ShouldFail where
o = 1:2
tcfail008.hs:3: No instance for:
`PrelBase.Num [t{-aHf-}]'
tcfail008.hs:3:
at an overloaded literal: 2
tcfail008.hs:3: No instance for:
`PrelBase.Num [t{-aHf-}]'
tcfail008.hs:3:
at an overloaded literal: 2
tcfail008.hs:3: No instance for:
`PrelBase.Num [PrelBase.Int]'
tcfail008.hs:3:
at an overloaded literal: 2
Compilation had errors
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