[Haskell-cafe] Happstack + network package issue on the Mac
Gregory Collins
greg at gregorycollins.net
Fri Oct 9 16:17:48 EDT 2009
"Bryan O'Sullivan" <bos at serpentine.com> writes:
> On Fri, Oct 9, 2009 at 7:25 AM, Gregory Collins <greg at gregorycollins.net> wrote:
>
>
> There's been an open ticket for months; personally I think this is
> a job for the C preprocessor, but nobody's written a patch yet.
>
> Is there an open ticket against the network package? Can someone write
> a simple standalone repro for me that doesn't require happstack
> (i.e. only depends on network)? I have access to a Mac and Johan and I
> co-maintain the network package, so in principle this shouldn't be
> hard to fix, given enough details and pointers.
No, against Happstack. The offending code:
------------------------------------------------------------------------------
-- find out at compile time if the SockAddr6 / HostAddress6
-- constructors are available
supportsIPv6 :: Bool
supportsIPv6 = $(let c = "Network.Socket.SockAddrInet6"; d = ''SockAddr in
do TyConI (DataD _ _ _ cs _) <- reify d
if isJust (find (\(NormalC n _) -> show n == c) cs)
then [| True |]
else [| False |] )
...
-- | alternative implementation of accept to work around EAI_AGAIN errors
acceptLite :: S.Socket -> IO (Handle, S.HostName, S.PortNumber)
acceptLite sock = do
(sock', addr) <- S.accept sock
h <- S.socketToHandle sock' ReadWriteMode
(N.PortNumber p) <- N.socketPort sock'
let peer = $(if supportsIPv6
then
return $ CaseE (VarE (mkName "addr"))
[Match
(ConP (mkName "S.SockAddrInet")
[WildP,VarP (mkName "ha")])
(NormalB (AppE (VarE (mkName "showHostAddress"))
(VarE (mkName "ha")))) []
,Match (ConP (mkName "S.SockAddrInet6") [WildP,WildP,VarP (mkName "ha"),WildP])
(NormalB (AppE (VarE (mkName "showHostAddress6")) (VarE (mkName "ha")))) []
,Match WildP (NormalB (AppE (VarE (mkName "error")) (LitE (StringL "Unsupported socket")))) []]
-- the above mess is the equivalent of this:
{-[| case addr of
(S.SockAddrInet _ ha) -> showHostAddress ha
(S.SockAddrInet6 _ _ ha _) -> showHostAddress6 ha
_ -> error "Unsupported socket"
|]-}
else
[| case addr of
(S.SockAddrInet _ ha) -> showHostAddress ha
_ -> error "Unsupported socket"
|])
return (h, peer, p)
------------------------------------------------------------------------------
Frankly I think this approach is dubious at best.
G
--
Gregory Collins <greg at gregorycollins.net>
More information about the Haskell-Cafe
mailing list