{-|
Module      : Network.Types.ICMPv6
Description : Data types for ICMPv6 types and codes
Copyright   : (c) 2021 Adam Flott
License     : BSD-3-Clause
Maintainer  : adam@adamflott.com
Stability   : experimental
Portability : POSIX

Data types and conversions for ICMPv6 automatically built from the specification at
<https://www.iana.org/assignments/icmpv6-parameters/icmpv6-parameters.xml>

Specification date: 2021-01-27
-}
module Network.Types.ICMPv6 (
    -- * Types
    ICMPv6Type(..)

    -- * Codes
    , ICMPv6CodeNum(..)
    , ICMPv6Code(..)

    -- * Codes from Type
    , icmpv6CodesForType

    -- * Conversions
    , icmpv6TypeToStringNum
    , icmpv6TypeFromStringNum
    , icmpv6TypeToNum
    , icmpv6CodeToStringNum

    -- * Deprecated testing
    , isICMPv6TypeDeprecated

) where


-- base
import Data.String (IsString)
import Data.Word (Word8)
import GHC.Generics

-- | Wrap a numeric ICMPv6 type.
--
-- @since 1.0.0
newtype ICMPv6TypeNum = ICMPv6TypeNum Word8


-- | ICMPv6 type.
--
-- @since 1.0.0
data ICMPv6Type
    = ICMPv6TypeUnknown
    | ICMPv6Type0Reserved -- ^ Reserved
    | ICMPv6Type1DestinationUnreachable -- ^ Destination Unreachable
    | ICMPv6Type2PacketTooBig -- ^ Packet Too Big
    | ICMPv6Type3TimeExceeded -- ^ Time Exceeded
    | ICMPv6Type4ParameterProblem -- ^ Parameter Problem
    | ICMPv6Type100PrivateExperimentation -- ^ Private experimentation
    | ICMPv6Type101PrivateExperimentation -- ^ Private experimentation
    | ICMPv6Type127ReservedForExpansionOfIcmpv6ErrorMessages -- ^ Reserved for expansion of ICMPv6 error messages
    | ICMPv6Type128EchoRequest -- ^ Echo Request
    | ICMPv6Type129EchoReply -- ^ Echo Reply
    | ICMPv6Type130MulticastListenerQuery -- ^ Multicast Listener Query
    | ICMPv6Type131MulticastListenerReport -- ^ Multicast Listener Report
    | ICMPv6Type132MulticastListenerDone -- ^ Multicast Listener Done
    | ICMPv6Type133RouterSolicitation -- ^ Router Solicitation
    | ICMPv6Type134RouterAdvertisement -- ^ Router Advertisement
    | ICMPv6Type135NeighborSolicitation -- ^ Neighbor Solicitation
    | ICMPv6Type136NeighborAdvertisement -- ^ Neighbor Advertisement
    | ICMPv6Type137RedirectMessage -- ^ Redirect Message
    | ICMPv6Type138RouterRenumbering -- ^ Router Renumbering
    | ICMPv6Type139IcmpNodeInformationQuery -- ^ ICMP Node Information Query
    | ICMPv6Type140IcmpNodeInformationResponse -- ^ ICMP Node Information Response
    | ICMPv6Type141InverseNeighborDiscoverySolicitationMessage -- ^ Inverse Neighbor Discovery Solicitation Message
    | ICMPv6Type142InverseNeighborDiscoveryAdvertisementMessage -- ^ Inverse Neighbor Discovery Advertisement Message
    | ICMPv6Type143Version2MulticastListenerReport -- ^ Version 2 Multicast Listener Report
    | ICMPv6Type144HomeAgentAddressDiscoveryRequestMessage -- ^ Home Agent Address Discovery Request Message
    | ICMPv6Type145HomeAgentAddressDiscoveryReplyMessage -- ^ Home Agent Address Discovery Reply Message
    | ICMPv6Type146MobilePrefixSolicitation -- ^ Mobile Prefix Solicitation
    | ICMPv6Type147MobilePrefixAdvertisement -- ^ Mobile Prefix Advertisement
    | ICMPv6Type148CertificationPathSolicitationMessage -- ^ Certification Path Solicitation Message
    | ICMPv6Type149CertificationPathAdvertisementMessage -- ^ Certification Path Advertisement Message
    | ICMPv6Type150IcmpMessagesUtilizedByExperimentalMobilityProtocolsSuchAsSeamoby -- ^ ICMP messages utilized by experimental            mobility protocols such as Seamoby
    | ICMPv6Type151MulticastRouterAdvertisement -- ^ Multicast Router Advertisement
    | ICMPv6Type152MulticastRouterSolicitation -- ^ Multicast Router Solicitation
    | ICMPv6Type153MulticastRouterTermination -- ^ Multicast Router Termination
    | ICMPv6Type154Fmipv6Messages -- ^ FMIPv6 Messages
    | ICMPv6Type155RplControlMessage -- ^ RPL Control Message
    | ICMPv6Type156Ilnpv6LocatorUpdateMessage -- ^ ILNPv6 Locator Update Message
    | ICMPv6Type157DuplicateAddressRequest -- ^ Duplicate Address Request
    | ICMPv6Type158DuplicateAddressConfirmation -- ^ Duplicate Address Confirmation
    | ICMPv6Type159MplControlMessage -- ^ MPL Control Message
    | ICMPv6Type160ExtendedEchoRequest -- ^ Extended Echo Request
    | ICMPv6Type161ExtendedEchoReply -- ^ Extended Echo Reply
    | ICMPv6Type200PrivateExperimentation -- ^ Private experimentation
    | ICMPv6Type201PrivateExperimentation -- ^ Private experimentation
    | ICMPv6Type255ReservedForExpansionOfIcmpv6InformationalMessages -- ^ Reserved for expansion of ICMPv6 informational    messages
    deriving stock (ICMPv6Type
ICMPv6Type -> ICMPv6Type -> Bounded ICMPv6Type
forall a. a -> a -> Bounded a
maxBound :: ICMPv6Type
$cmaxBound :: ICMPv6Type
minBound :: ICMPv6Type
$cminBound :: ICMPv6Type
Bounded, ICMPv6Type -> ICMPv6Type -> Bool
(ICMPv6Type -> ICMPv6Type -> Bool)
-> (ICMPv6Type -> ICMPv6Type -> Bool) -> Eq ICMPv6Type
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ICMPv6Type -> ICMPv6Type -> Bool
$c/= :: ICMPv6Type -> ICMPv6Type -> Bool
== :: ICMPv6Type -> ICMPv6Type -> Bool
$c== :: ICMPv6Type -> ICMPv6Type -> Bool
Eq, Int -> ICMPv6Type
ICMPv6Type -> Int
ICMPv6Type -> [ICMPv6Type]
ICMPv6Type -> ICMPv6Type
ICMPv6Type -> ICMPv6Type -> [ICMPv6Type]
ICMPv6Type -> ICMPv6Type -> ICMPv6Type -> [ICMPv6Type]
(ICMPv6Type -> ICMPv6Type)
-> (ICMPv6Type -> ICMPv6Type)
-> (Int -> ICMPv6Type)
-> (ICMPv6Type -> Int)
-> (ICMPv6Type -> [ICMPv6Type])
-> (ICMPv6Type -> ICMPv6Type -> [ICMPv6Type])
-> (ICMPv6Type -> ICMPv6Type -> [ICMPv6Type])
-> (ICMPv6Type -> ICMPv6Type -> ICMPv6Type -> [ICMPv6Type])
-> Enum ICMPv6Type
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 :: ICMPv6Type -> ICMPv6Type -> ICMPv6Type -> [ICMPv6Type]
$cenumFromThenTo :: ICMPv6Type -> ICMPv6Type -> ICMPv6Type -> [ICMPv6Type]
enumFromTo :: ICMPv6Type -> ICMPv6Type -> [ICMPv6Type]
$cenumFromTo :: ICMPv6Type -> ICMPv6Type -> [ICMPv6Type]
enumFromThen :: ICMPv6Type -> ICMPv6Type -> [ICMPv6Type]
$cenumFromThen :: ICMPv6Type -> ICMPv6Type -> [ICMPv6Type]
enumFrom :: ICMPv6Type -> [ICMPv6Type]
$cenumFrom :: ICMPv6Type -> [ICMPv6Type]
fromEnum :: ICMPv6Type -> Int
$cfromEnum :: ICMPv6Type -> Int
toEnum :: Int -> ICMPv6Type
$ctoEnum :: Int -> ICMPv6Type
pred :: ICMPv6Type -> ICMPv6Type
$cpred :: ICMPv6Type -> ICMPv6Type
succ :: ICMPv6Type -> ICMPv6Type
$csucc :: ICMPv6Type -> ICMPv6Type
Enum, (forall x. ICMPv6Type -> Rep ICMPv6Type x)
-> (forall x. Rep ICMPv6Type x -> ICMPv6Type) -> Generic ICMPv6Type
forall x. Rep ICMPv6Type x -> ICMPv6Type
forall x. ICMPv6Type -> Rep ICMPv6Type x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ICMPv6Type x -> ICMPv6Type
$cfrom :: forall x. ICMPv6Type -> Rep ICMPv6Type x
Generic, Eq ICMPv6Type
Eq ICMPv6Type
-> (ICMPv6Type -> ICMPv6Type -> Ordering)
-> (ICMPv6Type -> ICMPv6Type -> Bool)
-> (ICMPv6Type -> ICMPv6Type -> Bool)
-> (ICMPv6Type -> ICMPv6Type -> Bool)
-> (ICMPv6Type -> ICMPv6Type -> Bool)
-> (ICMPv6Type -> ICMPv6Type -> ICMPv6Type)
-> (ICMPv6Type -> ICMPv6Type -> ICMPv6Type)
-> Ord ICMPv6Type
ICMPv6Type -> ICMPv6Type -> Bool
ICMPv6Type -> ICMPv6Type -> Ordering
ICMPv6Type -> ICMPv6Type -> ICMPv6Type
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 :: ICMPv6Type -> ICMPv6Type -> ICMPv6Type
$cmin :: ICMPv6Type -> ICMPv6Type -> ICMPv6Type
max :: ICMPv6Type -> ICMPv6Type -> ICMPv6Type
$cmax :: ICMPv6Type -> ICMPv6Type -> ICMPv6Type
>= :: ICMPv6Type -> ICMPv6Type -> Bool
$c>= :: ICMPv6Type -> ICMPv6Type -> Bool
> :: ICMPv6Type -> ICMPv6Type -> Bool
$c> :: ICMPv6Type -> ICMPv6Type -> Bool
<= :: ICMPv6Type -> ICMPv6Type -> Bool
$c<= :: ICMPv6Type -> ICMPv6Type -> Bool
< :: ICMPv6Type -> ICMPv6Type -> Bool
$c< :: ICMPv6Type -> ICMPv6Type -> Bool
compare :: ICMPv6Type -> ICMPv6Type -> Ordering
$ccompare :: ICMPv6Type -> ICMPv6Type -> Ordering
$cp1Ord :: Eq ICMPv6Type
Ord, Int -> ICMPv6Type -> ShowS
[ICMPv6Type] -> ShowS
ICMPv6Type -> String
(Int -> ICMPv6Type -> ShowS)
-> (ICMPv6Type -> String)
-> ([ICMPv6Type] -> ShowS)
-> Show ICMPv6Type
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ICMPv6Type] -> ShowS
$cshowList :: [ICMPv6Type] -> ShowS
show :: ICMPv6Type -> String
$cshow :: ICMPv6Type -> String
showsPrec :: Int -> ICMPv6Type -> ShowS
$cshowsPrec :: Int -> ICMPv6Type -> ShowS
Show)


