| Copyright | (c) Winterland 2018 |
|---|---|
| License | BSD |
| Maintainer | drkoster@qq.com |
| Stability | experimental |
| Portability | non-portable |
| Safe Haskell | None |
| Language | Haskell2010 |
Z.IO.Network.SocketAddr
Description
This module provides necessary types and constant for low level socket address manipulating.
Synopsis
- data SocketAddr
- ipv4 :: HasCallStack => CBytes -> PortNumber -> SocketAddr
- ipv6 :: HasCallStack => CBytes -> PortNumber -> SocketAddr
- sockAddrFamily :: SocketAddr -> SocketFamily
- withSocketAddr :: SocketAddr -> (Ptr SocketAddr -> IO a) -> IO a
- withSocketAddrUnsafe :: SocketAddr -> (MBA# SocketAddr -> IO a) -> IO a
- sizeOfSocketAddr :: SocketAddr -> CSize
- withSocketAddrStorage :: (Ptr SocketAddr -> IO ()) -> IO SocketAddr
- withSocketAddrStorageUnsafe :: (MBA# SocketAddr -> IO ()) -> IO SocketAddr
- sizeOfSocketAddrStorage :: CSize
- newtype InetAddr = InetAddr {}
- inetAny :: InetAddr
- inetBroadcast :: InetAddr
- inetNone :: InetAddr
- inetLoopback :: InetAddr
- inetUnspecificGroup :: InetAddr
- inetAllHostsGroup :: InetAddr
- inetMaxLocalGroup :: InetAddr
- inetAddrToTuple :: InetAddr -> (Word8, Word8, Word8, Word8)
- tupleToInetAddr :: (Word8, Word8, Word8, Word8) -> InetAddr
- data Inet6Addr = Inet6Addr !Word32 !Word32 !Word32 !Word32
- inet6Any :: Inet6Addr
- inet6Loopback :: Inet6Addr
- inet6AddrToTuple :: Inet6Addr -> (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16)
- tupleToInet6Addr :: (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16) -> Inet6Addr
- type FlowInfo = Word32
- type ScopeID = Word32
- newtype PortNumber = PortNumber Word16
- portAny :: PortNumber
- newtype SocketFamily = SocketFamily CInt
- pattern AF_UNSPEC :: SocketFamily
- pattern AF_INET :: SocketFamily
- pattern AF_INET6 :: SocketFamily
- newtype SocketType = SocketType CInt
- pattern SOCK_DGRAM :: SocketType
- pattern SOCK_STREAM :: SocketType
- pattern SOCK_SEQPACKET :: SocketType
- pattern SOCK_RAW :: SocketType
- pattern SOCK_RDM :: SocketType
- pattern SOCK_ANY :: SocketType
- newtype ProtocolNumber = ProtocolNumber CInt
- pattern IPPROTO_DEFAULT :: ProtocolNumber
- pattern IPPROTO_IP :: ProtocolNumber
- pattern IPPROTO_TCP :: ProtocolNumber
- pattern IPPROTO_UDP :: ProtocolNumber
- peekSocketAddr :: HasCallStack => Ptr SocketAddr -> IO SocketAddr
- pokeSocketAddr :: Ptr SocketAddr -> SocketAddr -> IO ()
- peekSocketAddrMBA :: HasCallStack => MBA# SocketAddr -> IO SocketAddr
- pokeSocketAddrMBA :: MBA# SocketAddr -> SocketAddr -> IO ()
- htons :: Word16 -> Word16
- ntohs :: Word16 -> Word16
- ntohl :: Word32 -> Word32
- htonl :: Word32 -> Word32
name to address
data SocketAddr Source #
IPv4 or IPv6 socket address, i.e. the sockaddr_in or sockaddr_in6 struct.
Constructors
| SocketAddrInet !PortNumber !InetAddr | |
| SocketAddrInet6 !PortNumber !FlowInfo !Inet6Addr !ScopeID |
Instances
| Eq SocketAddr Source # | |
Defined in Z.IO.Network.SocketAddr | |
| Ord SocketAddr Source # | |
Defined in Z.IO.Network.SocketAddr Methods compare :: SocketAddr -> SocketAddr -> Ordering # (<) :: SocketAddr -> SocketAddr -> Bool # (<=) :: SocketAddr -> SocketAddr -> Bool # (>) :: SocketAddr -> SocketAddr -> Bool # (>=) :: SocketAddr -> SocketAddr -> Bool # max :: SocketAddr -> SocketAddr -> SocketAddr # min :: SocketAddr -> SocketAddr -> SocketAddr # | |
| Show SocketAddr Source # | |
Defined in Z.IO.Network.SocketAddr Methods showsPrec :: Int -> SocketAddr -> ShowS # show :: SocketAddr -> String # showList :: [SocketAddr] -> ShowS # | |
ipv4 :: HasCallStack => CBytes -> PortNumber -> SocketAddr Source #
Convert a string containing an IPv4 addresses to a binary structure
This is partial function, wrong address will throw InvalidArgument exception.
ipv6 :: HasCallStack => CBytes -> PortNumber -> SocketAddr Source #
Convert a string containing an IPv6 addresses to a binary structure
This is partial function, wrong address will throw InvalidArgument exception.
sockAddrFamily :: SocketAddr -> SocketFamily Source #
Show an IPv6 address in the most appropriate notation, based on recommended representation proposed by RFC 5952.
/The implementation is completely compatible with the current implementation
of the inet_ntop function in glibc./
withSocketAddr :: SocketAddr -> (Ptr SocketAddr -> IO a) -> IO a Source #
Pass SocketAddr to FFI as pointer.
withSocketAddrUnsafe :: SocketAddr -> (MBA# SocketAddr -> IO a) -> IO a Source #
Pass SocketAddr to FFI as pointer.
USE THIS FUNCTION WITH UNSAFE FFI CALL ONLY.
sizeOfSocketAddr :: SocketAddr -> CSize Source #
withSocketAddrStorage :: (Ptr SocketAddr -> IO ()) -> IO SocketAddr Source #
Allocate space for sockaddr_storage and pass to FFI.
withSocketAddrStorageUnsafe :: (MBA# SocketAddr -> IO ()) -> IO SocketAddr Source #
Allocate space for sockaddr_storage and pass to FFI.
USE THIS FUNCTION WITH UNSAFE FFI CALL ONLY.
IPv4 address
Independent of endianness. For example 127.0.0.1 is stored as (127, 0, 0, 1).
For direct manipulation prefer inetAddrToTuple and tupleToInetAddr.
Constructors
| InetAddr | |
Fields | |
Instances
| Eq InetAddr Source # | |
| Ord InetAddr Source # | |
Defined in Z.IO.Network.SocketAddr | |
| Show InetAddr Source # | |
| Storable InetAddr Source # | |
Defined in Z.IO.Network.SocketAddr | |
| UnalignedAccess InetAddr Source # | |
Defined in Z.IO.Network.SocketAddr Methods unalignedSize :: UnalignedSize InetAddr indexWord8ArrayAs# :: ByteArray# -> Int# -> InetAddr readWord8ArrayAs# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, InetAddr #) writeWord8ArrayAs# :: MutableByteArray# s -> Int# -> InetAddr -> State# s -> State# s peekMBA :: MutableByteArray# RealWorld -> Int -> IO InetAddr pokeMBA :: MutableByteArray# RealWorld -> Int -> InetAddr -> IO () indexBA :: ByteArray# -> Int -> InetAddr | |
inetBroadcast :: InetAddr Source #
255.255.255.255
inetLoopback :: InetAddr Source #
127.0.0.1
inetUnspecificGroup :: InetAddr Source #
224.0.0.0
inetAllHostsGroup :: InetAddr Source #
224.0.0.1
inetMaxLocalGroup :: InetAddr Source #
224.0.0.255
inetAddrToTuple :: InetAddr -> (Word8, Word8, Word8, Word8) Source #
Converts InetAddr to representation-independent IPv4 quadruple.
For example for 127.0.0.1 the function will return (127, 0, 0, 1)
regardless of host endianness.
tupleToInetAddr :: (Word8, Word8, Word8, Word8) -> InetAddr Source #
Converts IPv4 quadruple to InetAddr.
IPv6 address
Independent of endianness. For example ::1 is stored as (0, 0, 0, 1).
For direct manipulation prefer inet6AddrToTuple and tupleToInet6Addr.
Instances
| Eq Inet6Addr Source # | |
| Ord Inet6Addr Source # | |
| Show Inet6Addr Source # | |
| Storable Inet6Addr Source # | |
Defined in Z.IO.Network.SocketAddr | |
| UnalignedAccess Inet6Addr Source # | |
Defined in Z.IO.Network.SocketAddr Methods unalignedSize :: UnalignedSize Inet6Addr indexWord8ArrayAs# :: ByteArray# -> Int# -> Inet6Addr readWord8ArrayAs# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Inet6Addr #) writeWord8ArrayAs# :: MutableByteArray# s -> Int# -> Inet6Addr -> State# s -> State# s peekMBA :: MutableByteArray# RealWorld -> Int -> IO Inet6Addr pokeMBA :: MutableByteArray# RealWorld -> Int -> Inet6Addr -> IO () indexBA :: ByteArray# -> Int -> Inet6Addr | |
inet6Loopback :: Inet6Addr Source #
::1
inet6AddrToTuple :: Inet6Addr -> (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16) Source #
convert Inet6Addr to octets.
tupleToInet6Addr :: (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16) -> Inet6Addr Source #
convert Inet6Addr from octets.
port numbber
newtype PortNumber Source #
Port number.
Use the Num instance (i.e. use a literal) to create a
PortNumber value.
>>>1 :: PortNumber1>>>read "1" :: PortNumber1>>>show (12345 :: PortNumber)"12345">>>50000 < (51000 :: PortNumber)True>>>50000 < (52000 :: PortNumber)True>>>50000 + (10000 :: PortNumber)60000
Constructors
| PortNumber Word16 |
Instances
portAny :: PortNumber Source #
:0
family, type, protocol
newtype SocketFamily Source #
Constructors
| SocketFamily CInt |
Instances
pattern AF_UNSPEC :: SocketFamily Source #
unspecified
pattern AF_INET :: SocketFamily Source #
internetwork: UDP, TCP, etc
pattern AF_INET6 :: SocketFamily Source #
Internet Protocol version 6
newtype SocketType Source #
Constructors
| SocketType CInt |
Instances
pattern SOCK_DGRAM :: SocketType Source #
pattern SOCK_STREAM :: SocketType Source #
pattern SOCK_SEQPACKET :: SocketType Source #
pattern SOCK_RAW :: SocketType Source #
pattern SOCK_RDM :: SocketType Source #
pattern SOCK_ANY :: SocketType Source #
Used in getAddrInfo hints, for any type can be returned by getAddrInfo
newtype ProtocolNumber Source #
Constructors
| ProtocolNumber CInt |
Instances
pattern IPPROTO_DEFAULT :: ProtocolNumber Source #
pattern IPPROTO_IP :: ProtocolNumber Source #
pattern IPPROTO_TCP :: ProtocolNumber Source #
pattern IPPROTO_UDP :: ProtocolNumber Source #
Internal helper
peekSocketAddr :: HasCallStack => Ptr SocketAddr -> IO SocketAddr Source #
pokeSocketAddr :: Ptr SocketAddr -> SocketAddr -> IO () Source #
peekSocketAddrMBA :: HasCallStack => MBA# SocketAddr -> IO SocketAddr Source #
pokeSocketAddrMBA :: MBA# SocketAddr -> SocketAddr -> IO () Source #