Skip to content
Snippets Groups Projects
Commit dbcefc27 authored by Simon Marlow's avatar Simon Marlow
Browse files

[project @ 1997-09-08 09:48:01 by simonm]

reinstate tests that now work.
parent 1c8be26a
No related merge requests found
--!!! an example Simon made up
--
module ShouldSucceed where
f x = (x+1, x<3, g True, g 'c')
where
g y = if x>2 then [] else [y]
{-
Here the type-check of g will yield an LIE with an Ord dict
for x. g still has type forall a. a -> [a]. The dictionary is
free, bound by the x.
It should be ok to add the signature:
-}
f2 x = (x+1, x<3, g2 True, g2 'c')
where
-- NB: this sig:
g2 :: a -> [a]
g2 y = if x>2 then [] else [y]
{-
or to write:
-}
f3 x = (x+1, x<3, g3 True, g3 'c')
where
-- NB: this line:
g3 = (\ y -> if x>2 then [] else [y])::(a -> [a])
--!! Test for (->) instances
module ShouldRun where
class Flob k where
twice :: k a a -> k a a
instance Flob (->) where
twice f = f . f
inc :: Int -> Int
inc x = x+1
main = print (twice inc 2)
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