{-# LANGUAGE CPP #-}
{-# LANGUAGE UndecidableInstances #-}
module Pythia.Services.Types.Network
(
IpType (..),
IpAddress (..),
IpAddresses (..),
IpRefinement,
Ipv4Refinement,
Ipv6Refinement,
Device (..),
_Ipv4,
_Ipv6,
)
where
import Data.Char qualified as Char
import Data.Text qualified as T
import Data.Typeable (typeRep)
#if MIN_VERSION_base(4,17,0)
import GHC.IsList (IsList (Item, fromList, toList))
#else
import GHC.Exts (IsList (Item, fromList, toList))
#endif
import Pythia.Prelude
import Refined (Predicate, Refined)
import Refined qualified as R
type Device :: Type
newtype Device = MkDevice
{
Device -> Text
unDevice :: Text
}
deriving stock
(
Device -> Device -> Bool
(Device -> Device -> Bool)
-> (Device -> Device -> Bool) -> Eq Device
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Device -> Device -> Bool
== :: Device -> Device -> Bool
$c/= :: Device -> Device -> Bool
/= :: Device -> Device -> Bool
Eq,
(forall x. Device -> Rep Device x)
-> (forall x. Rep Device x -> Device) -> Generic Device
forall x. Rep Device x -> Device
forall x. Device -> Rep Device x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Device -> Rep Device x
from :: forall x. Device -> Rep Device x
$cto :: forall x. Rep Device x -> Device
to :: forall x. Rep Device x -> Device
Generic,
Eq Device
Eq Device =>
(Device -> Device -> Ordering)
-> (Device -> Device -> Bool)
-> (Device -> Device -> Bool)
-> (Device -> Device -> Bool)
-> (Device -> Device -> Bool)
-> (Device -> Device -> Device)
-> (Device -> Device -> Device)
-> Ord Device
Device -> Device -> Bool
Device -> Device -> Ordering
Device -> Device -> Device
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Device -> Device -> Ordering
compare :: Device -> Device -> Ordering
$c< :: Device -> Device -> Bool
< :: Device -> Device -> Bool
$c<= :: Device -> Device -> Bool
<= :: Device -> Device -> Bool
$c> :: Device -> Device -> Bool
> :: Device -> Device -> Bool
$c>= :: Device -> Device -> Bool
>= :: Device -> Device -> Bool
$cmax :: Device -> Device -> Device
max :: Device -> Device -> Device
$cmin :: Device -> Device -> Device
min :: Device -> Device -> Device
Ord,
ReadPrec [Device]
ReadPrec Device
Int -> ReadS Device
ReadS [Device]
(Int -> ReadS Device)
-> ReadS [Device]
-> ReadPrec Device
-> ReadPrec [Device]
-> Read Device
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Device
readsPrec :: Int -> ReadS Device
$creadList :: ReadS [Device]
readList :: ReadS [Device]
$creadPrec :: ReadPrec Device
readPrec :: ReadPrec Device
$creadListPrec :: ReadPrec [Device]
readListPrec :: ReadPrec [Device]
Read,
Int -> Device -> ShowS
[Device] -> ShowS
Device -> String
(Int -> Device -> ShowS)
-> (Device -> String) -> ([Device] -> ShowS) -> Show Device
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Device -> ShowS
showsPrec :: Int -> Device -> ShowS
$cshow :: Device -> String
show :: Device -> String
$cshowList :: [Device] -> ShowS
showList :: [Device] -> ShowS
Show
)
deriving
(
Int -> Device -> Builder
[Device] -> Builder
Device -> Builder
(Device -> Builder)
-> ([Device] -> Builder)
-> (Int -> Device -> Builder)
-> Display Device
forall a.
(a -> Builder)
-> ([a] -> Builder) -> (Int -> a -> Builder) -> Display a
$cdisplayBuilder :: Device -> Builder
displayBuilder :: Device -> Builder
$cdisplayList :: [Device] -> Builder
displayList :: [Device] -> Builder
$cdisplayPrec :: Int -> Device -> Builder
displayPrec :: Int -> Device -> Builder
Display,
String -> Device
(String -> Device) -> IsString Device
forall a. (String -> a) -> IsString a
$cfromString :: String -> Device
fromString :: String -> Device
IsString
)
via Text
deriving anyclass
(
Device -> ()
(Device -> ()) -> NFData Device
forall a. (a -> ()) -> NFData a
$crnf :: Device -> ()
rnf :: Device -> ()
NFData
)
instance
(k ~ An_Iso, a ~ Text, b ~ Text) =>
LabelOptic "unDevice" k Device Device a b
where
labelOptic :: Optic k NoIx Device Device a b
labelOptic = (Device -> a) -> (b -> Device) -> Iso Device Device a b
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso (\(MkDevice Text
d) -> a
Text
d) b -> Device
Text -> Device
MkDevice
{-# INLINE labelOptic #-}
type IpType :: Type
data IpType
=
Ipv4
|
Ipv6
deriving stock
(
IpType -> IpType -> Bool
(IpType -> IpType -> Bool)
-> (IpType -> IpType -> Bool) -> Eq IpType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: IpType -> IpType -> Bool
== :: IpType -> IpType -> Bool
$c/= :: IpType -> IpType -> Bool
/= :: IpType -> IpType -> Bool
Eq,
(forall x. IpType -> Rep IpType x)
-> (forall x. Rep IpType x -> IpType) -> Generic IpType
forall x. Rep IpType x -> IpType
forall x. IpType -> Rep IpType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. IpType -> Rep IpType x
from :: forall x. IpType -> Rep IpType x
$cto :: forall x. Rep IpType x -> IpType
to :: forall x. Rep IpType x -> IpType
Generic,
Int -> IpType -> ShowS
[IpType] -> ShowS
IpType -> String
(Int -> IpType -> ShowS)
-> (IpType -> String) -> ([IpType] -> ShowS) -> Show IpType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> IpType -> ShowS
showsPrec :: Int -> IpType -> ShowS
$cshow :: IpType -> String
show :: IpType -> String
$cshowList :: [IpType] -> ShowS
showList :: [IpType] -> ShowS
Show
)
deriving anyclass
(
IpType -> ()
(IpType -> ()) -> NFData IpType
forall a. (a -> ()) -> NFData a
$crnf :: IpType -> ()
rnf :: IpType -> ()
NFData
)
_Ipv4 :: Prism' IpType ()
_Ipv4 :: Prism' IpType ()
_Ipv4 =
(() -> IpType) -> (IpType -> Either IpType ()) -> Prism' IpType ()
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism
(IpType -> () -> IpType
forall a b. a -> b -> a
const IpType
Ipv4)
( \IpType
x -> case IpType
x of
IpType
Ipv4 -> () -> Either IpType ()
forall a b. b -> Either a b
Right ()
IpType
_ -> IpType -> Either IpType ()
forall a b. a -> Either a b
Left IpType
x
)
{-# INLINE _Ipv4 #-}
_Ipv6 :: Prism' IpType ()
_Ipv6 :: Prism' IpType ()
_Ipv6 =
(() -> IpType) -> (IpType -> Either IpType ()) -> Prism' IpType ()
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism
(IpType -> () -> IpType
forall a b. a -> b -> a
const IpType
Ipv6)
( \IpType
x -> case IpType
x of
IpType
Ipv6 -> () -> Either IpType ()
forall a b. b -> Either a b
Right ()
IpType
_ -> IpType -> Either IpType ()
forall a b. a -> Either a b
Left IpType
x
)
{-# INLINE _Ipv6 #-}
type IpRefinement :: IpType -> Type
type family IpRefinement a where
IpRefinement Ipv4 = Ipv4Refinement
IpRefinement Ipv6 = Ipv6Refinement
type Ipv4Refinement :: Type
data Ipv4Refinement
instance Predicate Ipv4Refinement Text where
validate :: Proxy Ipv4Refinement -> Text -> Maybe RefineException
validate Proxy Ipv4Refinement
p Text
txt
| Bool -> Bool
not Bool
validLen = TypeRep -> Text -> Maybe RefineException
R.throwRefineOtherException (Proxy Ipv4Refinement -> TypeRep
forall {k} (proxy :: k -> Type) (a :: k).
Typeable a =>
proxy a -> TypeRep
typeRep Proxy Ipv4Refinement
p) Text
errLen
| Bool -> Bool
not Bool
validChars = TypeRep -> Text -> Maybe RefineException
R.throwRefineOtherException (Proxy Ipv4Refinement -> TypeRep
forall {k} (proxy :: k -> Type) (a :: k).
Typeable a =>
proxy a -> TypeRep
typeRep Proxy Ipv4Refinement
p) Text
errChars
| Bool
otherwise = Maybe RefineException
forall a. Maybe a
Nothing
where
len :: Int
len = Text -> Int
T.length Text
txt
validLen :: Bool
validLen = Int
len Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 Bool -> Bool -> Bool
&& Int
len Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
16
validChars :: Bool
validChars = (Char -> Bool) -> Text -> Bool
T.all (\Char
c -> Char -> Bool
Char.isDigit Char
c Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'.') Text
txt
errLen :: Text
errLen =
if Int
len Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
then Text
"Expected IPv4 with length (0, 16). Received empty."
else
Text
"Expected IPv4 address with length (0, 16). Received '"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
txt
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"' of length "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text
forall a. Show a => a -> Text
showt Int
len
errChars :: Text
errChars =
Text
"IPv4 address should only contain decimal digits or dots. Received invalid: "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
txt
{-# INLINEABLE validate #-}
type Ipv6Refinement :: Type
data Ipv6Refinement
instance Predicate Ipv6Refinement Text where
validate :: Proxy Ipv6Refinement -> Text -> Maybe RefineException
validate Proxy Ipv6Refinement
p Text
txt
| Bool -> Bool
not Bool
validLen = TypeRep -> Text -> Maybe RefineException
R.throwRefineOtherException (Proxy Ipv6Refinement -> TypeRep
forall {k} (proxy :: k -> Type) (a :: k).
Typeable a =>
proxy a -> TypeRep
typeRep Proxy Ipv6Refinement
p) Text
errLen
| Bool -> Bool
not Bool
validChars = TypeRep -> Text -> Maybe RefineException
R.throwRefineOtherException (Proxy Ipv6Refinement -> TypeRep
forall {k} (proxy :: k -> Type) (a :: k).
Typeable a =>
proxy a -> TypeRep
typeRep Proxy Ipv6Refinement
p) Text
errChars
| Bool
otherwise = Maybe RefineException
forall a. Maybe a
Nothing
where
len :: Int
len = Text -> Int
T.length Text
txt
validLen :: Bool
validLen = Int
len Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 Bool -> Bool -> Bool
&& Int
len Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
40
validChars :: Bool
validChars = (Char -> Bool) -> Text -> Bool
T.all (\Char
c -> Char -> Bool
Char.isHexDigit Char
c Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
':') Text
txt
errLen :: Text
errLen =
if Int
len Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
then Text
"Expected IPv6 of length (0, 40). Received empty."
else
Text
"Expected IPv6 with length (0, 40). Received '"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
txt
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"' of length "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text
forall a. Show a => a -> Text
showt Int
len
errChars :: Text
errChars =
Text
"IPv6 address should only contain hex digits or colons. Received invalid: "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
txt
{-# INLINEABLE validate #-}
type IpAddress :: IpType -> Type
newtype IpAddress a = MkIpAddress
{
forall (a :: IpType). IpAddress a -> Refined (IpRefinement a) Text
unIpAddress :: Refined (IpRefinement a) Text
}
deriving stock
(
IpAddress a -> IpAddress a -> Bool
(IpAddress a -> IpAddress a -> Bool)
-> (IpAddress a -> IpAddress a -> Bool) -> Eq (IpAddress a)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (a :: IpType). IpAddress a -> IpAddress a -> Bool
$c== :: forall (a :: IpType). IpAddress a -> IpAddress a -> Bool
== :: IpAddress a -> IpAddress a -> Bool
$c/= :: forall (a :: IpType). IpAddress a -> IpAddress a -> Bool
/= :: IpAddress a -> IpAddress a -> Bool
Eq,
(forall x. IpAddress a -> Rep (IpAddress a) x)
-> (forall x. Rep (IpAddress a) x -> IpAddress a)
-> Generic (IpAddress a)
forall x. Rep (IpAddress a) x -> IpAddress a
forall x. IpAddress a -> Rep (IpAddress a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (a :: IpType) x. Rep (IpAddress a) x -> IpAddress a
forall (a :: IpType) x. IpAddress a -> Rep (IpAddress a) x
$cfrom :: forall (a :: IpType) x. IpAddress a -> Rep (IpAddress a) x
from :: forall x. IpAddress a -> Rep (IpAddress a) x
$cto :: forall (a :: IpType) x. Rep (IpAddress a) x -> IpAddress a
to :: forall x. Rep (IpAddress a) x -> IpAddress a
Generic,
Eq (IpAddress a)
Eq (IpAddress a) =>
(IpAddress a -> IpAddress a -> Ordering)
-> (IpAddress a -> IpAddress a -> Bool)
-> (IpAddress a -> IpAddress a -> Bool)
-> (IpAddress a -> IpAddress a -> Bool)
-> (IpAddress a -> IpAddress a -> Bool)
-> (IpAddress a -> IpAddress a -> IpAddress a)
-> (IpAddress a -> IpAddress a -> IpAddress a)
-> Ord (IpAddress a)
IpAddress a -> IpAddress a -> Bool
IpAddress a -> IpAddress a -> Ordering
IpAddress a -> IpAddress a -> IpAddress a
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
forall (a :: IpType). Eq (IpAddress a)
forall (a :: IpType). IpAddress a -> IpAddress a -> Bool
forall (a :: IpType). IpAddress a -> IpAddress a -> Ordering
forall (a :: IpType). IpAddress a -> IpAddress a -> IpAddress a
$ccompare :: forall (a :: IpType). IpAddress a -> IpAddress a -> Ordering
compare :: IpAddress a -> IpAddress a -> Ordering
$c< :: forall (a :: IpType). IpAddress a -> IpAddress a -> Bool
< :: IpAddress a -> IpAddress a -> Bool
$c<= :: forall (a :: IpType). IpAddress a -> IpAddress a -> Bool
<= :: IpAddress a -> IpAddress a -> Bool
$c> :: forall (a :: IpType). IpAddress a -> IpAddress a -> Bool
> :: IpAddress a -> IpAddress a -> Bool
$c>= :: forall (a :: IpType). IpAddress a -> IpAddress a -> Bool
>= :: IpAddress a -> IpAddress a -> Bool
$cmax :: forall (a :: IpType). IpAddress a -> IpAddress a -> IpAddress a
max :: IpAddress a -> IpAddress a -> IpAddress a
$cmin :: forall (a :: IpType). IpAddress a -> IpAddress a -> IpAddress a
min :: IpAddress a -> IpAddress a -> IpAddress a
Ord,
Int -> IpAddress a -> ShowS
[IpAddress a] -> ShowS
IpAddress a -> String
(Int -> IpAddress a -> ShowS)
-> (IpAddress a -> String)
-> ([IpAddress a] -> ShowS)
-> Show (IpAddress a)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall (a :: IpType). Int -> IpAddress a -> ShowS
forall (a :: IpType). [IpAddress a] -> ShowS
forall (a :: IpType). IpAddress a -> String
$cshowsPrec :: forall (a :: IpType). Int -> IpAddress a -> ShowS
showsPrec :: Int -> IpAddress a -> ShowS
$cshow :: forall (a :: IpType). IpAddress a -> String
show :: IpAddress a -> String
$cshowList :: forall (a :: IpType). [IpAddress a] -> ShowS
showList :: [IpAddress a] -> ShowS
Show
)
deriving anyclass
(
IpAddress a -> ()
(IpAddress a -> ()) -> NFData (IpAddress a)
forall a. (a -> ()) -> NFData a
forall (a :: IpType). IpAddress a -> ()
$crnf :: forall (a :: IpType). IpAddress a -> ()
rnf :: IpAddress a -> ()
NFData
)
instance
(k ~ An_Iso, a ~ Refined (IpRefinement s) Text, b ~ Refined (IpRefinement s) Text) =>
LabelOptic "unIpAddress" k (IpAddress s) (IpAddress s) a b
where
labelOptic :: Optic k NoIx (IpAddress s) (IpAddress s) a b
labelOptic = (IpAddress s -> a)
-> (b -> IpAddress s) -> Iso (IpAddress s) (IpAddress s) a b
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso (\(MkIpAddress Refined (IpRefinement s) Text
a) -> a
Refined (IpRefinement s) Text
a) b -> IpAddress s
Refined (IpRefinement s) Text -> IpAddress s
forall (a :: IpType). Refined (IpRefinement a) Text -> IpAddress a
MkIpAddress
{-# INLINE labelOptic #-}
instance Display (IpAddress a) where
displayBuilder :: IpAddress a -> Builder
displayBuilder = Text -> Builder
forall a. Display a => a -> Builder
displayBuilder (Text -> Builder)
-> (IpAddress a -> Text) -> IpAddress a -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Refined (IpRefinement a) Text -> Text
forall {k} (p :: k) x. Refined p x -> x
R.unrefine (Refined (IpRefinement a) Text -> Text)
-> (IpAddress a -> Refined (IpRefinement a) Text)
-> IpAddress a
-> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IpAddress a -> Refined (IpRefinement a) Text
forall (a :: IpType). IpAddress a -> Refined (IpRefinement a) Text
unIpAddress
type IpAddresses :: IpType -> Type
newtype IpAddresses a = MkIpAddresses
{
forall (a :: IpType). IpAddresses a -> [IpAddress a]
unIpAddresses :: [IpAddress a]
}
deriving stock
(
IpAddresses a -> IpAddresses a -> Bool
(IpAddresses a -> IpAddresses a -> Bool)
-> (IpAddresses a -> IpAddresses a -> Bool) -> Eq (IpAddresses a)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (a :: IpType). IpAddresses a -> IpAddresses a -> Bool
$c== :: forall (a :: IpType). IpAddresses a -> IpAddresses a -> Bool
== :: IpAddresses a -> IpAddresses a -> Bool
$c/= :: forall (a :: IpType). IpAddresses a -> IpAddresses a -> Bool
/= :: IpAddresses a -> IpAddresses a -> Bool
Eq,
(forall x. IpAddresses a -> Rep (IpAddresses a) x)
-> (forall x. Rep (IpAddresses a) x -> IpAddresses a)
-> Generic (IpAddresses a)
forall x. Rep (IpAddresses a) x -> IpAddresses a
forall x. IpAddresses a -> Rep (IpAddresses a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (a :: IpType) x. Rep (IpAddresses a) x -> IpAddresses a
forall (a :: IpType) x. IpAddresses a -> Rep (IpAddresses a) x
$cfrom :: forall (a :: IpType) x. IpAddresses a -> Rep (IpAddresses a) x
from :: forall x. IpAddresses a -> Rep (IpAddresses a) x
$cto :: forall (a :: IpType) x. Rep (IpAddresses a) x -> IpAddresses a
to :: forall x. Rep (IpAddresses a) x -> IpAddresses a
Generic,
Eq (IpAddresses a)
Eq (IpAddresses a) =>
(IpAddresses a -> IpAddresses a -> Ordering)
-> (IpAddresses a -> IpAddresses a -> Bool)
-> (IpAddresses a -> IpAddresses a -> Bool)
-> (IpAddresses a -> IpAddresses a -> Bool)
-> (IpAddresses a -> IpAddresses a -> Bool)
-> (IpAddresses a -> IpAddresses a -> IpAddresses a)
-> (IpAddresses a -> IpAddresses a -> IpAddresses a)
-> Ord (IpAddresses a)
IpAddresses a -> IpAddresses a -> Bool
IpAddresses a -> IpAddresses a -> Ordering
IpAddresses a -> IpAddresses a -> IpAddresses a
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
forall (a :: IpType). Eq (IpAddresses a)
forall (a :: IpType). IpAddresses a -> IpAddresses a -> Bool
forall (a :: IpType). IpAddresses a -> IpAddresses a -> Ordering
forall (a :: IpType).
IpAddresses a -> IpAddresses a -> IpAddresses a
$ccompare :: forall (a :: IpType). IpAddresses a -> IpAddresses a -> Ordering
compare :: IpAddresses a -> IpAddresses a -> Ordering
$c< :: forall (a :: IpType). IpAddresses a -> IpAddresses a -> Bool
< :: IpAddresses a -> IpAddresses a -> Bool
$c<= :: forall (a :: IpType). IpAddresses a -> IpAddresses a -> Bool
<= :: IpAddresses a -> IpAddresses a -> Bool
$c> :: forall (a :: IpType). IpAddresses a -> IpAddresses a -> Bool
> :: IpAddresses a -> IpAddresses a -> Bool
$c>= :: forall (a :: IpType). IpAddresses a -> IpAddresses a -> Bool
>= :: IpAddresses a -> IpAddresses a -> Bool
$cmax :: forall (a :: IpType).
IpAddresses a -> IpAddresses a -> IpAddresses a
max :: IpAddresses a -> IpAddresses a -> IpAddresses a
$cmin :: forall (a :: IpType).
IpAddresses a -> IpAddresses a -> IpAddresses a
min :: IpAddresses a -> IpAddresses a -> IpAddresses a
Ord,
Int -> IpAddresses a -> ShowS
[IpAddresses a] -> ShowS
IpAddresses a -> String
(Int -> IpAddresses a -> ShowS)
-> (IpAddresses a -> String)
-> ([IpAddresses a] -> ShowS)
-> Show (IpAddresses a)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall (a :: IpType). Int -> IpAddresses a -> ShowS
forall (a :: IpType). [IpAddresses a] -> ShowS
forall (a :: IpType). IpAddresses a -> String
$cshowsPrec :: forall (a :: IpType). Int -> IpAddresses a -> ShowS
showsPrec :: Int -> IpAddresses a -> ShowS
$cshow :: forall (a :: IpType). IpAddresses a -> String
show :: IpAddresses a -> String
$cshowList :: forall (a :: IpType). [IpAddresses a] -> ShowS
showList :: [IpAddresses a] -> ShowS
Show
)
deriving
(
NonEmpty (IpAddresses a) -> IpAddresses a
IpAddresses a -> IpAddresses a -> IpAddresses a
(IpAddresses a -> IpAddresses a -> IpAddresses a)
-> (NonEmpty (IpAddresses a) -> IpAddresses a)
-> (forall b. Integral b => b -> IpAddresses a -> IpAddresses a)
-> Semigroup (IpAddresses a)
forall b. Integral b => b -> IpAddresses a -> IpAddresses a
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
forall (a :: IpType). NonEmpty (IpAddresses a) -> IpAddresses a
forall (a :: IpType).
IpAddresses a -> IpAddresses a -> IpAddresses a
forall (a :: IpType) b.
Integral b =>
b -> IpAddresses a -> IpAddresses a
$c<> :: forall (a :: IpType).
IpAddresses a -> IpAddresses a -> IpAddresses a
<> :: IpAddresses a -> IpAddresses a -> IpAddresses a
$csconcat :: forall (a :: IpType). NonEmpty (IpAddresses a) -> IpAddresses a
sconcat :: NonEmpty (IpAddresses a) -> IpAddresses a
$cstimes :: forall (a :: IpType) b.
Integral b =>
b -> IpAddresses a -> IpAddresses a
stimes :: forall b. Integral b => b -> IpAddresses a -> IpAddresses a
Semigroup,
Semigroup (IpAddresses a)
IpAddresses a
Semigroup (IpAddresses a) =>
IpAddresses a
-> (IpAddresses a -> IpAddresses a -> IpAddresses a)
-> ([IpAddresses a] -> IpAddresses a)
-> Monoid (IpAddresses a)
[IpAddresses a] -> IpAddresses a
IpAddresses a -> IpAddresses a -> IpAddresses a
forall a.
Semigroup a =>
a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
forall (a :: IpType). Semigroup (IpAddresses a)
forall (a :: IpType). IpAddresses a
forall (a :: IpType). [IpAddresses a] -> IpAddresses a
forall (a :: IpType).
IpAddresses a -> IpAddresses a -> IpAddresses a
$cmempty :: forall (a :: IpType). IpAddresses a
mempty :: IpAddresses a
$cmappend :: forall (a :: IpType).
IpAddresses a -> IpAddresses a -> IpAddresses a
mappend :: IpAddresses a -> IpAddresses a -> IpAddresses a
$cmconcat :: forall (a :: IpType). [IpAddresses a] -> IpAddresses a
mconcat :: [IpAddresses a] -> IpAddresses a
Monoid
)
via [IpAddress a]
deriving anyclass
(
IpAddresses a -> ()
(IpAddresses a -> ()) -> NFData (IpAddresses a)
forall a. (a -> ()) -> NFData a
forall (a :: IpType). IpAddresses a -> ()
$crnf :: forall (a :: IpType). IpAddresses a -> ()
rnf :: IpAddresses a -> ()
NFData
)
instance
(k ~ An_Iso, a ~ [IpAddress s], b ~ [IpAddress s]) =>
LabelOptic "unIpAddresses" k (IpAddresses s) (IpAddresses s) a b
where
labelOptic :: Optic k NoIx (IpAddresses s) (IpAddresses s) a b
labelOptic = (IpAddresses s -> a)
-> (b -> IpAddresses s) -> Iso (IpAddresses s) (IpAddresses s) a b
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso (\(MkIpAddresses [IpAddress s]
a) -> a
[IpAddress s]
a) b -> IpAddresses s
[IpAddress s] -> IpAddresses s
forall (a :: IpType). [IpAddress a] -> IpAddresses a
MkIpAddresses
{-# INLINE labelOptic #-}
instance Display (IpAddresses a) where
displayBuilder :: IpAddresses a -> Builder
displayBuilder = [IpAddress a] -> Builder
forall a. Display a => [a] -> Builder
displayList ([IpAddress a] -> Builder)
-> (IpAddresses a -> [IpAddress a]) -> IpAddresses a -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Optic' An_Iso NoIx (IpAddresses a) [IpAddress a]
-> IpAddresses a -> [IpAddress a]
forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view Optic' An_Iso NoIx (IpAddresses a) [IpAddress a]
#unIpAddresses
instance IsList (IpAddresses a) where
type Item (IpAddresses a) = IpAddress a
fromList :: [Item (IpAddresses a)] -> IpAddresses a
fromList = [Item (IpAddresses a)] -> IpAddresses a
[IpAddress a] -> IpAddresses a
forall (a :: IpType). [IpAddress a] -> IpAddresses a
MkIpAddresses
toList :: IpAddresses a -> [Item (IpAddresses a)]
toList = IpAddresses a -> [Item (IpAddresses a)]
IpAddresses a -> [IpAddress a]
forall (a :: IpType). IpAddresses a -> [IpAddress a]
unIpAddresses