-- | Wrap a numeric ICMPv6 code.
--
-- @since 1.0.0
newtype ICMPv6CodeNum = ICMPv6CodeNum Word8


-- | ICMPv6 code.
--
-- @since 1.0.0
data ICMPv6Code
    = ICMPv6CodeUnknown -- ^ Unknown code
    | ICMPv6Type1Code0 -- ^ Type 1 code 0 - no route to destination
    | ICMPv6Type1Code1 -- ^ Type 1 code 1 - communication with destination administratively prohibited
    | ICMPv6Type1Code2 -- ^ Type 1 code 2 - beyond scope of source address
    | ICMPv6Type1Code3 -- ^ Type 1 code 3 - address unreachable
    | ICMPv6Type1Code4 -- ^ Type 1 code 4 - port unreachable
    | ICMPv6Type1Code5 -- ^ Type 1 code 5 - source address failed ingress/egress policy
    | ICMPv6Type1Code6 -- ^ Type 1 code 6 - reject route to destination
    | ICMPv6Type1Code7 -- ^ Type 1 code 7 - Error in Source Routing Header
    | ICMPv6Type1Code8 -- ^ Type 1 code 8 - Headers too long
    | ICMPv6Type2Code0 -- ^ Type 2 code 0 - N/A - No description in spec
    | ICMPv6Type3Code0 -- ^ Type 3 code 0 - hop limit exceeded in transit
    | ICMPv6Type3Code1 -- ^ Type 3 code 1 - fragment reassembly time exceeded
    | ICMPv6Type4Code0 -- ^ Type 4 code 0 - erroneous header field encountered
    | ICMPv6Type4Code1 -- ^ Type 4 code 1 - unrecognized Next Header type encountered
    | ICMPv6Type4Code2 -- ^ Type 4 code 2 - unrecognized IPv6 option encountered
    | ICMPv6Type4Code3 -- ^ Type 4 code 3 - IPv6 First Fragment has incomplete IPv6 Header Chain
    | ICMPv6Type4Code4 -- ^ Type 4 code 4 - SR Upper-layer Header Error
    | ICMPv6Type4Code5 -- ^ Type 4 code 5 - Unrecognized Next Header type encountered by intermediate node
    | ICMPv6Type4Code6 -- ^ Type 4 code 6 - Extension header too big
    | ICMPv6Type4Code7 -- ^ Type 4 code 7 - Extension header chain too long
    | ICMPv6Type4Code8 -- ^ Type 4 code 8 - Too many extension headers
    | ICMPv6Type4Code9 -- ^ Type 4 code 9 - Too many options in extension header
    | ICMPv6Type4Code10 -- ^ Type 4 code 10 - Option too big
    | ICMPv6Type128Code0 -- ^ Type 128 code 0 - N/A - No description in spec
    | ICMPv6Type129Code0 -- ^ Type 129 code 0 - N/A - No description in spec
    | ICMPv6Type130Code0 -- ^ Type 130 code 0 - N/A - No description in spec
    | ICMPv6Type131Code0 -- ^ Type 131 code 0 - N/A - No description in spec
    | ICMPv6Type132Code0 -- ^ Type 132 code 0 - N/A - No description in spec
    | ICMPv6Type133Code0 -- ^ Type 133 code 0 - N/A - No description in spec
    | ICMPv6Type134Code0 -- ^ Type 134 code 0 - N/A - No description in spec
    | ICMPv6Type135Code0 -- ^ Type 135 code 0 - N/A - No description in spec
    | ICMPv6Type136Code0 -- ^ Type 136 code 0 - N/A - No description in spec
    | ICMPv6Type137Code0 -- ^ Type 137 code 0 - N/A - No description in spec
    | ICMPv6Type138Code0 -- ^ Type 138 code 0 - Router Renumbering Command
    | ICMPv6Type138Code1 -- ^ Type 138 code 1 - Router Renumbering Result
    | ICMPv6Type138Code255 -- ^ Type 138 code 255 - Sequence Number Reset
    | ICMPv6Type139Code0 -- ^ Type 139 code 0 - The Data field contains an IPv6 address which is the Subject of this Query.
    | ICMPv6Type139Code1 -- ^ Type 139 code 1 - The Data field contains a name which is the Subject of this Query, or is empty, as in the case of a NOOP.
    | ICMPv6Type139Code2 -- ^ Type 139 code 2 - The Data field contains an IPv4 address which is the Subject of this Query.
    | ICMPv6Type140Code0 -- ^ Type 140 code 0 - A successful reply.  The Reply Data field may or may not be empty.
    | ICMPv6Type140Code1 -- ^ Type 140 code 1 - The Responder refuses to supply the answer.  The Reply Data field will be empty.
    | ICMPv6Type140Code2 -- ^ Type 140 code 2 - The Qtype of the Query is unknown to the Responder.  The Reply Data field will be empty.
    | ICMPv6Type141Code0 -- ^ Type 141 code 0 - N/A - No description in spec
    | ICMPv6Type142Code0 -- ^ Type 142 code 0 - N/A - No description in spec
    | ICMPv6Type144Code0 -- ^ Type 144 code 0 - N/A - No description in spec
    | ICMPv6Type145Code0 -- ^ Type 145 code 0 - N/A - No description in spec
    | ICMPv6Type146Code0 -- ^ Type 146 code 0 - N/A - No description in spec
    | ICMPv6Type147Code0 -- ^ Type 147 code 0 - N/A - No description in spec
    | ICMPv6Type157Code0 -- ^ Type 157 code 0 - DAR message
    | ICMPv6Type157Code1 -- ^ Type 157 code 1 - EDAR message with 64-bit ROVR field
    | ICMPv6Type157Code2 -- ^ Type 157 code 2 - EDAR message with 128-bit ROVR field
    | ICMPv6Type157Code3 -- ^ Type 157 code 3 - EDAR message with 192-bit ROVR field
    | ICMPv6Type157Code4 -- ^ Type 157 code 4 - EDAR message with 256-bit ROVR field
    | ICMPv6Type158Code0 -- ^ Type 158 code 0 - DAC message
    | ICMPv6Type158Code1 -- ^ Type 158 code 1 - EDAC message with 64-bit ROVR field
    | ICMPv6Type158Code2 -- ^ Type 158 code 2 - EDAC message with 128-bit ROVR field
    | ICMPv6Type158Code3 -- ^ Type 158 code 3 - EDAC message with 192-bit ROVR field
    | ICMPv6Type158Code4 -- ^ Type 158 code 4 - EDAC message with 256-bit ROVR field
    | ICMPv6Type160Code0 -- ^ Type 160 code 0 - No Error
    | ICMPv6Type161Code0 -- ^ Type 161 code 0 - No Error
    | ICMPv6Type161Code1 -- ^ Type 161 code 1 - Malformed Query
    | ICMPv6Type161Code2 -- ^ Type 161 code 2 - No Such Interface
    | ICMPv6Type161Code3 -- ^ Type 161 code 3 - No Such Table Entry
    | ICMPv6Type161Code4 -- ^ Type 161 code 4 - Multiple Interfaces Satisfy Query
    deriving stock (ICMPv6Code
ICMPv6Code -> ICMPv6Code -> Bounded ICMPv6Code
forall a. a -> a -> Bounded a
maxBound :: ICMPv6Code
$cmaxBound :: ICMPv6Code
minBound :: ICMPv6Code
$cminBound :: ICMPv6Code
Bounded, ICMPv6Code -> ICMPv6Code -> Bool
(ICMPv6Code -> ICMPv6Code -> Bool)
-> (ICMPv6Code -> ICMPv6Code -> Bool) -> Eq ICMPv6Code
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ICMPv6Code -> ICMPv6Code -> Bool
$c/= :: ICMPv6Code -> ICMPv6Code -> Bool
== :: ICMPv6Code -> ICMPv6Code -> Bool
$c== :: ICMPv6Code -> ICMPv6Code -> Bool
Eq, Int -> ICMPv6Code
ICMPv6Code -> Int
ICMPv6Code -> [ICMPv6Code]
ICMPv6Code -> ICMPv6Code
ICMPv6Code -> ICMPv6Code -> [ICMPv6Code]
ICMPv6Code -> ICMPv6Code -> ICMPv6Code -> [ICMPv6Code]
(ICMPv6Code -> ICMPv6Code)
-> (ICMPv6Code -> ICMPv6Code)
-> (Int -> ICMPv6Code)
-> (ICMPv6Code -> Int)
-> (ICMPv6Code -> [ICMPv6Code])
-> (ICMPv6Code -> ICMPv6Code -> [ICMPv6Code])
-> (ICMPv6Code -> ICMPv6Code -> [ICMPv6Code])
-> (ICMPv6Code -> ICMPv6Code -> ICMPv6Code -> [ICMPv6Code])
-> Enum ICMPv6Code
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 :: ICMPv6Code -> ICMPv6Code -> ICMPv6Code -> [ICMPv6Code]
$cenumFromThenTo :: ICMPv6Code -> ICMPv6Code -> ICMPv6Code -> [ICMPv6Code]
enumFromTo :: ICMPv6Code -> ICMPv6Code -> [ICMPv6Code]
$cenumFromTo :: ICMPv6Code -> ICMPv6Code -> [ICMPv6Code]
enumFromThen :: ICMPv6Code -> ICMPv6Code -> [ICMPv6Code]
$cenumFromThen :: ICMPv6Code -> ICMPv6Code -> [ICMPv6Code]
enumFrom :: ICMPv6Code -> [ICMPv6Code]
$cenumFrom :: ICMPv6Code -> [ICMPv6Code]
fromEnum :: ICMPv6Code -> Int
$cfromEnum :: ICMPv6Code -> Int
toEnum :: Int -> ICMPv6Code
$ctoEnum :: Int -> ICMPv6Code
pred :: ICMPv6Code -> ICMPv6Code
$cpred :: ICMPv6Code -> ICMPv6Code
succ :: ICMPv6Code -> ICMPv6Code
$csucc :: ICMPv6Code -> ICMPv6Code
Enum, (forall x. ICMPv6Code -> Rep ICMPv6Code x)
-> (forall x. Rep ICMPv6Code x -> ICMPv6Code) -> Generic ICMPv6Code
forall x. Rep ICMPv6Code x -> ICMPv6Code
forall x. ICMPv6Code -> Rep ICMPv6Code x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ICMPv6Code x -> ICMPv6Code
$cfrom :: forall x. ICMPv6Code -> Rep ICMPv6Code x
Generic, Eq ICMPv6Code
Eq ICMPv6Code
-> (ICMPv6Code -> ICMPv6Code -> Ordering)
-> (ICMPv6Code -> ICMPv6Code -> Bool)
-> (ICMPv6Code -> ICMPv6Code -> Bool)
-> (ICMPv6Code -> ICMPv6Code -> Bool)
-> (ICMPv6Code -> ICMPv6Code -> Bool)
-> (ICMPv6Code -> ICMPv6Code -> ICMPv6Code)
-> (ICMPv6Code -> ICMPv6Code -> ICMPv6Code)
-> Ord ICMPv6Code
ICMPv6Code -> ICMPv6Code -> Bool
ICMPv6Code -> ICMPv6Code -> Ordering
ICMPv6Code -> ICMPv6Code -> ICMPv6Code
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 :: ICMPv6Code -> ICMPv6Code -> ICMPv6Code
$cmin :: ICMPv6Code -> ICMPv6Code -> ICMPv6Code
max :: ICMPv6Code -> ICMPv6Code -> ICMPv6Code
$cmax :: ICMPv6Code -> ICMPv6Code -> ICMPv6Code
>= :: ICMPv6Code -> ICMPv6Code -> Bool
$c>= :: ICMPv6Code -> ICMPv6Code -> Bool
> :: ICMPv6Code -> ICMPv6Code -> Bool
$c> :: ICMPv6Code -> ICMPv6Code -> Bool
<= :: ICMPv6Code -> ICMPv6Code -> Bool
$c<= :: ICMPv6Code -> ICMPv6Code -> Bool
< :: ICMPv6Code -> ICMPv6Code -> Bool
$c< :: ICMPv6Code -> ICMPv6Code -> Bool
compare :: ICMPv6Code -> ICMPv6Code -> Ordering
$ccompare :: ICMPv6Code -> ICMPv6Code -> Ordering
$cp1Ord :: Eq ICMPv6Code
Ord, Int -> ICMPv6Code -> ShowS
[ICMPv6Code] -> ShowS
ICMPv6Code -> String
(Int -> ICMPv6Code -> ShowS)
-> (ICMPv6Code -> String)
-> ([ICMPv6Code] -> ShowS)
-> Show ICMPv6Code
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ICMPv6Code] -> ShowS
$cshowList :: [ICMPv6Code] -> ShowS
show :: ICMPv6Code -> String
$cshow :: ICMPv6Code -> String
showsPrec :: Int -> ICMPv6Code -> ShowS
$cshowsPrec :: Int -> ICMPv6Code -> ShowS
Show)

