{-# OPTIONS_GHC -Wno-missing-pattern-synonym-signatures #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE TemplateHaskell #-}
module Netw.Inet where
import Netw.Internal.Type
import Netw.Internal.Port
import Data.Bits
import Data.Primitive.ByteArray.Unaligned
import Numeric
import GHC.Exts
import GHC.ByteOrder
import GHC.Word
hton16# :: Word16# -> Word16#
hton32# :: Word32# -> Word32#
hton64# :: Word64# -> Word64#
hton16# :: Word16# -> Word16#
hton16# = $(case targetByteOrder of LittleEndian -> [| \ w# -> wordToWord16# (byteSwap16# (word16ToWord# w#)) |]; BigEndian -> [| \ w# -> w# |])
hton32# :: Word32# -> Word32#
hton32# = $(case targetByteOrder of LittleEndian -> [| \ w# -> wordToWord32# (byteSwap32# (word32ToWord# w#)) |]; BigEndian -> [| \ w# -> w# |])
hton64# :: Word64# -> Word64#
hton64# = $(case targetByteOrder of LittleEndian -> [| byteSwap64# |]; BigEndian -> [| \ w# -> w# |])
hton16 :: Word16 -> Word16
hton16 :: Word16 -> Word16
hton16 (W16# Word16#
w) = Word16# -> Word16
W16# (Word16# -> Word16#
hton16# Word16#
w)
hton32 :: Word32 -> Word32
hton32 :: Word32 -> Word32
hton32 (W32# Word32#
w) = Word32# -> Word32
W32# (Word32# -> Word32#
hton32# Word32#
w)
hton64 :: Word64 -> Word64
hton64 :: Word64 -> Word64
hton64 (W64# Word64#
w) = Word64# -> Word64
W64# (Word64# -> Word64#
hton64# Word64#
w)
ntoh16# :: Word16# -> Word16#
ntoh32# :: Word32# -> Word32#
ntoh64# :: Word64# -> Word64#
ntoh16# :: Word16# -> Word16#
ntoh16# = $(case targetByteOrder of LittleEndian -> [| \ w# -> wordToWord16# (byteSwap16# (word16ToWord# w#)) |]; BigEndian -> [| \ w# -> w# |])
ntoh32# :: Word32# -> Word32#
ntoh32# = $(case targetByteOrder of LittleEndian -> [| \ w# -> wordToWord32# (byteSwap32# (word32ToWord# w#)) |]; BigEndian -> [| \ w# -> w# |])
ntoh64# :: Word64# -> Word64#
ntoh64# = $(case targetByteOrder of LittleEndian -> [| byteSwap64# |]; BigEndian -> [| \ w# -> w# |])
ntoh16 :: Word16 -> Word16
ntoh16 :: Word16 -> Word16
ntoh16 (W16# Word16#
w) = Word16# -> Word16
W16# (Word16# -> Word16#
ntoh16# Word16#
w)
ntoh32 :: Word32 -> Word32
ntoh32 :: Word32 -> Word32
ntoh32 (W32# Word32#
w) = Word32# -> Word32
W32# (Word32# -> Word32#
ntoh32# Word32#
w)
ntoh64 :: Word64 -> Word64
ntoh64 :: Word64 -> Word64
ntoh64 (W64# Word64#
w) = Word64# -> Word64
W64# (Word64# -> Word64#
ntoh64# Word64#
w)
getPortInBE :: Port -> Word16
getPortInBE :: Port -> Word16
getPortInBE (Port Word16
p) = Word16 -> Word16
hton16 Word16
p
portFromBE :: Word16 -> Port
portFromBE :: Word16 -> Port
portFromBE = Word16 -> Port
Port (Word16 -> Port) -> (Word16 -> Word16) -> Word16 -> Port
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word16 -> Word16
ntoh16
isReserved :: Port -> Bool
isReserved :: Port -> Bool
isReserved (Port Word16
p) = Word16
p Word16 -> Word16 -> Bool
forall a. Ord a => a -> a -> Bool
< Word16
_IPPORT_RESERVED
isUserReserved :: Port -> Bool
isUserReserved :: Port -> Bool
isUserReserved (Port Word16
p) = Word16
p Word16 -> Word16 -> Bool
forall a. Ord a => a -> a -> Bool
>= Word16
_IPPORT_USERRESERVED
pattern PortRandom :: Port
pattern $mPortRandom :: forall {r}. Port -> ((# #) -> r) -> ((# #) -> r) -> r
$bPortRandom :: Port
PortRandom = Port 0
newtype InAddr = InAddr { InAddr -> Word32
inAddrContent :: Word32 } deriving ByteArray# -> Int# -> InAddr
(ByteArray# -> Int# -> InAddr)
-> (forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, InAddr #))
-> (forall s.
MutableByteArray# s -> Int# -> InAddr -> State# s -> State# s)
-> PrimUnaligned InAddr
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, InAddr #)
forall s.
MutableByteArray# s -> Int# -> InAddr -> State# s -> State# s
forall a.
(ByteArray# -> Int# -> a)
-> (forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> PrimUnaligned a
$cindexUnalignedByteArray# :: ByteArray# -> Int# -> InAddr
indexUnalignedByteArray# :: ByteArray# -> Int# -> InAddr
$creadUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, InAddr #)
readUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, InAddr #)
$cwriteUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> InAddr -> State# s -> State# s
writeUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> InAddr -> State# s -> State# s
PrimUnaligned
pattern InAddrAny :: InAddr
pattern $mInAddrAny :: forall {r}. InAddr -> ((# #) -> r) -> ((# #) -> r) -> r
$bInAddrAny :: InAddr
InAddrAny = InAddr 0
pattern InAddrBroadcast :: InAddr
pattern $mInAddrBroadcast :: forall {r}. InAddr -> ((# #) -> r) -> ((# #) -> r) -> r
$bInAddrBroadcast :: InAddr
InAddrBroadcast = InAddr 0xff_ff_ff_ff
pattern InAddrLoopback :: InAddr
pattern $mInAddrLoopback :: forall {r}. InAddr -> ((# #) -> r) -> ((# #) -> r) -> r
$bInAddrLoopback :: InAddr
InAddrLoopback = InAddr $(case targetByteOrder of LittleEndian -> [p| 0x01_00_00_7f |]; BigEndian -> [p| 0x7f_00_00_01 |])
data In6Addr = In6Addr# (# Word64#, Word64# #)
ip :: Word8 -> Word8 -> Word8 -> Word8 -> InAddr
ip :: Word8 -> Word8 -> Word8 -> Word8 -> InAddr
ip (Word8 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral -> Word32
_0) (Word8 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral -> Word32
_1) (Word8 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral -> Word32
_2) (Word8 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral -> Word32
_3) =
Word32 -> InAddr
InAddr (Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
shiftL Word32
_0 Int
24 Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.|. Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
shiftL Word32
_1 Int
16 Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.|. Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
shiftL Word32
_2 Int
8 Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.|. Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
shiftL Word32
_3 Int
0)
unIp :: InAddr -> (Word8, Word8, Word8, Word8)
unIp :: InAddr -> (Word8, Word8, Word8, Word8)
unIp (InAddr Word32
addr) = (Word32 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
_0, Word32 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
_1, Word32 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
_2, Word32 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
_3)
where _0 :: Word32
_0 = Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
shiftR Word32
addr Int
24
_1 :: Word32
_1 = Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
shiftR Word32
addr Int
16
_2 :: Word32
_2 = Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
shiftR Word32
addr Int
8
_3 :: Word32
_3 = Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
shiftR Word32
addr Int
0
instance Show InAddr where
show :: InAddr -> String
show (InAddr -> (Word8, Word8, Word8, Word8)
unIp -> (Word8
_0, Word8
_1, Word8
_2, Word8
_3)) = Word8 -> String
forall a. Show a => a -> String
show Word8
_0 String -> ShowS
forall a. [a] -> [a] -> [a]
++ Char
'.' Char -> ShowS
forall a. a -> [a] -> [a]
: Word8 -> String
forall a. Show a => a -> String
show Word8
_1 String -> ShowS
forall a. [a] -> [a] -> [a]
++ Char
'.' Char -> ShowS
forall a. a -> [a] -> [a]
: Word8 -> String
forall a. Show a => a -> String
show Word8
_2 String -> ShowS
forall a. [a] -> [a] -> [a]
++ Char
'.' Char -> ShowS
forall a. a -> [a] -> [a]
: Word8 -> String
forall a. Show a => a -> String
show Word8
_3
ip6 :: Word16 -> Word16 -> Word16 -> Word16 -> Word16 -> Word16 -> Word16 -> Word16 -> In6Addr
ip6 :: Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> In6Addr
ip6 = Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> In6Addr
ip6'
where cv :: Int -> Word16 -> Word64
cv :: Int -> Word16 -> Word64
cv Int
n = (Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
`shiftL` (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
16)) (Word64 -> Word64) -> (Word16 -> Word64) -> Word16 -> Word64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word16 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word16 -> Word64) -> (Word16 -> Word16) -> Word16 -> Word64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word16 -> Word16
hton16
ip6' :: Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> In6Addr
ip6' (Int -> Word16 -> Word64
cv Int
3 -> Word64
_0) (Int -> Word16 -> Word64
cv Int
2 -> Word64
_1) (Int -> Word16 -> Word64
cv Int
1 -> Word64
_2) (Int -> Word16 -> Word64
cv Int
0 -> Word64
_3) (Int -> Word16 -> Word64
cv Int
3 -> Word64
_4) (Int -> Word16 -> Word64
cv Int
2 -> Word64
_5) (Int -> Word16 -> Word64
cv Int
1 -> Word64
_6) (Int -> Word16 -> Word64
cv Int
0 -> Word64
_7) =
let !(W64# Word64#
high#) = Word64
_0 Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.|. Word64
_1 Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.|. Word64
_2 Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.|. Word64
_3
!(W64# Word64#
low#) = Word64
_4 Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.|. Word64
_5 Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.|. Word64
_6 Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.|. Word64
_7
in (# Word64#, Word64# #) -> In6Addr
In6Addr# (# Word64#
high#, Word64#
low# #)
unIp6 :: In6Addr -> (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16)
unIp6 :: In6Addr
-> (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16)
unIp6 (In6Addr# (# Word64#
high#, Word64#
low# #)) = (Int -> Word64# -> Word16
vc Int
3 Word64#
high#, Int -> Word64# -> Word16
vc Int
2 Word64#
high#, Int -> Word64# -> Word16
vc Int
1 Word64#
high#, Int -> Word64# -> Word16
vc Int
0 Word64#
high#, Int -> Word64# -> Word16
vc Int
3 Word64#
low#, Int -> Word64# -> Word16
vc Int
2 Word64#
low#, Int -> Word64# -> Word16
vc Int
1 Word64#
low#, Int -> Word64# -> Word16
vc Int
0 Word64#
low#)
where vc :: Int -> Word64# -> Word16
vc :: Int -> Word64# -> Word16
vc Int
n (Word64# -> Word64
W64# -> Word64
w) = Word64 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
shiftR Word64
w (Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
n))
instance Show In6Addr where
showsPrec :: Int -> In6Addr -> ShowS
showsPrec Int
_ In6Addr
addr = (Word16 -> ShowS -> ShowS) -> ShowS -> [Word16] -> ShowS
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (\ Word16
a ShowS
as -> Word16 -> ShowS
forall a. Integral a => a -> ShowS
showHex Word16
a ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char
':' :) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShowS
as ) ShowS
forall a. a -> a
id [Word16]
groups
where groups :: [Word16]
groups = let (Word16
a, Word16
b, Word16
c, Word16
d, Word16
e, Word16
f, Word16
g, Word16
h) = In6Addr
-> (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16)
unIp6 In6Addr
addr in [Word16
a, Word16
b, Word16
c, Word16
d, Word16
e, Word16
f, Word16
g, Word16
h]
newtype Port = Port Word16 deriving (Port -> Port -> Bool
(Port -> Port -> Bool) -> (Port -> Port -> Bool) -> Eq Port
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Port -> Port -> Bool
== :: Port -> Port -> Bool
$c/= :: Port -> Port -> Bool
/= :: Port -> Port -> Bool
Eq, Eq Port
Eq Port =>
(Port -> Port -> Ordering)
-> (Port -> Port -> Bool)
-> (Port -> Port -> Bool)
-> (Port -> Port -> Bool)
-> (Port -> Port -> Bool)
-> (Port -> Port -> Port)
-> (Port -> Port -> Port)
-> Ord Port
Port -> Port -> Bool
Port -> Port -> Ordering
Port -> Port -> Port
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Port -> Port -> Ordering
compare :: Port -> Port -> Ordering
$c< :: Port -> Port -> Bool
< :: Port -> Port -> Bool
$c<= :: Port -> Port -> Bool
<= :: Port -> Port -> Bool
$c> :: Port -> Port -> Bool
> :: Port -> Port -> Bool
$c>= :: Port -> Port -> Bool
>= :: Port -> Port -> Bool
$cmax :: Port -> Port -> Port
max :: Port -> Port -> Port
$cmin :: Port -> Port -> Port
min :: Port -> Port -> Port
Ord, Integer -> Port
Port -> Port
Port -> Port -> Port
(Port -> Port -> Port)
-> (Port -> Port -> Port)
-> (Port -> Port -> Port)
-> (Port -> Port)
-> (Port -> Port)
-> (Port -> Port)
-> (Integer -> Port)
-> Num Port
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: Port -> Port -> Port
+ :: Port -> Port -> Port
$c- :: Port -> Port -> Port
- :: Port -> Port -> Port
$c* :: Port -> Port -> Port
* :: Port -> Port -> Port
$cnegate :: Port -> Port
negate :: Port -> Port
$cabs :: Port -> Port
abs :: Port -> Port
$csignum :: Port -> Port
signum :: Port -> Port
$cfromInteger :: Integer -> Port
fromInteger :: Integer -> Port
Num, Int -> Port -> ShowS
[Port] -> ShowS
Port -> String
(Int -> Port -> ShowS)
-> (Port -> String) -> ([Port] -> ShowS) -> Show Port
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Port -> ShowS
showsPrec :: Int -> Port -> ShowS
$cshow :: Port -> String
show :: Port -> String
$cshowList :: [Port] -> ShowS
showList :: [Port] -> ShowS
Show)
$