5.3. SocketPrim: The low-level socket binding

The SocketPrim module is for when you want full control over the sockets, exposing the C socket API. Your best bet for documentation is to look at the code—really!— normally in fptools/hslibs/net/SocketPrim.lhs.
data Socket             -- instance of: Eq, Show

-- your mileage may vary depending on the OS you use...
data Family = instance of: Eq, Ord, Ix, Show
     AF_802             -- IEEE 802.2, also ISO 8802
   | AF_APPLETALK       -- Apple Talk
   | AF_ARP             -- (rev.) addr. res. prot. (RFC 826)
   | AF_AX25
   | AF_CCITT           -- CCITT protocols, X.25 etc
   | AF_CHAOS           -- mit CHAOS protocols
   | AF_CNT             -- Computer Network Technology
   | AF_COIP            -- connection-oriented IP, aka ST II
   | AF_CTF             -- Common Trace Facility
   | AF_DATAKIT         -- datakit protocols
   | AF_DECnet          -- DECnet
   | AF_DLI             -- DEC Direct data link interface
   | AF_ECMA            -- european computer manufacturers
   | AF_GOSSIP          -- US Government OSI
   | AF_HYLINK          -- NSC Hyperchannel
   | AF_IMPLINK         -- arpanet imp addresses
   | AF_INET            -- internetwork: UDP, TCP, etc
   | AF_INET6           -- IPv6
   | AF_INTF            -- Debugging use only
   | AF_IPX             -- Novell Internet Protocol
   | AF_ISDN            -- Integrated Services Digital Network
   | AF_ISO             -- ISO protocols
   | AF_LAT             -- LAT
   | AF_LINK            -- Link layer interface
   | AF_MAX
   | AF_NATM            -- native ATM access
   | AF_NBS             -- nbs protocols
   | AF_NDD
   | AF_NETBIOS         -- NetBios-style addresses
   | AF_NETMAN          -- DNA Network Management
   | AF_NETWARE
   | AF_NIT             -- Network Interface Tap
   | AF_NS              -- XEROX NS protocols
   | AF_OSI             -- OSI protocols
   | AF_OSINET          -- AFI
   | AF_PUP             -- pup protocols: e.g. BSP
   | AF_RAW             -- Link layer interface
   | AF_RIF             -- raw interface
   | AF_ROUTE           -- Internal Routing Protocol
   | AF_SIP             -- Simple Internet Protocol
   | AF_SNA             -- IBM SNA
   | AF_UNIX            -- local to host (pipes, portals
   | AF_UNSPEC          -- unspecified
   | AF_WAN             -- Wide Area Network protocols
   | AF_X25             -- CCITT X.25
   | Pseudo_AF_HDRCMPLT -- Used by BPF to not rewrite hdrs in iface output
   | Pseudo_AF_KEY      -- Internal key-management function
   | Pseudo_AF_PIP      -- Help Identify PIP packets
   | Pseudo_AF_RTIP     -- Help Identify RTIP packets
   | Pseudo_AF_XTP      -- eXpress Transfer Protocol (no AF)

data Socket
  = MkSocket Int        -- File Descriptor
             Family
             SocketType
             Int        -- Protocol Number
             (IORef SocketStatus) -- Status Flag

data SockAddr
  = SockAddrUnix String -- not available con Cygwin/Mingw
  | SockAddrInet PortNumber HostAddress

type HostAddress = Word

data ShutdownCmd = ShutdownReceive | ShutdownSend | ShutdownBoth

type ProtocolNumber = Int

socket          :: Family -> SocketType -> ProtocolNumber -> IO Socket 
connect         :: Socket -> SockAddr -> IO ()
bindSocket      :: Socket -> SockAddr -> IO ()
listen          :: Socket -> Int -> IO ()
accept          :: Socket -> IO (Socket, SockAddr)
getPeerName     :: Socket -> IO SockAddr
getSocketName   :: Socket -> IO SockAddr

socketPort      :: Socket -> IO PortNumber

writeSocket     :: Socket -> String -> IO Int
readSocket      :: Socket -> Int -> IO (String, Int)
readSocketAll   :: Socket -> IO String

socketToHandle  :: Socket -> IO Handle

sendTo          :: Socket -> String -> SockAddr -> IO Int
recvFrom        :: Socket -> Int -> IO (String, Int, SockAddr)

inet_addr       :: String -> IO HostAddress
inet_ntoa       :: HostAddress -> IO String

sIsConnected    :: Socket -> IO Bool
sIsBound        :: Socket -> IO Bool
sIsListening    :: Socket -> IO Bool 
sIsReadable     :: Socket -> IO Bool
sIsWritable     :: Socket -> IO Bool
shutdown        :: Socket -> ShutdownCmd -> IO ()
sClose          :: Socket -> IO ()

data SocketOption =
      Debug          -- SO_DEBUG
    | ReuseAddr      -- SO_REUSEADDR
    | Type           -- SO_TYPE
    | SoError        -- SO_ERROR
    | DontRoute      -- SO_DONTROUTE
    | Broadcast      -- SO_BROADCAST
    | SendBuffer     -- SO_SNDBUF
    | RecvBuffer     -- SO_RCVBUF
    | KeepAlive      -- SO_KEEPALIVE
    | OOBInline      -- SO_OOBINLINE
    | MaxSegment     -- TCP_MAXSEG, not available con Cygwin/Mingw
    | NoDelay        -- TCP_NODELAY

getSocketOption :: Socket -> SocketOption -> IO Int
setSocketOption :: Socket -> SocketOption -> Int -> IO ()

newtype PortNumber = -- instance of Eq, Ord, Enum, Num, Real, Integral, Show
   PNum Int          -- 16-bit value stored in network byte order.

mkPortNumber    :: Int -> PortNumber
                  
aNY_PORT        :: PortNumber
iNADDR_ANY      :: HostAddress
sOMAXCONN       :: Int
maxListenQueue  :: Int