-- | Get a list of 'ICMPv6Code' for a given 'ICMPv6Type'.
--
-- @since 1.0.0
icmpv6CodesForType :: ICMPv6Type -> [ICMPv6Code]
icmpv6CodesForType :: ICMPv6Type -> [ICMPv6Code]
icmpv6CodesForType ICMPv6Type
ty = case ICMPv6Type
ty of
    ICMPv6Type
ICMPv6TypeUnknown -> []
    ICMPv6Type
ICMPv6Type0Reserved -> [
        ]
    ICMPv6Type
ICMPv6Type1DestinationUnreachable -> [
        ICMPv6Code
ICMPv6Type1Code0,
        ICMPv6Code
ICMPv6Type1Code1,
        ICMPv6Code
ICMPv6Type1Code2,
        ICMPv6Code
ICMPv6Type1Code3,
        ICMPv6Code
ICMPv6Type1Code4,
        ICMPv6Code
ICMPv6Type1Code5,
        ICMPv6Code
ICMPv6Type1Code6,
        ICMPv6Code
ICMPv6Type1Code7,
        ICMPv6Code
ICMPv6Type1Code8
        ]
    ICMPv6Type
ICMPv6Type2PacketTooBig -> [
        ICMPv6Code
ICMPv6Type2Code0
        ]
    ICMPv6Type
