Skip to content

Commit

Permalink
We don't support any other compilers than GHC
Browse files Browse the repository at this point in the history
This commit was recreated from the 2.4.1.2 release, which commits were
somehow lost (i.e. not pushed to GitHub).
  • Loading branch information
tibbe committed Oct 9, 2013
1 parent 482dedf commit cde0eee
Show file tree
Hide file tree
Showing 7 changed files with 23 additions and 79 deletions.
6 changes: 2 additions & 4 deletions Network/BSD.hsc
Original file line number Diff line number Diff line change
Expand Up @@ -112,12 +112,10 @@ import Data.Typeable
import System.IO.Error (ioeSetErrorString, mkIOError)
import System.IO.Unsafe (unsafePerformIO)

#ifdef __GLASGOW_HASKELL__
# if __GLASGOW_HASKELL__ >= 611
#if __GLASGOW_HASKELL__ >= 611
import GHC.IO.Exception
# else
#else
import GHC.IOBase
# endif
#endif

import Control.Monad (liftM)
Expand Down
22 changes: 7 additions & 15 deletions Network/Socket.hsc
Original file line number Diff line number Diff line change
Expand Up @@ -199,7 +199,6 @@ import Control.Concurrent.MVar
import Data.Typeable
import System.IO.Error

#ifdef __GLASGOW_HASKELL__
import GHC.Conc (threadWaitRead, threadWaitWrite)
##if MIN_VERSION_base(4,3,1)
import GHC.Conc (closeFdWith)
Expand All @@ -218,9 +217,6 @@ import GHC.IOBase
import GHC.Handle
# endif
import qualified System.Posix.Internals
#else
import System.IO.Unsafe (unsafePerformIO)
#endif

# if __GLASGOW_HASKELL__ >= 611
import GHC.IO.FD
Expand Down Expand Up @@ -498,7 +494,7 @@ accept sock@(MkSocket s family stype protocol status) = do
else do
let sz = sizeOfSockAddrByFamily family
allocaBytes sz $ \ sockaddr -> do
#if defined(mingw32_HOST_OS) && defined(__GLASGOW_HASKELL__)
#if defined(mingw32_HOST_OS)
new_sock <-
if threaded
then with (fromIntegral sz) $ \ ptr_len ->
Expand Down Expand Up @@ -645,7 +641,7 @@ send sock@(MkSocket s _family _stype _protocol _status) xs = do
let len = length xs
withCString xs $ \str -> do
liftM fromIntegral $
#if defined(__GLASGOW_HASKELL__) && defined(mingw32_HOST_OS)
#if defined(mingw32_HOST_OS)
# if __GLASGOW_HASKELL__ >= 611
writeRawBufferPtr
"Network.Socket.send"
Expand Down Expand Up @@ -677,7 +673,7 @@ sendBuf :: Socket -- Bound/Connected Socket
-> IO Int -- Number of Bytes sent
sendBuf sock@(MkSocket s _family _stype _protocol _status) str len = do
liftM fromIntegral $
#if defined(__GLASGOW_HASKELL__) && defined(mingw32_HOST_OS)
#if defined(mingw32_HOST_OS)
# if __GLASGOW_HASKELL__ >= 611
writeRawBufferPtr
"Network.Socket.sendBuf"
Expand Down Expand Up @@ -720,7 +716,7 @@ recvLen sock@(MkSocket s _family _stype _protocol _status) nbytes
| otherwise = do
allocaBytes nbytes $ \ptr -> do
len <-
#if defined(__GLASGOW_HASKELL__) && defined(mingw32_HOST_OS)
#if defined(mingw32_HOST_OS)
# if __GLASGOW_HASKELL__ >= 611
readRawBufferPtr "Network.Socket.recvLen" (socket2FD sock) ptr 0
(fromIntegral nbytes)
Expand Down Expand Up @@ -758,7 +754,7 @@ recvLenBuf sock@(MkSocket s _family _stype _protocol _status) ptr nbytes
| nbytes <= 0 = ioError (mkInvalidRecvArgError "Network.Socket.recvBuf")
| otherwise = do
len <-
#if defined(__GLASGOW_HASKELL__) && defined(mingw32_HOST_OS)
#if defined(mingw32_HOST_OS)
# if __GLASGOW_HASKELL__ >= 611
readRawBufferPtr "Network.Socket.recvLenBuf" (socket2FD sock) ptr 0
(fromIntegral nbytes)
Expand Down Expand Up @@ -1183,7 +1179,7 @@ socketToHandle s@(MkSocket fd _ _ _ socketStatus) mode = do
h <- fdToHandle' (fromIntegral fd) (Just GHC.IO.Device.Stream) True (show s) mode True{-bin-}
# elif __GLASGOW_HASKELL__ >= 608
h <- fdToHandle' (fromIntegral fd) (Just System.Posix.Internals.Stream) True (show s) mode True{-bin-}
# elif __GLASGOW_HASKELL__ && __GLASGOW_HASKELL__ < 608
# elif __GLASGOW_HASKELL__ < 608
h <- openFd (fromIntegral fd) (Just System.Posix.Internals.Stream) True (show s) mode True{-bin-}
# endif
hSetBuffering h NoBuffering
Expand Down Expand Up @@ -1561,11 +1557,7 @@ foreign import ccall safe "hsnet_getnameinfo"

