Skip to content
Snippets Groups Projects
Commit 298d9fd8 authored by simonpj@microsoft.com's avatar simonpj@microsoft.com
Browse files

Remove unnecessary fromIntegral calls

parent 14022b58
No related branches found
No related tags found
No related merge requests found
......@@ -259,7 +259,7 @@ handleToFd' h h_@Handle__{haType=_,..} = do
-- state as a result.
flushWriteBuffer h_
FD.release fd
return (Handle__{haType=ClosedHandle,..}, Fd (fromIntegral (FD.fdFD fd)))
return (Handle__{haType=ClosedHandle,..}, Fd (FD.fdFD fd))
fdToHandle fd = FD.fdToHandle (fromIntegral fd)
......@@ -434,7 +434,7 @@ fdRead _fd 0 = return ("", 0)
fdRead fd nbytes = do
allocaBytes (fromIntegral nbytes) $ \ buf -> do
rc <- fdReadBuf fd buf nbytes
case fromIntegral rc of
case rc of
0 -> ioError (ioeSetErrorString (mkIOError EOF "fdRead" Nothing Nothing) "EOF")
n -> do
s <- peekCStringLen (castPtr buf, fromIntegral n)
......@@ -450,7 +450,7 @@ fdReadBuf _fd _buf 0 = return 0
fdReadBuf fd buf nbytes =
fmap fromIntegral $
throwErrnoIfMinus1Retry "fdReadBuf" $
c_safe_read (fromIntegral fd) (castPtr buf) (fromIntegral nbytes)
c_safe_read (fromIntegral fd) (castPtr buf) nbytes
foreign import ccall safe "read"
c_safe_read :: CInt -> Ptr CChar -> CSize -> IO CSsize
......@@ -459,9 +459,8 @@ foreign import ccall safe "read"
-- the least-significant 8 bits of each character are written).
fdWrite :: Fd -> String -> IO ByteCount
fdWrite fd str =
withCStringLen str $ \ (buf,len) -> do
rc <- fdWriteBuf fd (castPtr buf) (fromIntegral len)
return (fromIntegral rc)
withCStringLen str $ \ (buf,len) ->
fdWriteBuf fd (castPtr buf) (fromIntegral len)
-- | Write data from memory to an 'Fd'. This is exactly equivalent
-- to the POSIX @write@ function.
......@@ -472,7 +471,7 @@ fdWriteBuf :: Fd
fdWriteBuf fd buf len =
fmap fromIntegral $
throwErrnoIfMinus1Retry "fdWriteBuf" $
c_safe_write (fromIntegral fd) (castPtr buf) (fromIntegral len)
c_safe_write (fromIntegral fd) (castPtr buf) len
foreign import ccall safe "write"
c_safe_write :: CInt -> Ptr CChar -> CSize -> IO CSsize
......@@ -256,7 +256,7 @@ forkProcess action = do
stable <- newStablePtr (runIO action)
pid <- throwErrnoIfMinus1 "forkProcess" (forkProcessPrim stable)
freeStablePtr stable
return $ fromIntegral pid
return pid
foreign import ccall "forkProcess" forkProcessPrim :: StablePtr (IO ()) -> IO CPid
#endif /* __GLASGOW_HASKELL__ */
......
......@@ -34,12 +34,12 @@ decipherWaitStatus wstat =
if c_WIFSIGNALED wstat /= 0
then do
let termsig = c_WTERMSIG wstat
return (Terminated (fromIntegral termsig))
return (Terminated termsig)
else do
if c_WIFSTOPPED wstat /= 0
then do
let stopsig = c_WSTOPSIG wstat
return (Stopped (fromIntegral stopsig))
return (Stopped stopsig)
else do
ioError (mkIOError illegalOperationErrorType
"waitStatus" Nothing Nothing)
......
......@@ -276,7 +276,7 @@ fileSizeLimitExceeded = sigXFSZ
-- with interrupt signal @int@.
signalProcess :: Signal -> ProcessID -> IO ()
signalProcess sig pid
= throwErrnoIfMinus1_ "signalProcess" (c_kill (fromIntegral pid) sig)
= throwErrnoIfMinus1_ "signalProcess" (c_kill pid sig)
foreign import ccall unsafe "kill"
c_kill :: CPid -> CInt -> IO CInt
......@@ -286,7 +286,7 @@ foreign import ccall unsafe "kill"
-- all processes in group @pgid@ with interrupt signal @int@.
signalProcessGroup :: Signal -> ProcessGroupID -> IO ()
signalProcessGroup sig pgid
= throwErrnoIfMinus1_ "signalProcessGroup" (c_killpg (fromIntegral pgid) sig)
= throwErrnoIfMinus1_ "signalProcessGroup" (c_killpg pgid sig)
foreign import ccall unsafe "killpg"
c_killpg :: CPid -> CInt -> IO CInt
......
......@@ -462,7 +462,7 @@ throwErrorIfNonZero_ loc act = do
rc <- act
if (rc == 0)
then return ()
else ioError (errnoToIOError loc (Errno (fromIntegral rc)) Nothing Nothing)
else ioError (errnoToIOError loc (Errno rc) Nothing Nothing)
-- Used when a function returns NULL to indicate either an error or
-- EOF, depending on whether the global errno is nonzero.
......
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