{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE UnboxedTuples #-}
{-# OPTIONS_GHC -Wall #-}
module Net.IPv6
(
ipv6
, fromOctets
, fromWord16s
, fromWord32s
, fromTupleWord16s
, fromTupleWord32s
, toWord16s
, toWord32s
, any
, loopback
, encode
, decode
, parser
, print
, range
, fromBounds
, normalize
, contains
, member
, lowerInclusive
, upperInclusive
, encodeRange
, decodeRange
, parserRange
, printRange
, IPv6(..)
, IPv6Range(..)
) where
import Net.IPv4 (IPv4(..))
import qualified Net.IPv4 as IPv4
import Control.Applicative
import Control.DeepSeq (NFData)
import Control.Monad.Primitive
import Control.Monad.ST
import Data.Bits
import Data.Char (chr)
import Data.List (intercalate, group)
import Data.Primitive.Addr
import Data.Primitive.ByteArray
import Data.Primitive.Types (Prim(..))
#if !MIN_VERSION_base(4,11,0)
import Data.Semigroup ((<>))
#endif
import Data.Text (Text)
import Data.Word
import GHC.Enum (predError, succError)
import GHC.Exts
import GHC.Generics (Generic)
import Numeric (showHex)
import Prelude hiding (any, print)
import Text.ParserCombinators.ReadPrec (prec,step)
import Text.Read (Read(..),Lexeme(Ident),lexP,parens)
import qualified Data.Aeson as Aeson
import qualified Data.Attoparsec.Text as AT
import qualified Data.Attoparsec.Text as Atto
import qualified Data.Text as Text
import qualified Data.Text.IO as TIO
data IPv6 = IPv6
{ ipv6A :: {-# UNPACK #-} !Word64
, ipv6B :: {-# UNPACK #-} !Word64
} deriving (Eq,Ord,Generic)
instance NFData IPv6
instance Enum IPv6 where
succ (IPv6 a b)
| a == maxBound && b == maxBound = succError "IPv6"
| otherwise =
case b + 1 of
0 -> IPv6 (a + 1) 0
s -> IPv6 a s
pred (IPv6 a b)
| a == 0 && b == 0 = predError "IPv6"
| otherwise =
case b of
0 -> IPv6 (a - 1) maxBound
_ -> IPv6 a (b - 1)
toEnum :: Int -> IPv6
toEnum i = IPv6 0 (toEnum i)
fromEnum :: IPv6 -> Int
fromEnum (IPv6 _ b) = fromEnum b
{-# INLINE enumFrom #-}
enumFrom x = unfoldrLast (Just maxBound) (\b -> if b < maxBound then Just (b,succ b) else Nothing) x
{-# INLINE enumFromTo #-}
enumFromTo x y = unfoldrLast (if x <= y then Just y else Nothing) (\b -> if b < y then Just (b,succ b) else Nothing) x
enumFromThen = error "IPv6 currently lacks an implementation of enumFromThen"
enumFromThenTo = error "IPv6 currently lacks an implementation of enumFromThenTo"
unfoldrLast :: Maybe a -> (b -> Maybe (a, b)) -> b -> [a]
{-# INLINE unfoldrLast #-}
unfoldrLast a0 f b0 = build
(\c n ->
let go b = case f b of
Just (a, new_b) -> a `c` go new_b
Nothing -> case a0 of
Nothing -> n
Just x -> x `c` n
in go b0
)
instance Bounded IPv6 where
minBound = IPv6 0 0
maxBound = IPv6 maxBound maxBound
instance Show IPv6 where
showsPrec p addr = showParen (p > 10)
$ showString "ipv6 "
. showHexWord16 a
. showChar ' '
. showHexWord16 b
. showChar ' '
. showHexWord16 c
. showChar ' '
. showHexWord16 d
. showChar ' '
. showHexWord16 e
. showChar ' '
. showHexWord16 f
. showChar ' '
. showHexWord16 g
. showChar ' '
. showHexWord16 h
where
(a,b,c,d,e,f,g,h) = toWord16s addr
instance Prim IPv6 where
sizeOf# _ = 2# *# sizeOf# (undefined :: Word64)
alignment# _ = alignment# (undefined :: Word64)
indexByteArray# arr# i# =
let i = I# i#
arr = ByteArray arr#
in IPv6 (indexByteArray arr (2 * i + 0)) (indexByteArray arr (2 * i + 1))
readByteArray# :: forall s. () => MutableByteArray# s -> Int# -> State# s -> (# State# s, IPv6 #)
readByteArray# arr# i# = internal $ do
let i = I# i#
arr = MutableByteArray arr#
a <- readByteArray arr (2 * i + 0) :: ST s Word64
b <- readByteArray arr (2 * i + 1)
return (IPv6 a b)
writeByteArray# :: forall s. () => MutableByteArray# s -> Int# -> IPv6 -> State# s -> State# s
writeByteArray# arr# i# (IPv6 a b) = internal_ $ do
let i = I# i#
arr = MutableByteArray arr#
writeByteArray arr (2 * i + 0) a
writeByteArray arr (2 * i + 1) b :: ST s ()
setByteArray# arr# i# len# ident = go 0#
where
go ix# s0 = if isTrue# (ix# <# len#)
then case writeByteArray# arr# (i# +# ix#) ident s0 of
s1 -> go (ix# +# 1#) s1
else s0
indexOffAddr# :: Addr# -> Int# -> IPv6
indexOffAddr# addr# i# =
let i = I# i#
addr = Addr addr#
in IPv6 (indexOffAddr addr (2 * i + 0)) (indexOffAddr addr (2 * i + 1))
readOffAddr# :: forall s. () => Addr# -> Int# -> State# s -> (# State# s, IPv6 #)
readOffAddr# addr# i# = internal $ do
let i = I# i#
addr = Addr addr#
a <- readOffAddr addr (2 * i + 0) :: ST s Word64
b <- readOffAddr addr (2 * i + 1)
return (IPv6 a b)
writeOffAddr# :: forall s. () => Addr# -> Int# -> IPv6 -> State# s -> State# s
writeOffAddr# addr# i# (IPv6 a b) = internal_ $ do
let i = I# i#
addr = Addr addr#
writeOffAddr addr (2 * i + 0) a
writeOffAddr addr (2 * i + 1) b :: ST s ()
setOffAddr# addr# i# len# ident = go 0#
where
go ix# s0 = if isTrue# (ix# <# len#)
then case writeOffAddr# addr# (i# +# ix#) ident s0 of
s1 -> go (ix# +# 1#) s1
else s0
internal_ :: PrimBase m => m () -> State# (PrimState m) -> State# (PrimState m)
internal_ m s = case internal m s of
(# s', _ #) -> s'
print :: IPv6 -> IO ()
print = TIO.putStrLn . encode
showHexWord16 :: Word16 -> ShowS
showHexWord16 w =
showString "0x"
. showChar (nibbleToHex (unsafeShiftR (fromIntegral w) 12))
. showChar (nibbleToHex ((unsafeShiftR (fromIntegral w) 8) .&. 0xF))
. showChar (nibbleToHex ((unsafeShiftR (fromIntegral w) 4) .&. 0xF))
. showChar (nibbleToHex ((fromIntegral w) .&. 0xF))
nibbleToHex :: Word -> Char
nibbleToHex w
| w < 10 = chr (fromIntegral (w + 48))
| otherwise = chr (fromIntegral (w + 87))
instance Read IPv6 where
readPrec = parens $ prec 10 $ do
Ident "ipv6" <- lexP
a <- step readPrec
b <- step readPrec
c <- step readPrec
d <- step readPrec
e <- step readPrec
f <- step readPrec
g <- step readPrec
h <- step readPrec
return (fromWord16s a b c d e f g h)
instance Aeson.ToJSON IPv6 where
toJSON = Aeson.String . encode
instance Aeson.FromJSON IPv6 where
parseJSON = Aeson.withText "IPv6" $ \t -> case decode t of
Nothing -> fail "invalid IPv6 address"
Just i -> return i
rightToMaybe :: Either a b -> Maybe b
rightToMaybe = either (const Nothing) Just
fromOctets ::
Word8 -> Word8 -> Word8 -> Word8
-> Word8 -> Word8 -> Word8 -> Word8
-> Word8 -> Word8 -> Word8 -> Word8
-> Word8 -> Word8 -> Word8 -> Word8
-> IPv6
fromOctets a b c d e f g h i j k l m n o p =
let !(w1,w2) = fromOctetsV6
(fromIntegral a) (fromIntegral b) (fromIntegral c) (fromIntegral d)
(fromIntegral e) (fromIntegral f) (fromIntegral g) (fromIntegral h)
(fromIntegral i) (fromIntegral j) (fromIntegral k) (fromIntegral l)
(fromIntegral m) (fromIntegral n) (fromIntegral o) (fromIntegral p)
in IPv6 w1 w2
ipv6 ::
Word16 -> Word16 -> Word16 -> Word16
-> Word16 -> Word16 -> Word16 -> Word16
-> IPv6
ipv6 = fromWord16s
fromWord16s ::
Word16 -> Word16 -> Word16 -> Word16
-> Word16 -> Word16 -> Word16 -> Word16
-> IPv6
fromWord16s a b c d e f g h =
let !(w1,w2) = fromWord16sV6
(fromIntegral a) (fromIntegral b) (fromIntegral c) (fromIntegral d)
(fromIntegral e) (fromIntegral f) (fromIntegral g) (fromIntegral h)
in IPv6 w1 w2
toWord16s :: IPv6 -> (Word16,Word16,Word16,Word16,Word16,Word16,Word16,Word16)
toWord16s (IPv6 a b) =
( fromIntegral (unsafeShiftR a 48)
, fromIntegral (unsafeShiftR a 32)
, fromIntegral (unsafeShiftR a 16)
, fromIntegral a
, fromIntegral (unsafeShiftR b 48)
, fromIntegral (unsafeShiftR b 32)
, fromIntegral (unsafeShiftR b 16)
, fromIntegral b
)
fromTupleWord16s :: (Word16,Word16,Word16,Word16,Word16,Word16,Word16,Word16) -> IPv6
fromTupleWord16s (a,b,c,d,e,f,g,h) = fromWord16s a b c d e f g h
fromWord32s :: Word32 -> Word32 -> Word32 -> Word32 -> IPv6
fromWord32s a b c d =
let !(w1,w2) = fromWord32sV6
(fromIntegral a) (fromIntegral b) (fromIntegral c) (fromIntegral d)
in IPv6 w1 w2
fromTupleWord32s :: (Word32,Word32,Word32,Word32) -> IPv6
fromTupleWord32s (a,b,c,d) = fromWord32s a b c d
toWord32s :: IPv6 -> (Word32,Word32,Word32,Word32)
toWord32s (IPv6 a b) =
( fromIntegral (unsafeShiftR a 32)
, fromIntegral a
, fromIntegral (unsafeShiftR b 32)
, fromIntegral b
)
loopback :: IPv6
loopback = IPv6 0 1
any :: IPv6
any = IPv6 0 0
encode :: IPv6 -> Text
encode ip =
if isIPv4MappedAddress
then Text.pack "::ffff:" `mappend` IPv4.encode (IPv4.IPv4 (fromIntegral w7 `unsafeShiftL` 16 .|. fromIntegral w8))
else toText [w1, w2, w3, w4, w5, w6, w7, w8]
where
isIPv4MappedAddress = w1 == 0 && w2 == 0 && w3 == 0 && w4 == 0 && w5 == 0 && w6 == 0xFFFF
(w1, w2, w3, w4, w5, w6, w7, w8) = toWord16s ip
toText ws = Text.pack $ intercalate ":" $ expand 0 longestZ grouped
where
expand _ 8 _ = ["::"]
expand _ _ [] = []
expand i longest ((x, len):wsNext)
| x == 0 && len == longest =
(if i == 0 || (i+len) == 8 then ":" else "")
: expand (i+len) 0 wsNext
| otherwise = replicate len (showHex x "") ++ expand (i+len) longest wsNext
longestZ = maximum . (0:) . map snd . filter ((==0) . fst) $ grouped
grouped = map (\x -> (head x, length x)) (group ws)
decode :: Text -> Maybe IPv6
decode t = rightToMaybe (AT.parseOnly (parser <* AT.endOfInput) t)
parser :: Atto.Parser IPv6
parser = makeIP <$> ip
where
makeIP [w1, w2, w3, w4, w5, w6, w7, w8] = fromWord16s w1 w2 w3 w4 w5 w6 w7 w8
makeIP _ = error "Net.IPv6.parser: Implementation error. Please open a bug report."
ip = (Atto.char ':' *> Atto.char ':' *> doubleColon 0) <|> part 0
part :: Int -> Atto.Parser [Word16]
part n =
case n of
7 -> pure <$> Atto.hexadecimal
6 -> ipv4 <|> hexPart
_ -> hexPart
where
hexPart = (:)
<$> Atto.hexadecimal
<*> (Atto.char ':' *>
(
(Atto.char ':' *> doubleColon (n+1))
<|>
part (n+1)
)
)
doubleColon :: Int -> Atto.Parser [Word16]
doubleColon count = do
rest <- afterDoubleColon <|> pure []
let fillerLength = (8 - count - length rest)
if fillerLength <= 0
then fail "too many parts in IPv6 address"
else pure (replicate fillerLength 0 ++ rest)
afterDoubleColon :: Atto.Parser [Word16]
afterDoubleColon =
ipv4 <|>
(:) <$> Atto.hexadecimal <*> ((Atto.char ':' *> afterDoubleColon) <|> pure [])
ipv4 :: Atto.Parser [Word16]
ipv4 = ipv4ToWord16s <$> IPv4.parser
ipv4ToWord16s :: IPv4 -> [Word16]
ipv4ToWord16s (IPv4 word) = [fromIntegral (word `unsafeShiftR` 16), fromIntegral (word .&. 0xFFFF)]
fromOctetsV6 ::
Word64 -> Word64 -> Word64 -> Word64
-> Word64 -> Word64 -> Word64 -> Word64
-> Word64 -> Word64 -> Word64 -> Word64
-> Word64 -> Word64 -> Word64 -> Word64
-> (Word64,Word64)
fromOctetsV6 a b c d e f g h i j k l m n o p =
( fromOctetsWord64 a b c d e f g h
, fromOctetsWord64 i j k l m n o p
)
fromWord16sV6 ::
Word64 -> Word64 -> Word64 -> Word64
-> Word64 -> Word64 -> Word64 -> Word64
-> (Word64,Word64)
fromWord16sV6 a b c d e f g h =
( fromWord16Word64 a b c d
, fromWord16Word64 e f g h
)
fromWord32sV6 :: Word64 -> Word64 -> Word64 -> Word64 -> (Word64,Word64)
fromWord32sV6 a b c d =
( fromWord32Word64 a b
, fromWord32Word64 c d
)
fromOctetsWord64 ::
Word64 -> Word64 -> Word64 -> Word64
-> Word64 -> Word64 -> Word64 -> Word64
-> Word64
fromOctetsWord64 a b c d e f g h = fromIntegral
( shiftL a 56
.|. shiftL b 48
.|. shiftL c 40
.|. shiftL d 32
.|. shiftL e 24
.|. shiftL f 16
.|. shiftL g 8
.|. h
)
fromWord16Word64 :: Word64 -> Word64 -> Word64 -> Word64 -> Word64
fromWord16Word64 a b c d = fromIntegral
( unsafeShiftL a 48
.|. unsafeShiftL b 32
.|. unsafeShiftL c 16
.|. d
)
fromWord32Word64 :: Word64 -> Word64 -> Word64
fromWord32Word64 a b = fromIntegral (unsafeShiftL a 32 .|. b)
data IPv6Range = IPv6Range
{ ipv6RangeBase :: {-# UNPACK #-} !IPv6
, ipv6RangeLength :: {-# UNPACK #-} !Word8
} deriving (Eq,Ord,Show,Read,Generic)
instance NFData IPv6Range
mask :: Word8 -> Word64
mask w = if w > 63
then 0xffffffffffffffff
else complement (shiftR 0xffffffffffffffff (fromIntegral w))
normalize :: IPv6Range -> IPv6Range
normalize (IPv6Range (IPv6 w1 w2) len) =
let len' = min len 128
norm
| len' < 64 = (IPv6Range (IPv6 (w1 .&. mask len') (w2 .&. mask 0)) len')
| otherwise = (IPv6Range (IPv6 (w1 .&. mask 64) (w2 .&. mask (len' - 64))) len')
in norm
encodeRange :: IPv6Range -> Text
encodeRange x = encode (ipv6RangeBase x) <> Text.pack "/" <> (Text.pack $ (show . fromEnum) $ ipv6RangeLength x)
decodeRange :: Text -> Maybe IPv6Range
decodeRange = rightToMaybe . AT.parseOnly (parserRange <* AT.endOfInput)
parserRange :: AT.Parser IPv6Range
parserRange = do
ip <- parser
_ <- AT.char '/'
theMask <- AT.decimal >>= limitSize
return (normalize (IPv6Range ip theMask))
where
limitSize i =
if i > 128
then fail "An IP range length must be between 0 and 128"
else return i
contains :: IPv6Range -> IPv6 -> Bool
contains (IPv6Range (IPv6 wsubnetA wsubnetB) len) =
let lenA = if len > 64 then 64 else len
lenB = if len > 64 then len - 64 else 0
theMaskA = mask lenA
theMaskB = mask lenB
wsubnetNormalizedA = wsubnetA .&. theMaskA
wsubnetNormalizedB = wsubnetB .&. theMaskB
in \(IPv6 wA wB) ->
(wA .&. theMaskA) == wsubnetNormalizedA
&&
(wB .&. theMaskB) == wsubnetNormalizedB
member :: IPv6 -> IPv6Range -> Bool
member = flip contains
lowerInclusive :: IPv6Range -> IPv6
lowerInclusive (IPv6Range (IPv6 w1 w2) len) =
ipv6RangeBase (normalize (IPv6Range (IPv6 w1 w2) len))
upperInclusive :: IPv6Range -> IPv6
upperInclusive (IPv6Range (IPv6 w1 w2) len) =
let len' = min 128 len
theInvertedMask :: Word64
theInvertedMask = shiftR 0xffffffffffffffff (fromIntegral len')
theInvertedMask2 = shiftR 0xffffffffffffffff ((fromIntegral len')-64)
upper
| len' < 64 = IPv6 ((w1 .|. theInvertedMask)) ((w2 .|. shiftR 0xffffffffffffffff 0))
| otherwise = IPv6 (w1) (w2 .|. theInvertedMask2)
in upper
printRange :: IPv6Range -> IO ()
printRange = TIO.putStrLn . encodeRange
range :: IPv6 -> Word8 -> IPv6Range
range addr len = normalize (IPv6Range addr len)
fromBounds :: IPv6 -> IPv6 -> IPv6Range
fromBounds (IPv6 a1 a2) (IPv6 b1 b2) =
normalize (IPv6Range (IPv6 a1 a2) (maskFromBounds a1 b1 a2 b2))
maskFromBounds :: Word64 -> Word64 -> Word64 -> Word64 -> Word8
maskFromBounds lo1 hi1 lo2 hi2 =
let x = countLeadingZeros (xor lo1 hi1)
check
| x < 64 = fromIntegral x
| otherwise = fromIntegral $ x + (countLeadingZeros (xor lo2 hi2))
in check