ICMPv6Type3TimeExceeded -> [
        ICMPv6Code
ICMPv6Type3Code0,
        ICMPv6Code
ICMPv6Type3Code1
        ]
    ICMPv6Type
ICMPv6Type4ParameterProblem -> [
        ICMPv6Code
ICMPv6Type4Code0,
        ICMPv6Code
ICMPv6Type4Code1,
        ICMPv6Code
ICMPv6Type4Code2,
        ICMPv6Code
ICMPv6Type4Code3,
        ICMPv6Code
ICMPv6Type4Code4,
        ICMPv6Code
ICMPv6Type4Code5,
        ICMPv6Code
ICMPv6Type4Code6,
        ICMPv6Code
ICMPv6Type4Code7,
        ICMPv6Code
ICMPv6Type4Code8,
        ICMPv6Code
ICMPv6Type4Code9,
        ICMPv6Code
ICMPv6Type4Code10
        ]
    ICMPv6Type
ICMPv6Type100PrivateExperimentation -> [
        ]
    ICMPv6Type
ICMPv6Type101PrivateExperimentation -> [
        ]
    ICMPv6Type
ICMPv6Type127ReservedForExpansionOfIcmpv6ErrorMessages -> [
        ]
    ICMPv6Type
ICMPv6Type128EchoRequest -> [
        ICMPv6Code
ICMPv6Type128Code0
        ]
    ICMPv6Type
ICMPv6Type129EchoReply -> [
        ICMPv6Code
ICMPv6Type129Code0
        ]
    ICMPv6Type
ICMPv6Type130MulticastListenerQuery -> [
        ICMPv6Code
ICMPv6Type130Code0
        ]
    ICMPv6Type
ICMPv6Type131MulticastListenerReport -> [
        ICMPv6Code
ICMPv6Type131Code0
        ]
    ICMPv6Type
ICMPv6Type132MulticastListenerDone -> [
        ICMPv6Code
ICMPv6Type132Code0
        ]
    ICMPv6Type
ICMPv6Type133RouterSolicitation -> [
        ICMPv6Code
ICMPv6Type133Code0
        ]
    ICMPv6Type
ICMPv6Type134RouterAdvertisement -> [
        ICMPv6Code
ICMPv6Type134Code0
        ]
    ICMPv6Type
ICMPv6Type135NeighborSolicitation -> [
        ICMPv6Code
ICMPv6Type135Code0
        ]
    ICMPv6Type
ICMPv6Type136NeighborAdvertisement -> [
        ICMPv6Code
ICMPv6Type136Code0
        ]
    ICMPv6Type
ICMPv6Type137RedirectMessage -> [
        ICMPv6Code
ICMPv6Type137Code0
        ]
    ICMPv6Type
ICMPv6Type138RouterRenumbering -> [
        ICMPv6Code
ICMPv6Type138Code0,
        ICMPv6Code
ICMPv6Type138Code1,
        ICMPv6Code
ICMPv6Type138Code255
        ]
    ICMPv6Type
ICMPv6Type139IcmpNodeInformationQuery -> [
        ICMPv6Code
ICMPv6Type139Code0,
        ICMPv6Code
ICMPv6Type139Code1,
        ICMPv6Code
ICMPv6Type139Code2
        ]
    ICMPv6Type
ICMPv6Type140IcmpNodeInformationResponse -> [
        ICMPv6Code
ICMPv6Type140Code0,
        ICMPv6Code
ICMPv6Type140Code1,
        ICMPv6Code
ICMPv6Type140Code2
        ]
    ICMPv6Type
ICMPv6Type141InverseNeighborDiscoverySolicitationMessage -> [
        ICMPv6Code
ICMPv6Type141Code0
        ]
    ICMPv6Type
ICMPv6Type142InverseNeighborDiscoveryAdvertisementMessage -> [
        ICMPv6Code
ICMPv6Type142Code0
        ]
    ICMPv6Type
ICMPv6Type143Version2MulticastListenerReport -> [
        ]
    ICMPv6Type
ICMPv6Type144HomeAgentAddressDiscoveryRequestMessage -> [
        ICMPv6Code
ICMPv6Type144Code0
        ]
    ICMPv6Type
ICMPv6Type145HomeAgentAddressDiscoveryReplyMessage -> [
        ICMPv6Code
ICMPv6Type145Code0
        ]
    ICMPv6Type
ICMPv6Type146MobilePrefixSolicitation -> [
        ICMPv6Code
ICMPv6Type146Code0
        ]
    ICMPv6Type
