{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeInType #-}
{-# LANGUAGE UnboxedTuples #-}
module Net.IPv6
(
ipv6
, fromOctets
, fromWord16s
, fromWord32s
, fromTupleWord16s
, fromTupleWord32s
, toWord16s
, toWord32s
, any
, loopback
, localhost
, encode
, encodeShort
, decode
, decodeShort
, parser
, parserUtf8Bytes
, decodeUtf8Bytes
, boundedBuilderUtf8
, print
, range
, fromBounds
, normalize
, contains
, member
, lowerInclusive
, upperInclusive
, encodeRange
, decodeRange
, parserRange
, printRange
, parserRangeUtf8Bytes
, parserRangeUtf8BytesLenient
, IPv6(..)
, IPv6Range(..)
) where
import Prelude hiding (any, print)
import Net.IPv4 (IPv4(..))
import Control.Applicative
import Control.DeepSeq (NFData)
import Control.Monad (mzero)
import Control.Monad.ST (ST)
import Data.Bits
import Data.Char (chr)
import Data.Data (Data)
import Data.Ix (Ix)
import Data.List (intercalate, group)
import Data.Primitive (MutablePrimArray)
import Data.Primitive.Types (Prim)
import Data.Text (Text)
import Data.Text.Short (ShortText)
import Data.WideWord.Word128 (Word128(..), zeroWord128)
import Data.Word
import Foreign.Storable (Storable)
import GHC.Exts (Int#,Word#,Int(I#))
import GHC.Generics (Generic)
import GHC.Word (Word16(W16#))
import Numeric (showHex)
import Text.ParserCombinators.ReadPrec (prec,step)
import Text.Read (Read(..),Lexeme(Ident),lexP,parens)
import qualified Arithmetic.Lte as Lte
import qualified Arithmetic.Nat as Nat
import qualified Data.Aeson as Aeson
import qualified Data.Attoparsec.Text as AT
import qualified Data.Attoparsec.Text as Atto
import qualified Data.Bytes.Builder.Bounded as BB
import qualified Data.Bytes as Bytes
import qualified Data.Bytes.Parser as Parser
import qualified Data.Bytes.Parser.Latin as Latin
import qualified Data.ByteString.Short.Internal as BSS
import qualified Data.Primitive as PM
import qualified Data.Text as Text
import qualified Data.Text.IO as TIO
import qualified Data.Text.Short.Unsafe as TS
import qualified Data.Text.Short as TS
import qualified Net.IPv4 as IPv4
newtype IPv6 = IPv6 { IPv6 -> Word128
getIPv6 :: Word128 }
deriving (IPv6
IPv6 -> IPv6 -> Bounded IPv6
forall a. a -> a -> Bounded a
maxBound :: IPv6
$cmaxBound :: IPv6
minBound :: IPv6
$cminBound :: IPv6
Bounded,Int -> IPv6
IPv6 -> Int
IPv6 -> [IPv6]
IPv6 -> IPv6
IPv6 -> IPv6 -> [IPv6]
IPv6 -> IPv6 -> IPv6 -> [IPv6]
(IPv6 -> IPv6)
-> (IPv6 -> IPv6)
-> (Int -> IPv6)
-> (IPv6 -> Int)
-> (IPv6 -> [IPv6])
-> (IPv6 -> IPv6 -> [IPv6])
-> (IPv6 -> IPv6 -> [IPv6])
-> (IPv6 -> IPv6 -> IPv6 -> [IPv6])
-> Enum IPv6
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: IPv6 -> IPv6 -> IPv6 -> [IPv6]
$cenumFromThenTo :: IPv6 -> IPv6 -> IPv6 -> [IPv6]
enumFromTo :: IPv6 -> IPv6 -> [IPv6]
$cenumFromTo :: IPv6 -> IPv6 -> [IPv6]
enumFromThen :: IPv6 -> IPv6 -> [IPv6]
$cenumFromThen :: IPv6 -> IPv6 -> [IPv6]
enumFrom :: IPv6 -> [IPv6]
$cenumFrom :: IPv6 -> [IPv6]
fromEnum :: IPv6 -> Int
$cfromEnum :: IPv6 -> Int
toEnum :: Int -> IPv6
$ctoEnum :: Int -> IPv6
pred :: IPv6 -> IPv6
$cpred :: IPv6 -> IPv6
succ :: IPv6 -> IPv6
$csucc :: IPv6 -> IPv6
Enum,IPv6 -> IPv6 -> Bool
(IPv6 -> IPv6 -> Bool) -> (IPv6 -> IPv6 -> Bool) -> Eq IPv6
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IPv6 -> IPv6 -> Bool
$c/= :: IPv6 -> IPv6 -> Bool
== :: IPv6 -> IPv6 -> Bool
$c== :: IPv6 -> IPv6 -> Bool
Eq,Eq IPv6
Eq IPv6
-> (IPv6 -> IPv6 -> Ordering)
-> (IPv6 -> IPv6 -> Bool)
-> (IPv6 -> IPv6 -> Bool)
-> (IPv6 -> IPv6 -> Bool)
-> (IPv6 -> IPv6 -> Bool)
-> (IPv6 -> IPv6 -> IPv6)
-> (IPv6 -> IPv6 -> IPv6)
-> Ord IPv6
IPv6 -> IPv6 -> Bool
IPv6 -> IPv6 -> Ordering
IPv6 -> IPv6 -> IPv6
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
min :: IPv6 -> IPv6 -> IPv6
$cmin :: IPv6 -> IPv6 -> IPv6
max :: IPv6 -> IPv6 -> IPv6
$cmax :: IPv6 -> IPv6 -> IPv6
>= :: IPv6 -> IPv6 -> Bool
$c>= :: IPv6 -> IPv6 -> Bool
> :: IPv6 -> IPv6 -> Bool
$c> :: IPv6 -> IPv6 -> Bool
<= :: IPv6 -> IPv6 -> Bool
$c<= :: IPv6 -> IPv6 -> Bool
< :: IPv6 -> IPv6 -> Bool
$c< :: IPv6 -> IPv6 -> Bool
compare :: IPv6 -> IPv6 -> Ordering
$ccompare :: IPv6 -> IPv6 -> Ordering
$cp1Ord :: Eq IPv6
Ord,Ptr b -> Int -> IO IPv6
Ptr b -> Int -> IPv6 -> IO ()
Ptr IPv6 -> IO IPv6
Ptr IPv6 -> Int -> IO IPv6
Ptr IPv6 -> Int -> IPv6 -> IO ()
Ptr IPv6 -> IPv6 -> IO ()
IPv6 -> Int
(IPv6 -> Int)
-> (IPv6 -> Int)
-> (Ptr IPv6 -> Int -> IO IPv6)
-> (Ptr IPv6 -> Int -> IPv6 -> IO ())
-> (forall b. Ptr b -> Int -> IO IPv6)
-> (forall b. Ptr b -> Int -> IPv6 -> IO ())
-> (Ptr IPv6 -> IO IPv6)
-> (Ptr IPv6 -> IPv6 -> IO ())
-> Storable IPv6
forall b. Ptr b -> Int -> IO IPv6
forall b. Ptr b -> Int -> IPv6 -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr IPv6 -> IPv6 -> IO ()
$cpoke :: Ptr IPv6 -> IPv6 -> IO ()
peek :: Ptr IPv6 -> IO IPv6
$cpeek :: Ptr IPv6 -> IO IPv6
pokeByteOff :: Ptr b -> Int -> IPv6 -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> IPv6 -> IO ()
peekByteOff :: Ptr b -> Int -> IO IPv6
$cpeekByteOff :: forall b. Ptr b -> Int -> IO IPv6
pokeElemOff :: Ptr IPv6 -> Int -> IPv6 -> IO ()
$cpokeElemOff :: Ptr IPv6 -> Int -> IPv6 -> IO ()
peekElemOff :: Ptr IPv6 -> Int -> IO IPv6
$cpeekElemOff :: Ptr IPv6 -> Int -> IO IPv6
alignment :: IPv6 -> Int
$calignment :: IPv6 -> Int
sizeOf :: IPv6 -> Int
$csizeOf :: IPv6 -> Int
Storable,Eq IPv6
IPv6
Eq IPv6
-> (IPv6 -> IPv6 -> IPv6)
-> (IPv6 -> IPv6 -> IPv6)
-> (IPv6 -> IPv6 -> IPv6)
-> (IPv6 -> IPv6)
-> (IPv6 -> Int -> IPv6)
-> (IPv6 -> Int -> IPv6)
-> IPv6
-> (Int -> IPv6)
-> (IPv6 -> Int -> IPv6)
-> (IPv6 -> Int -> IPv6)
-> (IPv6 -> Int -> IPv6)
-> (IPv6 -> Int -> Bool)
-> (IPv6 -> Maybe Int)
-> (IPv6 -> Int)
-> (IPv6 -> Bool)
-> (IPv6 -> Int -> IPv6)
-> (IPv6 -> Int -> IPv6)
-> (IPv6 -> Int -> IPv6)
-> (IPv6 -> Int -> IPv6)
-> (IPv6 -> Int -> IPv6)
-> (IPv6 -> Int -> IPv6)
-> (IPv6 -> Int)
-> Bits IPv6
Int -> IPv6
IPv6 -> Bool
IPv6 -> Int
IPv6 -> Maybe Int
IPv6 -> IPv6
IPv6 -> Int -> Bool
IPv6 -> Int -> IPv6
IPv6 -> IPv6 -> IPv6
forall a.
Eq a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
popCount :: IPv6 -> Int
$cpopCount :: IPv6 -> Int
rotateR :: IPv6 -> Int -> IPv6
$crotateR :: IPv6 -> Int -> IPv6
rotateL :: IPv6 -> Int -> IPv6
$crotateL :: IPv6 -> Int -> IPv6
unsafeShiftR :: IPv6 -> Int -> IPv6
$cunsafeShiftR :: IPv6 -> Int -> IPv6
shiftR :: IPv6 -> Int -> IPv6
$cshiftR :: IPv6 -> Int -> IPv6
unsafeShiftL :: IPv6 -> Int -> IPv6
$cunsafeShiftL :: IPv6 -> Int -> IPv6
shiftL :: IPv6 -> Int -> IPv6
$cshiftL :: IPv6 -> Int -> IPv6
isSigned :: IPv6 -> Bool
$cisSigned :: IPv6 -> Bool
bitSize :: IPv6 -> Int
$cbitSize :: IPv6 -> Int
bitSizeMaybe :: IPv6 -> Maybe Int
$cbitSizeMaybe :: IPv6 -> Maybe Int
testBit :: IPv6 -> Int -> Bool
$ctestBit :: IPv6 -> Int -> Bool
complementBit :: IPv6 -> Int -> IPv6
$ccomplementBit :: IPv6 -> Int -> IPv6
clearBit :: IPv6 -> Int -> IPv6
$cclearBit :: IPv6 -> Int -> IPv6
setBit :: IPv6 -> Int -> IPv6
$csetBit :: IPv6 -> Int -> IPv6
bit :: Int -> IPv6
$cbit :: Int -> IPv6
zeroBits :: IPv6
$czeroBits :: IPv6
rotate :: IPv6 -> Int -> IPv6
$crotate :: IPv6 -> Int -> IPv6
shift :: IPv6 -> Int -> IPv6
$cshift :: IPv6 -> Int -> IPv6
complement :: IPv6 -> IPv6
$ccomplement :: IPv6 -> IPv6
xor :: IPv6 -> IPv6 -> IPv6
$cxor :: IPv6 -> IPv6 -> IPv6
.|. :: IPv6 -> IPv6 -> IPv6
$c.|. :: IPv6 -> IPv6 -> IPv6
.&. :: IPv6 -> IPv6 -> IPv6
$c.&. :: IPv6 -> IPv6 -> IPv6
$cp1Bits :: Eq IPv6
Bits,Bits IPv6
Bits IPv6
-> (IPv6 -> Int)
-> (IPv6 -> Int)
-> (IPv6 -> Int)
-> FiniteBits IPv6
IPv6 -> Int
forall b.
Bits b -> (b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
countTrailingZeros :: IPv6 -> Int
$ccountTrailingZeros :: IPv6 -> Int
countLeadingZeros :: IPv6 -> Int
$ccountLeadingZeros :: IPv6 -> Int
finiteBitSize :: IPv6 -> Int
$cfiniteBitSize :: IPv6 -> Int
$cp1FiniteBits :: Bits IPv6
FiniteBits,IPv6 -> ()
(IPv6 -> ()) -> NFData IPv6
forall a. (a -> ()) -> NFData a
rnf :: IPv6 -> ()
$crnf :: IPv6 -> ()
NFData,Addr# -> Int# -> IPv6
Addr# -> Int# -> Int# -> IPv6 -> State# s -> State# s
Addr# -> Int# -> State# s -> (# State# s, IPv6 #)
Addr# -> Int# -> IPv6 -> State# s -> State# s
ByteArray# -> Int# -> IPv6
MutableByteArray# s -> Int# -> State# s -> (# State# s, IPv6 #)
MutableByteArray# s -> Int# -> IPv6 -> State# s -> State# s
MutableByteArray# s -> Int# -> Int# -> IPv6 -> State# s -> State# s
IPv6 -> Int#
(IPv6 -> Int#)
-> (IPv6 -> Int#)
-> (ByteArray# -> Int# -> IPv6)
-> (forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, IPv6 #))
-> (forall s.
MutableByteArray# s -> Int# -> IPv6 -> State# s -> State# s)
-> (forall s.
MutableByteArray# s
-> Int# -> Int# -> IPv6 -> State# s -> State# s)
-> (Addr# -> Int# -> IPv6)
-> (forall s. Addr# -> Int# -> State# s -> (# State# s, IPv6 #))
-> (forall s. Addr# -> Int# -> IPv6 -> State# s -> State# s)
-> (forall s.
Addr# -> Int# -> Int# -> IPv6 -> State# s -> State# s)
-> Prim IPv6
forall s. Addr# -> Int# -> Int# -> IPv6 -> State# s -> State# s
forall s. Addr# -> Int# -> State# s -> (# State# s, IPv6 #)
forall s. Addr# -> Int# -> IPv6 -> State# s -> State# s
forall s.
MutableByteArray# s -> Int# -> Int# -> IPv6 -> State# s -> State# s
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, IPv6 #)
forall s.
MutableByteArray# s -> Int# -> IPv6 -> State# s -> State# s
forall a.
(a -> Int#)
-> (a -> Int#)
-> (ByteArray# -> Int# -> a)
-> (forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> (forall s.
MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s)
-> (Addr# -> Int# -> a)
-> (forall s. Addr# -> Int# -> State# s -> (# State# s, a #))
-> (forall s. Addr# -> Int# -> a -> State# s -> State# s)
-> (forall s. Addr# -> Int# -> Int# -> a -> State# s -> State# s)
-> Prim a
setOffAddr# :: Addr# -> Int# -> Int# -> IPv6 -> State# s -> State# s
$csetOffAddr# :: forall s. Addr# -> Int# -> Int# -> IPv6 -> State# s -> State# s
writeOffAddr# :: Addr# -> Int# -> IPv6 -> State# s -> State# s
$cwriteOffAddr# :: forall s. Addr# -> Int# -> IPv6 -> State# s -> State# s
readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, IPv6 #)
$creadOffAddr# :: forall s. Addr# -> Int# -> State# s -> (# State# s, IPv6 #)
indexOffAddr# :: Addr# -> Int# -> IPv6
$cindexOffAddr# :: Addr# -> Int# -> IPv6
setByteArray# :: MutableByteArray# s -> Int# -> Int# -> IPv6 -> State# s -> State# s
$csetByteArray# :: forall s.
MutableByteArray# s -> Int# -> Int# -> IPv6 -> State# s -> State# s
writeByteArray# :: MutableByteArray# s -> Int# -> IPv6 -> State# s -> State# s
$cwriteByteArray# :: forall s.
MutableByteArray# s -> Int# -> IPv6 -> State# s -> State# s
readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, IPv6 #)
$creadByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, IPv6 #)
indexByteArray# :: ByteArray# -> Int# -> IPv6
$cindexByteArray# :: ByteArray# -> Int# -> IPv6
alignment# :: IPv6 -> Int#
$calignment# :: IPv6 -> Int#
sizeOf# :: IPv6 -> Int#
$csizeOf# :: IPv6 -> Int#
Prim,Ord IPv6
Ord IPv6
-> ((IPv6, IPv6) -> [IPv6])
-> ((IPv6, IPv6) -> IPv6 -> Int)
-> ((IPv6, IPv6) -> IPv6 -> Int)
-> ((IPv6, IPv6) -> IPv6 -> Bool)
-> ((IPv6, IPv6) -> Int)
-> ((IPv6, IPv6) -> Int)
-> Ix IPv6
(IPv6, IPv6) -> Int
(IPv6, IPv6) -> [IPv6]
(IPv6, IPv6) -> IPv6 -> Bool
(IPv6, IPv6) -> IPv6 -> Int
forall a.
Ord a
-> ((a, a) -> [a])
-> ((a, a) -> a -> Int)
-> ((a, a) -> a -> Int)
-> ((a, a) -> a -> Bool)
-> ((a, a) -> Int)
-> ((a, a) -> Int)
-> Ix a
unsafeRangeSize :: (IPv6, IPv6) -> Int
$cunsafeRangeSize :: (IPv6, IPv6) -> Int
rangeSize :: (IPv6, IPv6) -> Int
$crangeSize :: (IPv6, IPv6) -> Int
inRange :: (IPv6, IPv6) -> IPv6 -> Bool
$cinRange :: (IPv6, IPv6) -> IPv6 -> Bool
unsafeIndex :: (IPv6, IPv6) -> IPv6 -> Int
$cunsafeIndex :: (IPv6, IPv6) -> IPv6 -> Int
index :: (IPv6, IPv6) -> IPv6 -> Int
$cindex :: (IPv6, IPv6) -> IPv6 -> Int
range :: (IPv6, IPv6) -> [IPv6]
$crange :: (IPv6, IPv6) -> [IPv6]
$cp1Ix :: Ord IPv6
Ix,Typeable IPv6
DataType
Constr
Typeable IPv6
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IPv6 -> c IPv6)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IPv6)
-> (IPv6 -> Constr)
-> (IPv6 -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c IPv6))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IPv6))
-> ((forall b. Data b => b -> b) -> IPv6 -> IPv6)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IPv6 -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IPv6 -> r)
-> (forall u. (forall d. Data d => d -> u) -> IPv6 -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> IPv6 -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> IPv6 -> m IPv6)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IPv6 -> m IPv6)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IPv6 -> m IPv6)
-> Data IPv6
IPv6 -> DataType
IPv6 -> Constr
(forall b. Data b => b -> b) -> IPv6 -> IPv6
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IPv6 -> c IPv6
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IPv6
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> IPv6 -> u
forall u. (forall d. Data d => d -> u) -> IPv6 -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IPv6 -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IPv6 -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> IPv6 -> m IPv6
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IPv6 -> m IPv6
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IPv6
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IPv6 -> c IPv6
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c IPv6)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IPv6)
$cIPv6 :: Constr
$tIPv6 :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> IPv6 -> m IPv6
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IPv6 -> m IPv6
gmapMp :: (forall d. Data d => d -> m d) -> IPv6 -> m IPv6
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IPv6 -> m IPv6
gmapM :: (forall d. Data d => d -> m d) -> IPv6 -> m IPv6
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> IPv6 -> m IPv6
gmapQi :: Int -> (forall d. Data d => d -> u) -> IPv6 -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> IPv6 -> u
gmapQ :: (forall d. Data d => d -> u) -> IPv6 -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> IPv6 -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IPv6 -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IPv6 -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IPv6 -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IPv6 -> r
gmapT :: (forall b. Data b => b -> b) -> IPv6 -> IPv6
$cgmapT :: (forall b. Data b => b -> b) -> IPv6 -> IPv6
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IPv6)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IPv6)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c IPv6)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c IPv6)
dataTypeOf :: IPv6 -> DataType
$cdataTypeOf :: IPv6 -> DataType
toConstr :: IPv6 -> Constr
$ctoConstr :: IPv6 -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IPv6
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IPv6
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IPv6 -> c IPv6
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IPv6 -> c IPv6
$cp1Data :: Typeable IPv6
Data)
instance Show IPv6 where
showsPrec :: Int -> IPv6 -> ShowS
showsPrec Int
p IPv6
addr = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10)
(ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ String -> ShowS
showString String
"ipv6 "
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word16 -> ShowS
showHexWord16 Word16
a
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
' '
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word16 -> ShowS
showHexWord16 Word16
b
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
' '
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word16 -> ShowS
showHexWord16 Word16
c
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
' '
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word16 -> ShowS
showHexWord16 Word16
d
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
' '
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word16 -> ShowS
showHexWord16 Word16
e
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
' '
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word16 -> ShowS
showHexWord16 Word16
f
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
' '
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word16 -> ShowS
showHexWord16 Word16
g
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
' '
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word16 -> ShowS
showHexWord16 Word16
h
where
(Word16
a,Word16
b,Word16
c,Word16
d,Word16
e,Word16
f,Word16
g,Word16
h) = IPv6
-> (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16)
toWord16s IPv6
addr
print :: IPv6 -> IO ()
print :: IPv6 -> IO ()
print = Text -> IO ()
TIO.putStrLn (Text -> IO ()) -> (IPv6 -> Text) -> IPv6 -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IPv6 -> Text
encode
decodeShort :: ShortText -> Maybe IPv6
decodeShort :: ShortText -> Maybe IPv6
decodeShort ShortText
t = Bytes -> Maybe IPv6
decodeUtf8Bytes (ByteArray -> Bytes
Bytes.fromByteArray ByteArray
b)
where b :: ByteArray
b = ShortByteString -> ByteArray
shortByteStringToByteArray (ShortText -> ShortByteString
TS.toShortByteString ShortText
t)
shortByteStringToByteArray :: BSS.ShortByteString -> PM.ByteArray
shortByteStringToByteArray :: ShortByteString -> ByteArray
shortByteStringToByteArray (BSS.SBS ByteArray#
x) = ByteArray# -> ByteArray
PM.ByteArray ByteArray#
x
showHexWord16 :: Word16 -> ShowS
showHexWord16 :: Word16 -> ShowS
showHexWord16 Word16
w =
String -> ShowS
showString String
"0x"
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar (Word -> Char
nibbleToHex (Word -> Int -> Word
forall a. Bits a => a -> Int -> a
unsafeShiftR (Word16 -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
w) Int
12))
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar (Word -> Char
nibbleToHex ((Word -> Int -> Word
forall a. Bits a => a -> Int -> a
unsafeShiftR (Word16 -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
w) Int
8) Word -> Word -> Word
forall a. Bits a => a -> a -> a
.&. Word
0xF))
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar (Word -> Char
nibbleToHex ((Word -> Int -> Word
forall a. Bits a => a -> Int -> a
unsafeShiftR (Word16 -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
w) Int
4) Word -> Word -> Word
forall a. Bits a => a -> a -> a
.&. Word
0xF))
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar (Word -> Char
nibbleToHex ((Word16 -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
w) Word -> Word -> Word
forall a. Bits a => a -> a -> a
.&. Word
0xF))
nibbleToHex :: Word -> Char
nibbleToHex :: Word -> Char
nibbleToHex Word
w
| Word
w Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
< Word
10 = Int -> Char
chr (Word -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word
w Word -> Word -> Word
forall a. Num a => a -> a -> a
+ Word
48))
| Bool
otherwise = Int -> Char
chr (Word -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word
w Word -> Word -> Word
forall a. Num a => a -> a -> a
+ Word
87))
instance Read IPv6 where
readPrec :: ReadPrec IPv6
readPrec = ReadPrec IPv6 -> ReadPrec IPv6
forall a. ReadPrec a -> ReadPrec a
parens (ReadPrec IPv6 -> ReadPrec IPv6) -> ReadPrec IPv6 -> ReadPrec IPv6
forall a b. (a -> b) -> a -> b
$ Int -> ReadPrec IPv6 -> ReadPrec IPv6
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
10 (ReadPrec IPv6 -> ReadPrec IPv6) -> ReadPrec IPv6 -> ReadPrec IPv6
forall a b. (a -> b) -> a -> b
$ do
Ident String
"ipv6" <- ReadPrec Lexeme
lexP
Word16
a <- ReadPrec Word16 -> ReadPrec Word16
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Word16
forall a. Read a => ReadPrec a
readPrec
Word16
b <- ReadPrec Word16 -> ReadPrec Word16
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Word16
forall a. Read a => ReadPrec a
readPrec
Word16
c <- ReadPrec Word16 -> ReadPrec Word16
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Word16
forall a. Read a => ReadPrec a
readPrec
Word16
d <- ReadPrec Word16 -> ReadPrec Word16
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Word16
forall a. Read a => ReadPrec a
readPrec
Word16
e <- ReadPrec Word16 -> ReadPrec Word16
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Word16
forall a. Read a => ReadPrec a
readPrec
Word16
f <- ReadPrec Word16 -> ReadPrec Word16
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Word16
forall a. Read a => ReadPrec a
readPrec
Word16
g <- ReadPrec Word16 -> ReadPrec Word16
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Word16
forall a. Read a => ReadPrec a
readPrec
Word16
h <- ReadPrec Word16 -> ReadPrec Word16
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Word16
forall a. Read a => ReadPrec a
readPrec
IPv6 -> ReadPrec IPv6
forall (m :: * -> *) a. Monad m => a -> m a
return (Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> IPv6
fromWord16s Word16
a Word16
b Word16
c Word16
d Word16
e Word16
f Word16
g Word16
h)
instance Aeson.ToJSON IPv6 where
toJSON :: IPv6 -> Value
toJSON = Text -> Value
Aeson.String (Text -> Value) -> (IPv6 -> Text) -> IPv6 -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IPv6 -> Text
encode
instance Aeson.FromJSON IPv6 where
parseJSON :: Value -> Parser IPv6
parseJSON = String -> (Text -> Parser IPv6) -> Value -> Parser IPv6
forall a. String -> (Text -> Parser a) -> Value -> Parser a
Aeson.withText String
"IPv6" ((Text -> Parser IPv6) -> Value -> Parser IPv6)
-> (Text -> Parser IPv6) -> Value -> Parser IPv6
forall a b. (a -> b) -> a -> b
$ \Text
t -> case Text -> Maybe IPv6
decode Text
t of
Maybe IPv6
Nothing -> String -> Parser IPv6
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"invalid IPv6 address"
Just IPv6
i -> IPv6 -> Parser IPv6
forall (m :: * -> *) a. Monad m => a -> m a
return IPv6
i
rightToMaybe :: Either a b -> Maybe b
rightToMaybe :: Either a b -> Maybe b
rightToMaybe = (a -> Maybe b) -> (b -> Maybe b) -> Either a b -> Maybe b
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe b -> a -> Maybe b
forall a b. a -> b -> a
const Maybe b
forall a. Maybe a
Nothing) b -> Maybe b
forall a. a -> Maybe a
Just
fromOctets ::
Word8 -> Word8 -> Word8 -> Word8
-> Word8 -> Word8 -> Word8 -> Word8
-> Word8 -> Word8 -> Word8 -> Word8
-> Word8 -> Word8 -> Word8 -> Word8
-> IPv6
fromOctets :: Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> IPv6
fromOctets Word8
a Word8
b Word8
c Word8
d Word8
e Word8
f Word8
g Word8
h Word8
i Word8
j Word8
k Word8
l Word8
m Word8
n Word8
o Word8
p =
Word128 -> IPv6
IPv6 (Word128 -> IPv6) -> Word128 -> IPv6
forall a b. (a -> b) -> a -> b
$ Word128
-> Word128
-> Word128
-> Word128
-> Word128
-> Word128
-> Word128
-> Word128
-> Word128
-> Word128
-> Word128
-> Word128
-> Word128
-> Word128
-> Word128
-> Word128
-> Word128
fromOctetsWord128
(Word8 -> Word128
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
a) (Word8 -> Word128
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
b) (Word8 -> Word128
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
c) (Word8 -> Word128
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
d)
(Word8 -> Word128
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
e) (Word8 -> Word128
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
f) (Word8 -> Word128
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
g) (Word8 -> Word128
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
h)
(Word8 -> Word128
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
i) (Word8 -> Word128
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
j) (Word8 -> Word128
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
k) (Word8 -> Word128
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
l)
(Word8 -> Word128
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
m) (Word8 -> Word128
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
n) (Word8 -> Word128
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
o) (Word8 -> Word128
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
p)
fromOctetsWord128 ::
Word128 -> Word128 -> Word128 -> Word128
-> Word128 -> Word128 -> Word128 -> Word128
-> Word128 -> Word128 -> Word128 -> Word128
-> Word128 -> Word128 -> Word128 -> Word128
-> Word128
fromOctetsWord128 :: Word128
-> Word128
-> Word128
-> Word128
-> Word128
-> Word128
-> Word128
-> Word128
-> Word128
-> Word128
-> Word128
-> Word128
-> Word128
-> Word128
-> Word128
-> Word128
-> Word128
fromOctetsWord128 Word128
a Word128
b Word128
c Word128
d Word128
e Word128
f Word128
g Word128
h Word128
i Word128
j Word128
k Word128
l Word128
m Word128
n Word128
o Word128
p = Word128 -> Word128
forall a b. (Integral a, Num b) => a -> b
fromIntegral
( Word128 -> Int -> Word128
forall a. Bits a => a -> Int -> a
shiftL Word128
a Int
120
Word128 -> Word128 -> Word128
forall a. Bits a => a -> a -> a
.|. Word128 -> Int -> Word128
forall a. Bits a => a -> Int -> a
shiftL Word128
b Int
112
Word128 -> Word128 -> Word128
forall a. Bits a => a -> a -> a
.|. Word128 -> Int -> Word128
forall a. Bits a => a -> Int -> a
shiftL Word128
c Int
104
Word128 -> Word128 -> Word128
forall a. Bits a => a -> a -> a
.|. Word128 -> Int -> Word128
forall a. Bits a => a -> Int -> a
shiftL Word128
d Int
96
Word128 -> Word128 -> Word128
forall a. Bits a => a -> a -> a
.|. Word128 -> Int -> Word128
forall a. Bits a => a -> Int -> a
shiftL Word128
e Int
88
Word128 -> Word128 -> Word128
forall a. Bits a => a -> a -> a
.|. Word128 -> Int -> Word128
forall a. Bits a => a -> Int -> a
shiftL Word128
f Int
80
Word128 -> Word128 -> Word128
forall a. Bits a => a -> a -> a
.|. Word128 -> Int -> Word128
forall a. Bits a => a -> Int -> a
shiftL Word128
g Int
72
Word128 -> Word128 -> Word128
forall a. Bits a => a -> a -> a
.|. Word128 -> Int -> Word128
forall a. Bits a => a -> Int -> a
shiftL Word128
h Int
64
Word128 -> Word128 -> Word128
forall a. Bits a => a -> a -> a
.|. Word128 -> Int -> Word128
forall a. Bits a => a -> Int -> a
shiftL Word128
i Int
56
Word128 -> Word128 -> Word128
forall a. Bits a => a -> a -> a
.|. Word128 -> Int -> Word128
forall a. Bits a => a -> Int -> a
shiftL Word128
j Int
48
Word128 -> Word128 -> Word128
forall a. Bits a => a -> a -> a
.|. Word128 -> Int -> Word128
forall a. Bits a => a -> Int -> a
shiftL Word128
k Int
40
Word128 -> Word128 -> Word128
forall a. Bits a => a -> a -> a
.|. Word128 -> Int -> Word128
forall a. Bits a => a -> Int -> a
shiftL Word128
l Int
32
Word128 -> Word128 -> Word128
forall a. Bits a => a -> a -> a
.|. Word128 -> Int -> Word128
forall a. Bits a => a -> Int -> a
shiftL Word128
m Int
24
Word128 -> Word128 -> Word128
forall a. Bits a => a -> a -> a
.|. Word128 -> Int -> Word128
forall a. Bits a => a -> Int -> a
shiftL Word128
n Int
16
Word128 -> Word128 -> Word128
forall a. Bits a => a -> a -> a
.|. Word128 -> Int -> Word128
forall a. Bits a => a -> Int -> a
shiftL Word128
o Int
8
Word128 -> Word128 -> Word128
forall a. Bits a => a -> a -> a
.|. Word128
p
)
ipv6 ::
Word16 -> Word16 -> Word16 -> Word16
-> Word16 -> Word16 -> Word16 -> Word16
-> IPv6
ipv6 :: Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> IPv6
ipv6 = Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> IPv6
fromWord16s
fromWord16s ::
Word16 -> Word16 -> Word16 -> Word16
-> Word16 -> Word16 -> Word16 -> Word16
-> IPv6
fromWord16s :: Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> IPv6
fromWord16s Word16
a Word16
b Word16
c Word16
d Word16
e Word16
f Word16
g Word16
h =
Word128 -> IPv6
IPv6 (Word128 -> IPv6) -> Word128 -> IPv6
forall a b. (a -> b) -> a -> b
$ Word128
-> Word128
-> Word128
-> Word128
-> Word128
-> Word128
-> Word128
-> Word128
-> Word128
fromWord16sWord128
(Word16 -> Word128
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
a) (Word16 -> Word128
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
b) (Word16 -> Word128
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
c) (Word16 -> Word128
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
d)
(Word16 -> Word128
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
e) (Word16 -> Word128
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
f) (Word16 -> Word128
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
g) (Word16 -> Word128
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
h)
fromWord16sWord128 ::
Word128 -> Word128 -> Word128 -> Word128
-> Word128 -> Word128 -> Word128 -> Word128
-> Word128
fromWord16sWord128 :: Word128
-> Word128
-> Word128
-> Word128
-> Word128
-> Word128
-> Word128
-> Word128
-> Word128
fromWord16sWord128 Word128
a Word128
b Word128
c Word128
d Word128
e Word128
f Word128
g Word128
h = Word128 -> Word128
forall a b. (Integral a, Num b) => a -> b
fromIntegral
( Word128 -> Int -> Word128
forall a. Bits a => a -> Int -> a
shiftL Word128
a Int
112
Word128 -> Word128 -> Word128
forall a. Bits a => a -> a -> a
.|. Word128 -> Int -> Word128
forall a. Bits a => a -> Int -> a
shiftL Word128
b Int
96
Word128 -> Word128 -> Word128
forall a. Bits a => a -> a -> a
.|. Word128 -> Int -> Word128
forall a. Bits a => a -> Int -> a
shiftL Word128
c Int
80
Word128 -> Word128 -> Word128
forall a. Bits a => a -> a -> a
.|. Word128 -> Int -> Word128
forall a. Bits a => a -> Int -> a
shiftL Word128
d Int
64
Word128 -> Word128 -> Word128
forall a. Bits a => a -> a -> a
.|. Word128 -> Int -> Word128
forall a. Bits a => a -> Int -> a
shiftL Word128
e Int
48
Word128 -> Word128 -> Word128
forall a. Bits a => a -> a -> a
.|. Word128 -> Int -> Word128
forall a. Bits a => a -> Int -> a
shiftL Word128
f Int
32
Word128 -> Word128 -> Word128
forall a. Bits a => a -> a -> a
.|. Word128 -> Int -> Word128
forall a. Bits a => a -> Int -> a
shiftL Word128
g Int
16
Word128 -> Word128 -> Word128
forall a. Bits a => a -> a -> a
.|. Word128
h
)
toWord16s :: IPv6 -> (Word16,Word16,Word16,Word16,Word16,Word16,Word16,Word16)
toWord16s :: IPv6
-> (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16)
toWord16s (IPv6 (Word128 Word64
a Word64
b)) =
( Word64 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
unsafeShiftR Word64
a Int
48)
, Word64 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
unsafeShiftR Word64
a Int
32)
, Word64 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
unsafeShiftR Word64
a Int
16)
, Word64 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
a
, Word64 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
unsafeShiftR Word64
b Int
48)
, Word64 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
unsafeShiftR Word64
b Int
32)
, Word64 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
unsafeShiftR Word64
b Int
16)
, Word64 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
b
)
fromTupleWord16s :: (Word16,Word16,Word16,Word16,Word16,Word16,Word16,Word16) -> IPv6
fromTupleWord16s :: (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16)
-> IPv6
fromTupleWord16s (Word16
a,Word16
b,Word16
c,Word16
d,Word16
e,Word16
f,Word16
g,Word16
h) = Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> IPv6
fromWord16s Word16
a Word16
b Word16
c Word16
d Word16
e Word16
f Word16
g Word16
h
fromWord32s :: Word32 -> Word32 -> Word32 -> Word32 -> IPv6
fromWord32s :: Word32 -> Word32 -> Word32 -> Word32 -> IPv6
fromWord32s Word32
a Word32
b Word32
c Word32
d =
Word128 -> IPv6
IPv6 (Word128 -> IPv6) -> Word128 -> IPv6
forall a b. (a -> b) -> a -> b
$ Word128 -> Word128 -> Word128 -> Word128 -> Word128
fromWord32sWord128
(Word32 -> Word128
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
a) (Word32 -> Word128
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
b) (Word32 -> Word128
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
c) (Word32 -> Word128
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
d)
fromWord32sWord128 ::
Word128 -> Word128 -> Word128 -> Word128
-> Word128
fromWord32sWord128 :: Word128 -> Word128 -> Word128 -> Word128 -> Word128
fromWord32sWord128 Word128
a Word128
b Word128
c Word128
d = Word128 -> Word128
forall a b. (Integral a, Num b) => a -> b
fromIntegral
( Word128 -> Int -> Word128
forall a. Bits a => a -> Int -> a
shiftL Word128
a Int
96
Word128 -> Word128 -> Word128
forall a. Bits a => a -> a -> a
.|. Word128 -> Int -> Word128
forall a. Bits a => a -> Int -> a
shiftL Word128
b Int
64
Word128 -> Word128 -> Word128
forall a. Bits a => a -> a -> a
.|. Word128 -> Int -> Word128
forall a. Bits a => a -> Int -> a
shiftL Word128
c Int
32
Word128 -> Word128 -> Word128
forall a. Bits a => a -> a -> a
.|. Word128
d
)
fromTupleWord32s :: (Word32,Word32,Word32,Word32) -> IPv6
fromTupleWord32s :: (Word32, Word32, Word32, Word32) -> IPv6
fromTupleWord32s (Word32
a,Word32
b,Word32
c,Word32
d) = Word32 -> Word32 -> Word32 -> Word32 -> IPv6
fromWord32s Word32
a Word32
b Word32
c Word32
d
toWord32s :: IPv6 -> (Word32,Word32,Word32,Word32)
toWord32s :: IPv6 -> (Word32, Word32, Word32, Word32)
toWord32s (IPv6 (Word128 Word64
a Word64
b)) =
( Word64 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
unsafeShiftR Word64
a Int
32)
, Word64 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
a
, Word64 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
unsafeShiftR Word64
b Int
32)
, Word64 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
b
)
loopback :: IPv6
loopback :: IPv6
loopback = Word128 -> IPv6
IPv6 (Word64 -> Word64 -> Word128
Word128 Word64
0 Word64
1)
localhost :: IPv6
localhost :: IPv6
localhost = IPv6
loopback
any :: IPv6
any :: IPv6
any = Word128 -> IPv6
IPv6 Word128
zeroWord128
encode :: IPv6 -> Text
encode :: IPv6 -> Text
encode !IPv6
ip =
if IPv6 -> Bool
isIPv4Mapped IPv6
ip
then
String -> Text
Text.pack String
"::ffff:"
Text -> Text -> Text
forall a. Monoid a => a -> a -> a
`mappend`
IPv4 -> Text
IPv4.encode (Word32 -> IPv4
IPv4.IPv4 (Word16 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
w7 Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
`unsafeShiftL` Int
16 Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.|. Word16 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
w8))
else [Word16] -> Text
forall a. (Integral a, Show a) => [a] -> Text
toText [Word16
w1, Word16
w2, Word16
w3, Word16
w4, Word16
w5, Word16
w6, Word16
w7, Word16
w8]
where
(Word16
w1, Word16
w2, Word16
w3, Word16
w4, Word16
w5, Word16
w6, Word16
w7, Word16
w8) = IPv6
-> (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16)
toWord16s IPv6
ip
toText :: [a] -> Text
toText [a]
ws = String -> Text
Text.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
":"
([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ Int -> Int -> [(a, Int)] -> [String]
forall a.
(Integral a, Show a) =>
Int -> Int -> [(a, Int)] -> [String]
expand Int
0 (if Int
longestZ Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
1 then Int
longestZ else Int
0) [(a, Int)]
grouped
where
expand :: Int -> Int -> [(a, Int)] -> [String]
expand !Int
_ Int
8 ![(a, Int)]
_ = [String
"::"]
expand !Int
_ !Int
_ [] = []
expand !Int
i !Int
longest ((a
x, Int
len):[(a, Int)]
wsNext)
| a
x a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
0 Bool -> Bool -> Bool
&& Int
len Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
longest =
(if Int
i Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 Bool -> Bool -> Bool
|| (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
len) Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
8 then String
":" else String
"")
String -> [String] -> [String]
forall a. a -> [a] -> [a]
: Int -> Int -> [(a, Int)] -> [String]
expand (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
len) Int
0 [(a, Int)]
wsNext
| Bool
otherwise = Int -> String -> [String]
forall a. Int -> a -> [a]
replicate Int
len (a -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex a
x String
"") [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ Int -> Int -> [(a, Int)] -> [String]
expand (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
len) Int
longest [(a, Int)]
wsNext
longestZ :: Int
longestZ = [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum ([Int] -> Int) -> ([(a, Int)] -> [Int]) -> [(a, Int)] -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int
0Int -> [Int] -> [Int]
forall a. a -> [a] -> [a]
:) ([Int] -> [Int]) -> ([(a, Int)] -> [Int]) -> [(a, Int)] -> [Int]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((a, Int) -> Int) -> [(a, Int)] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map (a, Int) -> Int
forall a b. (a, b) -> b
snd ([(a, Int)] -> [Int])
-> ([(a, Int)] -> [(a, Int)]) -> [(a, Int)] -> [Int]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((a, Int) -> Bool) -> [(a, Int)] -> [(a, Int)]
forall a. (a -> Bool) -> [a] -> [a]
filter ((a -> a -> Bool
forall a. Eq a => a -> a -> Bool
==a
0) (a -> Bool) -> ((a, Int) -> a) -> (a, Int) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a, Int) -> a
forall a b. (a, b) -> a
fst) ([(a, Int)] -> Int) -> [(a, Int)] -> Int
forall a b. (a -> b) -> a -> b
$ [(a, Int)]
grouped
grouped :: [(a, Int)]
grouped = ([a] -> (a, Int)) -> [[a]] -> [(a, Int)]
forall a b. (a -> b) -> [a] -> [b]
map (\[a]
x -> ([a] -> a
forall a. [a] -> a
head [a]
x, [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
x)) ([a] -> [[a]]
forall a. Eq a => [a] -> [[a]]
group [a]
ws)
isIPv4Mapped :: IPv6 -> Bool
isIPv4Mapped :: IPv6 -> Bool
isIPv4Mapped (IPv6 (Word128 Word64
w1 Word64
w2)) =
Word64
w1 Word64 -> Word64 -> Bool
forall a. Eq a => a -> a -> Bool
== Word64
0 Bool -> Bool -> Bool
&& (Word64
0xFFFFFFFF00000000 Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.&. Word64
w2 Word64 -> Word64 -> Bool
forall a. Eq a => a -> a -> Bool
== Word64
0x0000FFFF00000000)
decodeUtf8Bytes :: Bytes.Bytes -> Maybe IPv6
decodeUtf8Bytes :: Bytes -> Maybe IPv6
decodeUtf8Bytes !Bytes
b = case (forall s. Parser () s IPv6) -> Bytes -> Result () IPv6
forall e a. (forall s. Parser e s a) -> Bytes -> Result e a
Parser.parseBytes (() -> Parser () s IPv6
forall e s. e -> Parser e s IPv6
parserUtf8Bytes ()) Bytes
b of
Parser.Success (Parser.Slice Int
_ Int
len IPv6
addr) -> case Int
len of
Int
0 -> IPv6 -> Maybe IPv6
forall a. a -> Maybe a
Just IPv6
addr
Int
_ -> Maybe IPv6
forall a. Maybe a
Nothing
Parser.Failure ()
_ -> Maybe IPv6
forall a. Maybe a
Nothing
boundedBuilderUtf8 :: IPv6 -> BB.Builder 39
boundedBuilderUtf8 :: IPv6 -> Builder 39
boundedBuilderUtf8 !ip :: IPv6
ip@(IPv6 (Word128 Word64
hi Word64
lo))
| Word64
hi Word64 -> Word64 -> Bool
forall a. Eq a => a -> a -> Bool
== Word64
0 Bool -> Bool -> Bool
&& Word64
lo Word64 -> Word64 -> Bool
forall a. Eq a => a -> a -> Bool
== Word64
0 = (2 <= 39) -> Builder 2 -> Builder 39
forall (m :: Nat) (n :: Nat). (m <= n) -> Builder m -> Builder n
BB.weaken 2 <= 39
forall (a :: Nat) (b :: Nat).
(IsLte (CmpNat a b) ~ 'True) =>
a <= b
Lte.constant
(Char -> Builder 1
BB.ascii Char
':' Builder 1 -> Builder 1 -> Builder (1 + 1)
forall (m :: Nat) (n :: Nat).
Builder m -> Builder n -> Builder (m + n)
`BB.append` Char -> Builder 1
BB.ascii Char
':')
| IPv6 -> Bool
isIPv4Mapped IPv6
ip = (22 <= 39) -> Builder 22 -> Builder 39
forall (m :: Nat) (n :: Nat). (m <= n) -> Builder m -> Builder n
BB.weaken 22 <= 39
forall (a :: Nat) (b :: Nat).
(IsLte (CmpNat a b) ~ 'True) =>
a <= b
Lte.constant (Builder 22 -> Builder 39) -> Builder 22 -> Builder 39
forall a b. (a -> b) -> a -> b
$
Char -> Builder 1
BB.ascii Char
':'
Builder 1 -> Builder 21 -> Builder (1 + 21)
forall (m :: Nat) (n :: Nat).
Builder m -> Builder n -> Builder (m + n)
`BB.append`
Char -> Builder 1
BB.ascii Char
':'
Builder 1 -> Builder 20 -> Builder (1 + 20)
forall (m :: Nat) (n :: Nat).
Builder m -> Builder n -> Builder (m + n)
`BB.append`
Char -> Builder 1
BB.ascii Char
'f'
Builder 1 -> Builder 19 -> Builder (1 + 19)
forall (m :: Nat) (n :: Nat).
Builder m -> Builder n -> Builder (m + n)
`BB.append`
Char -> Builder 1
BB.ascii Char
'f'
Builder 1 -> Builder 18 -> Builder (1 + 18)
forall (m :: Nat) (n :: Nat).
Builder m -> Builder n -> Builder (m + n)
`BB.append`
Char -> Builder 1
BB.ascii Char
'f'
Builder 1 -> Builder 17 -> Builder (1 + 17)
forall (m :: Nat) (n :: Nat).
Builder m -> Builder n -> Builder (m + n)
`BB.append`
Char -> Builder 1
BB.ascii Char
'f'
Builder 1 -> Builder 16 -> Builder (1 + 16)
forall (m :: Nat) (n :: Nat).
Builder m -> Builder n -> Builder (m + n)
`BB.append`
Char -> Builder 1
BB.ascii Char
':'
Builder 1 -> Builder 15 -> Builder (1 + 15)
forall (m :: Nat) (n :: Nat).
Builder m -> Builder n -> Builder (m + n)
`BB.append`
IPv4 -> Builder 15
IPv4.boundedBuilderUtf8 (Word32 -> IPv4
IPv4.IPv4 (Word64 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
lo))
| Bool
otherwise =
let (Word16
w0,Word16
w1,Word16
w2,Word16
w3,Word16
w4,Word16
w5,Word16
w6,Word16
w7) = IPv6
-> (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16)
toWord16s IPv6
ip
IntTriple Int
startLongest Int
longest Int
_ = Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> IntTriple
longestRun Word16
w0 Word16
w1 Word16
w2 Word16
w3 Word16
w4 Word16
w5 Word16
w6 Word16
w7
start :: Int
start = Int
startLongest
end :: Int
end = Int
start Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
longest
in Word16 -> Int -> Builder 4
firstPiece Word16
w0 Int
start
Builder 4 -> Builder 35 -> Builder (4 + 35)
forall (m :: Nat) (n :: Nat).
Builder m -> Builder n -> Builder (m + n)
`BB.append`
Int -> Word16 -> Int -> Int -> Builder 5
piece Int
1 Word16
w1 Int
start Int
end
Builder 5 -> Builder 30 -> Builder (5 + 30)
forall (m :: Nat) (n :: Nat).
Builder m -> Builder n -> Builder (m + n)
`BB.append`
Int -> Word16 -> Int -> Int -> Builder 5
piece Int
2 Word16
w2 Int
start Int
end
Builder 5 -> Builder 25 -> Builder (5 + 25)
forall (m :: Nat) (n :: Nat).
Builder m -> Builder n -> Builder (m + n)
`BB.append`
Int -> Word16 -> Int -> Int -> Builder 5
piece Int
3 Word16
w3 Int
start Int
end
Builder 5 -> Builder 20 -> Builder (5 + 20)
forall (m :: Nat) (n :: Nat).
Builder m -> Builder n -> Builder (m + n)
`BB.append`
Int -> Word16 -> Int -> Int -> Builder 5
piece Int
4 Word16
w4 Int
start Int
end
Builder 5 -> Builder 15 -> Builder (5 + 15)
forall (m :: Nat) (n :: Nat).
Builder m -> Builder n -> Builder (m + n)
`BB.append`
Int -> Word16 -> Int -> Int -> Builder 5
piece Int
5 Word16
w5 Int
start Int
end
Builder 5 -> Builder 10 -> Builder (5 + 10)
forall (m :: Nat) (n :: Nat).
Builder m -> Builder n -> Builder (m + n)
`BB.append`
Int -> Word16 -> Int -> Int -> Builder 5
piece Int
6 Word16
w6 Int
start Int
end
Builder 5 -> Builder 5 -> Builder (5 + 5)
forall (m :: Nat) (n :: Nat).
Builder m -> Builder n -> Builder (m + n)
`BB.append`
Word16 -> Int -> Builder 5
lastPiece Word16
w7 Int
end
firstPiece :: Word16 -> Int -> BB.Builder 4
firstPiece :: Word16 -> Int -> Builder 4
firstPiece !Word16
w !Int
start = case Int
start of
Int
0 -> (1 <= 4) -> Builder 1 -> Builder 4
forall (m :: Nat) (n :: Nat). (m <= n) -> Builder m -> Builder n
BB.weaken 1 <= 4
forall (a :: Nat) (b :: Nat).
(IsLte (CmpNat a b) ~ 'True) =>
a <= b
Lte.constant (Char -> Builder 1
BB.ascii Char
':')
Int
_ -> Word16 -> Builder 4
BB.word16LowerHex Word16
w
piece :: Int -> Word16 -> Int -> Int -> BB.Builder 5
{-# inline piece #-}
piece :: Int -> Word16 -> Int -> Int -> Builder 5
piece (I# Int#
ix) (W16# Word#
w) (I# Int#
start) (I# Int#
end) =
Int# -> Word# -> Int# -> Int# -> Builder 5
piece# Int#
ix Word#
w Int#
start Int#
end
piece# :: Int# -> Word# -> Int# -> Int# -> BB.Builder 5
{-# noinline piece# #-}
piece# :: Int# -> Word# -> Int# -> Int# -> Builder 5
piece# !Int#
ix# !Word#
w# !Int#
start# !Int#
end# = case Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Int
ix Int
start of
Ordering
LT -> Char -> Builder 1
BB.ascii Char
':' Builder 1 -> Builder 4 -> Builder (1 + 4)
forall (m :: Nat) (n :: Nat).
Builder m -> Builder n -> Builder (m + n)
`BB.append` Word16 -> Builder 4
BB.word16LowerHex Word16
w
Ordering
EQ -> (1 <= 5) -> Builder 1 -> Builder 5
forall (m :: Nat) (n :: Nat). (m <= n) -> Builder m -> Builder n
BB.weaken 1 <= 5
forall (a :: Nat) (b :: Nat).
(IsLte (CmpNat a b) ~ 'True) =>
a <= b
Lte.constant (Char -> Builder 1
BB.ascii Char
':')
Ordering
GT -> if Int
ix Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
end
then (0 <= 5) -> Builder 0 -> Builder 5
forall (m :: Nat) (n :: Nat). (m <= n) -> Builder m -> Builder n
BB.weaken 0 <= 5
forall (a :: Nat) (b :: Nat).
(IsLte (CmpNat a b) ~ 'True) =>
a <= b
Lte.constant Builder 0
BB.empty
else Char -> Builder 1
BB.ascii Char
':' Builder 1 -> Builder 4 -> Builder (1 + 4)
forall (m :: Nat) (n :: Nat).
Builder m -> Builder n -> Builder (m + n)
`BB.append` Word16 -> Builder 4
BB.word16LowerHex Word16
w
where
ix :: Int
ix = Int# -> Int
I# Int#
ix#
start :: Int
start = Int# -> Int
I# Int#
start#
end :: Int
end = Int# -> Int
I# Int#
end#
w :: Word16
w = Word# -> Word16
W16# Word#
w#
lastPiece :: Word16 -> Int -> BB.Builder 5
lastPiece :: Word16 -> Int -> Builder 5
lastPiece !Word16
w !Int
end = case Int
end of
Int
8 -> (1 <= 5) -> Builder 1 -> Builder 5
forall (m :: Nat) (n :: Nat). (m <= n) -> Builder m -> Builder n
BB.weaken 1 <= 5
forall (a :: Nat) (b :: Nat).
(IsLte (CmpNat a b) ~ 'True) =>
a <= b
Lte.constant (Char -> Builder 1
BB.ascii Char
':')
Int
_ -> Char -> Builder 1
BB.ascii Char
':' Builder 1 -> Builder 4 -> Builder (1 + 4)
forall (m :: Nat) (n :: Nat).
Builder m -> Builder n -> Builder (m + n)
`BB.append` Word16 -> Builder 4
BB.word16LowerHex Word16
w
data IntTriple = IntTriple !Int !Int !Int
stepZeroRunLength :: Int -> Word16 -> IntTriple -> IntTriple
stepZeroRunLength :: Int -> Word16 -> IntTriple -> IntTriple
stepZeroRunLength !Int
ix !Word16
w (IntTriple Int
startLongest Int
longest Int
current) = case Word16
w of
Word16
0 -> let !x :: Int
x = Int
current Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1 in
if Int
x Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
longest
then Int -> Int -> Int -> IntTriple
IntTriple (Int
ix Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
current) Int
x Int
x
else Int -> Int -> Int -> IntTriple
IntTriple Int
startLongest Int
longest Int
x
Word16
_ -> Int -> Int -> Int -> IntTriple
IntTriple Int
startLongest Int
longest Int
0
longestRun ::
Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> IntTriple
longestRun :: Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> IntTriple
longestRun !Word16
w0 !Word16
w1 !Word16
w2 !Word16
w3 !Word16
w4 !Word16
w5 !Word16
w6 !Word16
w7 = IntTriple -> IntTriple
forall a. a -> a
id
(IntTriple -> IntTriple) -> IntTriple -> IntTriple
forall a b. (a -> b) -> a -> b
$ Int -> Word16 -> IntTriple -> IntTriple
stepZeroRunLength Int
7 Word16
w7
(IntTriple -> IntTriple) -> IntTriple -> IntTriple
forall a b. (a -> b) -> a -> b
$ Int -> Word16 -> IntTriple -> IntTriple
stepZeroRunLength Int
6 Word16
w6
(IntTriple -> IntTriple) -> IntTriple -> IntTriple
forall a b. (a -> b) -> a -> b
$ Int -> Word16 -> IntTriple -> IntTriple
stepZeroRunLength Int
5 Word16
w5
(IntTriple -> IntTriple) -> IntTriple -> IntTriple
forall a b. (a -> b) -> a -> b
$ Int -> Word16 -> IntTriple -> IntTriple
stepZeroRunLength Int
4 Word16
w4
(IntTriple -> IntTriple) -> IntTriple -> IntTriple
forall a b. (a -> b) -> a -> b
$ Int -> Word16 -> IntTriple -> IntTriple
stepZeroRunLength Int
3 Word16
w3
(IntTriple -> IntTriple) -> IntTriple -> IntTriple
forall a b. (a -> b) -> a -> b
$ Int -> Word16 -> IntTriple -> IntTriple
stepZeroRunLength Int
2 Word16
w2
(IntTriple -> IntTriple) -> IntTriple -> IntTriple
forall a b. (a -> b) -> a -> b
$ Int -> Word16 -> IntTriple -> IntTriple
stepZeroRunLength Int
1 Word16
w1
(IntTriple -> IntTriple) -> IntTriple -> IntTriple
forall a b. (a -> b) -> a -> b
$ Int -> Word16 -> IntTriple -> IntTriple
stepZeroRunLength Int
0 Word16
w0
(IntTriple -> IntTriple) -> IntTriple -> IntTriple
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Int -> IntTriple
IntTriple (-Int
1) Int
1 Int
0
encodeShort :: IPv6 -> ShortText
encodeShort :: IPv6 -> ShortText
encodeShort IPv6
w = ShortText -> ShortText
forall a. a -> a
id
(ShortText -> ShortText) -> ShortText -> ShortText
forall a b. (a -> b) -> a -> b
$ ShortByteString -> ShortText
TS.fromShortByteStringUnsafe
(ShortByteString -> ShortText) -> ShortByteString -> ShortText
forall a b. (a -> b) -> a -> b
$ ByteArray -> ShortByteString
byteArrayToShortByteString
(ByteArray -> ShortByteString) -> ByteArray -> ShortByteString
forall a b. (a -> b) -> a -> b
$ Nat 39 -> Builder 39 -> ByteArray
forall (n :: Nat). Nat n -> Builder n -> ByteArray
BB.run Nat 39
forall (n :: Nat). KnownNat n => Nat n
Nat.constant
(Builder 39 -> ByteArray) -> Builder 39 -> ByteArray
forall a b. (a -> b) -> a -> b
$ IPv6 -> Builder 39
boundedBuilderUtf8
(IPv6 -> Builder 39) -> IPv6 -> Builder 39
forall a b. (a -> b) -> a -> b
$ IPv6
w
byteArrayToShortByteString :: PM.ByteArray -> BSS.ShortByteString
byteArrayToShortByteString :: ByteArray -> ShortByteString
byteArrayToShortByteString (PM.ByteArray ByteArray#
x) = ByteArray# -> ShortByteString
BSS.SBS ByteArray#
x
decode :: Text -> Maybe IPv6
decode :: Text -> Maybe IPv6
decode Text
t = Either String IPv6 -> Maybe IPv6
forall a b. Either a b -> Maybe b
rightToMaybe (Parser IPv6 -> Text -> Either String IPv6
forall a. Parser a -> Text -> Either String a
AT.parseOnly (Parser IPv6
parser Parser IPv6 -> Parser Text () -> Parser IPv6
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser Text ()
forall t. Chunk t => Parser t ()
AT.endOfInput) Text
t)
parserUtf8Bytes :: e -> Parser.Parser e s IPv6
parserUtf8Bytes :: e -> Parser e s IPv6
parserUtf8Bytes e
e = do
MutablePrimArray s Word16
marr <- ST s (MutablePrimArray s Word16)
-> Parser e s (MutablePrimArray s Word16)
forall s a e. ST s a -> Parser e s a
Parser.effect (Int -> ST s (MutablePrimArray (PrimState (ST s)) Word16)
forall (m :: * -> *) a.
(PrimMonad m, Prim a) =>
Int -> m (MutablePrimArray (PrimState m) a)
PM.newPrimArray Int
8)
(Char -> Bool) -> Parser e s Bool
forall e s. (Char -> Bool) -> Parser e s Bool
Latin.trySatisfy (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
':') Parser e s Bool -> (Bool -> Parser e s IPv6) -> Parser e s IPv6
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Bool
True -> do
e -> Char -> Parser e s ()
forall e s. e -> Char -> Parser e s ()
Latin.char e
e Char
':'
e -> MutablePrimArray s Word16 -> Int -> Int -> Parser e s IPv6
forall e s.
e -> MutablePrimArray s Word16 -> Int -> Int -> Parser e s IPv6
postZeroesBegin e
e MutablePrimArray s Word16
marr Int
0 Int
0
Bool
False -> do
Word16
w <- e -> Parser e s Word16
forall e s. e -> Parser e s Word16
pieceParser e
e
ST s () -> Parser e s ()
forall s a e. ST s a -> Parser e s a
Parser.effect (MutablePrimArray (PrimState (ST s)) Word16
-> Int -> Word16 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
PM.writePrimArray MutablePrimArray s Word16
MutablePrimArray (PrimState (ST s)) Word16
marr Int
0 Word16
w)
e -> MutablePrimArray s Word16 -> Int -> Parser e s IPv6
forall e s.
e -> MutablePrimArray s Word16 -> Int -> Parser e s IPv6
preZeroes e
e MutablePrimArray s Word16
marr Int
1
preZeroes ::
e
-> MutablePrimArray s Word16
-> Int
-> Parser.Parser e s IPv6
preZeroes :: e -> MutablePrimArray s Word16 -> Int -> Parser e s IPv6
preZeroes e
e !MutablePrimArray s Word16
marr !Int
ix = case Int
ix of
Int
8 -> ST s IPv6 -> Parser e s IPv6
forall s a e. ST s a -> Parser e s a
Parser.effect (MutablePrimArray s Word16 -> ST s IPv6
forall s. MutablePrimArray s Word16 -> ST s IPv6
combinePieces MutablePrimArray s Word16
marr)
Int
_ -> do
e -> Char -> Parser e s ()
forall e s. e -> Char -> Parser e s ()
Latin.char e
e Char
':'
(Char -> Bool) -> Parser e s Bool
forall e s. (Char -> Bool) -> Parser e s Bool
Latin.trySatisfy (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
':') Parser e s Bool -> (Bool -> Parser e s IPv6) -> Parser e s IPv6
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Bool
True -> e -> MutablePrimArray s Word16 -> Int -> Int -> Parser e s IPv6
forall e s.
e -> MutablePrimArray s Word16 -> Int -> Int -> Parser e s IPv6
postZeroesBegin e
e MutablePrimArray s Word16
marr Int
ix Int
ix
Bool
False -> do
Word16
w <- e -> Parser e s Word16
forall e s. e -> Parser e s Word16
pieceParser e
e
ST s () -> Parser e s ()
forall s a e. ST s a -> Parser e s a
Parser.effect (MutablePrimArray (PrimState (ST s)) Word16
-> Int -> Word16 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
PM.writePrimArray MutablePrimArray s Word16
MutablePrimArray (PrimState (ST s)) Word16
marr Int
ix Word16
w)
e -> MutablePrimArray s Word16 -> Int -> Parser e s IPv6
forall e s.
e -> MutablePrimArray s Word16 -> Int -> Parser e s IPv6
preZeroes e
e MutablePrimArray s Word16
marr (Int
ix Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
postZeroesBegin ::
e
-> MutablePrimArray s Word16
-> Int
-> Int
-> Parser.Parser e s IPv6
postZeroesBegin :: e -> MutablePrimArray s Word16 -> Int -> Int -> Parser e s IPv6
postZeroesBegin e
e !MutablePrimArray s Word16
marr !Int
ix !Int
compress = do
e -> Parser e s (Maybe Word16)
forall e s. e -> Parser e s (Maybe Word16)
optionalPieceParser e
e Parser e s (Maybe Word16)
-> (Maybe Word16 -> Parser e s IPv6) -> Parser e s IPv6
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Maybe Word16
Nothing -> do
ST s IPv6 -> Parser e s IPv6
forall s a e. ST s a -> Parser e s a
Parser.effect (MutablePrimArray s Word16 -> Int -> Int -> ST s IPv6
forall s. MutablePrimArray s Word16 -> Int -> Int -> ST s IPv6
conclude MutablePrimArray s Word16
marr Int
ix Int
compress)
Just Word16
w -> do
ST s () -> Parser e s ()
forall s a e. ST s a -> Parser e s a
Parser.effect (MutablePrimArray (PrimState (ST s)) Word16
-> Int -> Word16 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
PM.writePrimArray MutablePrimArray s Word16
MutablePrimArray (PrimState (ST s)) Word16
marr Int
ix Word16
w)
e -> MutablePrimArray s Word16 -> Int -> Int -> Parser e s IPv6
forall e s.
e -> MutablePrimArray s Word16 -> Int -> Int -> Parser e s IPv6
postZeroes e
e MutablePrimArray s Word16
marr (Int
ix Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Int
compress
postZeroes ::
e
-> MutablePrimArray s Word16
-> Int
-> Int
-> Parser.Parser e s IPv6
postZeroes :: e -> MutablePrimArray s Word16 -> Int -> Int -> Parser e s IPv6
postZeroes e
e !MutablePrimArray s Word16
marr !Int
ix !Int
compress = case Int
ix of
Int
8 -> e -> Parser e s IPv6
forall e s a. e -> Parser e s a
Parser.fail e
e
Int
_ -> do
(Char -> Bool) -> Parser e s Bool
forall e s. (Char -> Bool) -> Parser e s Bool
Latin.trySatisfy (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
':') Parser e s Bool -> (Bool -> Parser e s IPv6) -> Parser e s IPv6
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Bool
False ->
ST s IPv6 -> Parser e s IPv6
forall s a e. ST s a -> Parser e s a
Parser.effect (MutablePrimArray s Word16 -> Int -> Int -> ST s IPv6
forall s. MutablePrimArray s Word16 -> Int -> Int -> ST s IPv6
conclude MutablePrimArray s Word16
marr Int
ix Int
compress)
Bool
True -> do
Word16
w <- e -> Parser e s Word16
forall e s. e -> Parser e s Word16
pieceParser e
e
ST s () -> Parser e s ()
forall s a e. ST s a -> Parser e s a
Parser.effect (MutablePrimArray (PrimState (ST s)) Word16
-> Int -> Word16 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
PM.writePrimArray MutablePrimArray s Word16
MutablePrimArray (PrimState (ST s)) Word16
marr Int
ix Word16
w)
e -> MutablePrimArray s Word16 -> Int -> Int -> Parser e s IPv6
forall e s.
e -> MutablePrimArray s Word16 -> Int -> Int -> Parser e s IPv6
postZeroes e
e MutablePrimArray s Word16
marr (Int
ix Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Int
compress
conclude :: MutablePrimArray s Word16 -> Int -> Int -> ST s IPv6
conclude :: MutablePrimArray s Word16 -> Int -> Int -> ST s IPv6
conclude !MutablePrimArray s Word16
marr !Int
ix !Int
compress = do
let postCompressionLen :: Int
postCompressionLen = Int
ix Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
compress
MutablePrimArray (PrimState (ST s)) Word16
-> Int
-> MutablePrimArray (PrimState (ST s)) Word16
-> Int
-> Int
-> ST s ()
forall (m :: * -> *) a.
(PrimMonad m, Prim a) =>
MutablePrimArray (PrimState m) a
-> Int -> MutablePrimArray (PrimState m) a -> Int -> Int -> m ()
PM.copyMutablePrimArray MutablePrimArray s Word16
MutablePrimArray (PrimState (ST s)) Word16
marr (Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
postCompressionLen) MutablePrimArray s Word16
MutablePrimArray (PrimState (ST s)) Word16
marr Int
compress Int
postCompressionLen
let compressedArea :: Int
compressedArea = Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
ix
MutablePrimArray (PrimState (ST s)) Word16
-> Int -> Int -> Word16 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> Int -> a -> m ()
PM.setPrimArray MutablePrimArray s Word16
MutablePrimArray (PrimState (ST s)) Word16
marr Int
compress Int
compressedArea (Word16
0 :: Word16)
MutablePrimArray s Word16 -> ST s IPv6
forall s. MutablePrimArray s Word16 -> ST s IPv6
combinePieces MutablePrimArray s Word16
marr
combinePieces ::
MutablePrimArray s Word16
-> ST s IPv6
combinePieces :: MutablePrimArray s Word16 -> ST s IPv6
combinePieces !MutablePrimArray s Word16
marr = Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> IPv6
fromWord16s
(Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> IPv6)
-> ST s Word16
-> ST
s
(Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> IPv6)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MutablePrimArray (PrimState (ST s)) Word16 -> Int -> ST s Word16
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> m a
PM.readPrimArray MutablePrimArray s Word16
MutablePrimArray (PrimState (ST s)) Word16
marr Int
0
ST
s
(Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> IPv6)
-> ST s Word16
-> ST
s
(Word16 -> Word16 -> Word16 -> Word16 -> Word16 -> Word16 -> IPv6)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> MutablePrimArray (PrimState (ST s)) Word16 -> Int -> ST s Word16
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> m a
PM.readPrimArray MutablePrimArray s Word16
MutablePrimArray (PrimState (ST s)) Word16
marr Int
1
ST
s
(Word16 -> Word16 -> Word16 -> Word16 -> Word16 -> Word16 -> IPv6)
-> ST s Word16
-> ST s (Word16 -> Word16 -> Word16 -> Word16 -> Word16 -> IPv6)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> MutablePrimArray (PrimState (ST s)) Word16 -> Int -> ST s Word16
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> m a
PM.readPrimArray MutablePrimArray s Word16
MutablePrimArray (PrimState (ST s)) Word16
marr Int
2
ST s (Word16 -> Word16 -> Word16 -> Word16 -> Word16 -> IPv6)
-> ST s Word16
-> ST s (Word16 -> Word16 -> Word16 -> Word16 -> IPv6)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> MutablePrimArray (PrimState (ST s)) Word16 -> Int -> ST s Word16
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> m a
PM.readPrimArray MutablePrimArray s Word16
MutablePrimArray (PrimState (ST s)) Word16
marr Int
3
ST s (Word16 -> Word16 -> Word16 -> Word16 -> IPv6)
-> ST s Word16 -> ST s (Word16 -> Word16 -> Word16 -> IPv6)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> MutablePrimArray (PrimState (ST s)) Word16 -> Int -> ST s Word16
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> m a
PM.readPrimArray MutablePrimArray s Word16
MutablePrimArray (PrimState (ST s)) Word16
marr Int
4
ST s (Word16 -> Word16 -> Word16 -> IPv6)
-> ST s Word16 -> ST s (Word16 -> Word16 -> IPv6)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> MutablePrimArray (PrimState (ST s)) Word16 -> Int -> ST s Word16
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> m a
PM.readPrimArray MutablePrimArray s Word16
MutablePrimArray (PrimState (ST s)) Word16
marr Int
5
ST s (Word16 -> Word16 -> IPv6)
-> ST s Word16 -> ST s (Word16 -> IPv6)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> MutablePrimArray (PrimState (ST s)) Word16 -> Int -> ST s Word16
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> m a
PM.readPrimArray MutablePrimArray s Word16
MutablePrimArray (PrimState (ST s)) Word16
marr Int
6
ST s (Word16 -> IPv6) -> ST s Word16 -> ST s IPv6
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> MutablePrimArray (PrimState (ST s)) Word16 -> Int -> ST s Word16
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> m a
PM.readPrimArray MutablePrimArray s Word16
MutablePrimArray (PrimState (ST s)) Word16
marr Int
7
optionalPieceParser :: e -> Parser.Parser e s (Maybe Word16)
optionalPieceParser :: e -> Parser e s (Maybe Word16)
optionalPieceParser e
e = Parser e s (Maybe Word)
forall e s. Parser e s (Maybe Word)
Latin.tryHexNibble Parser e s (Maybe Word)
-> (Maybe Word -> Parser e s (Maybe Word16))
-> Parser e s (Maybe Word16)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Maybe Word
Nothing -> Maybe Word16 -> Parser e s (Maybe Word16)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Word16
forall a. Maybe a
Nothing
Just Word
w0 -> do
Word16
r <- e -> Word -> Parser e s Word16
forall e s. e -> Word -> Parser e s Word16
pieceParserStep e
e Word
w0
Maybe Word16 -> Parser e s (Maybe Word16)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Word16 -> Maybe Word16
forall a. a -> Maybe a
Just Word16
r)
pieceParser :: e -> Parser.Parser e s Word16
pieceParser :: e -> Parser e s Word16
pieceParser e
e = e -> Parser e s Word
forall e s. e -> Parser e s Word
Latin.hexNibble e
e Parser e s Word -> (Word -> Parser e s Word16) -> Parser e s Word16
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= e -> Word -> Parser e s Word16
forall e s. e -> Word -> Parser e s Word16
pieceParserStep e
e
pieceParserStep ::
e
-> Word
-> Parser.Parser e s Word16
pieceParserStep :: e -> Word -> Parser e s Word16
pieceParserStep e
e !Word
acc = if Word
acc Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
> Word
0xFFFF
then e -> Parser e s Word16
forall e s a. e -> Parser e s a
Parser.fail e
e
else Parser e s (Maybe Word)
forall e s. Parser e s (Maybe Word)
Latin.tryHexNibble Parser e s (Maybe Word)
-> (Maybe Word -> Parser e s Word16) -> Parser e s Word16
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Maybe Word
Nothing -> Word16 -> Parser e s Word16
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Word -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word
acc)
Just Word
w -> e -> Word -> Parser e s Word16
forall e s. e -> Word -> Parser e s Word16
pieceParserStep e
e (Word
16 Word -> Word -> Word
forall a. Num a => a -> a -> a
* Word
acc Word -> Word -> Word
forall a. Num a => a -> a -> a
+ Word
w)
parserRangeUtf8Bytes :: e -> Parser.Parser e s IPv6Range
parserRangeUtf8Bytes :: e -> Parser e s IPv6Range
parserRangeUtf8Bytes e
e = do
IPv6
base <- e -> Parser e s IPv6
forall e s. e -> Parser e s IPv6
parserUtf8Bytes e
e
e -> Char -> Parser e s ()
forall e s. e -> Char -> Parser e s ()
Latin.char e
e Char
'/'
Word8
theMask <- e -> Parser e s Word8
forall e s. e -> Parser e s Word8
Latin.decWord8 e
e
if Word8
theMask Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
> Word8
128
then e -> Parser e s IPv6Range
forall e s a. e -> Parser e s a
Parser.fail e
e
else IPv6Range -> Parser e s IPv6Range
forall (f :: * -> *) a. Applicative f => a -> f a
pure (IPv6Range -> Parser e s IPv6Range)
-> IPv6Range -> Parser e s IPv6Range
forall a b. (a -> b) -> a -> b
$! IPv6Range -> IPv6Range
normalize (IPv6 -> Word8 -> IPv6Range
IPv6Range IPv6
base Word8
theMask)
parserRangeUtf8BytesLenient :: e -> Parser.Parser e s IPv6Range
parserRangeUtf8BytesLenient :: e -> Parser e s IPv6Range
parserRangeUtf8BytesLenient e
e = do
IPv6
base <- e -> Parser e s IPv6
forall e s. e -> Parser e s IPv6
parserUtf8Bytes e
e
(Char -> Bool) -> Parser e s Bool
forall e s. (Char -> Bool) -> Parser e s Bool
Latin.trySatisfy (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==Char
'/') Parser e s Bool
-> (Bool -> Parser e s IPv6Range) -> Parser e s IPv6Range
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Bool
True -> do
Word8
theMask <- e -> Parser e s Word8
forall e s. e -> Parser e s Word8
Latin.decWord8 e
e
if Word8
theMask Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
> Word8
128
then e -> Parser e s IPv6Range
forall e s a. e -> Parser e s a
Parser.fail e
e
else IPv6Range -> Parser e s IPv6Range
forall (f :: * -> *) a. Applicative f => a -> f a
pure (IPv6Range -> Parser e s IPv6Range)
-> IPv6Range -> Parser e s IPv6Range
forall a b. (a -> b) -> a -> b
$! IPv6Range -> IPv6Range
normalize (IPv6 -> Word8 -> IPv6Range
IPv6Range IPv6
base Word8
theMask)
Bool
False -> IPv6Range -> Parser e s IPv6Range
forall (f :: * -> *) a. Applicative f => a -> f a
pure (IPv6Range -> Parser e s IPv6Range)
-> IPv6Range -> Parser e s IPv6Range
forall a b. (a -> b) -> a -> b
$! IPv6 -> Word8 -> IPv6Range
IPv6Range IPv6
base Word8
128
parser :: Atto.Parser IPv6
parser :: Parser IPv6
parser = [Word16] -> IPv6
makeIP ([Word16] -> IPv6) -> Parser Text [Word16] -> Parser IPv6
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Text [Word16]
ip
where
makeIP :: [Word16] -> IPv6
makeIP [Word16
w1, Word16
w2, Word16
w3, Word16
w4, Word16
w5, Word16
w6, Word16
w7, Word16
w8] = Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> Word16
-> IPv6
fromWord16s Word16
w1 Word16
w2 Word16
w3 Word16
w4 Word16
w5 Word16
w6 Word16
w7 Word16
w8
makeIP [Word16]
_ = String -> IPv6
forall a. HasCallStack => String -> a
error String
"Net.IPv6.parser: Implementation error. Please open a bug report."
ip :: Parser Text [Word16]
ip = (Char -> Parser Char
Atto.char Char
':' Parser Char -> Parser Char -> Parser Char
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Char -> Parser Char
Atto.char Char
':' Parser Char -> Parser Text [Word16] -> Parser Text [Word16]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Int -> Parser Text [Word16]
doubleColon Int
0) Parser Text [Word16]
-> Parser Text [Word16] -> Parser Text [Word16]
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Int -> Parser Text [Word16]
part Int
0
part :: Int -> Atto.Parser [Word16]
part :: Int -> Parser Text [Word16]
part Int
n =
case Int
n of
Int
7 -> Word16 -> [Word16]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Word16 -> [Word16]) -> Parser Text Word16 -> Parser Text [Word16]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Text Word16
forall a. (Integral a, Bits a) => Parser a
Atto.hexadecimal
Int
6 -> Parser Text [Word16]
ipv4 Parser Text [Word16]
-> Parser Text [Word16] -> Parser Text [Word16]
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser Text [Word16]
hexPart
Int
_ -> Parser Text [Word16]
hexPart
where
hexPart :: Parser Text [Word16]
hexPart = (:)
(Word16 -> [Word16] -> [Word16])
-> Parser Text Word16 -> Parser Text ([Word16] -> [Word16])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Text Word16
forall a. (Integral a, Bits a) => Parser a
Atto.hexadecimal
Parser Text ([Word16] -> [Word16])
-> Parser Text [Word16] -> Parser Text [Word16]
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Char -> Parser Char
Atto.char Char
':' Parser Char -> Parser Text [Word16] -> Parser Text [Word16]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
(
(Char -> Parser Char
Atto.char Char
':' Parser Char -> Parser Text [Word16] -> Parser Text [Word16]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Int -> Parser Text [Word16]
doubleColon (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1))
Parser Text [Word16]
-> Parser Text [Word16] -> Parser Text [Word16]
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
Int -> Parser Text [Word16]
part (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
)
)
doubleColon :: Int -> Atto.Parser [Word16]
doubleColon :: Int -> Parser Text [Word16]
doubleColon Int
count = do
[Word16]
rest <- Parser Text [Word16]
afterDoubleColon Parser Text [Word16]
-> Parser Text [Word16] -> Parser Text [Word16]
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> [Word16] -> Parser Text [Word16]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
let fillerLength :: Int
fillerLength = (Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
count Int -> Int -> Int
forall a. Num a => a -> a -> a
- [Word16] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Word16]
rest)
if Int
fillerLength Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0
then String -> Parser Text [Word16]
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"too many parts in IPv6 address"
else [Word16] -> Parser Text [Word16]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int -> Word16 -> [Word16]
forall a. Int -> a -> [a]
replicate Int
fillerLength Word16
0 [Word16] -> [Word16] -> [Word16]
forall a. [a] -> [a] -> [a]
++ [Word16]
rest)
afterDoubleColon :: Atto.Parser [Word16]
afterDoubleColon :: Parser Text [Word16]
afterDoubleColon =
Parser Text [Word16]
ipv4 Parser Text [Word16]
-> Parser Text [Word16] -> Parser Text [Word16]
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
(:) (Word16 -> [Word16] -> [Word16])
-> Parser Text Word16 -> Parser Text ([Word16] -> [Word16])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Text Word16
forall a. (Integral a, Bits a) => Parser a
Atto.hexadecimal Parser Text ([Word16] -> [Word16])
-> Parser Text [Word16] -> Parser Text [Word16]
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((Char -> Parser Char
Atto.char Char
':' Parser Char -> Parser Text [Word16] -> Parser Text [Word16]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser Text [Word16]
afterDoubleColon) Parser Text [Word16]
-> Parser Text [Word16] -> Parser Text [Word16]
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> [Word16] -> Parser Text [Word16]
forall (f :: * -> *) a. Applicative f => a -> f a
pure [])
ipv4 :: Atto.Parser [Word16]
ipv4 :: Parser Text [Word16]
ipv4 = IPv4 -> [Word16]
ipv4ToWord16s (IPv4 -> [Word16]) -> Parser Text IPv4 -> Parser Text [Word16]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Text IPv4
IPv4.parser
ipv4ToWord16s :: IPv4 -> [Word16]
ipv4ToWord16s :: IPv4 -> [Word16]
ipv4ToWord16s (IPv4 Word32
word) = [Word32 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
word Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int
16), Word32 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
word Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.&. Word32
0xFFFF)]
data IPv6Range = IPv6Range
{ IPv6Range -> IPv6
ipv6RangeBase :: {-# UNPACK #-} !IPv6
, IPv6Range -> Word8
ipv6RangeLength :: {-# UNPACK #-} !Word8
} deriving (IPv6Range -> IPv6Range -> Bool
(IPv6Range -> IPv6Range -> Bool)
-> (IPv6Range -> IPv6Range -> Bool) -> Eq IPv6Range
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IPv6Range -> IPv6Range -> Bool
$c/= :: IPv6Range -> IPv6Range -> Bool
== :: IPv6Range -> IPv6Range -> Bool
$c== :: IPv6Range -> IPv6Range -> Bool
Eq,Eq IPv6Range
Eq IPv6Range
-> (IPv6Range -> IPv6Range -> Ordering)
-> (IPv6Range -> IPv6Range -> Bool)
-> (IPv6Range -> IPv6Range -> Bool)
-> (IPv6Range -> IPv6Range -> Bool)
-> (IPv6Range -> IPv6Range -> Bool)
-> (IPv6Range -> IPv6Range -> IPv6Range)
-> (IPv6Range -> IPv6Range -> IPv6Range)
-> Ord IPv6Range
IPv6Range -> IPv6Range -> Bool
IPv6Range -> IPv6Range -> Ordering
IPv6Range -> IPv6Range -> IPv6Range
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
min :: IPv6Range -> IPv6Range -> IPv6Range
$cmin :: IPv6Range -> IPv6Range -> IPv6Range
max :: IPv6Range -> IPv6Range -> IPv6Range
$cmax :: IPv6Range -> IPv6Range -> IPv6Range
>= :: IPv6Range -> IPv6Range -> Bool
$c>= :: IPv6Range -> IPv6Range -> Bool
> :: IPv6Range -> IPv6Range -> Bool
$c> :: IPv6Range -> IPv6Range -> Bool
<= :: IPv6Range -> IPv6Range -> Bool
$c<= :: IPv6Range -> IPv6Range -> Bool
< :: IPv6Range -> IPv6Range -> Bool
$c< :: IPv6Range -> IPv6Range -> Bool
compare :: IPv6Range -> IPv6Range -> Ordering
$ccompare :: IPv6Range -> IPv6Range -> Ordering
$cp1Ord :: Eq IPv6Range
Ord,Int -> IPv6Range -> ShowS
[IPv6Range] -> ShowS
IPv6Range -> String
(Int -> IPv6Range -> ShowS)
-> (IPv6Range -> String)
-> ([IPv6Range] -> ShowS)
-> Show IPv6Range
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IPv6Range] -> ShowS
$cshowList :: [IPv6Range] -> ShowS
show :: IPv6Range -> String
$cshow :: IPv6Range -> String
showsPrec :: Int -> IPv6Range -> ShowS
$cshowsPrec :: Int -> IPv6Range -> ShowS
Show,ReadPrec [IPv6Range]
ReadPrec IPv6Range
Int -> ReadS IPv6Range
ReadS [IPv6Range]
(Int -> ReadS IPv6Range)
-> ReadS [IPv6Range]
-> ReadPrec IPv6Range
-> ReadPrec [IPv6Range]
-> Read IPv6Range
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [IPv6Range]
$creadListPrec :: ReadPrec [IPv6Range]
readPrec :: ReadPrec IPv6Range
$creadPrec :: ReadPrec IPv6Range
readList :: ReadS [IPv6Range]
$creadList :: ReadS [IPv6Range]
readsPrec :: Int -> ReadS IPv6Range
$creadsPrec :: Int -> ReadS IPv6Range
Read,(forall x. IPv6Range -> Rep IPv6Range x)
-> (forall x. Rep IPv6Range x -> IPv6Range) -> Generic IPv6Range
forall x. Rep IPv6Range x -> IPv6Range
forall x. IPv6Range -> Rep IPv6Range x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep IPv6Range x -> IPv6Range
$cfrom :: forall x. IPv6Range -> Rep IPv6Range x
Generic,Typeable IPv6Range
DataType
Constr
Typeable IPv6Range
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IPv6Range -> c IPv6Range)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IPv6Range)
-> (IPv6Range -> Constr)
-> (IPv6Range -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c IPv6Range))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IPv6Range))
-> ((forall b. Data b => b -> b) -> IPv6Range -> IPv6Range)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IPv6Range -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IPv6Range -> r)
-> (forall u. (forall d. Data d => d -> u) -> IPv6Range -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> IPv6Range -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> IPv6Range -> m IPv6Range)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IPv6Range -> m IPv6Range)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IPv6Range -> m IPv6Range)
-> Data IPv6Range
IPv6Range -> DataType
IPv6Range -> Constr
(forall b. Data b => b -> b) -> IPv6Range -> IPv6Range
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IPv6Range -> c IPv6Range
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IPv6Range
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> IPv6Range -> u
forall u. (forall d. Data d => d -> u) -> IPv6Range -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IPv6Range -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IPv6Range -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> IPv6Range -> m IPv6Range
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IPv6Range -> m IPv6Range
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IPv6Range
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IPv6Range -> c IPv6Range
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c IPv6Range)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IPv6Range)
$cIPv6Range :: Constr
$tIPv6Range :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> IPv6Range -> m IPv6Range
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IPv6Range -> m IPv6Range
gmapMp :: (forall d. Data d => d -> m d) -> IPv6Range -> m IPv6Range
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IPv6Range -> m IPv6Range
gmapM :: (forall d. Data d => d -> m d) -> IPv6Range -> m IPv6Range
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> IPv6Range -> m IPv6Range
gmapQi :: Int -> (forall d. Data d => d -> u) -> IPv6Range -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> IPv6Range -> u
gmapQ :: (forall d. Data d => d -> u) -> IPv6Range -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> IPv6Range -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IPv6Range -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IPv6Range -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IPv6Range -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IPv6Range -> r
gmapT :: (forall b. Data b => b -> b) -> IPv6Range -> IPv6Range
$cgmapT :: (forall b. Data b => b -> b) -> IPv6Range -> IPv6Range
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IPv6Range)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IPv6Range)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c IPv6Range)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c IPv6Range)
dataTypeOf :: IPv6Range -> DataType
$cdataTypeOf :: IPv6Range -> DataType
toConstr :: IPv6Range -> Constr
$ctoConstr :: IPv6Range -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IPv6Range
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IPv6Range
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IPv6Range -> c IPv6Range
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IPv6Range -> c IPv6Range
$cp1Data :: Typeable IPv6Range
Data)
instance NFData IPv6Range
instance Aeson.ToJSON IPv6Range where
toJSON :: IPv6Range -> Value
toJSON = Text -> Value
Aeson.String (Text -> Value) -> (IPv6Range -> Text) -> IPv6Range -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IPv6Range -> Text
encodeRange
instance Aeson.FromJSON IPv6Range where
parseJSON :: Value -> Parser IPv6Range
parseJSON (Aeson.String Text
t) = case Text -> Maybe IPv6Range
decodeRange Text
t of
Maybe IPv6Range
Nothing -> String -> Parser IPv6Range
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Could not decodeRange IPv6 range"
Just IPv6Range
res -> IPv6Range -> Parser IPv6Range
forall (m :: * -> *) a. Monad m => a -> m a
return IPv6Range
res
parseJSON Value
_ = Parser IPv6Range
forall (m :: * -> *) a. MonadPlus m => m a
mzero
mask128 :: IPv6
mask128 :: IPv6
mask128 = IPv6
forall a. Bounded a => a
maxBound
mask :: Word8 -> IPv6
mask :: Word8 -> IPv6
mask = IPv6 -> IPv6
forall a. Bits a => a -> a
complement (IPv6 -> IPv6) -> (Word8 -> IPv6) -> Word8 -> IPv6
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IPv6 -> Int -> IPv6
forall a. Bits a => a -> Int -> a
shiftR IPv6
mask128 (Int -> IPv6) -> (Word8 -> Int) -> Word8 -> IPv6
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral
normalize :: IPv6Range -> IPv6Range
normalize :: IPv6Range -> IPv6Range
normalize (IPv6Range IPv6
ip Word8
len) =
let len' :: Word8
len' = Word8 -> Word8 -> Word8
forall a. Ord a => a -> a -> a
min Word8
len Word8
128
ip' :: IPv6
ip' = IPv6
ip IPv6 -> IPv6 -> IPv6
forall a. Bits a => a -> a -> a
.&. Word8 -> IPv6
mask Word8
len'
in IPv6 -> Word8 -> IPv6Range
IPv6Range IPv6
ip' Word8
len'
encodeRange :: IPv6Range -> Text
encodeRange :: IPv6Range -> Text
encodeRange IPv6Range
x = IPv6 -> Text
encode (IPv6Range -> IPv6
ipv6RangeBase IPv6Range
x) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
Text.pack String
"/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> (String -> Text
Text.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ (Int -> String
forall a. Show a => a -> String
show (Int -> String) -> (Word8 -> Int) -> Word8 -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Int
forall a. Enum a => a -> Int
fromEnum) (Word8 -> String) -> Word8 -> String
forall a b. (a -> b) -> a -> b
$ IPv6Range -> Word8
ipv6RangeLength IPv6Range
x)
decodeRange :: Text -> Maybe IPv6Range
decodeRange :: Text -> Maybe IPv6Range
decodeRange = Either String IPv6Range -> Maybe IPv6Range
forall a b. Either a b -> Maybe b
rightToMaybe (Either String IPv6Range -> Maybe IPv6Range)
-> (Text -> Either String IPv6Range) -> Text -> Maybe IPv6Range
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Parser IPv6Range -> Text -> Either String IPv6Range
forall a. Parser a -> Text -> Either String a
AT.parseOnly (Parser IPv6Range
parserRange Parser IPv6Range -> Parser Text () -> Parser IPv6Range
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser Text ()
forall t. Chunk t => Parser t ()
AT.endOfInput)
parserRange :: AT.Parser IPv6Range
parserRange :: Parser IPv6Range
parserRange = do
IPv6
ip <- Parser IPv6
parser
Char
_ <- Char -> Parser Char
AT.char Char
'/'
Word8
theMask <- Parser Word8
forall a. Integral a => Parser a
AT.decimal Parser Word8 -> (Word8 -> Parser Word8) -> Parser Word8
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Word8 -> Parser Word8
forall a (m :: * -> *). (Ord a, Num a, MonadFail m) => a -> m a
limitSize
IPv6Range -> Parser IPv6Range
forall (m :: * -> *) a. Monad m => a -> m a
return (IPv6Range -> IPv6Range
normalize (IPv6 -> Word8 -> IPv6Range
IPv6Range IPv6
ip Word8
theMask))
where
limitSize :: a -> m a
limitSize a
i =
if a
i a -> a -> Bool
forall a. Ord a => a -> a -> Bool
> a
128
then String -> m a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"An IP range length must be between 0 and 128"
else a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return a
i
contains :: IPv6Range -> IPv6 -> Bool
contains :: IPv6Range -> IPv6 -> Bool
contains (IPv6Range IPv6
subnet Word8
len) =
let theMask :: IPv6
theMask = Word8 -> IPv6
mask Word8
len
subnetNormalized :: IPv6
subnetNormalized = IPv6
subnet IPv6 -> IPv6 -> IPv6
forall a. Bits a => a -> a -> a
.&. IPv6
theMask
in \IPv6
ip -> (IPv6
ip IPv6 -> IPv6 -> IPv6
forall a. Bits a => a -> a -> a
.&. IPv6
theMask) IPv6 -> IPv6 -> Bool
forall a. Eq a => a -> a -> Bool
== IPv6
subnetNormalized
member :: IPv6 -> IPv6Range -> Bool
member :: IPv6 -> IPv6Range -> Bool
member = (IPv6Range -> IPv6 -> Bool) -> IPv6 -> IPv6Range -> Bool
forall a b c. (a -> b -> c) -> b -> a -> c
flip IPv6Range -> IPv6 -> Bool
contains
lowerInclusive :: IPv6Range -> IPv6
lowerInclusive :: IPv6Range -> IPv6
lowerInclusive = IPv6Range -> IPv6
ipv6RangeBase (IPv6Range -> IPv6)
-> (IPv6Range -> IPv6Range) -> IPv6Range -> IPv6
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IPv6Range -> IPv6Range
normalize
upperInclusive :: IPv6Range -> IPv6
upperInclusive :: IPv6Range -> IPv6
upperInclusive (IPv6Range IPv6
ip Word8
len) =
let len' :: Word8
len' = Word8 -> Word8 -> Word8
forall a. Ord a => a -> a -> a
min Word8
128 Word8
len
theInvertedMask :: IPv6
theInvertedMask :: IPv6
theInvertedMask = IPv6 -> Int -> IPv6
forall a. Bits a => a -> Int -> a
shiftR IPv6
mask128 (Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
len')
in IPv6
ip IPv6 -> IPv6 -> IPv6
forall a. Bits a => a -> a -> a
.|. IPv6
theInvertedMask
printRange :: IPv6Range -> IO ()
printRange :: IPv6Range -> IO ()
printRange = Text -> IO ()
TIO.putStrLn (Text -> IO ()) -> (IPv6Range -> Text) -> IPv6Range -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IPv6Range -> Text
encodeRange
range :: IPv6 -> Word8 -> IPv6Range
range :: IPv6 -> Word8 -> IPv6Range
range IPv6
addr Word8
len = IPv6Range -> IPv6Range
normalize (IPv6 -> Word8 -> IPv6Range
IPv6Range IPv6
addr Word8
len)
fromBounds :: IPv6 -> IPv6 -> IPv6Range
fromBounds :: IPv6 -> IPv6 -> IPv6Range
fromBounds IPv6
lo IPv6
hi =
IPv6Range -> IPv6Range
normalize (IPv6 -> Word8 -> IPv6Range
IPv6Range IPv6
lo (IPv6 -> IPv6 -> Word8
maskFromBounds IPv6
lo IPv6
hi))
maskFromBounds :: IPv6 -> IPv6 -> Word8
maskFromBounds :: IPv6 -> IPv6 -> Word8
maskFromBounds IPv6
lo IPv6
hi = Int -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (IPv6 -> Int
forall b. FiniteBits b => b -> Int
countLeadingZeros (IPv6 -> Int) -> IPv6 -> Int
forall a b. (a -> b) -> a -> b
$ IPv6 -> IPv6 -> IPv6
forall a. Bits a => a -> a -> a
xor IPv6
lo IPv6
hi)