Skip to content

Commit d3dfd7b

Browse files
committed
Fix C/Haskell type mismatches
1 parent d3d45b3 commit d3dfd7b

File tree

19 files changed

+219
-216
lines changed

19 files changed

+219
-216
lines changed

Data/Array/Base.hs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -25,6 +25,7 @@ import qualified Control.Monad.ST.Lazy as Lazy (ST)
2525
import Data.Ix ( Ix, range, index, rangeSize )
2626
import Data.Int
2727
import Data.Word
28+
import Foreign.C.Types
2829
import Foreign.Ptr
2930
import Foreign.StablePtr
3031

@@ -1593,7 +1594,8 @@ thawSTUArray (UArray l u arr#) = ST $ \s1# ->
15931594
(# s3#, STUArray l u marr# #) }}}
15941595

15951596
foreign import ccall unsafe "memcpy"
1596-
memcpy :: MutableByteArray# RealWorld -> ByteArray# -> Int# -> IO ()
1597+
memcpy :: MutableByteArray# RealWorld -> ByteArray# -> CSize
1598+
-> IO (Ptr a)
15971599

15981600
{-# RULES
15991601
"thaw/STArray" thaw = ArrST.thawSTArray

Data/ByteString/Base.hs

Lines changed: 21 additions & 24 deletions
Original file line numberDiff line numberDiff line change
@@ -456,21 +456,34 @@ foreign import ccall unsafe "static stdlib.h free" c_free
456456
foreign import ccall unsafe "static stdlib.h &free" c_free_finalizer
457457
:: FunPtr (Ptr Word8 -> IO ())
458458

459-
foreign import ccall unsafe "string.h memchr" memchr
460-
:: Ptr Word8 -> Word8 -> CSize -> IO (Ptr Word8)
459+
foreign import ccall unsafe "string.h memchr" c_memchr
460+
:: Ptr Word8 -> CInt -> CSize -> IO (Ptr Word8)
461+
462+
memchr :: Ptr Word8 -> Word8 -> CSize -> IO (Ptr Word8)
463+
memchr p w s = c_memchr p (fromIntegral w) s
461464

462465
foreign import ccall unsafe "string.h memcmp" memcmp
463466
:: Ptr Word8 -> Ptr Word8 -> CSize -> IO CInt
464467

465-
foreign import ccall unsafe "string.h memcpy" memcpy
466-
:: Ptr Word8 -> Ptr Word8 -> CSize -> IO ()
468+
foreign import ccall unsafe "string.h memcpy" c_memcpy
469+
:: Ptr Word8 -> Ptr Word8 -> CSize -> IO (Ptr Word8)
470+
471+
memcpy :: Ptr Word8 -> Ptr Word8 -> CSize -> IO ()
472+
memcpy p q s = do c_memcpy p q s
473+
return ()
467474

468-
foreign import ccall unsafe "string.h memmove" memmove
469-
:: Ptr Word8 -> Ptr Word8 -> CSize -> IO ()
475+
foreign import ccall unsafe "string.h memmove" c_memmove
476+
:: Ptr Word8 -> Ptr Word8 -> CSize -> IO (Ptr Word8)
470477

471-
foreign import ccall unsafe "string.h memset" memset
472-
:: Ptr Word8 -> Word8 -> CSize -> IO (Ptr Word8)
478+
memmove :: Ptr Word8 -> Ptr Word8 -> CSize -> IO ()
479+
memmove p q s = do c_memmove p q s
480+
return ()
473481

482+
foreign import ccall unsafe "string.h memset" c_memset
483+
:: Ptr Word8 -> CInt -> CSize -> IO (Ptr Word8)
484+
485+
memset :: Ptr Word8 -> Word8 -> CSize -> IO (Ptr Word8)
486+
memset p w s = c_memset p (fromIntegral w) s
474487

475488
-- ---------------------------------------------------------------------
476489
--
@@ -492,22 +505,6 @@ foreign import ccall unsafe "static fpstring.h fps_minimum" c_minimum
492505
foreign import ccall unsafe "static fpstring.h fps_count" c_count
493506
:: Ptr Word8 -> CULong -> Word8 -> IO CULong
494507

495-
-- ---------------------------------------------------------------------
496-
-- MMap
497-
498-
{-
499-
foreign import ccall unsafe "static fpstring.h my_mmap" my_mmap
500-
:: Int -> Int -> IO (Ptr Word8)
501-
502-
foreign import ccall unsafe "static unistd.h close" c_close
503-
:: Int -> IO Int
504-
505-
# if !defined(__OpenBSD__)
506-
foreign import ccall unsafe "static sys/mman.h munmap" c_munmap
507-
:: Ptr Word8 -> Int -> IO Int
508-
# endif
509-
-}
510-
511508
-- ---------------------------------------------------------------------
512509
-- Internal GHC Haskell magic
513510

Foreign/Marshal/Utils.hs

Lines changed: 6 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -159,19 +159,21 @@ withMany withFoo (x:xs) f = withFoo x $ \x' ->
159159
-- first (destination); the copied areas may /not/ overlap
160160
--
161161
copyBytes :: Ptr a -> Ptr a -> Int -> IO ()
162-
copyBytes dest src size = memcpy dest src (fromIntegral size)
162+
copyBytes dest src size = do memcpy dest src (fromIntegral size)
163+
return ()
163164

164165
-- |Copies the given number of bytes from the second area (source) into the
165166
-- first (destination); the copied areas /may/ overlap
166167
--
167168
moveBytes :: Ptr a -> Ptr a -> Int -> IO ()
168-
moveBytes dest src size = memmove dest src (fromIntegral size)
169+
moveBytes dest src size = do memmove dest src (fromIntegral size)
170+
return ()
169171

170172

171173
-- auxilliary routines
172174
-- -------------------
173175

174176
-- |Basic C routines needed for memory copying
175177
--
176-
foreign import ccall unsafe "string.h" memcpy :: Ptr a -> Ptr a -> CSize -> IO ()
177-
foreign import ccall unsafe "string.h" memmove :: Ptr a -> Ptr a -> CSize -> IO ()
178+
foreign import ccall unsafe "string.h" memcpy :: Ptr a -> Ptr a -> CSize -> IO (Ptr a)
179+
foreign import ccall unsafe "string.h" memmove :: Ptr a -> Ptr a -> CSize -> IO (Ptr a)

GHC/Conc.lhs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -146,7 +146,7 @@ instance Show ThreadId where
146146
showString "ThreadId " .
147147
showsPrec d (getThreadId (id2TSO t))
148148
149-
foreign import ccall unsafe "rts_getThreadId" getThreadId :: ThreadId# -> Int
149+
foreign import ccall unsafe "rts_getThreadId" getThreadId :: ThreadId# -> CInt
150150
151151
id2TSO :: ThreadId -> ThreadId#
152152
id2TSO (ThreadId t) = t
@@ -915,7 +915,7 @@ service_loop wakeup readfds writefds ptimeval old_reqs old_delays = do
915915
now <- getUSecOfDay
916916
(delays', timeout) <- getDelay now ptimeval delays
917917
918-
res <- c_select ((max wakeup maxfd)+1) readfds writefds
918+
res <- c_select (fromIntegral ((max wakeup maxfd)+1)) readfds writefds
919919
nullPtr timeout
920920
if (res == -1)
921921
then do
@@ -1065,7 +1065,7 @@ foreign import ccall unsafe "setTimevalTicks"
10651065
newtype CFdSet = CFdSet ()
10661066
10671067
foreign import ccall safe "select"
1068-
c_select :: Fd -> Ptr CFdSet -> Ptr CFdSet -> Ptr CFdSet -> Ptr CTimeVal
1068+
c_select :: CInt -> Ptr CFdSet -> Ptr CFdSet -> Ptr CFdSet -> Ptr CTimeVal
10691069
-> IO CInt
10701070
10711071
foreign import ccall unsafe "hsFD_SETSIZE"

GHC/Int.hs

Lines changed: 27 additions & 27 deletions
Original file line numberDiff line numberDiff line change
@@ -688,33 +688,33 @@ a `iShiftRA64#` b | b >=# 64# = if a `ltInt64#` (intToInt64# 0#)
688688
| otherwise = a `uncheckedIShiftRA64#` b
689689

690690

691-
foreign import ccall unsafe "stg_eqInt64" eqInt64# :: Int64# -> Int64# -> Bool
692-
foreign import ccall unsafe "stg_neInt64" neInt64# :: Int64# -> Int64# -> Bool
693-
foreign import ccall unsafe "stg_ltInt64" ltInt64# :: Int64# -> Int64# -> Bool
694-
foreign import ccall unsafe "stg_leInt64" leInt64# :: Int64# -> Int64# -> Bool
695-
foreign import ccall unsafe "stg_gtInt64" gtInt64# :: Int64# -> Int64# -> Bool
696-
foreign import ccall unsafe "stg_geInt64" geInt64# :: Int64# -> Int64# -> Bool
697-
foreign import ccall unsafe "stg_plusInt64" plusInt64# :: Int64# -> Int64# -> Int64#
698-
foreign import ccall unsafe "stg_minusInt64" minusInt64# :: Int64# -> Int64# -> Int64#
699-
foreign import ccall unsafe "stg_timesInt64" timesInt64# :: Int64# -> Int64# -> Int64#
700-
foreign import ccall unsafe "stg_negateInt64" negateInt64# :: Int64# -> Int64#
701-
foreign import ccall unsafe "stg_quotInt64" quotInt64# :: Int64# -> Int64# -> Int64#
702-
foreign import ccall unsafe "stg_remInt64" remInt64# :: Int64# -> Int64# -> Int64#
703-
foreign import ccall unsafe "stg_intToInt64" intToInt64# :: Int# -> Int64#
704-
foreign import ccall unsafe "stg_int64ToInt" int64ToInt# :: Int64# -> Int#
705-
foreign import ccall unsafe "stg_wordToWord64" wordToWord64# :: Word# -> Word64#
706-
foreign import ccall unsafe "stg_int64ToWord64" int64ToWord64# :: Int64# -> Word64#
707-
foreign import ccall unsafe "stg_word64ToInt64" word64ToInt64# :: Word64# -> Int64#
708-
foreign import ccall unsafe "stg_and64" and64# :: Word64# -> Word64# -> Word64#
709-
foreign import ccall unsafe "stg_or64" or64# :: Word64# -> Word64# -> Word64#
710-
foreign import ccall unsafe "stg_xor64" xor64# :: Word64# -> Word64# -> Word64#
711-
foreign import ccall unsafe "stg_not64" not64# :: Word64# -> Word64#
712-
foreign import ccall unsafe "stg_uncheckedShiftL64" uncheckedShiftL64# :: Word64# -> Int# -> Word64#
713-
foreign import ccall unsafe "stg_uncheckedShiftRL64" uncheckedShiftRL64# :: Word64# -> Int# -> Word64#
714-
foreign import ccall unsafe "stg_uncheckedIShiftL64" uncheckedIShiftL64# :: Int64# -> Int# -> Int64#
715-
foreign import ccall unsafe "stg_uncheckedIShiftRA64" uncheckedIShiftRA64# :: Int64# -> Int# -> Int64#
716-
717-
foreign import ccall unsafe "stg_integerToInt64" integerToInt64# :: Int# -> ByteArray# -> Int64#
691+
foreign import ccall unsafe "hs_eqInt64" eqInt64# :: Int64# -> Int64# -> Bool
692+
foreign import ccall unsafe "hs_neInt64" neInt64# :: Int64# -> Int64# -> Bool
693+
foreign import ccall unsafe "hs_ltInt64" ltInt64# :: Int64# -> Int64# -> Bool
694+
foreign import ccall unsafe "hs_leInt64" leInt64# :: Int64# -> Int64# -> Bool
695+
foreign import ccall unsafe "hs_gtInt64" gtInt64# :: Int64# -> Int64# -> Bool
696+
foreign import ccall unsafe "hs_geInt64" geInt64# :: Int64# -> Int64# -> Bool
697+
foreign import ccall unsafe "hs_plusInt64" plusInt64# :: Int64# -> Int64# -> Int64#
698+
foreign import ccall unsafe "hs_minusInt64" minusInt64# :: Int64# -> Int64# -> Int64#
699+
foreign import ccall unsafe "hs_timesInt64" timesInt64# :: Int64# -> Int64# -> Int64#
700+
foreign import ccall unsafe "hs_negateInt64" negateInt64# :: Int64# -> Int64#
701+
foreign import ccall unsafe "hs_quotInt64" quotInt64# :: Int64# -> Int64# -> Int64#
702+
foreign import ccall unsafe "hs_remInt64" remInt64# :: Int64# -> Int64# -> Int64#
703+
foreign import ccall unsafe "hs_intToInt64" intToInt64# :: Int# -> Int64#
704+
foreign import ccall unsafe "hs_int64ToInt" int64ToInt# :: Int64# -> Int#
705+
foreign import ccall unsafe "hs_wordToWord64" wordToWord64# :: Word# -> Word64#
706+
foreign import ccall unsafe "hs_int64ToWord64" int64ToWord64# :: Int64# -> Word64#
707+
foreign import ccall unsafe "hs_word64ToInt64" word64ToInt64# :: Word64# -> Int64#
708+
foreign import ccall unsafe "hs_and64" and64# :: Word64# -> Word64# -> Word64#
709+
foreign import ccall unsafe "hs_or64" or64# :: Word64# -> Word64# -> Word64#
710+
foreign import ccall unsafe "hs_xor64" xor64# :: Word64# -> Word64# -> Word64#
711+
foreign import ccall unsafe "hs_not64" not64# :: Word64# -> Word64#
712+
foreign import ccall unsafe "hs_uncheckedShiftL64" uncheckedShiftL64# :: Word64# -> Int# -> Word64#
713+
foreign import ccall unsafe "hs_uncheckedShiftRL64" uncheckedShiftRL64# :: Word64# -> Int# -> Word64#
714+
foreign import ccall unsafe "hs_uncheckedIShiftL64" uncheckedIShiftL64# :: Int64# -> Int# -> Int64#
715+
foreign import ccall unsafe "hs_uncheckedIShiftRA64" uncheckedIShiftRA64# :: Int64# -> Int# -> Int64#
716+
717+
foreign import ccall unsafe "hs_integerToInt64" integerToInt64# :: Int# -> ByteArray# -> Int64#
718718

719719
{-# RULES
720720
"fromIntegral/Int->Int64" fromIntegral = \(I# x#) -> I64# (intToInt64# x#)

GHC/TopHandler.lhs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -123,12 +123,12 @@ cleanUpAndExit r = do cleanUp; safeExit r
123123
-- we have to use unsafeCoerce# to get the 'IO a' result type, since the
124124
-- compiler doesn't let us declare that as the result type of a foreign export.
125125
safeExit :: Int -> IO a
126-
safeExit r = unsafeCoerce# (shutdownHaskellAndExit r)
126+
safeExit r = unsafeCoerce# (shutdownHaskellAndExit $ fromIntegral r)
127127
128128
-- NOTE: shutdownHaskellAndExit must be called "safe", because it *can*
129129
-- re-enter Haskell land through finalizers.
130130
foreign import ccall "Rts.h shutdownHaskellAndExit"
131-
shutdownHaskellAndExit :: Int -> IO ()
131+
shutdownHaskellAndExit :: CInt -> IO ()
132132
133133
fastExit :: Int -> IO a
134134
fastExit r = unsafeCoerce# (stg_exit (fromIntegral r))

GHC/Word.hs

Lines changed: 25 additions & 25 deletions
Original file line numberDiff line numberDiff line change
@@ -745,31 +745,31 @@ a `shiftRL64#` b | b >=# 64# = wordToWord64# (int2Word# 0#)
745745
| otherwise = a `uncheckedShiftRL64#` b
746746

747747

748-
foreign import ccall unsafe "stg_eqWord64" eqWord64# :: Word64# -> Word64# -> Bool
749-
foreign import ccall unsafe "stg_neWord64" neWord64# :: Word64# -> Word64# -> Bool
750-
foreign import ccall unsafe "stg_ltWord64" ltWord64# :: Word64# -> Word64# -> Bool
751-
foreign import ccall unsafe "stg_leWord64" leWord64# :: Word64# -> Word64# -> Bool
752-
foreign import ccall unsafe "stg_gtWord64" gtWord64# :: Word64# -> Word64# -> Bool
753-
foreign import ccall unsafe "stg_geWord64" geWord64# :: Word64# -> Word64# -> Bool
754-
foreign import ccall unsafe "stg_int64ToWord64" int64ToWord64# :: Int64# -> Word64#
755-
foreign import ccall unsafe "stg_word64ToInt64" word64ToInt64# :: Word64# -> Int64#
756-
foreign import ccall unsafe "stg_intToInt64" intToInt64# :: Int# -> Int64#
757-
foreign import ccall unsafe "stg_wordToWord64" wordToWord64# :: Word# -> Word64#
758-
foreign import ccall unsafe "stg_word64ToWord" word64ToWord# :: Word64# -> Word#
759-
foreign import ccall unsafe "stg_plusInt64" plusInt64# :: Int64# -> Int64# -> Int64#
760-
foreign import ccall unsafe "stg_minusInt64" minusInt64# :: Int64# -> Int64# -> Int64#
761-
foreign import ccall unsafe "stg_timesInt64" timesInt64# :: Int64# -> Int64# -> Int64#
762-
foreign import ccall unsafe "stg_negateInt64" negateInt64# :: Int64# -> Int64#
763-
foreign import ccall unsafe "stg_quotWord64" quotWord64# :: Word64# -> Word64# -> Word64#
764-
foreign import ccall unsafe "stg_remWord64" remWord64# :: Word64# -> Word64# -> Word64#
765-
foreign import ccall unsafe "stg_and64" and64# :: Word64# -> Word64# -> Word64#
766-
foreign import ccall unsafe "stg_or64" or64# :: Word64# -> Word64# -> Word64#
767-
foreign import ccall unsafe "stg_xor64" xor64# :: Word64# -> Word64# -> Word64#
768-
foreign import ccall unsafe "stg_not64" not64# :: Word64# -> Word64#
769-
foreign import ccall unsafe "stg_uncheckedShiftL64" uncheckedShiftL64# :: Word64# -> Int# -> Word64#
770-
foreign import ccall unsafe "stg_uncheckedShiftRL64" uncheckedShiftRL64# :: Word64# -> Int# -> Word64#
771-
772-
foreign import ccall unsafe "stg_integerToWord64" integerToWord64# :: Int# -> ByteArray# -> Word64#
748+
foreign import ccall unsafe "hs_eqWord64" eqWord64# :: Word64# -> Word64# -> Bool
749+
foreign import ccall unsafe "hs_neWord64" neWord64# :: Word64# -> Word64# -> Bool
750+
foreign import ccall unsafe "hs_ltWord64" ltWord64# :: Word64# -> Word64# -> Bool
751+
foreign import ccall unsafe "hs_leWord64" leWord64# :: Word64# -> Word64# -> Bool
752+
foreign import ccall unsafe "hs_gtWord64" gtWord64# :: Word64# -> Word64# -> Bool
753+
foreign import ccall unsafe "hs_geWord64" geWord64# :: Word64# -> Word64# -> Bool
754+
foreign import ccall unsafe "hs_int64ToWord64" int64ToWord64# :: Int64# -> Word64#
755+
foreign import ccall unsafe "hs_word64ToInt64" word64ToInt64# :: Word64# -> Int64#
756+
foreign import ccall unsafe "hs_intToInt64" intToInt64# :: Int# -> Int64#
757+
foreign import ccall unsafe "hs_wordToWord64" wordToWord64# :: Word# -> Word64#
758+
foreign import ccall unsafe "hs_word64ToWord" word64ToWord# :: Word64# -> Word#
759+
foreign import ccall unsafe "hs_plusInt64" plusInt64# :: Int64# -> Int64# -> Int64#
760+
foreign import ccall unsafe "hs_minusInt64" minusInt64# :: Int64# -> Int64# -> Int64#
761+
foreign import ccall unsafe "hs_timesInt64" timesInt64# :: Int64# -> Int64# -> Int64#
762+
foreign import ccall unsafe "hs_negateInt64" negateInt64# :: Int64# -> Int64#
763+
foreign import ccall unsafe "hs_quotWord64" quotWord64# :: Word64# -> Word64# -> Word64#
764+
foreign import ccall unsafe "hs_remWord64" remWord64# :: Word64# -> Word64# -> Word64#
765+
foreign import ccall unsafe "hs_and64" and64# :: Word64# -> Word64# -> Word64#
766+
foreign import ccall unsafe "hs_or64" or64# :: Word64# -> Word64# -> Word64#
767+
foreign import ccall unsafe "hs_xor64" xor64# :: Word64# -> Word64# -> Word64#
768+
foreign import ccall unsafe "hs_not64" not64# :: Word64# -> Word64#
769+
foreign import ccall unsafe "hs_uncheckedShiftL64" uncheckedShiftL64# :: Word64# -> Int# -> Word64#
770+
foreign import ccall unsafe "hs_uncheckedShiftRL64" uncheckedShiftRL64# :: Word64# -> Int# -> Word64#
771+
772+
foreign import ccall unsafe "hs_integerToWord64" integerToWord64# :: Int# -> ByteArray# -> Word64#
773773

774774

775775
{-# RULES

System/Directory.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -862,9 +862,9 @@ fileNameEndClean name =
862862
i = (length name) - 1
863863
ec = name !! i
864864

865-
foreign import ccall unsafe "__hscore_R_OK" r_OK :: CMode
866-
foreign import ccall unsafe "__hscore_W_OK" w_OK :: CMode
867-
foreign import ccall unsafe "__hscore_X_OK" x_OK :: CMode
865+
foreign import ccall unsafe "__hscore_R_OK" r_OK :: CInt
866+
foreign import ccall unsafe "__hscore_W_OK" w_OK :: CInt
867+
foreign import ccall unsafe "__hscore_X_OK" x_OK :: CInt
868868

869869
foreign import ccall unsafe "__hscore_S_IRUSR" s_IRUSR :: CMode
870870
foreign import ccall unsafe "__hscore_S_IWUSR" s_IWUSR :: CMode

System/Environment.hs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -29,6 +29,7 @@ module System.Environment
2929
import Prelude
3030

3131
#ifdef __GLASGOW_HASKELL__
32+
import Data.List
3233
import Foreign
3334
import Foreign.C
3435
import Control.Exception ( bracket )
@@ -165,11 +166,11 @@ freeArgv argv = do
165166
setArgs :: [String] -> IO (Ptr CString)
166167
setArgs argv = do
167168
vs <- mapM newCString argv >>= newArray0 nullPtr
168-
setArgsPrim (length argv) vs
169+
setArgsPrim (genericLength argv) vs
169170
return vs
170171

171172
foreign import ccall unsafe "setProgArgv"
172-
setArgsPrim :: Int -> Ptr CString -> IO ()
173+
setArgsPrim :: CInt -> Ptr CString -> IO ()
173174

174175
-- |'getEnvironment' retrieves the entire environment as a
175176
-- list of @(key,value)@ pairs.

System/Posix/Internals.hs

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -295,7 +295,7 @@ setNonBlockingFD fd = do
295295
-- there are certain file handles on which this will fail (eg. /dev/null
296296
-- on FreeBSD) so we throw away the return code from fcntl_write.
297297
unless (testBit flags (fromIntegral o_NONBLOCK)) $ do
298-
c_fcntl_write fd const_f_setfl (flags .|. o_NONBLOCK)
298+
c_fcntl_write fd const_f_setfl (fromIntegral (flags .|. o_NONBLOCK))
299299
return ()
300300
#else
301301

@@ -308,7 +308,7 @@ setNonBlockingFD fd = return ()
308308
-- foreign imports
309309

310310
foreign import ccall unsafe "HsBase.h access"
311-
c_access :: CString -> CMode -> IO CInt
311+
c_access :: CString -> CInt -> IO CInt
312312

313313
foreign import ccall unsafe "HsBase.h chmod"
314314
c_chmod :: CString -> CMode -> IO CInt
@@ -335,7 +335,7 @@ foreign import ccall unsafe "HsBase.h __hscore_fstat"
335335
c_fstat :: CInt -> Ptr CStat -> IO CInt
336336

337337
foreign import ccall unsafe "HsBase.h getcwd"
338-
c_getcwd :: Ptr CChar -> CInt -> IO (Ptr CChar)
338+
c_getcwd :: Ptr CChar -> CSize -> IO (Ptr CChar)
339339

340340
foreign import ccall unsafe "HsBase.h isatty"
341341
c_isatty :: CInt -> IO CInt
@@ -390,7 +390,7 @@ foreign import ccall unsafe "HsBase.h fcntl"
390390
c_fcntl_read :: CInt -> CInt -> IO CInt
391391

392392
foreign import ccall unsafe "HsBase.h fcntl"
393-
c_fcntl_write :: CInt -> CInt -> CInt -> IO CInt
393+
c_fcntl_write :: CInt -> CInt -> CLong -> IO CInt
394394

395395
foreign import ccall unsafe "HsBase.h fcntl"
396396
c_fcntl_lock :: CInt -> CInt -> Ptr CFLock -> IO CInt
@@ -423,7 +423,7 @@ foreign import ccall unsafe "HsBase.h tcsetattr"
423423
c_tcsetattr :: CInt -> CInt -> Ptr CTermios -> IO CInt
424424

425425
foreign import ccall unsafe "HsBase.h utime"
426-
c_utime :: CString -> Ptr CUtimbuf -> IO CMode
426+
c_utime :: CString -> Ptr CUtimbuf -> IO CInt
427427

428428
foreign import ccall unsafe "HsBase.h waitpid"
429429
c_waitpid :: CPid -> Ptr CInt -> CInt -> IO CPid

System/Posix/Signals.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -281,7 +281,7 @@ signalProcessGroup sig pgid
281281
= throwErrnoIfMinus1_ "signalProcessGroup" (c_killpg (fromIntegral pgid) sig)
282282

283283
foreign import ccall unsafe "killpg"
284-
c_killpg :: CPid -> CInt -> IO CInt
284+
c_killpg :: CInt -> CInt -> IO CInt
285285

286286
-- | @raiseSignal int@ calls @kill@ to signal the current process
287287
-- with interrupt signal @int@.

System/Random.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -84,7 +84,7 @@ import Numeric ( readDec )
8484
-- replacement here.
8585
#ifdef __NHC__
8686
data ClockTime = TOD Integer ()
87-
foreign import ccall "time.h time" readtime :: Ptr () -> IO Int
87+
foreign import ccall "time.h time" readtime :: Ptr CTime -> IO CTime
8888
getClockTime :: IO ClockTime
8989
getClockTime = do t <- readtime nullPtr; return (TOD (toInteger t) ())
9090
#endif

System/Time.hsc

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -357,10 +357,10 @@ gmtoff x = (#peek struct tm,tm_gmtoff) x
357357
# define tzname _tzname
358358
# endif
359359
# ifndef mingw32_HOST_OS
360-
foreign import ccall unsafe "time.h &tzname" tzname :: Ptr (Ptr CChar)
360+
foreign import ccall unsafe "time.h &tzname" tzname :: Ptr CString
361361
# else
362362
foreign import ccall unsafe "__hscore_timezone" timezone :: Ptr CLong
363-
foreign import ccall unsafe "__hscore_tzname" tzname :: Ptr (Ptr CChar)
363+
foreign import ccall unsafe "__hscore_tzname" tzname :: Ptr CString
364364
# endif
365365
zone x = do
366366
dst <- (#peek struct tm,tm_isdst) x
@@ -740,8 +740,9 @@ foreign import ccall unsafe "time.h mktime"
740740

741741
#if HAVE_GETTIMEOFDAY
742742
type CTimeVal = ()
743+
type CTimeZone = ()
743744
foreign import ccall unsafe "time.h gettimeofday"
744-
gettimeofday :: Ptr CTimeVal -> Ptr () -> IO CInt
745+
gettimeofday :: Ptr CTimeVal -> Ptr CTimeZone -> IO CInt
745746
#elif HAVE_FTIME
746747
type CTimeB = ()
747748
#ifndef mingw32_HOST_OS

0 commit comments

Comments
 (0)