ICMPv6Type147MobilePrefixAdvertisement -> [
        ICMPv6Code
ICMPv6Type147Code0
        ]
    ICMPv6Type
ICMPv6Type148CertificationPathSolicitationMessage -> [
        ]
    ICMPv6Type
ICMPv6Type149CertificationPathAdvertisementMessage -> [
        ]
    ICMPv6Type
ICMPv6Type150IcmpMessagesUtilizedByExperimentalMobilityProtocolsSuchAsSeamoby -> [
        ]
    ICMPv6Type
ICMPv6Type151MulticastRouterAdvertisement -> [
        ]
    ICMPv6Type
ICMPv6Type152MulticastRouterSolicitation -> [
        ]
    ICMPv6Type
ICMPv6Type153MulticastRouterTermination -> [
        ]
    ICMPv6Type
ICMPv6Type154Fmipv6Messages -> [
        ]
    ICMPv6Type
ICMPv6Type155RplControlMessage -> [
        ]
    ICMPv6Type
ICMPv6Type156Ilnpv6LocatorUpdateMessage -> [
        ]
    ICMPv6Type
ICMPv6Type157DuplicateAddressRequest -> [
        ICMPv6Code
ICMPv6Type157Code0,
        ICMPv6Code
ICMPv6Type157Code1,
        ICMPv6Code
ICMPv6Type157Code2,
        ICMPv6Code
ICMPv6Type157Code3,
        ICMPv6Code
ICMPv6Type157Code4
        ]
    ICMPv6Type
ICMPv6Type158DuplicateAddressConfirmation -> [
        ICMPv6Code
ICMPv6Type158Code0,
        ICMPv6Code
ICMPv6Type158Code1,
        ICMPv6Code
ICMPv6Type158Code2,
        ICMPv6Code
ICMPv6Type158Code3,
        ICMPv6Code
ICMPv6Type158Code4
        ]
    ICMPv6Type
ICMPv6Type159MplControlMessage -> [
        ]
    ICMPv6Type
ICMPv6Type160ExtendedEchoRequest -> [
        ICMPv6Code
ICMPv6Type160Code0
        ]
    ICMPv6Type
ICMPv6Type161ExtendedEchoReply -> [
        ICMPv6Code
ICMPv6Type161Code0,
        ICMPv6Code
ICMPv6Type161Code1,
        ICMPv6Code
ICMPv6Type161Code2,
        ICMPv6Code
ICMPv6Type161Code3,
        ICMPv6Code
ICMPv6Type161Code4
        ]
    ICMPv6Type
ICMPv6Type200PrivateExperimentation -> [
        ]
    ICMPv6Type
ICMPv6Type201PrivateExperimentation -> [
        ]
    ICMPv6Type
ICMPv6Type255ReservedForExpansionOfIcmpv6InformationalMessages -> [
        ]

-- | Convert a 'ICMPv6Type' into a string.
--
-- @since 1.0.0
icmpv6TypeToStringNum :: IsString a => ICMPv6Type -> a
icmpv6TypeToStringNum :: ICMPv6Type -> a
icmpv6TypeToStringNum ICMPv6Type
t = case ICMPv6Type
t of
    ICMPv6Type
ICMPv6Type0Reserved -> a
"0"
    ICMPv6Type
ICMPv6Type1DestinationUnreachable -> a
"1"
    ICMPv6Type
ICMPv6Type2PacketTooBig -> a
"2"
    ICMPv6Type
ICMPv6Type3TimeExceeded -> a
"3"
    ICMPv6Type
ICMPv6Type4ParameterProblem -> a
"4"
    ICMPv6Type
ICMPv6Type100PrivateExperimentation -> a
"100"
    ICMPv6Type
ICMPv6Type101PrivateExperimentation -> a
"101"
    ICMPv6Type
ICMPv6Type127ReservedForExpansionOfIcmpv6ErrorMessages -> a
"127"
    ICMPv6Type
ICMPv6Type128EchoRequest -> a
"128"
    ICMPv6Type
ICMPv6Type129EchoReply -> a
"129"
    ICMPv6Type
ICMPv6Type130MulticastListenerQuery -> a
"130"
    ICMPv6Type
ICMPv6Type131MulticastListenerReport -> a
"131"
    ICMPv6Type
ICMPv6Type132MulticastListenerDone -> a
"132"
    ICMPv6Type
ICMPv6Type133RouterSolicitation -> a
"133"
    ICMPv6Type
ICMPv6Type134RouterAdvertisement -> a
"134"
    ICMPv6Type
ICMPv6Type135NeighborSolicitation -> a
"135"
    ICMPv6Type
ICMPv6Type136NeighborAdvertisement -> a
"136"
    ICMPv6Type
ICMPv6Type137RedirectMessage -> a
"137"
    ICMPv6Type
ICMPv6Type138RouterRenumbering -> a
"138"
    ICMPv6Type
ICMPv6Type139IcmpNodeInformationQuery -> a
"139"
    ICMPv6Type
ICMPv6Type140IcmpNodeInformationResponse -> a
"140"
    ICMPv6Type
ICMPv6Type141InverseNeighborDiscoverySolicitationMessage -> a
"141"
    ICMPv6Type
ICMPv6Type142InverseNeighborDiscoveryAdvertisementMessage -> a
"142"
    ICMPv6Type
ICMPv6Type143Version2MulticastListenerReport -> a
"143"
    ICMPv6Type
ICMPv6Type144HomeAgentAddressDiscoveryRequestMessage -> a
"144"
    ICMPv6Type
ICMPv6Type145HomeAgentAddressDiscoveryReplyMessage -> a
"145"
    ICMPv6Type
ICMPv6Type146MobilePrefixSolicitation -> a
"146"
    ICMPv6Type
ICMPv6Type147MobilePrefixAdvertisement -> a
"147"
    ICMPv6Type
ICMPv6Type148CertificationPathSolicitationMessage -> a
"148"
    ICMPv6Type
ICMPv6Type149CertificationPathAdvertisementMessage -> a
"149"
    ICMPv6Type
ICMPv6Type150IcmpMessagesUtilizedByExperimentalMobilityProtocolsSuchAsSeamoby -> a
"150"
    ICMPv6Type
ICMPv6Type151MulticastRouterAdvertisement -> a
"151"
    ICMPv6Type
ICMPv6Type152MulticastRouterSolicitation -> a
"152"
    ICMPv6Type
ICMPv6Type153MulticastRouterTermination -> a
"153"
    ICMPv6Type
ICMPv6Type154Fmipv6Messages -> a
"154"
    ICMPv6Type
ICMPv6Type155RplControlMessage -> a
"155"
    ICMPv6Type
ICMPv6Type156Ilnpv6LocatorUpdateMessage -> a
"156"
    ICMPv6Type
ICMPv6Type157DuplicateAddressRequest -> a
"157"
    ICMPv6Type
ICMPv6Type158DuplicateAddressConfirmation -> a
"158"
    ICMPv6Type
ICMPv6Type159MplControlMessage -> a
"159"
    ICMPv6Type
ICMPv6Type160ExtendedEchoRequest -> a
"160"
    ICMPv6Type
ICMPv6Type161ExtendedEchoReply -> a
"161"
    ICMPv6Type
ICMPv6Type200PrivateExperimentation -> a
"200"
    ICMPv6Type
ICMPv6Type201PrivateExperimentation -> a
"201"
    ICMPv6Type
ICMPv6Type255ReservedForExpansionOfIcmpv6InformationalMessages -> a
"255"
    ICMPv6Type
ICMPv6TypeUnknown -> a
"?"


