instance Show SockAddr
Peter Simons
simons at cryp.to
Mon Oct 18 06:54:35 EDT 2004
Simon Marlow writes:
> If someone has code for a version that works on both
> endians [...]
import Foreign
import Network.Socket
data Endian = LittleEndian | BigEndian | PDPEndian
deriving (Show, Eq)
getEndian :: Endian
getEndian =
unsafePerformIO $
allocaArray (sizeOf (undefined :: Word32)) $ \p -> do
let val = 0x01020304 :: Word32
poke p val
let p' = castPtr p :: Ptr Word8
val' <- peekArray 4 p'
case val' of
(0x01:0x02:0x03:0x04:[]) -> return BigEndian
(0x04:0x03:0x02:0x01:[]) -> return LittleEndian
(0x02:0x01:0x03:0x04:[]) -> return PDPEndian
_ -> error "unknown endian"
instance Show SockAddr where
show (SockAddrUnix str) = str
show (SockAddrInet port ha) =
shows b1 . ('.':) .
shows b2 . ('.':) .
shows b3 . ('.':) .
shows b4 . (':':) $ show port
where
(b1,b2,b3,b4) = ha2tpl ha
ha2tpl :: HostAddress -> (Int, Int, Int, Int)
ha2tpl n =
let (b1,n1) = (n .&. 255, n `shiftR` 8)
(b2,n2) = (n1 .&. 255, n1 `shiftR` 8)
(b3,n3) = (n2 .&. 255, n2 `shiftR` 8)
b4 = n3 .&. 255
in
case getEndian of
BigEndian -> (fromEnum b4, fromEnum b3, fromEnum b2, fromEnum b1)
LittleEndian -> (fromEnum b1, fromEnum b2, fromEnum b3, fromEnum b4)
PDPEndian -> (fromEnum b4, fromEnum b3, fromEnum b1, fromEnum b2)
More information about the Libraries
mailing list