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

[project @ 1997-11-12 16:55:57 by simonm]

Update test suite.

	* PrimIO ==> IO
	* change to type of _ccall_

	* update the stdout/stderr files where necessary.

	* make module names consistent: should_compile modules are called
	  ShouldSucceed (don't know why, most of them were already),
	  should_fail modules are called ShouldFail, and should_run
	  modules are called Main (for obvious reasons).
	  Not all done yet.

	* Some tests had bitrot.  Especially some should_fail tests
	  were failing for different reasons than they were originally
	  intended to.
parent 84d1a90e
No related merge requests found
Showing
with 31 additions and 117 deletions
......@@ -6,7 +6,6 @@ SUBDIRS = \
codeGen \
deSugar \
deriving \
io \
printing \
reader \
rename \
......@@ -14,7 +13,8 @@ SUBDIRS = \
stranal \
typecheck
#programs
# io \
# programs
include $(TOP)/mk/target.mk
......
--!!! cc001 -- ccall with standard boxed arguments and results
module Test where
import GlaExts
module ShouldCompile where
-- simple functions
a :: PrimIO Int
a :: IO Int
a = _ccall_ a
b :: Int -> PrimIO Int
b :: Int -> IO Int
b x = _ccall_ b x
c :: Int -> Char -> Float -> Double -> PrimIO Float
c :: Int -> Char -> Float -> Double -> IO Float
c x1 x2 x3 x4 = _ccall_ c x1 x2 x3 x4
-- simple monadic code
d = a `thenPrimIO` \ x ->
b x `thenPrimIO` \ y ->
d = a >>= \ x ->
b x >>= \ y ->
c y 'f' 1.0 2.0
......
--!!! cc003 -- ccall with unresolved polymorphism (should fail)
--!!! not anymore (as of 0.29, result type will default to ())
module Test where
module ShouldCompile where
import GlaExts
fubar :: PrimIO Int
fubar = _ccall_ f `seqPrimIO` _ccall_ b
fubar :: IO Int
fubar = _ccall_ f >>_ccall_ b
--^ result type of f "lost" (never gets generalised)
......@@ -2,21 +2,21 @@
module Test where
import GlaExts
import Foreign
import CCall
-- Test returning results
a :: PrimIO Int
a :: IO Int
a = _ccall_ a
b :: PrimIO (StablePtr Int)
b :: IO (StablePtr Int)
b = _ccall_ b
-- Test taking arguments
c :: ForeignObj -> PrimIO Int
c :: ForeignObj -> IO Int
c x = _ccall_ c x
d :: StablePtr Int -> PrimIO Int
d :: StablePtr Int -> IO Int
d x = _ccall_ d x
......@@ -2,21 +2,20 @@
module Test where
import GlaExts
import Foreign
-- Test returning results
a :: PrimIO ForeignObj
a :: IO ForeignObj
a = _ccall_ a
b :: PrimIO (StablePtr Double)
b :: IO (StablePtr Double)
b = _ccall_ b
-- Test taking arguments
c :: ForeignObj -> PrimIO Int
c :: ForeignObj -> IO Int
c x = _ccall_ c x
d :: StablePtr Int -> PrimIO Int
d :: StablePtr Int -> IO Int
d x = _ccall_ d x
cc002.hs:11: No instance for: `Foreign.CReturnable Foreign.ForeignObj'
arising from the result of the _ccall_ to a at cc002.hs:11
cc002.hs:10: No instance for: `CReturnable ForeignObj'
arising from the result of the _ccall_ to a at cc002.hs:10
When checking signature(s) for: `a'
Compilation had errors
--!!! cc004 -- ccall with synonyms, polymorphic type variables and user type variables.
module Test where
import GlaExts
-- Since I messed up the handling of polymorphism originally, I'll
-- explicitly test code with UserSysTyVar (ie an explicit polymorphic
-- signature)
foo = _ccall_ f `thenADR` \ a -> returnPrimIO (a + 1)
foo = _ccall_ f `thenADR` \ a -> return (a + 1)
where
thenADR :: PrimIO a -> (a -> PrimIO b) -> PrimIO b
thenADR = thenPrimIO
thenADR :: IO a -> (a -> IO b) -> IO b
thenADR = (>>=)
-- and with a PolySysTyVar (ie no explicit signature)
bar = _ccall_ f `thenADR` \ a -> returnPrimIO (a + 1)
bar = _ccall_ f `thenADR` \ a -> return (a + 1)
where
-- thenADR :: PrimIO a -> (a -> PrimIO b) -> PrimIO b
thenADR = thenPrimIO
-- thenADR :: IO a -> (a -> IO b) -> IO b
thenADR = (>>=)
-- and with a type synonym
type INT = Int
barfu :: PrimIO INT
barfu :: IO INT
barfu = _ccall_ b
cc004.hs:2: Cannot generalise these overloadings (in a _ccall_):
`Foreign.CReturnable taWY'
`CReturnable taLM'
cc004.hs:2: Cannot generalise these overloadings (in a _ccall_):
`Foreign.CReturnable taXF'
`CReturnable taMJ'
Compilation had errors
ds002.hs:13:
Warning: Possibly incomplete patterns
in the definition of function `g'
ds002.hs:8:
Warning: Pattern match(es) completely overlapped
in the definition of function `f'
ds002.hs:9:
Warning: Pattern match(es) completely overlapped
in the definition of function `f'
ds004.hs:6:
Warning: Possibly incomplete patterns
in the definition of function `nodups'
ds005.hs:13:
Warning: Possibly incomplete patterns
in the definition of function `mappairs''
ds015.hs:9:
Warning: Possibly incomplete patterns
in a lambda abstraction: `(x PrelBase.: xs) -> ...'
ds018.hs:39:
Warning: Possibly incomplete patterns
in the definition of function `fa'
ds018.hs:41:
Warning: Possibly incomplete patterns
in the definition of function `fb'
ds019.hs:7:
Warning: Pattern match(es) completely overlapped
in the definition of function `f'
ds019.hs:8:
Warning: Pattern match(es) completely overlapped
in the definition of function `f'
ds020.hs:6:
Warning: Pattern match(es) completely overlapped
in the definition of function `a'
ds020.hs:9:
Warning: Pattern match(es) completely overlapped
in the definition of function `b'
ds020.hs:16:
Warning: Pattern match(es) completely overlapped
in the definition of function `d'
ds020.hs:17:
Warning: Pattern match(es) completely overlapped
in the definition of function `d'
ds020.hs:20:
Warning: Pattern match(es) completely overlapped
in the definition of function `f'
NOTE: Simplifier still going after 4 iterations; bailing out.
ds021.hs:8:
Warning: Possibly incomplete patterns
in the definition of function `f'
ds022.hs:5:
Warning: Possibly incomplete patterns
in the definition of function `f'
ds022.hs:10:
Warning: Possibly incomplete patterns
in the definition of function `g'
ds022.hs:15:
Warning: Possibly incomplete patterns
in the definition of function `h'
ds022.hs:22:
Warning: Pattern match(es) completely overlapped
in the definition of function `i'
ds022.hs:23:
Warning: Pattern match(es) completely overlapped
in the definition of function `i'
ds022.hs:20:
Warning: Possibly incomplete patterns
in the definition of function `i'
ds025.hs:6:
Warning: Possibly incomplete patterns
in the definition of function `ehead'
ds027.hs:9:
Warning: Possibly incomplete patterns
in the definition of function `/='
ds027.hs:8:
Warning: Possibly incomplete patterns
in the definition of function `=='
ds031.hs:4:
Warning: Possibly incomplete patterns
in the definition of function `foldPair'
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