-- | Convert a string into a 'ICMPv6Type'.
--
-- @since 1.0.0
icmpv6TypeFromStringNum :: (Eq a, IsString a) => a -> ICMPv6Type
icmpv6TypeFromStringNum :: a -> ICMPv6Type
icmpv6TypeFromStringNum a
s = case a
s of
    a
"0" -> ICMPv6Type
ICMPv6Type0Reserved
    a
"1" -> ICMPv6Type
ICMPv6Type1DestinationUnreachable
    a
"2" -> ICMPv6Type
ICMPv6Type2PacketTooBig
    a
"3" -> ICMPv6Type
ICMPv6Type3TimeExceeded
    a
"4" -> ICMPv6Type
ICMPv6Type4ParameterProblem
    a
"100" -> ICMPv6Type
ICMPv6Type100PrivateExperimentation
    a
"101" -> ICMPv6Type
ICMPv6Type101PrivateExperimentation
    a
"127" -> ICMPv6Type
ICMPv6Type127ReservedForExpansionOfIcmpv6ErrorMessages
    a
"128" -> ICMPv6Type
ICMPv6Type128EchoRequest
    a
"129" -> ICMPv6Type
ICMPv6Type129EchoReply
    a
"130" -> ICMPv6Type
ICMPv6Type130MulticastListenerQuery
    a
"131" -> ICMPv6Type
ICMPv6Type131MulticastListenerReport
    a
"132" -> ICMPv6Type
ICMPv6Type132MulticastListenerDone
    a
"133" -> ICMPv6Type
ICMPv6Type133RouterSolicitation
    a
"134" -> ICMPv6Type
ICMPv6Type134RouterAdvertisement
    a
"135" -> ICMPv6Type
ICMPv6Type135NeighborSolicitation
    a
"136" -> ICMPv6Type
ICMPv6Type136NeighborAdvertisement
    a
"137" -> ICMPv6Type
ICMPv6Type137RedirectMessage
    a
"138" -> ICMPv6Type
ICMPv6Type138RouterRenumbering
    a
"139" -> ICMPv6Type
ICMPv6Type139IcmpNodeInformationQuery
    a
"140" -> ICMPv6Type
ICMPv6Type140IcmpNodeInformationResponse
    a
"141" -> ICMPv6Type
ICMPv6Type141InverseNeighborDiscoverySolicitationMessage
    a
"142" -> ICMPv6Type
ICMPv6Type142InverseNeighborDiscoveryAdvertisementMessage
    a
"143" -> ICMPv6Type
ICMPv6Type143Version2MulticastListenerReport
    a
"144" -> ICMPv6Type
ICMPv6Type144HomeAgentAddressDiscoveryRequestMessage
    a
"145" -> ICMPv6Type
ICMPv6Type145HomeAgentAddressDiscoveryReplyMessage
    a
"146" -> ICMPv6Type
ICMPv6Type146MobilePrefixSolicitation
    a
"147" -> ICMPv6Type
ICMPv6Type147MobilePrefixAdvertisement
    a
"148" -> ICMPv6Type
ICMPv6Type148CertificationPathSolicitationMessage
    a
"149" -> ICMPv6Type
ICMPv6Type149CertificationPathAdvertisementMessage
    a
"150" -> ICMPv6Type
ICMPv6Type150IcmpMessagesUtilizedByExperimentalMobilityProtocolsSuchAsSeamoby
    a
"151" -> ICMPv6Type
ICMPv6Type151MulticastRouterAdvertisement
    a
"152" -> ICMPv6Type
ICMPv6Type152MulticastRouterSolicitation
    a
"153" -> ICMPv6Type
ICMPv6Type153MulticastRouterTermination
    a
"154" -> ICMPv6Type
ICMPv6Type154Fmipv6Messages
    a
"155" -> ICMPv6Type
ICMPv6Type155RplControlMessage
    a
"156" -> ICMPv6Type
ICMPv6Type156Ilnpv6LocatorUpdateMessage
    a
"157" -> ICMPv6Type
ICMPv6Type157DuplicateAddressRequest
    a
"158" -> ICMPv6Type
ICMPv6Type158DuplicateAddressConfirmation
    a
"159" -> ICMPv6Type
ICMPv6Type159MplControlMessage
    a
"160" -> ICMPv6Type
ICMPv6Type160ExtendedEchoRequest
    a
"161" -> ICMPv6Type
ICMPv6Type161ExtendedEchoReply
    a
"200" -> ICMPv6Type
ICMPv6Type200PrivateExperimentation
    a
"201" -> ICMPv6Type
ICMPv6Type201PrivateExperimentation
    a
"255" -> ICMPv6Type
ICMPv6Type255ReservedForExpansionOfIcmpv6InformationalMessages
    a
_ -> ICMPv6Type
ICMPv6TypeUnknown


-- | Turn an 'ICMPv6Type' into a 'ICMPv6TypeNum'.
--
-- @since 1.0.0
icmpv6TypeToNum :: ICMPv6Type -> ICMPv6TypeNum
icmpv6TypeToNum :: ICMPv6Type -> ICMPv6TypeNum
icmpv6TypeToNum ICMPv6Type
t = case ICMPv6Type
t of
    ICMPv6Type
ICMPv6Type0Reserved -> Word8 -> ICMPv6TypeNum
ICMPv6TypeNum Word8
0
    ICMPv6Type
ICMPv6Type1DestinationUnreachable -> Word8 -> ICMPv6TypeNum
ICMPv6TypeNum Word8
1
    ICMPv6Type
ICMPv6Type2PacketTooBig -> Word8 -> ICMPv6TypeNum
ICMPv6TypeNum Word8
2
    ICMPv6Type
ICMPv6Type3TimeExceeded -> Word8 -> ICMPv6TypeNum
ICMPv6TypeNum Word8
3
    ICMPv6Type
ICMPv6Type4ParameterProblem -> Word8 -> ICMPv6TypeNum
ICMPv6TypeNum Word8
4
    ICMPv6Type
ICMPv6Type100PrivateExperimentation -> Word8 -> ICMPv6TypeNum
ICMPv6TypeNum Word8
100
    ICMPv6Type
ICMPv6Type101PrivateExperimentation -> Word8 -> ICMPv6TypeNum
ICMPv6TypeNum Word8
101
    ICMPv6Type
ICMPv6Type127ReservedForExpansionOfIcmpv6ErrorMessages -> Word8 -> ICMPv6TypeNum
ICMPv6TypeNum Word8
127
    ICMPv6Type
ICMPv6Type128EchoRequest -> Word8 -> ICMPv6TypeNum
ICMPv6TypeNum Word8
128
    ICMPv6Type
ICMPv6Type129EchoReply -> Word8 -> ICMPv6TypeNum
ICMPv6TypeNum Word8
129
    ICMPv6Type
ICMPv6Type130MulticastListenerQuery -> Word8 -> ICMPv6TypeNum
ICMPv6TypeNum Word8
130
    ICMPv6Type
ICMPv6Type131MulticastListenerReport -> Word8 -> ICMPv6TypeNum
ICMPv6TypeNum Word8
131
    ICMPv6Type
ICMPv6Type132MulticastListenerDone -> Word8 -> ICMPv6TypeNum
ICMPv6TypeNum Word8
132
    ICMPv6Type
ICMPv6Type133RouterSolicitation -> Word8 -> ICMPv6TypeNum
ICMPv6TypeNum Word8
133
    ICMPv6Type
ICMPv6Type134RouterAdvertisement -> Word8 -> ICMPv6TypeNum
ICMPv6TypeNum Word8
134
    ICMPv6Type
ICMPv6Type135NeighborSolicitation -> Word8 -> ICMPv6TypeNum
ICMPv6TypeNum Word8
135
    ICMPv6Type
