Proposal [Trac #1212]: add IPv6 support to network library
Bryan O'Sullivan
bos at serpentine.com
Mon Apr 2 13:12:48 EDT 2007
Sven Panne wrote:
> * You use an internal class HostAddr and make two type synonyms an instance
> of it.
You must have downloaded the first version of the patch that I posted a
few weeks ago. The updated version doesn't have this rather unpleasant
wart. Unfortunately, Trac won't let me drop old versions of a patch.
> * The types and values of AddrInfoFlags/NameInfoFlags are not very
> Haskell-like. Using
>
> data AddrInfoFlag = Passive | CanonName | NumericHost | ...
>
> and [AddrInfoFlag] instead of AddrInfoFlags is much nicer.
OK, I'll update the interface to look like this. It would be nice if
there were helper functions in Foreign.Marshal.Utils or Data.Bits to
make this a more mindless operation:
import Data.Bits
import Data.List (foldl')
packBits :: (Eq a, Bits b) => [(a, b)] -> [a] -> b
packBits mapping xs = foldl' pack 0 mapping
where pack acc (k, v) | k `elem` xs = acc .|. v
| otherwise = acc
unpackBits :: Bits b => [(a, b)] -> b -> [a]
unpackBits mapping bits = foldl' unpack [] mapping
where unpack acc (k, v) | bits .&. v == 0 = acc
| otherwise = k:acc
It's simple boilerplate, but nice not to need to write. This would make
the conversion process very tidy:
aiMapping = [(AI_PASSIVE, #const AI_PASSIVE),
(AI_CANONNAME, #const AI_CANONNAME),
...and so on...]
packAIFlags = packBits aiMapping
unpackAIFlags = unpackBits aiMapping
Assuming people like the interface, should I submit this as a separate
proposal, or just fold it into Network.Socket?
> Alas, the X11 package is not nice regarding the last item, either... :-(
True. But there's an SoC proposal to add XCB bindings, which could
presumably use this bit-swizzling code :-)
<b
More information about the Libraries
mailing list