Skip to content

Commit c3fbba7

Browse files
Merge pull request #558 from kazu-yamamoto/strict2
Strict and StrictData
2 parents eea4dfc + 7a99213 commit c3fbba7

File tree

15 files changed

+94
-86
lines changed

15 files changed

+94
-86
lines changed

Network/Socket/ByteString/IO.hsc

Lines changed: 3 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,3 @@
1-
{-# LANGUAGE BangPatterns #-}
21
{-# LANGUAGE RecordWildCards #-}
32
{-# LANGUAGE OverloadedStrings #-}
43

@@ -294,9 +293,9 @@ withWSABuffromBS cs f = withBufSizs cs $ \bufsizs -> withWSABuf bufsizs f
294293
withBufSizs :: [ByteString] -> ([(Ptr Word8, Int)] -> IO a) -> IO a
295294
withBufSizs bss0 f = loop bss0 id
296295
where
297-
loop [] !build = f $ build []
298-
loop (PS fptr off len:bss) !build = withForeignPtr fptr $ \ptr -> do
299-
let !ptr' = ptr `plusPtr` off
296+
loop [] build = f $ build []
297+
loop (PS fptr off len:bss) build = withForeignPtr fptr $ \ptr -> do
298+
let ptr' = ptr `plusPtr` off
300299
loop bss (build . ((ptr',len) :))
301300

302301
-- | Send data to the socket using sendmsg(2).

Network/Socket/ByteString/Lazy/Posix.hs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,3 @@
1-
{-# LANGUAGE BangPatterns #-}
21
{-# LANGUAGE OverloadedStrings #-}
32

43
module Network.Socket.ByteString.Lazy.Posix (
@@ -34,7 +33,7 @@ send s lbs = do
3433
where
3534
withPokes ss p f = loop ss p 0 0
3635
where
37-
loop (c:cs) q k !niovs
36+
loop (c:cs) q k niovs
3837
| k < maxNumBytes = unsafeUseAsCStringLen c $ \(ptr, len) -> do
3938
poke q $ IOVec (castPtr ptr) (fromIntegral len)
4039
loop cs

Network/Socket/Info.hsc

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -108,8 +108,8 @@ data AddrInfo = AddrInfo {
108108
} deriving (Eq, Show)
109109

110110
instance Storable AddrInfo where
111-
sizeOf _ = #const sizeof(struct addrinfo)
112-
alignment _ = alignment (0 :: CInt)
111+
sizeOf ~_ = #const sizeof(struct addrinfo)
112+
alignment ~_ = alignment (0 :: CInt)
113113

114114
peek p = do
115115
ai_flags <- (#peek struct addrinfo, ai_flags) p

Network/Socket/Options.hsc

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -50,11 +50,11 @@ import Network.Socket.ReadShow
5050
-- is supported on your system: see 'isSupportedSocketOption'
5151
data SocketOption = SockOpt
5252
#if __GLASGOW_HASKELL__ >= 806
53-
!CInt -- ^ Option Level
54-
!CInt -- ^ Option Name
53+
CInt -- ^ Option Level
54+
CInt -- ^ Option Name
5555
#else
56-
!CInt -- Option Level
57-
!CInt -- Option Name
56+
CInt -- Option Level
57+
CInt -- Option Name
5858
#endif
5959
deriving (Eq)
6060

@@ -466,8 +466,8 @@ data StructLinger = StructLinger {
466466
deriving (Eq, Ord, Show)
467467

468468
instance Storable StructLinger where
469-
sizeOf _ = (#const sizeof(struct linger))
470-
alignment _ = alignment (0 :: CInt)
469+
sizeOf ~_ = (#const sizeof(struct linger))
470+
alignment ~_ = alignment (0 :: CInt)
471471

472472
peek p = do
473473
onoff <- (#peek struct linger, l_onoff) p

Network/Socket/Posix/Cmsg.hsc

Lines changed: 12 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -26,16 +26,16 @@ import qualified Text.Read as P
2626

2727
-- | Control message (ancillary data) including a pair of level and type.
2828
data Cmsg = Cmsg {
29-
cmsgId :: !CmsgId
30-
, cmsgData :: !ByteString
29+
cmsgId :: CmsgId
30+
, cmsgData :: ByteString
3131
} deriving (Eq, Show)
3232

3333
----------------------------------------------------------------
3434

3535
-- | Identifier of control message (ancillary data).
3636
data CmsgId = CmsgId {
37-
cmsgLevel :: !CInt
38-
, cmsgType :: !CInt
37+
cmsgLevel :: CInt
38+
, cmsgType :: CInt
3939
} deriving (Eq)
4040

4141
-- | Unsupported identifier
@@ -177,8 +177,8 @@ instance ControlMessage IPv4PktInfo where
177177

178178
instance Storable IPv4PktInfo where
179179
#if defined (IP_PKTINFO)
180-
sizeOf _ = (#size struct in_pktinfo)
181-
alignment _ = alignment (0 :: CInt)
180+
sizeOf ~_ = (#size struct in_pktinfo)
181+
alignment ~_ = alignment (0 :: CInt)
182182
poke p (IPv4PktInfo n sa ha) = do
183183
(#poke struct in_pktinfo, ipi_ifindex) p (fromIntegral n :: CInt)
184184
(#poke struct in_pktinfo, ipi_spec_dst) p sa
@@ -189,8 +189,8 @@ instance Storable IPv4PktInfo where
189189
ha <- (#peek struct in_pktinfo, ipi_addr) p
190190
return $ IPv4PktInfo n sa ha
191191
#else
192-
sizeOf _ = 0
193-
alignment _ = 1
192+
sizeOf ~_ = 0
193+
alignment ~_ = 1
194194
poke _ _ = error "Unsupported control message type"
195195
peek _ = error "Unsupported control message type"
196196
#endif
@@ -208,8 +208,8 @@ instance ControlMessage IPv6PktInfo where
208208

209209
instance Storable IPv6PktInfo where
210210
#if defined (IPV6_PKTINFO)
211-
sizeOf _ = (#size struct in6_pktinfo)
212-
alignment _ = alignment (0 :: CInt)
211+
sizeOf ~_ = (#size struct in6_pktinfo)
212+
alignment ~_ = alignment (0 :: CInt)
213213
poke p (IPv6PktInfo n ha6) = do
214214
(#poke struct in6_pktinfo, ipi6_ifindex) p (fromIntegral n :: CInt)
215215
(#poke struct in6_pktinfo, ipi6_addr) p (In6Addr ha6)
@@ -218,8 +218,8 @@ instance Storable IPv6PktInfo where
218218
n :: CInt <- (#peek struct in6_pktinfo, ipi6_ifindex) p
219219
return $ IPv6PktInfo (fromIntegral n) ha6
220220
#else
221-
sizeOf _ = 0
222-
alignment _ = 1
221+
sizeOf ~_ = 0
222+
alignment ~_ = 1
223223
poke _ _ = error "Unsupported control message type"
224224
peek _ = error "Unsupported control message type"
225225
#endif

Network/Socket/Posix/CmsgHdr.hsc

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -23,17 +23,17 @@ import Network.Socket.Types
2323

2424
data CmsgHdr = CmsgHdr {
2525
#ifdef __linux__
26-
cmsgHdrLen :: !CSize
26+
cmsgHdrLen :: CSize
2727
#else
28-
cmsgHdrLen :: !(#type socklen_t)
28+
cmsgHdrLen :: #type socklen_t
2929
#endif
30-
, cmsgHdrLevel :: !CInt
31-
, cmsgHdrType :: !CInt
30+
, cmsgHdrLevel :: CInt
31+
, cmsgHdrType :: CInt
3232
} deriving (Eq, Show)
3333

3434
instance Storable CmsgHdr where
35-
sizeOf _ = (#size struct cmsghdr)
36-
alignment _ = alignment (0 :: CInt)
35+
sizeOf ~_ = (#size struct cmsghdr)
36+
alignment ~_ = alignment (0 :: CInt)
3737

3838
peek p = do
3939
len <- (#peek struct cmsghdr, cmsg_len) p

Network/Socket/Posix/IOVec.hsc

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -14,13 +14,13 @@ import Network.Socket.Imports
1414
#include <sys/uio.h>
1515

1616
data IOVec = IOVec
17-
{ iovBase :: !(Ptr Word8)
18-
, iovLen :: !CSize
17+
{ iovBase :: Ptr Word8
18+
, iovLen :: CSize
1919
}
2020

2121
instance Storable IOVec where
22-
sizeOf _ = (#const sizeof(struct iovec))
23-
alignment _ = alignment (0 :: CInt)
22+
sizeOf ~_ = (#const sizeof(struct iovec))
23+
alignment ~_ = alignment (0 :: CInt)
2424

2525
peek p = do
2626
base <- (#peek struct iovec, iov_base) p

Network/Socket/Posix/MsgHdr.hsc

Lines changed: 11 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -14,26 +14,26 @@ import Network.Socket.Internal (zeroMemory)
1414
import Network.Socket.Posix.IOVec (IOVec)
1515

1616
data MsgHdr sa = MsgHdr
17-
{ msgName :: !(Ptr sa)
18-
, msgNameLen :: !(#type socklen_t)
19-
, msgIov :: !(Ptr IOVec)
17+
{ msgName :: Ptr sa
18+
, msgNameLen :: #type socklen_t
19+
, msgIov :: Ptr IOVec
2020
#ifdef __linux__
21-
, msgIovLen :: !CSize
21+
, msgIovLen :: CSize
2222
#else
23-
, msgIovLen :: !CInt
23+
, msgIovLen :: CInt
2424
#endif
25-
, msgCtrl :: !(Ptr Word8)
25+
, msgCtrl :: Ptr Word8
2626
#ifdef __linux__
27-
, msgCtrlLen :: !CSize
27+
, msgCtrlLen :: CSize
2828
#else
29-
, msgCtrlLen :: !(#type socklen_t)
29+
, msgCtrlLen :: #type socklen_t
3030
#endif
31-
, msgFlags :: !CInt
31+
, msgFlags :: CInt
3232
}
3333

3434
instance Storable (MsgHdr sa) where
35-
sizeOf _ = (#const sizeof(struct msghdr))
36-
alignment _ = alignment (0 :: CInt)
35+
sizeOf ~_ = (#const sizeof(struct msghdr))
36+
alignment ~_ = alignment (0 :: CInt)
3737

3838
peek p = do
3939
name <- (#peek struct msghdr, msg_name) p

Network/Socket/Types.hsc

Lines changed: 15 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -104,7 +104,7 @@ import Network.Socket.ReadShow
104104
-----------------------------------------------------------------------------
105105

106106
-- | Basic type for a socket.
107-
data Socket = Socket !(IORef CInt) !CInt {- for Show -}
107+
data Socket = Socket (IORef CInt) CInt {- for Show -}
108108

109109
instance Show Socket where
110110
show (Socket _ ofd) = "<socket: " ++ show ofd ++ ">"
@@ -982,8 +982,8 @@ foreign import CALLCONV unsafe "ntohl" ntohl :: Word32 -> Word32
982982
{-# DEPRECATED ntohl "Use getAddrInfo instead" #-}
983983

984984
instance Storable PortNumber where
985-
sizeOf _ = sizeOf (0 :: Word16)
986-
alignment _ = alignment (0 :: Word16)
985+
sizeOf ~_ = sizeOf (0 :: Word16)
986+
alignment ~_ = alignment (0 :: Word16)
987987
poke p (PortNum po) = poke (castPtr p) (htons po)
988988
peek p = PortNum . ntohs <$> peek (castPtr p)
989989

@@ -1007,6 +1007,7 @@ class SocketAddress sa where
10071007
sockaddrStorageLen :: Int
10081008
sockaddrStorageLen = 128
10091009

1010+
{-# NOINLINE withSocketAddress #-}
10101011
withSocketAddress :: SocketAddress sa => sa -> (Ptr sa -> Int -> IO a) -> IO a
10111012
withSocketAddress addr f = do
10121013
let sz = sizeOfSocketAddress addr
@@ -1051,13 +1052,13 @@ type ScopeID = Word32
10511052
-- 'isSupportedSockAddr'.
10521053
data SockAddr
10531054
= SockAddrInet
1054-
!PortNumber -- sin_port
1055-
!HostAddress -- sin_addr (ditto)
1055+
PortNumber -- sin_port
1056+
HostAddress -- sin_addr (ditto)
10561057
| SockAddrInet6
1057-
!PortNumber -- sin6_port
1058-
!FlowInfo -- sin6_flowinfo (ditto)
1059-
!HostAddress6 -- sin6_addr (ditto)
1060-
!ScopeID -- sin6_scope_id (ditto)
1058+
PortNumber -- sin6_port
1059+
FlowInfo -- sin6_flowinfo (ditto)
1060+
HostAddress6 -- sin6_addr (ditto)
1061+
ScopeID -- sin6_scope_id (ditto)
10611062
-- | The path must have fewer than 104 characters. All of these characters must have code points less than 256.
10621063
| SockAddrUnix
10631064
String -- sun_path
@@ -1114,6 +1115,9 @@ sizeOfSockAddr SockAddrUnix{} = #const sizeof(struct sockaddr_un)
11141115
sizeOfSockAddr SockAddrInet{} = #const sizeof(struct sockaddr_in)
11151116
sizeOfSockAddr SockAddrInet6{} = #const sizeof(struct sockaddr_in6)
11161117

1118+
-- The combination of "-XString" and inlining results in a bug where
1119+
-- "sz" is always 0.
1120+
{-# NOINLINE withSockAddr #-}
11171121
-- | Use a 'SockAddr' with a function requiring a pointer to a
11181122
-- 'SockAddr' and the length of that 'SockAddr'.
11191123
withSockAddr :: SockAddr -> (Ptr SockAddr -> Int -> IO a) -> IO a
@@ -1279,8 +1283,8 @@ newtype In6Addr = In6Addr HostAddress6
12791283
#endif
12801284

12811285
instance Storable In6Addr where
1282-
sizeOf _ = #const sizeof(struct in6_addr)
1283-
alignment _ = #alignment struct in6_addr
1286+
sizeOf ~_ = #const sizeof(struct in6_addr)
1287+
alignment ~_ = #alignment struct in6_addr
12841288

12851289
peek p = do
12861290
a <- peek32 p 0

Network/Socket/Unix.hsc

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -88,8 +88,8 @@ getPeerCred s = do
8888

8989
newtype PeerCred = PeerCred (CUInt, CUInt, CUInt)
9090
instance Storable PeerCred where
91-
sizeOf _ = (#const sizeof(struct ucred))
92-
alignment _ = alignment (0 :: CInt)
91+
sizeOf ~_ = (#const sizeof(struct ucred))
92+
alignment ~_ = alignment (0 :: CInt)
9393
poke _ _ = return ()
9494
peek p = do
9595
pid <- (#peek struct ucred, pid) p

Network/Socket/Win32/Cmsg.hsc

Lines changed: 8 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -27,16 +27,16 @@ type ULONG = Word32
2727

2828
-- | Control message (ancillary data) including a pair of level and type.
2929
data Cmsg = Cmsg {
30-
cmsgId :: !CmsgId
31-
, cmsgData :: !ByteString
30+
cmsgId :: CmsgId
31+
, cmsgData :: ByteString
3232
} deriving (Eq, Show)
3333

3434
----------------------------------------------------------------
3535

3636
-- | Identifier of control message (ancillary data).
3737
data CmsgId = CmsgId {
38-
cmsgLevel :: !CInt
39-
, cmsgType :: !CInt
38+
cmsgLevel :: CInt
39+
, cmsgType :: CInt
4040
} deriving (Eq)
4141

4242
-- | Unsupported identifier
@@ -160,8 +160,8 @@ instance ControlMessage IPv4PktInfo where
160160
controlMessageId = CmsgIdIPv4PktInfo
161161

162162
instance Storable IPv4PktInfo where
163-
sizeOf _ = #{size IN_PKTINFO}
164-
alignment _ = #alignment IN_PKTINFO
163+
sizeOf ~_ = #{size IN_PKTINFO}
164+
alignment ~_ = #alignment IN_PKTINFO
165165
poke p (IPv4PktInfo n _ ha) = do
166166
(#poke IN_PKTINFO, ipi_ifindex) p (fromIntegral n :: CInt)
167167
(#poke IN_PKTINFO, ipi_addr) p ha
@@ -182,8 +182,8 @@ instance ControlMessage IPv6PktInfo where
182182
controlMessageId = CmsgIdIPv6PktInfo
183183

184184
instance Storable IPv6PktInfo where
185-
sizeOf _ = #{size IN6_PKTINFO}
186-
alignment _ = #alignment IN6_PKTINFO
185+
sizeOf ~_ = #{size IN6_PKTINFO}
186+
alignment ~_ = #alignment IN6_PKTINFO
187187
poke p (IPv6PktInfo n ha6) = do
188188
(#poke IN6_PKTINFO, ipi6_ifindex) p (fromIntegral n :: CInt)
189189
(#poke IN6_PKTINFO, ipi6_addr) p (In6Addr ha6)

Network/Socket/Win32/CmsgHdr.hsc

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -19,14 +19,14 @@ import Network.Socket.Win32.MsgHdr
1919
import Network.Socket.Types
2020

2121
data CmsgHdr = CmsgHdr {
22-
cmsgHdrLen :: !CUInt
23-
, cmsgHdrLevel :: !CInt
24-
, cmsgHdrType :: !CInt
22+
cmsgHdrLen :: CUInt
23+
, cmsgHdrLevel :: CInt
24+
, cmsgHdrType :: CInt
2525
} deriving (Eq, Show)
2626

2727
instance Storable CmsgHdr where
28-
sizeOf _ = #{size WSACMSGHDR}
29-
alignment _ = #alignment WSACMSGHDR
28+
sizeOf ~_ = #{size WSACMSGHDR}
29+
alignment ~_ = #alignment WSACMSGHDR
3030

3131
peek p = do
3232
len <- (#peek WSACMSGHDR, cmsg_len) p

Network/Socket/Win32/MsgHdr.hsc

Lines changed: 9 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -18,18 +18,18 @@ type ULONG = Word32
1818
-- The size of BufferLen is different on pre-vista compilers.
1919
-- But since those platforms are out of support anyway we ignore that.
2020
data MsgHdr sa = MsgHdr
21-
{ msgName :: !(Ptr sa)
22-
, msgNameLen :: !CInt
23-
, msgBuffer :: !(Ptr WSABuf)
24-
, msgBufferLen :: !DWORD
25-
, msgCtrl :: !(Ptr Word8)
26-
, msgCtrlLen :: !ULONG
27-
, msgFlags :: !DWORD
21+
{ msgName :: Ptr sa
22+
, msgNameLen :: CInt
23+
, msgBuffer :: Ptr WSABuf
24+
, msgBufferLen :: DWORD
25+
, msgCtrl :: Ptr Word8
26+
, msgCtrlLen :: ULONG
27+
, msgFlags :: DWORD
2828
} deriving Show
2929

3030
instance Storable (MsgHdr sa) where
31-
sizeOf _ = #{size WSAMSG}
32-
alignment _ = #alignment WSAMSG
31+
sizeOf ~_ = #{size WSAMSG}
32+
alignment ~_ = #alignment WSAMSG
3333

3434
peek p = do
3535
name <- (#peek WSAMSG, name) p

0 commit comments

Comments
 (0)