ICMPv6Type136NeighborAdvertisement -> Word8 -> ICMPv6TypeNum
ICMPv6TypeNum Word8
136
    ICMPv6Type
ICMPv6Type137RedirectMessage -> Word8 -> ICMPv6TypeNum
ICMPv6TypeNum Word8
137
    ICMPv6Type
ICMPv6Type138RouterRenumbering -> Word8 -> ICMPv6TypeNum
ICMPv6TypeNum Word8
138
    ICMPv6Type
ICMPv6Type139IcmpNodeInformationQuery -> Word8 -> ICMPv6TypeNum
ICMPv6TypeNum Word8
139
    ICMPv6Type
ICMPv6Type140IcmpNodeInformationResponse -> Word8 -> ICMPv6TypeNum
ICMPv6TypeNum Word8
140
    ICMPv6Type
ICMPv6Type141InverseNeighborDiscoverySolicitationMessage -> Word8 -> ICMPv6TypeNum
ICMPv6TypeNum Word8
141
    ICMPv6Type
ICMPv6Type142InverseNeighborDiscoveryAdvertisementMessage -> Word8 -> ICMPv6TypeNum
ICMPv6TypeNum Word8
142
    ICMPv6Type
ICMPv6Type143Version2MulticastListenerReport -> Word8 -> ICMPv6TypeNum
ICMPv6TypeNum Word8
143
    ICMPv6Type
ICMPv6Type144HomeAgentAddressDiscoveryRequestMessage -> Word8 -> ICMPv6TypeNum
ICMPv6TypeNum Word8
144
    ICMPv6Type
ICMPv6Type145HomeAgentAddressDiscoveryReplyMessage -> Word8 -> ICMPv6TypeNum
ICMPv6TypeNum Word8
145
    ICMPv6Type
ICMPv6Type146MobilePrefixSolicitation -> Word8 -> ICMPv6TypeNum
ICMPv6TypeNum Word8
146
    ICMPv6Type
ICMPv6Type147MobilePrefixAdvertisement -> Word8 -> ICMPv6TypeNum
ICMPv6TypeNum Word8
147
    ICMPv6Type
ICMPv6Type148CertificationPathSolicitationMessage -> Word8 -> ICMPv6TypeNum
ICMPv6TypeNum Word8
148
    ICMPv6Type
ICMPv6Type149CertificationPathAdvertisementMessage -> Word8 -> ICMPv6TypeNum
ICMPv6TypeNum Word8
149
    ICMPv6Type
ICMPv6Type150IcmpMessagesUtilizedByExperimentalMobilityProtocolsSuchAsSeamoby -> Word8 -> ICMPv6TypeNum
ICMPv6TypeNum Word8
150
    ICMPv6Type
ICMPv6Type151MulticastRouterAdvertisement -> Word8 -> ICMPv6TypeNum
ICMPv6TypeNum Word8
151
    ICMPv6Type
ICMPv6Type152MulticastRouterSolicitation -> Word8 -> ICMPv6TypeNum
ICMPv6TypeNum Word8
152
    ICMPv6Type
ICMPv6Type153MulticastRouterTermination -> Word8 -> ICMPv6TypeNum
ICMPv6TypeNum Word8
153
    ICMPv6Type
ICMPv6Type154Fmipv6Messages -> Word8 -> ICMPv6TypeNum
ICMPv6TypeNum Word8
154
    ICMPv6Type
ICMPv6Type155RplControlMessage -> Word8 -> ICMPv6TypeNum
ICMPv6TypeNum Word8
155
    ICMPv6Type
ICMPv6Type156Ilnpv6LocatorUpdateMessage -> Word8 -> ICMPv6TypeNum
ICMPv6TypeNum Word8
156
    ICMPv6Type
ICMPv6Type157DuplicateAddressRequest -> Word8 -> ICMPv6TypeNum
ICMPv6TypeNum Word8
157
    ICMPv6Type
ICMPv6Type158DuplicateAddressConfirmation -> Word8 -> ICMPv6TypeNum
ICMPv6TypeNum Word8
158
    ICMPv6Type
ICMPv6Type159MplControlMessage -> Word8 -> ICMPv6TypeNum
ICMPv6TypeNum Word8
159
    ICMPv6Type
ICMPv6Type160ExtendedEchoRequest -> Word8 -> ICMPv6TypeNum
ICMPv6TypeNum Word8
160
    ICMPv6Type
ICMPv6Type161ExtendedEchoReply -> Word8 -> ICMPv6TypeNum
ICMPv6TypeNum Word8
161
    ICMPv6Type
ICMPv6Type200PrivateExperimentation -> Word8 -> ICMPv6TypeNum
ICMPv6TypeNum Word8
200
    ICMPv6Type
ICMPv6Type201PrivateExperimentation -> Word8 -> ICMPv6TypeNum
ICMPv6TypeNum Word8
201
    ICMPv6Type
ICMPv6Type255ReservedForExpansionOfIcmpv6InformationalMessages -> Word8 -> ICMPv6TypeNum
ICMPv6TypeNum Word8
255
    ICMPv6Type
ICMPv6TypeUnknown -> Word8 -> ICMPv6TypeNum
ICMPv6TypeNum Word8
0


-- | Test if an 'ICMPv6Type' has been deprecated.
--
-- @since 1.0.0
isICMPv6TypeDeprecated :: ICMPv6Type -> Bool
isICMPv6TypeDeprecated :: ICMPv6Type -> Bool
isICMPv6TypeDeprecated ICMPv6Type
ty = case ICMPv6Type
ty of
   ICMPv6Type
ICMPv6Type0Reserved-> Bool
False
   ICMPv6Type
ICMPv6Type1DestinationUnreachable-> Bool
False
   ICMPv6Type
ICMPv6Type2PacketTooBig-> Bool
False
   ICMPv6Type
ICMPv6Type3TimeExceeded-> Bool
False
   ICMPv6Type
ICMPv6Type4ParameterProblem-> Bool
False
   ICMPv6Type
ICMPv6Type100PrivateExperimentation-> Bool
False
   ICMPv6Type
ICMPv6Type101PrivateExperimentation-> Bool
False
   ICMPv6Type
ICMPv6Type127ReservedForExpansionOfIcmpv6ErrorMessages-> Bool
False
   ICMPv6Type
ICMPv6Type128EchoRequest-> Bool
False
   ICMPv6Type
ICMPv6Type129EchoReply-> Bool
False
   ICMPv6Type
ICMPv6Type130MulticastListenerQuery-> Bool
False
   ICMPv6Type
ICMPv6Type131MulticastListenerReport-> Bool
False
   ICMPv6Type
ICMPv6Type132MulticastListenerDone-> Bool
False
   ICMPv6Type
ICMPv6Type133RouterSolicitation-> Bool
False
   ICMPv6Type
ICMPv6Type134RouterAdvertisement-> Bool
False
   ICMPv6Type
ICMPv6Type135NeighborSolicitation-> Bool
False
   ICMPv6Type
ICMPv6Type136NeighborAdvertisement-> Bool
False
   ICMPv6Type
ICMPv6Type137RedirectMessage-> Bool
False
   ICMPv6Type
ICMPv6Type138RouterRenumbering-> Bool
False
   ICMPv6Type
ICMPv6Type139IcmpNodeInformationQuery-> Bool
False
   ICMPv6Type
ICMPv6Type140IcmpNodeInformationResponse-> Bool
False
   ICMPv6Type
ICMPv6Type141InverseNeighborDiscoverySolicitationMessage-> Bool
False
   ICMPv6Type
ICMPv6Type142InverseNeighborDiscoveryAdvertisementMessage-> Bool
False
   ICMPv6Type
