Skip to content
Snippets Groups Projects
Commit 9c0ab382 authored by Ryan Scott's avatar Ryan Scott
Browse files

Patches adapting to unix-2.8.*

parent 0b1c7adc
No related branches found
No related tags found
No related merge requests found
diff --git a/src-unix/FileIO.hs b/src-unix/FileIO.hs
index 667562a..fac81a5 100644
--- a/src-unix/FileIO.hs
+++ b/src-unix/FileIO.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE CPP #-}
{-# LANGUAGE ForeignFunctionInterface #-}
module FileIO(FHandle,open,write,flush,close) where
import System.Posix(Fd(Fd),
@@ -16,7 +17,11 @@ data FHandle = FHandle Fd
-- should handle opening flags correctly
open :: FilePath -> IO FHandle
-open filename = fmap FHandle $ openFd filename WriteOnly (Just stdFileMode) defaultFileFlags
+open filename = fmap FHandle $ openFd filename WriteOnly
+#if !(MIN_VERSION_unix(2,8,0))
+ (Just stdFileMode)
+#endif
+ defaultFileFlags
write :: FHandle -> Ptr Word8 -> Word32 -> IO Word32
write (FHandle fd) data' length = fmap fromIntegral $ fdWriteBuf fd data' $ fromIntegral length
diff --git a/Network/Wai/Handler/Warp/FdCache.hs b/Network/Wai/Handler/Warp/FdCache.hs
index 2b6ad3f..b3c997d 100644
--- a/Network/Wai/Handler/Warp/FdCache.hs
+++ b/Network/Wai/Handler/Warp/FdCache.hs
@@ -67,7 +67,11 @@ data FdEntry = FdEntry !Fd !MutableStatus
openFile :: FilePath -> IO Fd
openFile path = do
- fd <- openFd path ReadOnly Nothing defaultFileFlags{nonBlock=False}
+ fd <- openFd path ReadOnly
+#if !(MIN_VERSION_unix(2,8,0))
+ Nothing
+#endif
+ defaultFileFlags{nonBlock=False}
setFileCloseOnExec fd
return fd
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