mkInvalidRecvArgError :: String -> IOError
mkInvalidRecvArgError loc = ioeSetErrorString (mkIOError
#ifdef __GLASGOW_HASKELL__
InvalidArgument
#else
IllegalOperation
#endif
loc Nothing Nothing) "non-positive length"

mkEOFError :: String -> IOError
Expand Down Expand Up @@ -1609,7 +1601,7 @@ foreign import CALLCONV unsafe "accept4"
foreign import CALLCONV unsafe "listen"
c_listen :: CInt -> CInt -> IO CInt

#if defined(mingw32_HOST_OS) && defined(__GLASGOW_HASKELL__)
#if defined(mingw32_HOST_OS)
foreign import CALLCONV safe "accept"
c_accept_safe :: CInt -> Ptr SockAddr -> Ptr CInt{-CSockLen???-} -> IO CInt

Expand Down
12 changes: 4 additions & 8 deletions Network/Socket/ByteString.hsc
Original file line number Diff line number Diff line change
Expand Up @@ -79,16 +79,12 @@ import Foreign.Storable (Storable(..))
import Network.Socket.ByteString.IOVec (IOVec(..))
import Network.Socket.ByteString.MsgHdr (MsgHdr(..))

# if defined(__GLASGOW_HASKELL__)
import GHC.Conc (threadWaitRead, threadWaitWrite)
# endif
#else
# if defined(__GLASGOW_HASKELL__)
# if __GLASGOW_HASKELL__ >= 611
# if __GLASGOW_HASKELL__ >= 611
import GHC.IO.FD
# else
# else
import GHC.Handle (readRawBufferPtr, writeRawBufferPtr)
# endif
# endif
#endif

Expand All @@ -111,7 +107,7 @@ send :: Socket -- ^ Connected socket
send sock@(MkSocket s _ _ _ _) xs =
unsafeUseAsCStringLen xs $ \(str, len) ->
liftM fromIntegral $
#if defined(__GLASGOW_HASKELL__) && defined(mingw32_HOST_OS)
#if defined(mingw32_HOST_OS)
# if __GLASGOW_HASKELL__ >= 611
writeRawBufferPtr "Network.Socket.ByteString.send"
(FD s 1) (castPtr str) 0 (fromIntegral len)
Expand Down Expand Up @@ -258,7 +254,7 @@ recv sock nbytes
recvInner :: Socket -> Int -> Ptr Word8 -> IO Int
recvInner sock nbytes ptr =
fmap fromIntegral $
#if defined(__GLASGOW_HASKELL__) && defined(mingw32_HOST_OS)
#if defined(mingw32_HOST_OS)
# if __GLASGOW_HASKELL__ >= 611
readRawBufferPtr "Network.Socket.ByteString.recv" (FD s 1) ptr 0 (fromIntegral nbytes)
# else
Expand Down
10 changes: 2 additions & 8 deletions Network/Socket/ByteString/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -34,21 +34,15 @@ import Network.Socket.ByteString.IOVec (IOVec)
import Network.Socket.ByteString.MsgHdr (MsgHdr)
#endif

#ifdef __GLASGOW_HASKELL__
# if __GLASGOW_HASKELL__ < 611
#if __GLASGOW_HASKELL__ < 611
import GHC.IOBase (IOErrorType(..))
# else
#else
import GHC.IO.Exception (IOErrorType(..))
# endif
#endif

mkInvalidRecvArgError :: String -> IOError
mkInvalidRecvArgError loc = ioeSetErrorString (mkIOError
#ifdef __GLASGOW_HASKELL__
InvalidArgument
#else
IllegalOperation
#endif
loc Nothing Nothing) "non-positive length"

#if !defined(mingw32_HOST_OS)
Expand Down
2 changes: 0 additions & 2 deletions Network/Socket/ByteString/Lazy.hsc
Original file line number Diff line number Diff line change
Expand Up @@ -57,9 +57,7 @@ import Network.Socket.Internal

import qualified Data.ByteString.Lazy as L