ICMPv6Type143Version2MulticastListenerReport-> Bool
False
   ICMPv6Type
ICMPv6Type144HomeAgentAddressDiscoveryRequestMessage-> Bool
False
   ICMPv6Type
ICMPv6Type145HomeAgentAddressDiscoveryReplyMessage-> Bool
False
   ICMPv6Type
ICMPv6Type146MobilePrefixSolicitation-> Bool
False
   ICMPv6Type
ICMPv6Type147MobilePrefixAdvertisement-> Bool
False
   ICMPv6Type
ICMPv6Type148CertificationPathSolicitationMessage-> Bool
False
   ICMPv6Type
ICMPv6Type149CertificationPathAdvertisementMessage-> Bool
False
   ICMPv6Type
ICMPv6Type150IcmpMessagesUtilizedByExperimentalMobilityProtocolsSuchAsSeamoby-> Bool
False
   ICMPv6Type
ICMPv6Type151MulticastRouterAdvertisement-> Bool
False
   ICMPv6Type
ICMPv6Type152MulticastRouterSolicitation-> Bool
False
   ICMPv6Type
ICMPv6Type153MulticastRouterTermination-> Bool
False
   ICMPv6Type
ICMPv6Type154Fmipv6Messages-> Bool
False
   ICMPv6Type
ICMPv6Type155RplControlMessage-> Bool
False
   ICMPv6Type
ICMPv6Type156Ilnpv6LocatorUpdateMessage-> Bool
False
   ICMPv6Type
ICMPv6Type157DuplicateAddressRequest-> Bool
False
   ICMPv6Type
ICMPv6Type158DuplicateAddressConfirmation-> Bool
False
   ICMPv6Type
ICMPv6Type159MplControlMessage-> Bool
False
   ICMPv6Type
ICMPv6Type160ExtendedEchoRequest-> Bool
False
   ICMPv6Type
ICMPv6Type161ExtendedEchoReply-> Bool
False
   ICMPv6Type
ICMPv6Type200PrivateExperimentation-> Bool
False
   ICMPv6Type
ICMPv6Type201PrivateExperimentation-> Bool
False
   ICMPv6Type
ICMPv6Type255ReservedForExpansionOfIcmpv6InformationalMessages-> Bool
False
   ICMPv6Type
ICMPv6TypeUnknown -> Bool
False


-- | Convert a 'ICMPv6Code' into a string.
--
-- @since 1.0.1
icmpv6CodeToStringNum :: IsString a => ICMPv6Code -> a
icmpv6CodeToStringNum :: ICMPv6Code -> a
icmpv6CodeToStringNum ICMPv6Code
t = case ICMPv6Code
t of
        ICMPv6Code
ICMPv6Type1Code0 -> a
"0"
        ICMPv6Code
ICMPv6Type1Code1 -> a
"1"
        ICMPv6Code
ICMPv6Type1Code2 -> a
"2"
        ICMPv6Code
ICMPv6Type1Code3 -> a
"3"
        ICMPv6Code
ICMPv6Type1Code4 -> a
"4"
        ICMPv6Code
ICMPv6Type1Code5 -> a
"5"
        ICMPv6Code
ICMPv6Type1Code6 -> a
"6"
        ICMPv6Code
ICMPv6Type1Code7 -> a
"7"
        ICMPv6Code
ICMPv6Type1Code8 -> a
"8"
        ICMPv6Code
ICMPv6Type2Code0 -> a
"0"
        ICMPv6Code
ICMPv6Type3Code0 -> a
"0"
        ICMPv6Code
ICMPv6Type3Code1 -> a
"1"
        ICMPv6Code
ICMPv6Type4Code0 -> a
"0"
        ICMPv6Code
ICMPv6Type4Code1 -> a
"1"
        ICMPv6Code
ICMPv6Type4Code2 -> a
"2"
        ICMPv6Code
ICMPv6Type4Code3 -> a
"3"
        ICMPv6Code
ICMPv6Type4Code4 -> a
"4"
        ICMPv6Code
ICMPv6Type4Code5 -> a
"5"
        ICMPv6Code
ICMPv6Type4Code6 -> a
"6"
        ICMPv6Code
ICMPv6Type4Code7 -> a
"7"
        ICMPv6Code
ICMPv6Type4Code8 -> a
"8"
        ICMPv6Code
ICMPv6Type4Code9 -> a
"9"
        ICMPv6Code
ICMPv6Type4Code10 -> a
"10"
        ICMPv6Code
ICMPv6Type128Code0 -> a
"0"
        ICMPv6Code
ICMPv6Type129Code0 -> a
"0"
        ICMPv6Code
ICMPv6Type130Code0 -> a
"0"
        ICMPv6Code
ICMPv6Type131Code0 -> a
"0"
        ICMPv6Code
ICMPv6Type132Code0 -> a
"0"
        ICMPv6Code
ICMPv6Type133Code0 -> a
"0"
        ICMPv6Code
ICMPv6Type134Code0 -> a
"0"
        ICMPv6Code
ICMPv6Type135Code0 -> a
"0"
        ICMPv6Code
ICMPv6Type136Code0 -> a
"0"
        ICMPv6Code
ICMPv6Type137Code0 -> a
"0"
        ICMPv6Code
ICMPv6Type138Code0 -> a
"0"
        ICMPv6Code
ICMPv6Type138Code1 -> a
"1"
        ICMPv6Code
ICMPv6Type138Code255 -> a
"255"
        ICMPv6Code
ICMPv6Type139Code0 -> a
"0"
        ICMPv6Code
ICMPv6Type139Code1 -> a
"1"
        ICMPv6Code
ICMPv6Type139Code2 -> a
"2"
        ICMPv6Code
ICMPv6Type140Code0 -> a
"0"
        ICMPv6Code
ICMPv6Type140Code1 -> a
"1"
        ICMPv6Code
ICMPv6Type140Code2 -> a
"2"
        ICMPv6Code
ICMPv6Type141Code0 -> a
"0"
        ICMPv6Code
ICMPv6Type142Code0 -> a
"0"
        ICMPv6Code
ICMPv6Type144Code0 -> a
"0"
        ICMPv6Code
ICMPv6Type145Code0 -> a
"0"
        ICMPv6Code
ICMPv6Type146Code0 -> a
"0"
        ICMPv6Code
ICMPv6Type147Code0 -> a
"0"
        ICMPv6Code
ICMPv6Type157Code0 -> a
"0"
        ICMPv6Code
ICMPv6Type157Code1 -> a
"1"
        ICMPv6Code
ICMPv6Type157Code2 -> a
"2"
        ICMPv6Code
ICMPv6Type157Code3 -> a
"3"
        ICMPv6Code
ICMPv6Type157Code4 -> a
"4"
        ICMPv6Code
ICMPv6Type158Code0 -> a
"0"
        ICMPv6Code
ICMPv6Type158Code1 -> a
"1"
        ICMPv6Code
ICMPv6Type158Code2 -> a
"2"
        ICMPv6Code
ICMPv6Type158Code3 -> a
"3"
        ICMPv6Code
ICMPv6Type158Code4 -> a
"4"
        ICMPv6Code
ICMPv6Type160Code0 -> a
"0"
        ICMPv6Code
ICMPv6Type161Code0 -> a
"0"
        ICMPv6Code
ICMPv6Type161Code1 -> a
"1"
        ICMPv6Code
ICMPv6Type161Code2 -> a
"2"
        ICMPv6Code
ICMPv6Type161Code3 -> a
"3"
        ICMPv6Code
ICMPv6Type161Code4 -> a
"4"
        ICMPv6Code
ICMPv6CodeUnknown -> a
"?"