{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeInType #-}
{-# LANGUAGE UnboxedTuples #-}
module Net.IPv6
(
ipv6
, fromOctets
, fromWord16s
, fromWord32s
, fromTupleWord16s
, fromTupleWord32s
, toWord16s
, toWord32s
, any
, loopback
, localhost
, 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 Data.Bits
import Data.Char (chr)
import Data.List (intercalate, group)
import Data.Primitive.Types (Prim)
#if !MIN_VERSION_base(4,11,0)
import Data.Semigroup ((<>))
#endif
import qualified Data.Aeson as Aeson
import qualified Data.Attoparsec.Text as AT
import qualified Data.Attoparsec.Text as Atto
import Data.Text (Text)
import qualified Data.Text as Text
import qualified Data.Text.IO as TIO
import Data.WideWord.Word128 (Word128(..), zeroWord128)
import Data.Word
import Foreign.Storable (Storable)
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)
newtype IPv6 = IPv6 { getIPv6 :: Word128 }
deriving (Bounded,Enum,Eq,Integral,Num,Ord,Real,Storable,Bits,FiniteBits,NFData,Prim)
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
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 =
IPv6 $ fromOctetsWord128
(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)
fromOctetsWord128 ::
Word128 -> Word128 -> Word128 -> Word128
-> Word128 -> Word128 -> Word128 -> Word128
-> Word128 -> Word128 -> Word128 -> Word128
-> Word128 -> Word128 -> Word128 -> Word128
-> Word128
fromOctetsWord128 a b c d e f g h i j k l m n o p = fromIntegral
( shiftL a 120
.|. shiftL b 112
.|. shiftL c 104
.|. shiftL d 96
.|. shiftL e 88
.|. shiftL f 80
.|. shiftL g 72
.|. shiftL h 64
.|. shiftL i 56
.|. shiftL j 48
.|. shiftL k 40
.|. shiftL l 32
.|. shiftL m 24
.|. shiftL n 16
.|. shiftL o 8
.|. p
)
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 =
IPv6 $ fromWord16sWord128
(fromIntegral a) (fromIntegral b) (fromIntegral c) (fromIntegral d)
(fromIntegral e) (fromIntegral f) (fromIntegral g) (fromIntegral h)
fromWord16sWord128 ::
Word128 -> Word128 -> Word128 -> Word128
-> Word128 -> Word128 -> Word128 -> Word128
-> Word128
fromWord16sWord128 a b c d e f g h = fromIntegral
( shiftL a 112
.|. shiftL b 96
.|. shiftL c 80
.|. shiftL d 64
.|. shiftL e 48
.|. shiftL f 32
.|. shiftL g 16
.|. h
)
toWord16s :: IPv6 -> (Word16,Word16,Word16,Word16,Word16,Word16,Word16,Word16)
toWord16s (IPv6 (Word128 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 =
IPv6 $ fromWord32sWord128
(fromIntegral a) (fromIntegral b) (fromIntegral c) (fromIntegral d)
fromWord32sWord128 ::
Word128 -> Word128 -> Word128 -> Word128
-> Word128
fromWord32sWord128 a b c d = fromIntegral
( shiftL a 96
.|. shiftL b 64
.|. shiftL c 32
.|. d
)
fromTupleWord32s :: (Word32,Word32,Word32,Word32) -> IPv6
fromTupleWord32s (a,b,c,d) = fromWord32s a b c d
toWord32s :: IPv6 -> (Word32,Word32,Word32,Word32)
toWord32s (IPv6 (Word128 a b)) =
( fromIntegral (unsafeShiftR a 32)
, fromIntegral a
, fromIntegral (unsafeShiftR b 32)
, fromIntegral b
)
loopback :: IPv6
loopback = IPv6 (Word128 0 1)
localhost :: IPv6
localhost = loopback
any :: IPv6
any = IPv6 zeroWord128
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)]
data IPv6Range = IPv6Range
{ ipv6RangeBase :: {-# UNPACK #-} !IPv6
, ipv6RangeLength :: {-# UNPACK #-} !Word8
} deriving (Eq,Ord,Show,Read,Generic)
instance NFData IPv6Range
mask128 :: IPv6
mask128 = maxBound
mask :: Word8 -> IPv6
mask = complement . shiftR mask128 . fromIntegral
normalize :: IPv6Range -> IPv6Range
normalize (IPv6Range ip len) =
let len' = min len 128
ip' = ip .&. mask len'
in IPv6Range ip' len'
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 subnet len) =
let theMask = mask len
subnetNormalized = subnet .&. theMask
in \ip -> (ip .&. theMask) == subnetNormalized
member :: IPv6 -> IPv6Range -> Bool
member = flip contains
lowerInclusive :: IPv6Range -> IPv6
lowerInclusive = ipv6RangeBase . normalize
upperInclusive :: IPv6Range -> IPv6
upperInclusive (IPv6Range ip len) =
let len' = min 128 len
theInvertedMask :: IPv6
theInvertedMask = shiftR mask128 (fromIntegral len')
in ip .|. theInvertedMask
printRange :: IPv6Range -> IO ()
printRange = TIO.putStrLn . encodeRange
range :: IPv6 -> Word8 -> IPv6Range
range addr len = normalize (IPv6Range addr len)
fromBounds :: IPv6 -> IPv6 -> IPv6Range
fromBounds lo hi =
normalize (IPv6Range lo (maskFromBounds lo hi))
maskFromBounds :: IPv6 -> IPv6 -> Word8
maskFromBounds lo hi = fromIntegral (countLeadingZeros $ xor lo hi)