summaryrefslogtreecommitdiff
path: root/ghc/compiler/tests/ccall/cc004.hs
blob: 7ad0ceda1682ae0b7711aa12b44a71e46d8364ba (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
--!!! cc004 -- ccall with synonyms, polymorphic type variables and user type variables.
module Test where

import PreludeGlaIO

-- 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)
 where 
   thenADR :: PrimIO a -> (a -> PrimIO b) -> PrimIO b
   m `thenADR` k  = \ s -> case m s of
                         (a,t) -> k a t

-- and with a PolySysTyVar (ie no explicit signature)

bar = _ccall_ f	`thenADR` \ a -> returnPrimIO (a + 1)
 where 
   -- thenADR :: PrimIO a -> (a -> PrimIO b) -> PrimIO b
   m `thenADR` k  = \ s -> case m s of
                         (a,t) -> k a t

-- and with a type synonym

type INT = Int
barfu :: PrimIO INT
barfu = _ccall_ b