# if defined(__GLASGOW_HASKELL__)
import GHC.Conc (threadWaitWrite)
# endif
#endif

#if !defined(mingw32_HOST_OS)
Expand Down
14 changes: 4 additions & 10 deletions Network/Socket/Internal.hsc
Original file line number Diff line number Diff line change
Expand Up @@ -88,12 +88,10 @@ import GHC.Conc (threadWaitRead, threadWaitWrite)

#if defined(HAVE_WINSOCK2_H) && !defined(cygwin32_HOST_OS)
import Control.Exception ( finally )
# if __GLASGOW_HASKELL__
# if __GLASGOW_HASKELL__ >= 707
# if __GLASGOW_HASKELL__ >= 707
import GHC.IO.Exception ( IOErrorType(..) )
# else
# else
import GHC.IOBase ( IOErrorType(..) )
# endif
# endif
import Foreign.C.Types ( CChar )
import System.IO.Error ( ioeSetErrorString, mkIOError )
Expand Down Expand Up @@ -150,7 +148,7 @@ throwSocketErrorIfMinus1RetryMayBlock
{-# SPECIALIZE throwSocketErrorIfMinus1RetryMayBlock
:: String -> IO b -> IO CInt -> IO CInt #-}

#if defined(__GLASGOW_HASKELL__) && (!defined(HAVE_WINSOCK2_H) || defined(cygwin32_HOST_OS))
#if (!defined(HAVE_WINSOCK2_H) || defined(cygwin32_HOST_OS))

throwSocketErrorIfMinus1RetryMayBlock name on_block act =
throwErrnoIfMinus1RetryMayBlock name act on_block
Expand Down Expand Up @@ -192,11 +190,7 @@ throwSocketErrorIfMinus1Retry name act = do
throwSocketErrorCode name rc = do
pstr <- c_getWSError rc
str <- peekCString pstr
# if __GLASGOW_HASKELL__
ioError (ioeSetErrorString (mkIOError OtherError name Nothing Nothing) str)
# else
ioError (userError (name ++ ": socket error - " ++ str))
# endif

throwSocketError name =
c_getLastError >>= throwSocketErrorCode name
Expand All @@ -214,7 +208,7 @@ throwSocketError = throwErrno
throwSocketErrorCode loc errno =
ioError (errnoToIOError loc (Errno errno) Nothing Nothing)
# endif
#endif /* __GLASGOW_HASKELL */
#endif

-- | Like 'throwSocketErrorIfMinus1Retry', but if the action fails with
-- @EWOULDBLOCK@ or similar, wait for the socket to be read-ready,
Expand Down
36 changes: 4 additions & 32 deletions Network/URI.hs
Original file line number Diff line number Diff line change
Expand Up @@ -130,15 +130,11 @@ import Data.Bits ((.|.),(.&.),shiftL,shiftR)
import Debug.Trace (trace)
import Numeric (showIntAtBase)

#ifdef __GLASGOW_HASKELL__
import Data.Typeable (Typeable)
# if MIN_VERSION_base(4,0,0)
#if MIN_VERSION_base(4,0,0)
import Data.Data (Data)
# else
import Data.Generics (Data)
# endif
#else
import Data.Typeable (Typeable(..), TyCon, mkTyCon, mkTyConApp)
import Data.Generics (Data)
#endif

------------------------------------------------------------
Expand All @@ -160,38 +156,14 @@ data URI = URI
, uriPath :: String -- ^ @\/ghc@
, uriQuery :: String -- ^ @?query@
, uriFragment :: String -- ^ @#frag@
} deriving (Eq, Ord
#ifdef __GLASGOW_HASKELL__
, Typeable, Data
#endif
)

#ifndef __GLASGOW_HASKELL__
uriTc :: TyCon
uriTc = mkTyCon "URI"

instance Typeable URI where
typeOf _ = mkTyConApp uriTc []
#endif
} deriving (Eq, Ord, Typeable, Data)

-- |Type for authority value within a URI
data URIAuth = URIAuth
{ uriUserInfo :: String -- ^ @anonymous\@@
, uriRegName :: String -- ^ @www.haskell.org@
, uriPort :: String -- ^ @:42@
} deriving (Eq, Ord, Show
#ifdef __GLASGOW_HASKELL__
, Typeable, Data
#endif
)

#ifndef __GLASGOW_HASKELL__
uriAuthTc :: TyCon
uriAuthTc = mkTyCon "URIAuth"

instance Typeable URIAuth where
typeOf _ = mkTyConApp uriAuthTc []
#endif
} deriving (Eq, Ord, Show, Typeable, Data)

-- |Blank URI
nullURI :: URI
Expand Down

0 comments on commit cde0eee

Please sign in to comment.