{-# LINE1"Network/Socket/Info.hsc"#-}{-# LANGUAGE CPP #-}{-# LANGUAGE DeriveDataTypeable #-}{-# LANGUAGE RecordWildCards #-}{-# OPTIONS_GHC -fno-warn-orphans #-}#include "HsNetDef.h"
moduleNetwork.Socket.InfowhereimportForeign.Marshal.Alloc(alloca,allocaBytes)importForeign.Marshal.Utils(maybeWith,with)importGHC.IO(unsafePerformIO)importGHC.IO.Exception(IOErrorType(NoSuchThing))importSystem.IO.Error(ioeSetErrorString,mkIOError)importNetwork.Socket.Imports importNetwork.Socket.Internal importNetwork.Socket.Types ------------------------------------------------------------------------------- | Either a host name e.g., @\"haskell.org\"@ or a numeric host-- address string consisting of a dotted decimal IPv4 address or an-- IPv6 address e.g., @\"192.168.0.1\"@.typeHostName =String-- | Either a service name e.g., @\"http\"@ or a numeric port number.typeServiceName =String------------------------------------------------------------------------------- Address and service lookups-- | Flags that control the querying behaviour of 'getAddrInfo'.-- For more information, see <https://tools.ietf.org/html/rfc3493#page-25>dataAddrInfoFlag =-- | The list of returned 'AddrInfo' values will-- only contain IPv4 addresses if the local system has at least-- one IPv4 interface configured, and likewise for IPv6.-- (Only some platforms support this.)AI_ADDRCONFIG -- | If 'AI_ALL' is specified, return all matching IPv6 and-- IPv4 addresses. Otherwise, this flag has no effect.-- (Only some platforms support this.)|AI_ALL -- | The 'addrCanonName' field of the first returned-- 'AddrInfo' will contain the "canonical name" of the host.|AI_CANONNAME -- | The 'HostName' argument /must/ be a numeric-- address in string form, and network name lookups will not be-- attempted.|AI_NUMERICHOST -- | The 'ServiceName' argument /must/ be a port-- number in string form, and service name lookups will not be-- attempted. (Only some platforms support this.)|AI_NUMERICSERV -- | If no 'HostName' value is provided, the network-- address in each 'SockAddr'-- will be left as a "wild card".-- This is useful for server applications that-- will accept connections from any client.|AI_PASSIVE -- | If an IPv6 lookup is performed, and no IPv6-- addresses are found, IPv6-mapped IPv4 addresses will be-- returned. (Only some platforms support this.)|AI_V4MAPPED deriving(Eq,Read,Show,Typeable)aiFlagMapping::[(AddrInfoFlag ,CInt)]aiFlagMapping =[{-# LINE73"Network/Socket/Info.hsc"#-}(AI_ADDRCONFIG,32),{-# LINE74"Network/Socket/Info.hsc"#-}{-# LINE77"Network/Socket/Info.hsc"#-}{-# LINE78"Network/Socket/Info.hsc"#-}(AI_ALL,16),{-# LINE79"Network/Socket/Info.hsc"#-}{-# LINE82"Network/Socket/Info.hsc"#-}(AI_CANONNAME,2),{-# LINE83"Network/Socket/Info.hsc"#-}(AI_NUMERICHOST,4),{-# LINE84"Network/Socket/Info.hsc"#-}{-# LINE85"Network/Socket/Info.hsc"#-}(AI_NUMERICSERV,1024),{-# LINE86"Network/Socket/Info.hsc"#-}{-# LINE89"Network/Socket/Info.hsc"#-}(AI_PASSIVE,1),{-# LINE90"Network/Socket/Info.hsc"#-}{-# LINE91"Network/Socket/Info.hsc"#-}(AI_V4MAPPED,8){-# LINE92"Network/Socket/Info.hsc"#-}{-# LINE95"Network/Socket/Info.hsc"#-}]-- | Indicate whether the given 'AddrInfoFlag' will have any effect on-- this system.addrInfoFlagImplemented::AddrInfoFlag->BooladdrInfoFlagImplementedf=packBitsaiFlagMapping[f]/=0dataAddrInfo=AddrInfo{addrFlags::[AddrInfoFlag],addrFamily::Family,addrSocketType::SocketType,addrProtocol::ProtocolNumber,addrAddress::SockAddr,addrCanonName::MaybeString}deriving(Eq,Show,Typeable)instanceStorableAddrInfowheresizeOf_=48{-# LINE113"Network/Socket/Info.hsc"#-}alignment_=alignment(undefined::CInt)peekp=doai_flags<-((\hsc_ptr->peekByteOffhsc_ptr0))p{-# LINE117"Network/Socket/Info.hsc"#-}ai_family<-((\hsc_ptr->peekByteOffhsc_ptr4))p{-# LINE118"Network/Socket/Info.hsc"#-}ai_socktype<-((\hsc_ptr->peekByteOffhsc_ptr8))p{-# LINE119"Network/Socket/Info.hsc"#-}ai_protocol<-((\hsc_ptr->peekByteOffhsc_ptr12))p{-# LINE120"Network/Socket/Info.hsc"#-}ai_addr<-((\hsc_ptr->peekByteOffhsc_ptr24))p>>=peekSockAddr{-# LINE121"Network/Socket/Info.hsc"#-}ai_canonname_ptr<-((\hsc_ptr->peekByteOffhsc_ptr32))p{-# LINE122"Network/Socket/Info.hsc"#-}ai_canonname<-ifai_canonname_ptr==nullPtrthenreturnNothingelseJust<$>peekCStringai_canonname_ptrsocktype<-unpackSocketType'"AddrInfo.peek"ai_socktypereturn$AddrInfo{addrFlags=unpackBitsaiFlagMappingai_flags,addrFamily=unpackFamilyai_family,addrSocketType=socktype,addrProtocol=ai_protocol,addrAddress=ai_addr,addrCanonName=ai_canonname}pokep(AddrInfoflagsfamilysockTypeprotocol__)=doc_stype<-packSocketTypeOrThrow"AddrInfo.poke"sockType((\hsc_ptr->pokeByteOffhsc_ptr0))p(packBitsaiFlagMappingflags){-# LINE141"Network/Socket/Info.hsc"#-}((\hsc_ptr->pokeByteOffhsc_ptr4))p(packFamilyfamily){-# LINE142"Network/Socket/Info.hsc"#-}((\hsc_ptr->pokeByteOffhsc_ptr8))pc_stype{-# LINE143"Network/Socket/Info.hsc"#-}((\hsc_ptr->pokeByteOffhsc_ptr12))pprotocol{-# LINE144"Network/Socket/Info.hsc"#-}-- stuff below is probably not needed, but let's zero it for safety((\hsc_ptr->pokeByteOffhsc_ptr16))p(0::CSize){-# LINE148"Network/Socket/Info.hsc"#-}((\hsc_ptr->pokeByteOffhsc_ptr24))pnullPtr{-# LINE149"Network/Socket/Info.hsc"#-}((\hsc_ptr->pokeByteOffhsc_ptr32))pnullPtr{-# LINE150"Network/Socket/Info.hsc"#-}((\hsc_ptr->pokeByteOffhsc_ptr40))pnullPtr{-# LINE151"Network/Socket/Info.hsc"#-}-- | Flags that control the querying behaviour of 'getNameInfo'.-- For more information, see <https://tools.ietf.org/html/rfc3493#page-30>dataNameInfoFlag=-- | Resolve a datagram-based service name. This is-- required only for the few protocols that have different port-- numbers for their datagram-based versions than for their-- stream-based versions.NI_DGRAM-- | If the hostname cannot be looked up, an IO error is thrown.|NI_NAMEREQD-- | If a host is local, return only the hostname part of the FQDN.|NI_NOFQDN-- | The name of the host is not looked up.-- Instead, a numeric representation of the host's-- address is returned. For an IPv4 address, this will be a-- dotted-quad string. For IPv6, it will be colon-separated-- hexadecimal.|NI_NUMERICHOST-- | The name of the service is not-- looked up. Instead, a numeric representation of the-- service is returned.|NI_NUMERICSERVderiving(Eq,Read,Show,Typeable)niFlagMapping::[(NameInfoFlag,CInt)]niFlagMapping=[(NI_DGRAM,16),{-# LINE179"Network/Socket/Info.hsc"#-}(NI_NAMEREQD,8),{-# LINE180"Network/Socket/Info.hsc"#-}(NI_NOFQDN,4),{-# LINE181"Network/Socket/Info.hsc"#-}(NI_NUMERICHOST,1),{-# LINE182"Network/Socket/Info.hsc"#-}(NI_NUMERICSERV,2)]{-# LINE183"Network/Socket/Info.hsc"#-}-- | Default hints for address lookup with 'getAddrInfo'. The values-- of the 'addrAddress' and 'addrCanonName' fields are 'undefined',-- and are never inspected by 'getAddrInfo'.---- >>> addrFlags defaultHints-- []-- >>> addrFamily defaultHints-- AF_UNSPEC-- >>> addrSocketType defaultHints-- NoSocketType-- >>> addrProtocol defaultHints-- 0defaultHints::AddrInfodefaultHints=AddrInfo{addrFlags=[],addrFamily=AF_UNSPEC,addrSocketType=NoSocketType,addrProtocol=defaultProtocol,addrAddress=undefined,addrCanonName=undefined}-- | Shows the fields of 'defaultHints', without inspecting the by-default undefined fields 'addrAddress' and 'addrCanonName'.showDefaultHints::AddrInfo->StringshowDefaultHintsAddrInfo{..}=concat["AddrInfo {","addrFlags = ",showaddrFlags,", addrFamily = ",showaddrFamily,", addrSocketType = ",showaddrSocketType,", addrProtocol = ",showaddrProtocol,", addrAddress = ","<assumed to be undefined>",", addrCanonName = ","<assumed to be undefined>","}"]------------------------------------------------------------------------------- | Resolve a host or service name to one or more addresses.-- The 'AddrInfo' values that this function returns contain 'SockAddr'-- values that you can pass directly to 'connect' or-- 'bind'.---- This function is protocol independent. It can return both IPv4 and-- IPv6 address information.---- The 'AddrInfo' argument specifies the preferred query behaviour,-- socket options, or protocol. You can override these conveniently-- using Haskell's record update syntax on 'defaultHints', for example-- as follows:---- >>> let hints = defaultHints { addrFlags = [AI_NUMERICHOST], addrSocketType = Stream }---- You must provide a 'Just' value for at least one of the 'HostName'-- or 'ServiceName' arguments. 'HostName' can be either a numeric-- network address (dotted quad for IPv4, colon-separated hex for-- IPv6) or a hostname. In the latter case, its addresses will be-- looked up unless 'AI_NUMERICHOST' is specified as a hint. If you-- do not provide a 'HostName' value /and/ do not set 'AI_PASSIVE' as-- a hint, network addresses in the result will contain the address of-- the loopback interface.---- If the query fails, this function throws an IO exception instead of-- returning an empty list. Otherwise, it returns a non-empty list-- of 'AddrInfo' values.---- There are several reasons why a query might result in several-- values. For example, the queried-for host could be multihomed, or-- the service might be available via several protocols.---- Note: the order of arguments is slightly different to that defined-- for @getaddrinfo@ in RFC 2553. The 'AddrInfo' parameter comes first-- to make partial application easier.---- >>> addr:_ <- getAddrInfo (Just hints) (Just "127.0.0.1") (Just "http")-- >>> addrAddress addr-- 127.0.0.1:80getAddrInfo::MaybeAddrInfo-- ^ preferred socket type or protocol->MaybeHostName-- ^ host name to look up->MaybeServiceName-- ^ service name to look up->IO[AddrInfo]-- ^ resolved addresses, with "best" firstgetAddrInfohintsnodeservice=allocgetaddrinfowhereallocbody=withSocketsDo$maybeWithwithCStringnode$\c_node->maybeWithwithCStringservice$\c_service->maybeWithwithfilteredHints$\c_hints->alloca$\ptr_ptr_addrs->bodyc_nodec_servicec_hintsptr_ptr_addrsgetaddrinfoc_nodec_servicec_hintsptr_ptr_addrs=doret<-c_getaddrinfoc_nodec_servicec_hintsptr_ptr_addrsifret==0thendoptr_addrs<-peekptr_ptr_addrsais<-followAddrInfoptr_addrsc_freeaddrinfoptr_addrsreturnaiselsedoerr<-gai_strerrorretioError$ioeSetErrorString(mkIOErrorNoSuchThingmessageNothingNothing)errmessage=concat["Network.Socket.getAddrInfo (called with preferred socket type/protocol: ",maybe(showhints)showDefaultHintshints,", host name: ",shownode,", service name: ",showservice,")"]{-# LINE309"Network/Socket/Info.hsc"#-}filteredHints=hints{-# LINE311"Network/Socket/Info.hsc"#-}followAddrInfo::PtrAddrInfo->IO[AddrInfo]followAddrInfoptr_ai|ptr_ai==nullPtr=return[]|otherwise=doa<-peekptr_aias<-((\hsc_ptr->peekByteOffhsc_ptr40))ptr_ai>>=followAddrInfo{-# LINE318"Network/Socket/Info.hsc"#-}return(a:as)foreignimportccallsafe"hsnet_getaddrinfo"c_getaddrinfo::CString->CString->PtrAddrInfo->Ptr(PtrAddrInfo)->IOCIntforeignimportccallsafe"hsnet_freeaddrinfo"c_freeaddrinfo::PtrAddrInfo->IO()gai_strerror::CInt->IOString{-# LINE330"Network/Socket/Info.hsc"#-}gai_strerrorn=c_gai_strerrorn>>=peekCStringforeignimportccallsafe"gai_strerror"c_gai_strerror::CInt->IOCString{-# LINE337"Network/Socket/Info.hsc"#-}-----------------------------------------------------------------------------withCStringIf::Bool->Int->(CSize->CString->IOa)->IOawithCStringIfFalse_f=f0nullPtrwithCStringIfTruenf=allocaBytesn(f(fromIntegraln))-- | Resolve an address to a host or service name.-- This function is protocol independent.-- The list of 'NameInfoFlag' values controls query behaviour.---- If a host or service's name cannot be looked up, then the numeric-- form of the address or service will be returned.---- If the query fails, this function throws an IO exception.---- >>> addr:_ <- getAddrInfo (Just defaultHints) (Just "127.0.0.1") (Just "http")-- >>> getNameInfo [NI_NUMERICHOST, NI_NUMERICSERV] True True $ addrAddress addr-- (Just "127.0.0.1",Just "80"){-
-- >>> getNameInfo [] True True $ addrAddress addr
-- (Just "localhost",Just "http")
-}getNameInfo::[NameInfoFlag]-- ^ flags to control lookup behaviour->Bool-- ^ whether to look up a hostname->Bool-- ^ whether to look up a service name->SockAddr-- ^ the address to look up->IO(MaybeHostName,MaybeServiceName)getNameInfoflagsdoHostdoServiceaddr=allocgetnameinfowhereallocbody=withSocketsDo$withCStringIfdoHost(1025)$\c_hostlenc_host->{-# LINE370"Network/Socket/Info.hsc"#-}withCStringIfdoService(32)$\c_servlenc_serv->{-# LINE371"Network/Socket/Info.hsc"#-}withSockAddraddr$\ptr_addrsz->bodyc_hostlenc_hostc_servlenc_servptr_addrszgetnameinfoc_hostlenc_hostc_servlenc_servptr_addrsz=doret<-c_getnameinfoptr_addr(fromIntegralsz)c_hostc_hostlenc_servc_servlen(packBitsniFlagMappingflags)ifret==0thendoletpeekIfdoIfc_val=ifdoIfthenJust<$>peekCStringc_valelsereturnNothinghost<-peekIfdoHostc_hostserv<-peekIfdoServicec_servreturn(host,serv)elsedoerr<-gai_strerrorretioError$ioeSetErrorString(mkIOErrorNoSuchThingmessageNothingNothing)errmessage=concat["Network.Socket.getNameInfo (called with flags: ",showflags,", hostname lookup: ",showdoHost,", service name lookup: ",showdoService,", socket address: ",showaddr,")"]foreignimportccallsafe"hsnet_getnameinfo"c_getnameinfo::PtrSockAddr->CInt{-CSockLen???-}->CString->CSize->CString->CSize->CInt->IOCInt-- | Pack a list of values into a bitmask. The possible mappings from-- value to bit-to-set are given as the first argument. We assume-- that each value can cause exactly one bit to be set; unpackBits will-- break if this property is not true.-----------------------------------------------------------------------------packBits::(Eqa,Numb,Bitsb)=>[(a,b)]->[a]->bpackBitsmappingxs=foldl'pack0mappingwherepackacc(k,v)|k`elem`xs=acc.|.v|otherwise=acc-- | Unpack a bitmask into a list of values.unpackBits::(Numb,Bitsb)=>[(a,b)]->b->[a]-- Be permissive and ignore unknown bit values. At least on OS X,-- getaddrinfo returns an ai_flags field with bits set that have no-- entry in <netdb.h>.unpackBits[]_=[]unpackBits((k,v):xs)r|r.&.v/=0=k:unpackBitsxs(r.&.complementv)|otherwise=unpackBitsxsr------------------------------------------------------------------------------- SockAddrinstanceShowSockAddrwhere{-# LINE436"Network/Socket/Info.hsc"#-}showsPrec_(SockAddrUnixstr)=showStringstr{-# LINE440"Network/Socket/Info.hsc"#-}showsPrec_addr@(SockAddrInetport_)=showString(unsafePerformIO$fst<$>getNameInfo[NI_NUMERICHOST]TrueFalseaddr>>=maybe(fail"showsPrec: impossible internal error")return).showString":".showsportshowsPrec_addr@(SockAddrInet6port___)=showChar'['.showString(unsafePerformIO$fst<$>getNameInfo[NI_NUMERICHOST]TrueFalseaddr>>=maybe(fail"showsPrec: impossible internal error")return).showString"]:".showsport

AltStyle によって変換されたページ (->オリジナル) /