hslibs/ObjectIO

Mike Thomas miketh@brisbane.paradigmgeo.com
Mon, 15 Oct 2001 17:01:46 +1000


This is a multi-part message in MIME format.

------=_NextPart_000_0250_01C1559B.12D07DF0
Content-Type: text/plain;
	charset="iso-8859-1"
Content-Transfer-Encoding: 7bit

Hi all.

I thought I would try compiling the GHC CVS ObjectIO library on NT with GHC
5.02.

Following error messages passed out by the compiler I modified C_util12.lhs
as follows (see attached file):
    - import MarshallAlloc
    - import Ptr instead of Addr
    - Change Addr to Ptr
    - AddrOff changed to Int

and get the following error message in the fpeek function:

$ make
ghc -static -c ../../OSWindows/Cutil_12.hs -fglasgow-exts -syslib
concurrent -syslib
ang -cpp  -i../../CleanStdEnv:../../OSWindows:../../ObjectIO:../../OSWindo
ws/Windows_C_12 -I../../ObjectIO -DMVAR=1

..\\..\\OSWindows\\Cutil_12.hs:34:
    Couldn't match `* -> *' against `Type bx'
        Expected kind: * -> *
        Inferred kind: Type bx
    When checking that `Ptr' is a type
    In the type: forall a. (Storable a) => Ptr -> IO a
    While checking the type signature for `fpeek'
make: *** [../../OSWindows/Cutil_12.o] Error 1

I am stumped on this (I don't know what the stars mean).  My best guess is
that it is something to do with the monomorphism restriction.

Any advice on how to clear this up?

Are the changes I made in keeping with the intention of the original code?

Cheers

Mike Thomas

------=_NextPart_000_0250_01C1559B.12D07DF0
Content-Type: application/octet-stream;
	name="Cutil_12.hs"
Content-Transfer-Encoding: quoted-printable
Content-Disposition: attachment;
	filename="Cutil_12.hs"

module Cutil_12 ( module Cutil_12, module Ptr, module Bits, module Int, =
module Storable ) where=0A=
=0A=
=0A=
{-	This module contains some additional routines required for =
marshalling =0A=
	Haskell arguments to OS C calling routines.=0A=
-}=0A=
=0A=
import Ptr=0A=
import Bits=0A=
import Int=0A=
import Storable=0A=
import MarshalAlloc=0A=
=0A=
=0A=
--	Conversion operations:=0A=
i8 :: Int -> Int8=0A=
i8 i =3D fromIntegral i=0A=
=0A=
i16 :: Int -> Int16=0A=
i16 i =3D fromIntegral i=0A=
=0A=
i32 :: Int -> Int32=0A=
i32 i =3D fromIntegral i=0A=
=0A=
btoi :: Bool -> Int=0A=
btoi True =3D -1=0A=
btoi _    =3D 0=0A=
=0A=
itob :: Int -> Bool=0A=
itob 0 =3D False=0A=
itob _ =3D True=0A=
=0A=
--	fpeek addr first peeks addr, then frees addr:=0A=
fpeek :: (Storable a) =3D> Ptr -> IO a=0A=
fpeek addr=0A=
	=3D do {=0A=
		x <- peek addr;=0A=
		free addr;=0A=
		return x=0A=
	  }=0A=
=0A=
-- CLEAN_STRING operations:=0A=
createCLEAN_STRING :: String -> IO Ptr=0A=
createCLEAN_STRING string=0A=
	=3D do {=0A=
		csPtr <- malloc (4 + nrChars + 1);=0A=
		poke csPtr (i32 nrChars);=0A=
		pokeString csPtr (fromIntegral 4) string;=0A=
		return csPtr=0A=
	  }=0A=
	where=0A=
		nrChars =3D length string=0A=
		=0A=
		pokeString :: Ptr -> Int -> String -> IO ()=0A=
		pokeString csPtr off []     =3D pokeByteOff csPtr off (i8 0) >> return =
()=0A=
		pokeString csPtr off (c:cs) =3D pokeByteOff csPtr off c >> pokeString =
csPtr (off+fromIntegral 1) cs=0A=
=0A=
freeCLEAN_STRING :: Ptr -> IO ()=0A=
freeCLEAN_STRING csPtr=0A=
	=3D free csPtr=0A=
=0A=
i8toChar :: Int8 -> Char=0A=
i8toChar x =3D toEnum ((fromIntegral x)::Int)=0A=
=0A=
readCLEAN_STRING :: Ptr -> IO String=0A=
readCLEAN_STRING csPtr=0A=
	=3D peekString csPtr (fromIntegral 4)=0A=
	where=0A=
		peekString :: Ptr -> Int -> IO String=0A=
		peekString csPtr off=0A=
			=3D peekByteOff csPtr off >>=3D \(c::Int8) ->=0A=
				if c=3D=3D0 then return []=0A=
				        else peekString csPtr (off+fromIntegral 1) >>=3D =0A=
				             \s->return ((i8toChar c):s)=0A=

------=_NextPart_000_0250_01C1559B.12D07DF0--