{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Data.ASN1
( ASN1(..)
, ASN1Constructed(..)
, ASN1Decode
, ASN1Encode
, toBinaryPut
, toBinaryGet
, GASN1EncodeCompOf, gasn1encodeCompOf
, GASN1DecodeCompOf, gasn1decodeCompOf
, GASN1EncodeChoice, gasn1encodeChoice
, GASN1DecodeChoice, gasn1decodeChoice
, ENUMERATED(..), Enumerated(..)
, IMPLICIT(..), implicit
, EXPLICIT(..), explicit
, COMPONENTS_OF(..)
, CHOICE(..)
, OCTET_STRING
, NULL
, BOOLEAN
, BOOLEAN_DEFAULT(..)
, OPTIONAL
, SET(..)
, SET1(..)
, asn1fail
, retag, wraptag
, dec'SEQUENCE
, enc'SEQUENCE
, enc'SEQUENCE_COMPS
, dec'SET_OF
, dec'SEQUENCE_OF
, dec'CHOICE
, dec'OPTIONAL
, dec'BoundedEnum
, enc'BoundedEnum
, dec'NULL
, enc'NULL
) where
import Common
import Data.ASN1.Prim
import Data.Int.Subtypes
import GHC.Generics ((:*:) (..), (:+:) (..), K1 (..), M1 (..), Rep, V1, from, to)
import Data.Binary as Bin
import Data.Binary.Get as Bin
import Data.Binary.Put as Bin
import qualified Data.ByteString as BS
import qualified Data.ByteString.Short as SBS
import qualified Data.Map.Strict as Map
import Data.Set (Set)
import qualified Data.Set as Set
import Data.String (IsString)
import qualified Data.Text.Short as TS
class Enumerated x where
toEnumerated :: Int64 -> Maybe x
default toEnumerated :: (Bounded x, Enum x) => Int64 -> Maybe x
toEnumerated i0 :: Int64
i0
| Just i :: Int
i <- Int64 -> Maybe Int
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
intCastMaybe Int64
i0
, Int
i Int -> (Int, Int) -> Bool
forall a. Ord a => a -> (a, a) -> Bool
`inside` (Int
lb,Int
ub) = x -> Maybe x
forall a. a -> Maybe a
Just (Int -> x
forall a. Enum a => Int -> a
toEnum Int
i)
| Bool
otherwise = Maybe x
forall a. Maybe a
Nothing
where
lb :: Int
lb = x -> Int
forall a. Enum a => a -> Int
fromEnum (x
forall a. Bounded a => a
minBound :: x)
ub :: Int
ub = x -> Int
forall a. Enum a => a -> Int
fromEnum (x
forall a. Bounded a => a
maxBound :: x)
:: x -> Int64
default :: Enum x => x -> Int64
fromEnumerated = Int -> Int64
forall a b.
(Integral a, Integral b, IsIntSubType a b ~ 'True) =>
a -> b
intCast (Int -> Int64) -> (x -> Int) -> x -> Int64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. x -> Int
forall a. Enum a => a -> Int
fromEnum
instance Enumerated Int64 where
toEnumerated :: Int64 -> Maybe Int64
toEnumerated = Int64 -> Maybe Int64
forall a. a -> Maybe a
Just
fromEnumerated :: Int64 -> Int64
fromEnumerated = Int64 -> Int64
forall a. a -> a
id
instance Enumerated Int where
toEnumerated :: Int64 -> Maybe Int
toEnumerated = Int64 -> Maybe Int
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
intCastMaybe
fromEnumerated :: Int -> Int64
fromEnumerated = Int -> Int64
forall a b.
(Integral a, Integral b, IsIntSubType a b ~ 'True) =>
a -> b
intCast
newtype ASN1Encode a = ASN1Encode (Maybe Tag -> PutM a)
empty'ASN1Encode :: ASN1Encode Word64
empty'ASN1Encode :: ASN1Encode Word64
empty'ASN1Encode = (Maybe Tag -> PutM Word64) -> ASN1Encode Word64
forall a. (Maybe Tag -> PutM a) -> ASN1Encode a
ASN1Encode ((Maybe Tag -> PutM Word64) -> ASN1Encode Word64)
-> (Maybe Tag -> PutM Word64) -> ASN1Encode Word64
forall a b. (a -> b) -> a -> b
$ \case
Just _ -> [Char] -> PutM Word64
forall a. HasCallStack => [Char] -> a
error "empty'ASN1Encode: called with tag-override"
Nothing -> Word64 -> PutM Word64
forall (f :: * -> *) a. Applicative f => a -> f a
pure 0
toBinaryPut :: ASN1Encode a -> PutM a
toBinaryPut :: ASN1Encode a -> PutM a
toBinaryPut (ASN1Encode body :: Maybe Tag -> PutM a
body) = Maybe Tag -> PutM a
body Maybe Tag
forall a. Maybe a
Nothing
enc'SEQUENCE_COMPS :: [ASN1Encode Word64] -> ASN1Encode Word64
enc'SEQUENCE_COMPS :: [ASN1Encode Word64] -> ASN1Encode Word64
enc'SEQUENCE_COMPS [] = ASN1Encode Word64
empty'ASN1Encode
enc'SEQUENCE_COMPS xs0 :: [ASN1Encode Word64]
xs0 = (Maybe Tag -> PutM Word64) -> ASN1Encode Word64
forall a. (Maybe Tag -> PutM a) -> ASN1Encode a
ASN1Encode ((Maybe Tag -> PutM Word64) -> ASN1Encode Word64)
-> (Maybe Tag -> PutM Word64) -> ASN1Encode Word64
forall a b. (a -> b) -> a -> b
$ \case
Just _ -> [Char] -> PutM Word64
forall a. HasCallStack => [Char] -> a
error "enc'SEQUENCE_COMPS: called with tag-override"
Nothing -> [ASN1Encode Word64] -> Word64 -> PutM Word64
forall t. Num t => [ASN1Encode t] -> t -> PutM t
go [ASN1Encode Word64]
xs0 0
where
go :: [ASN1Encode t] -> t -> PutM t
go [] sz :: t
sz = t -> PutM t
forall (f :: * -> *) a. Applicative f => a -> f a
pure t
sz
go (ASN1Encode x :: Maybe Tag -> PutM t
x:xs :: [ASN1Encode t]
xs) sz :: t
sz = do
t
n1 <- Maybe Tag -> PutM t
x Maybe Tag
forall a. Maybe a
Nothing
[ASN1Encode t] -> t -> PutM t
go [ASN1Encode t]
xs (t
szt -> t -> t
forall a. Num a => a -> a -> a
+t
n1)
instance Semigroup (ASN1Encode Word64) where
ASN1Encode x :: Maybe Tag -> PutM Word64
x <> :: ASN1Encode Word64 -> ASN1Encode Word64 -> ASN1Encode Word64
<> ASN1Encode y :: Maybe Tag -> PutM Word64
y = (Maybe Tag -> PutM Word64) -> ASN1Encode Word64
forall a. (Maybe Tag -> PutM a) -> ASN1Encode a
ASN1Encode ((Maybe Tag -> PutM Word64) -> ASN1Encode Word64)
-> (Maybe Tag -> PutM Word64) -> ASN1Encode Word64
forall a b. (a -> b) -> a -> b
$ \case
Just _ -> [Char] -> PutM Word64
forall a. HasCallStack => [Char] -> a
error "ASN1Encode append called with tag-override"
Nothing -> Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
(+) (Word64 -> Word64 -> Word64)
-> PutM Word64 -> PutM (Word64 -> Word64)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Tag -> PutM Word64
x Maybe Tag
forall a. Maybe a
Nothing PutM (Word64 -> Word64) -> PutM Word64 -> PutM Word64
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe Tag -> PutM Word64
y Maybe Tag
forall a. Maybe a
Nothing
enc'SEQUENCE :: [ASN1Encode Word64] -> ASN1Encode Word64
enc'SEQUENCE :: [ASN1Encode Word64] -> ASN1Encode Word64
enc'SEQUENCE = Tag -> ASN1Encode Word64 -> ASN1Encode Word64
wraptag (Word64 -> Tag
Universal 16) (ASN1Encode Word64 -> ASN1Encode Word64)
-> ([ASN1Encode Word64] -> ASN1Encode Word64)
-> [ASN1Encode Word64]
-> ASN1Encode Word64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ASN1Encode Word64] -> ASN1Encode Word64
enc'SEQUENCE_COMPS
enc'SET :: [ASN1Encode Word64] -> ASN1Encode Word64
enc'SET :: [ASN1Encode Word64] -> ASN1Encode Word64
enc'SET = Tag -> ASN1Encode Word64 -> ASN1Encode Word64
forall a. Tag -> ASN1Encode a -> ASN1Encode a
retag (Word64 -> Tag
Universal 17) (ASN1Encode Word64 -> ASN1Encode Word64)
-> ([ASN1Encode Word64] -> ASN1Encode Word64)
-> [ASN1Encode Word64]
-> ASN1Encode Word64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ASN1Encode Word64] -> ASN1Encode Word64
enc'SEQUENCE
data ASN1Res x = Consumed ( Maybe TL) x
| Unexpected TL
| UnexpectedEOF
deriving (Int -> ASN1Res x -> ShowS
[ASN1Res x] -> ShowS
ASN1Res x -> [Char]
(Int -> ASN1Res x -> ShowS)
-> (ASN1Res x -> [Char])
-> ([ASN1Res x] -> ShowS)
-> Show (ASN1Res x)
forall x. Show x => Int -> ASN1Res x -> ShowS
forall x. Show x => [ASN1Res x] -> ShowS
forall x. Show x => ASN1Res x -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [ASN1Res x] -> ShowS
$cshowList :: forall x. Show x => [ASN1Res x] -> ShowS
show :: ASN1Res x -> [Char]
$cshow :: forall x. Show x => ASN1Res x -> [Char]
showsPrec :: Int -> ASN1Res x -> ShowS
$cshowsPrec :: forall x. Show x => Int -> ASN1Res x -> ShowS
Show,a -> ASN1Res b -> ASN1Res a
(a -> b) -> ASN1Res a -> ASN1Res b
(forall a b. (a -> b) -> ASN1Res a -> ASN1Res b)
-> (forall a b. a -> ASN1Res b -> ASN1Res a) -> Functor ASN1Res
forall a b. a -> ASN1Res b -> ASN1Res a
forall a b. (a -> b) -> ASN1Res a -> ASN1Res b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> ASN1Res b -> ASN1Res a
$c<$ :: forall a b. a -> ASN1Res b -> ASN1Res a
fmap :: (a -> b) -> ASN1Res a -> ASN1Res b
$cfmap :: forall a b. (a -> b) -> ASN1Res a -> ASN1Res b
Functor)
data Card = Card !Word !Word
deriving (Card -> Card -> Bool
(Card -> Card -> Bool) -> (Card -> Card -> Bool) -> Eq Card
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Card -> Card -> Bool
$c/= :: Card -> Card -> Bool
== :: Card -> Card -> Bool
$c== :: Card -> Card -> Bool
Eq,Eq Card
Eq Card =>
(Card -> Card -> Ordering)
-> (Card -> Card -> Bool)
-> (Card -> Card -> Bool)
-> (Card -> Card -> Bool)
-> (Card -> Card -> Bool)
-> (Card -> Card -> Card)
-> (Card -> Card -> Card)
-> Ord Card
Card -> Card -> Bool
Card -> Card -> Ordering
Card -> Card -> Card
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 :: Card -> Card -> Card
$cmin :: Card -> Card -> Card
max :: Card -> Card -> Card
$cmax :: Card -> Card -> Card
>= :: Card -> Card -> Bool
$c>= :: Card -> Card -> Bool
> :: Card -> Card -> Bool
$c> :: Card -> Card -> Bool
<= :: Card -> Card -> Bool
$c<= :: Card -> Card -> Bool
< :: Card -> Card -> Bool
$c< :: Card -> Card -> Bool
compare :: Card -> Card -> Ordering
$ccompare :: Card -> Card -> Ordering
$cp1Ord :: Eq Card
Ord,Int -> Card -> ShowS
[Card] -> ShowS
Card -> [Char]
(Int -> Card -> ShowS)
-> (Card -> [Char]) -> ([Card] -> ShowS) -> Show Card
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [Card] -> ShowS
$cshowList :: [Card] -> ShowS
show :: Card -> [Char]
$cshow :: Card -> [Char]
showsPrec :: Int -> Card -> ShowS
$cshowsPrec :: Int -> Card -> ShowS
Show)
cardMaySkip :: Card -> Bool
cardMaySkip :: Card -> Bool
cardMaySkip (Card 0 _) = Bool
True
cardMaySkip (Card _ _) = Bool
False
instance Semigroup Card where
Card l1 :: Word
l1 u1 :: Word
u1 <> :: Card -> Card -> Card
<> Card l2 :: Word
l2 u2 :: Word
u2 = Word -> Word -> Card
Card (Word
l1Word -> Word -> Word
forall a. Num a => a -> a -> a
+Word
l2) (Word
u1Word -> Word -> Word
forall a. Num a => a -> a -> a
+Word
u2)
instance Monoid Card where
mappend :: Card -> Card -> Card
mappend = Card -> Card -> Card
forall a. Semigroup a => a -> a -> a
(<>)
mempty :: Card
mempty = Word -> Word -> Card
Card 0 0
data ASN1Decode x = ASN1Decode
{ ASN1Decode x -> Set Tag
asn1dTags :: !(Set Tag)
, ASN1Decode x -> Bool
asn1dAny :: !Bool
, ASN1Decode x -> Card
asn1dCard :: !Card
, ASN1Decode x -> Maybe TL -> Get (ASN1Res x)
asn1dContent :: Maybe TL -> Get (ASN1Res x)
}
getASN1Decode :: ASN1Decode x -> Maybe TL -> Get (ASN1Res x)
getASN1Decode :: ASN1Decode x -> Maybe TL -> Get (ASN1Res x)
getASN1Decode (ASN1Decode{..}) Nothing
| Card -> Bool
cardMaySkip Card
asn1dCard = Maybe TL -> Get (ASN1Res x)
asn1dContent Maybe TL
forall a. Maybe a
Nothing
| Bool
otherwise = ASN1Res x -> Get (ASN1Res x)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ASN1Res x
forall x. ASN1Res x
UnexpectedEOF
getASN1Decode (ASN1Decode{..}) (Just tl :: TL
tl@(t :: Tag
t,_,_))
| Card -> Bool
cardMaySkip Card
asn1dCard Bool -> Bool -> Bool
|| Bool
asn1dAny Bool -> Bool -> Bool
|| Tag -> Set Tag -> Bool
forall a. Ord a => a -> Set a -> Bool
Set.member Tag
t Set Tag
asn1dTags = Maybe TL -> Get (ASN1Res x)
asn1dContent (TL -> Maybe TL
forall a. a -> Maybe a
Just TL
tl)
| Bool
otherwise = ASN1Res x -> Get (ASN1Res x)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (TL -> ASN1Res x
forall x. TL -> ASN1Res x
Unexpected TL
tl)
instance Alternative ASN1Decode where
empty :: ASN1Decode a
empty = Set Tag
-> Bool -> Card -> (Maybe TL -> Get (ASN1Res a)) -> ASN1Decode a
forall x.
Set Tag
-> Bool -> Card -> (Maybe TL -> Get (ASN1Res x)) -> ASN1Decode x
ASN1Decode Set Tag
forall a. Monoid a => a
mempty Bool
False Card
forall a. Monoid a => a
mempty (ASN1Res a -> Get (ASN1Res a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ASN1Res a -> Get (ASN1Res a))
-> (Maybe TL -> ASN1Res a) -> Maybe TL -> Get (ASN1Res a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ASN1Res a -> (TL -> ASN1Res a) -> Maybe TL -> ASN1Res a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ASN1Res a
forall x. ASN1Res x
UnexpectedEOF TL -> ASN1Res a
forall x. TL -> ASN1Res x
Unexpected)
x :: ASN1Decode a
x <|> :: ASN1Decode a -> ASN1Decode a -> ASN1Decode a
<|> y :: ASN1Decode a
y
| ASN1Decode a -> Bool
forall x. ASN1Decode x -> Bool
asn1decodeIsEmpty ASN1Decode a
x = ASN1Decode a
y
| ASN1Decode a -> Bool
forall x. ASN1Decode x -> Bool
asn1decodeIsEmpty ASN1Decode a
y = ASN1Decode a
x
| ASN1Decode a -> Card
forall x. ASN1Decode x -> Card
asn1dCard ASN1Decode a
x Card -> Card -> Bool
forall a. Eq a => a -> a -> Bool
/= ASN1Decode a -> Card
forall x. ASN1Decode x -> Card
asn1dCard ASN1Decode a
y = [Char] -> ASN1Decode a
error' "ASN1Decode: CHOICE over different cardinalities not supported"
| ASN1Decode a -> Bool
forall x. ASN1Decode x -> Bool
asn1dAny ASN1Decode a
x, ASN1Decode a -> Bool
forall x. ASN1Decode x -> Bool
asn1dAny ASN1Decode a
y = [Char] -> ASN1Decode a
error' "ASN1Decode: CHOICE not possible over multiple ANYs"
| Card -> Bool
cardMaySkip (ASN1Decode a -> Card
forall x. ASN1Decode x -> Card
asn1dCard ASN1Decode a
x) Bool -> Bool -> Bool
|| Card -> Bool
cardMaySkip (ASN1Decode a -> Card
forall x. ASN1Decode x -> Card
asn1dCard ASN1Decode a
y) = [Char] -> ASN1Decode a
error' "ASN1Decode: CHOICE over OPTIONAL not supported"
| Bool -> Bool
not (Set Tag -> Bool
forall a. Set a -> Bool
Set.null (ASN1Decode a -> Set Tag
forall x. ASN1Decode x -> Set Tag
asn1dTags ASN1Decode a
x Set Tag -> Set Tag -> Set Tag
forall a. Ord a => Set a -> Set a -> Set a
`Set.intersection` ASN1Decode a -> Set Tag
forall x. ASN1Decode x -> Set Tag
asn1dTags ASN1Decode a
y)) = [Char] -> ASN1Decode a
error' "ASN1Decode: CHOICEs overlap"
| Bool
otherwise = $WASN1Decode :: forall x.
Set Tag
-> Bool -> Card -> (Maybe TL -> Get (ASN1Res x)) -> ASN1Decode x
ASN1Decode
{ asn1dTags :: Set Tag
asn1dTags = ASN1Decode a -> Set Tag
forall x. ASN1Decode x -> Set Tag
asn1dTags ASN1Decode a
x Set Tag -> Set Tag -> Set Tag
forall a. Semigroup a => a -> a -> a
<> ASN1Decode a -> Set Tag
forall x. ASN1Decode x -> Set Tag
asn1dTags ASN1Decode a
y
, asn1dAny :: Bool
asn1dAny = ASN1Decode a -> Bool
forall x. ASN1Decode x -> Bool
asn1dAny ASN1Decode a
x Bool -> Bool -> Bool
|| ASN1Decode a -> Bool
forall x. ASN1Decode x -> Bool
asn1dAny ASN1Decode a
y
, asn1dCard :: Card
asn1dCard = ASN1Decode a -> Card
forall x. ASN1Decode x -> Card
asn1dCard ASN1Decode a
x
, asn1dContent :: Maybe TL -> Get (ASN1Res a)
asn1dContent = \case
tl :: Maybe TL
tl@(Just tl' :: TL
tl'@(t :: Tag
t,_,_)) -> case () of
_ | Tag -> Set Tag -> Bool
forall a. Ord a => a -> Set a -> Bool
Set.member Tag
t (ASN1Decode a -> Set Tag
forall x. ASN1Decode x -> Set Tag
asn1dTags ASN1Decode a
x) -> ASN1Decode a -> Maybe TL -> Get (ASN1Res a)
forall x. ASN1Decode x -> Maybe TL -> Get (ASN1Res x)
asn1dContent ASN1Decode a
x Maybe TL
tl
| Tag -> Set Tag -> Bool
forall a. Ord a => a -> Set a -> Bool
Set.member Tag
t (ASN1Decode a -> Set Tag
forall x. ASN1Decode x -> Set Tag
asn1dTags ASN1Decode a
y) -> ASN1Decode a -> Maybe TL -> Get (ASN1Res a)
forall x. ASN1Decode x -> Maybe TL -> Get (ASN1Res x)
asn1dContent ASN1Decode a
y Maybe TL
tl
| ASN1Decode a -> Bool
forall x. ASN1Decode x -> Bool
asn1dAny ASN1Decode a
x -> ASN1Decode a -> Maybe TL -> Get (ASN1Res a)
forall x. ASN1Decode x -> Maybe TL -> Get (ASN1Res x)
asn1dContent ASN1Decode a
x Maybe TL
tl
| ASN1Decode a -> Bool
forall x. ASN1Decode x -> Bool
asn1dAny ASN1Decode a
y -> ASN1Decode a -> Maybe TL -> Get (ASN1Res a)
forall x. ASN1Decode x -> Maybe TL -> Get (ASN1Res x)
asn1dContent ASN1Decode a
y Maybe TL
tl
| Bool
otherwise -> ASN1Res a -> Get (ASN1Res a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (TL -> ASN1Res a
forall x. TL -> ASN1Res x
Unexpected TL
tl')
Nothing -> ASN1Res a -> Get (ASN1Res a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ASN1Res a
forall x. ASN1Res x
UnexpectedEOF
}
where
error' :: [Char] -> ASN1Decode a
error' s :: [Char]
s = [Char] -> ASN1Decode a
forall a. HasCallStack => [Char] -> a
error ([Char]
s [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ " => " [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ ((Set Tag, Bool, Card), (Set Tag, Bool, Card)) -> [Char]
forall a. Show a => a -> [Char]
show ((ASN1Decode a -> Set Tag
forall x. ASN1Decode x -> Set Tag
asn1dTags ASN1Decode a
x, ASN1Decode a -> Bool
forall x. ASN1Decode x -> Bool
asn1dAny ASN1Decode a
x, ASN1Decode a -> Card
forall x. ASN1Decode x -> Card
asn1dCard ASN1Decode a
x), (ASN1Decode a -> Set Tag
forall x. ASN1Decode x -> Set Tag
asn1dTags ASN1Decode a
y, ASN1Decode a -> Bool
forall x. ASN1Decode x -> Bool
asn1dAny ASN1Decode a
y, ASN1Decode a -> Card
forall x. ASN1Decode x -> Card
asn1dCard ASN1Decode a
y)))
asum'ASN1Decode :: [ASN1Decode x] -> ASN1Decode x
asum'ASN1Decode :: [ASN1Decode x] -> ASN1Decode x
asum'ASN1Decode xs0 :: [ASN1Decode x]
xs0
| Map Tag (Maybe TL -> Get (ASN1Res x)) -> Int
forall k a. Map k a -> Int
Map.size Map Tag (Maybe TL -> Get (ASN1Res x))
tagmap Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ((ASN1Decode x -> Int) -> [ASN1Decode x] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map (Set Tag -> Int
forall a. Set a -> Int
Set.size (Set Tag -> Int)
-> (ASN1Decode x -> Set Tag) -> ASN1Decode x -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ASN1Decode x -> Set Tag
forall x. ASN1Decode x -> Set Tag
asn1dTags) [ASN1Decode x]
xs) = [Char] -> ASN1Decode x
forall a. [Char] -> a
error' "ASN1Decode: CHOICEs overlap"
| x0 :: ASN1Decode x
x0:_ <- [ASN1Decode x]
xs = $WASN1Decode :: forall x.
Set Tag
-> Bool -> Card -> (Maybe TL -> Get (ASN1Res x)) -> ASN1Decode x
ASN1Decode { asn1dTags :: Set Tag
asn1dTags = [Set Tag] -> Set Tag
forall a. Monoid a => [a] -> a
mconcat ((ASN1Decode x -> Set Tag) -> [ASN1Decode x] -> [Set Tag]
forall a b. (a -> b) -> [a] -> [b]
map ASN1Decode x -> Set Tag
forall x. ASN1Decode x -> Set Tag
asn1dTags [ASN1Decode x]
xs)
, asn1dAny :: Bool
asn1dAny = (ASN1Decode x -> Bool) -> [ASN1Decode x] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any ASN1Decode x -> Bool
forall x. ASN1Decode x -> Bool
asn1dAny [ASN1Decode x]
xs
, asn1dCard :: Card
asn1dCard = ASN1Decode x -> Card
forall x. ASN1Decode x -> Card
asn1dCard ASN1Decode x
x0
, asn1dContent :: Maybe TL -> Get (ASN1Res x)
asn1dContent = \case
tl :: Maybe TL
tl@(Just tl' :: TL
tl'@(t :: Tag
t,_,_)) -> case () of
_ | Just h :: Maybe TL -> Get (ASN1Res x)
h <- Tag
-> Map Tag (Maybe TL -> Get (ASN1Res x))
-> Maybe (Maybe TL -> Get (ASN1Res x))
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Tag
t Map Tag (Maybe TL -> Get (ASN1Res x))
tagmap -> Maybe TL -> Get (ASN1Res x)
h Maybe TL
tl
| Bool
otherwise -> TL -> Get (ASN1Res x)
anydispatch TL
tl'
Nothing -> ASN1Res x -> Get (ASN1Res x)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ASN1Res x
forall x. ASN1Res x
UnexpectedEOF
}
| Bool
otherwise = ASN1Decode x
forall (f :: * -> *) a. Alternative f => f a
empty
where
xs :: [ASN1Decode x]
xs = (ASN1Decode x -> Bool) -> [ASN1Decode x] -> [ASN1Decode x]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (ASN1Decode x -> Bool) -> ASN1Decode x -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ASN1Decode x -> Bool
forall x. ASN1Decode x -> Bool
asn1decodeIsEmpty) [ASN1Decode x]
xs0
tagmap :: Map Tag (Maybe TL -> Get (ASN1Res x))
tagmap = [Map Tag (Maybe TL -> Get (ASN1Res x))]
-> Map Tag (Maybe TL -> Get (ASN1Res x))
forall a. Monoid a => [a] -> a
mconcat [ (Tag -> Maybe TL -> Get (ASN1Res x))
-> Set Tag -> Map Tag (Maybe TL -> Get (ASN1Res x))
forall k a. (k -> a) -> Set k -> Map k a
Map.fromSet ((Maybe TL -> Get (ASN1Res x)) -> Tag -> Maybe TL -> Get (ASN1Res x)
forall a b. a -> b -> a
const Maybe TL -> Get (ASN1Res x)
asn1dContent) Set Tag
asn1dTags | ASN1Decode{..} <- [ASN1Decode x]
xs ]
anydispatch :: TL -> Get (ASN1Res x)
anydispatch = case [ Maybe TL -> Get (ASN1Res x)
asn1dContent | ASN1Decode{..} <- [ASN1Decode x]
xs, Bool
asn1dAny ] of
[] -> \tl :: TL
tl -> ASN1Res x -> Get (ASN1Res x)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (TL -> ASN1Res x
forall x. TL -> ASN1Res x
Unexpected TL
tl)
[x :: Maybe TL -> Get (ASN1Res x)
x] -> Maybe TL -> Get (ASN1Res x)
x (Maybe TL -> Get (ASN1Res x))
-> (TL -> Maybe TL) -> TL -> Get (ASN1Res x)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TL -> Maybe TL
forall a. a -> Maybe a
Just
(_:_:_) -> [Char] -> TL -> Get (ASN1Res x)
forall a. [Char] -> a
error' "ASN1Decode: CHOICE not possible over multiple ANYs"
error' :: String -> a
error' :: [Char] -> a
error' s :: [Char]
s = [Char] -> a
forall a. HasCallStack => [Char] -> a
error ([Char]
s [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ " => " [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ [(Set Tag, Bool, Card)] -> [Char]
forall a. Show a => a -> [Char]
show [(ASN1Decode x -> Set Tag
forall x. ASN1Decode x -> Set Tag
asn1dTags ASN1Decode x
x, ASN1Decode x -> Bool
forall x. ASN1Decode x -> Bool
asn1dAny ASN1Decode x
x, ASN1Decode x -> Card
forall x. ASN1Decode x -> Card
asn1dCard ASN1Decode x
x) | ASN1Decode x
x <- [ASN1Decode x]
xs ])
asn1decodeIsEmpty :: ASN1Decode x -> Bool
asn1decodeIsEmpty :: ASN1Decode x -> Bool
asn1decodeIsEmpty ASN1Decode{..} = Bool -> Bool
not Bool
asn1dAny Bool -> Bool -> Bool
&& Set Tag -> Bool
forall a. Set a -> Bool
Set.null Set Tag
asn1dTags Bool -> Bool -> Bool
&& Card
asn1dCard Card -> Card -> Bool
forall a. Eq a => a -> a -> Bool
== Word -> Word -> Card
Card 0 0
asn1decodeIsMono :: ASN1Decode x -> Maybe Tag
asn1decodeIsMono :: ASN1Decode x -> Maybe Tag
asn1decodeIsMono (ASN1Decode {..})
| Bool
asn1dAny = Maybe Tag
forall a. Maybe a
Nothing
| [t1 :: Tag
t1] <- Set Tag -> [Tag]
forall a. Set a -> [a]
Set.toList Set Tag
asn1dTags = Tag -> Maybe Tag
forall a. a -> Maybe a
Just Tag
t1
| Bool
otherwise = Maybe Tag
forall a. Maybe a
Nothing
asn1DecodeSingleton :: Tag -> (TL -> Get x) -> ASN1Decode x
asn1DecodeSingleton :: Tag -> (TL -> Get x) -> ASN1Decode x
asn1DecodeSingleton t :: Tag
t c :: TL -> Get x
c = Tag -> (TL -> Get (ASN1Res x)) -> ASN1Decode x
forall x. Tag -> (TL -> Get (ASN1Res x)) -> ASN1Decode x
asn1DecodeSingleton' Tag
t ((Maybe TL -> x -> ASN1Res x
forall x. Maybe TL -> x -> ASN1Res x
Consumed Maybe TL
forall a. Maybe a
Nothing (x -> ASN1Res x) -> Get x -> Get (ASN1Res x)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>) (Get x -> Get (ASN1Res x))
-> (TL -> Get x) -> TL -> Get (ASN1Res x)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TL -> Get x
c)
asn1DecodeSingleton' :: Tag -> (TL -> Get (ASN1Res x)) -> ASN1Decode x
asn1DecodeSingleton' :: Tag -> (TL -> Get (ASN1Res x)) -> ASN1Decode x
asn1DecodeSingleton' t :: Tag
t c :: TL -> Get (ASN1Res x)
c = ASN1Decode Any
forall (f :: * -> *) a. Alternative f => f a
empty { asn1dTags :: Set Tag
asn1dTags = Tag -> Set Tag
forall a. a -> Set a
Set.singleton Tag
t
, asn1dCard :: Card
asn1dCard = Word -> Word -> Card
Card 1 0
, asn1dContent :: Maybe TL -> Get (ASN1Res x)
asn1dContent = \case
Just tl :: TL
tl@(t' :: Tag
t',_,_) | Tag
t Tag -> Tag -> Bool
forall a. Eq a => a -> a -> Bool
/= Tag
t' -> ASN1Res x -> Get (ASN1Res x)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (TL -> ASN1Res x
forall x. TL -> ASN1Res x
Unexpected TL
tl)
| Bool
otherwise -> TL -> Get (ASN1Res x)
c TL
tl
Nothing -> ASN1Res x -> Get (ASN1Res x)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ASN1Res x
forall x. ASN1Res x
UnexpectedEOF
}
dec'OPTIONAL :: ASN1Decode x -> ASN1Decode (Maybe x)
dec'OPTIONAL :: ASN1Decode x -> ASN1Decode (Maybe x)
dec'OPTIONAL x :: ASN1Decode x
x
| ASN1Decode x -> Card
forall x. ASN1Decode x -> Card
asn1dCard ASN1Decode x
x Card -> Card -> Bool
forall a. Eq a => a -> a -> Bool
/= Word -> Word -> Card
Card 1 0 = [Char] -> ASN1Decode (Maybe x)
forall a. HasCallStack => [Char] -> a
error "OPTIONAL applied to non-singleton"
| Bool
otherwise = ASN1Decode x
x { asn1dCard :: Card
asn1dCard = Word -> Word -> Card
Card 0 1
, asn1dContent :: Maybe TL -> Get (ASN1Res (Maybe x))
asn1dContent = \case
Nothing -> ASN1Res (Maybe x) -> Get (ASN1Res (Maybe x))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ASN1Res (Maybe x) -> Get (ASN1Res (Maybe x)))
-> ASN1Res (Maybe x) -> Get (ASN1Res (Maybe x))
forall a b. (a -> b) -> a -> b
$ Maybe TL -> Maybe x -> ASN1Res (Maybe x)
forall x. Maybe TL -> x -> ASN1Res x
Consumed Maybe TL
forall a. Maybe a
Nothing Maybe x
forall a. Maybe a
Nothing
Just tl :: TL
tl -> ASN1Res x -> ASN1Res (Maybe x)
forall a. ASN1Res a -> ASN1Res (Maybe a)
g (ASN1Res x -> ASN1Res (Maybe x))
-> Get (ASN1Res x) -> Get (ASN1Res (Maybe x))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ASN1Decode x -> Maybe TL -> Get (ASN1Res x)
forall x. ASN1Decode x -> Maybe TL -> Get (ASN1Res x)
asn1dContent ASN1Decode x
x (TL -> Maybe TL
forall a. a -> Maybe a
Just TL
tl)
}
where
g :: ASN1Res a -> ASN1Res (Maybe a)
g (Consumed mleftover :: Maybe TL
mleftover v :: a
v) = Maybe TL -> Maybe a -> ASN1Res (Maybe a)
forall x. Maybe TL -> x -> ASN1Res x
Consumed Maybe TL
mleftover (a -> Maybe a
forall a. a -> Maybe a
Just a
v)
g (Unexpected leftover :: TL
leftover) = Maybe TL -> Maybe a -> ASN1Res (Maybe a)
forall x. Maybe TL -> x -> ASN1Res x
Consumed (TL -> Maybe TL
forall a. a -> Maybe a
Just TL
leftover) Maybe a
forall a. Maybe a
Nothing
g UnexpectedEOF = Maybe TL -> Maybe a -> ASN1Res (Maybe a)
forall x. Maybe TL -> x -> ASN1Res x
Consumed Maybe TL
forall a. Maybe a
Nothing Maybe a
forall a. Maybe a
Nothing
instance Functor ASN1Decode where
fmap :: (a -> b) -> ASN1Decode a -> ASN1Decode b
fmap f :: a -> b
f dec :: ASN1Decode a
dec = ASN1Decode a
dec { asn1dContent :: Maybe TL -> Get (ASN1Res b)
asn1dContent = \tl :: Maybe TL
tl -> (a -> b) -> ASN1Res a -> ASN1Res b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f (ASN1Res a -> ASN1Res b) -> Get (ASN1Res a) -> Get (ASN1Res b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ASN1Decode a -> Maybe TL -> Get (ASN1Res a)
forall x. ASN1Decode x -> Maybe TL -> Get (ASN1Res x)
asn1dContent ASN1Decode a
dec Maybe TL
tl }
instance Applicative ASN1Decode where
pure :: a -> ASN1Decode a
pure x :: a
x = ASN1Decode Any
forall (f :: * -> *) a. Alternative f => f a
empty { asn1dContent :: Maybe TL -> Get (ASN1Res a)
asn1dContent = \tl :: Maybe TL
tl -> ASN1Res a -> Get (ASN1Res a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe TL -> a -> ASN1Res a
forall x. Maybe TL -> x -> ASN1Res x
Consumed Maybe TL
tl a
x), asn1dAny :: Bool
asn1dAny = Bool
True }
<*> :: ASN1Decode (a -> b) -> ASN1Decode a -> ASN1Decode b
(<*>) = ASN1Decode (a -> b) -> ASN1Decode a -> ASN1Decode b
forall a b. ASN1Decode (a -> b) -> ASN1Decode a -> ASN1Decode b
ap'ASN1Decode
*> :: ASN1Decode a -> ASN1Decode b -> ASN1Decode b
(*>) = ASN1Decode a -> ASN1Decode b -> ASN1Decode b
forall a b. ASN1Decode a -> ASN1Decode b -> ASN1Decode b
then'ASN1Decode
ap'ASN1Decode :: ASN1Decode (a -> b) -> ASN1Decode a -> ASN1Decode b
ap'ASN1Decode :: ASN1Decode (a -> b) -> ASN1Decode a -> ASN1Decode b
ap'ASN1Decode f :: ASN1Decode (a -> b)
f x :: ASN1Decode a
x
= $WASN1Decode :: forall x.
Set Tag
-> Bool -> Card -> (Maybe TL -> Get (ASN1Res x)) -> ASN1Decode x
ASN1Decode { asn1dAny :: Bool
asn1dAny = if Bool
fMaySkip then ASN1Decode (a -> b) -> Bool
forall x. ASN1Decode x -> Bool
asn1dAny ASN1Decode (a -> b)
f Bool -> Bool -> Bool
|| ASN1Decode a -> Bool
forall x. ASN1Decode x -> Bool
asn1dAny ASN1Decode a
x else ASN1Decode (a -> b) -> Bool
forall x. ASN1Decode x -> Bool
asn1dAny ASN1Decode (a -> b)
f
, asn1dTags :: Set Tag
asn1dTags = if Bool
fMaySkip then ASN1Decode (a -> b) -> Set Tag
forall x. ASN1Decode x -> Set Tag
asn1dTags ASN1Decode (a -> b)
f Set Tag -> Set Tag -> Set Tag
forall a. Semigroup a => a -> a -> a
<> ASN1Decode a -> Set Tag
forall x. ASN1Decode x -> Set Tag
asn1dTags ASN1Decode a
x else ASN1Decode (a -> b) -> Set Tag
forall x. ASN1Decode x -> Set Tag
asn1dTags ASN1Decode (a -> b)
f
, asn1dCard :: Card
asn1dCard = ASN1Decode (a -> b) -> Card
forall x. ASN1Decode x -> Card
asn1dCard ASN1Decode (a -> b)
f Card -> Card -> Card
forall a. Semigroup a => a -> a -> a
<> ASN1Decode a -> Card
forall x. ASN1Decode x -> Card
asn1dCard ASN1Decode a
x
, asn1dContent :: Maybe TL -> Get (ASN1Res b)
asn1dContent = \mtl :: Maybe TL
mtl -> do
ASN1Res (a -> b)
res <- ASN1Decode (a -> b) -> Maybe TL -> Get (ASN1Res (a -> b))
forall x. ASN1Decode x -> Maybe TL -> Get (ASN1Res x)
getASN1Decode ASN1Decode (a -> b)
f Maybe TL
mtl
case ASN1Res (a -> b)
res of
Consumed (Just tl' :: TL
tl') f' :: a -> b
f' -> do
ASN1Res a
a' <- ASN1Decode a -> Maybe TL -> Get (ASN1Res a)
forall x. ASN1Decode x -> Maybe TL -> Get (ASN1Res x)
getASN1Decode ASN1Decode a
x (TL -> Maybe TL
forall a. a -> Maybe a
Just TL
tl')
ASN1Res b -> Get (ASN1Res b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((a -> b) -> ASN1Res a -> ASN1Res b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f' ASN1Res a
a')
Consumed Nothing f' :: a -> b
f' -> do
Maybe TL
mtl' <- EncodingRule -> Get (Maybe TL)
getTagLength EncodingRule
BER
ASN1Res a
a' <- ASN1Decode a -> Maybe TL -> Get (ASN1Res a)
forall x. ASN1Decode x -> Maybe TL -> Get (ASN1Res x)
getASN1Decode ASN1Decode a
x Maybe TL
mtl'
ASN1Res b -> Get (ASN1Res b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((a -> b) -> ASN1Res a -> ASN1Res b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f' ASN1Res a
a')
Unexpected (t :: Tag
t,_,_) ->
[Char] -> Get (ASN1Res b)
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail ("ap'ASN1Decode: Unexpected " [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ Tag -> [Char]
forall a. Show a => a -> [Char]
show Tag
t)
UnexpectedEOF ->
[Char] -> Get (ASN1Res b)
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail ("ap'ASN1Decode: UnexpectedEOF")
}
where
fMaySkip :: Bool
fMaySkip = Card -> Bool
cardMaySkip (ASN1Decode (a -> b) -> Card
forall x. ASN1Decode x -> Card
asn1dCard ASN1Decode (a -> b)
f)
then'ASN1Decode :: ASN1Decode a -> ASN1Decode b -> ASN1Decode b
then'ASN1Decode :: ASN1Decode a -> ASN1Decode b -> ASN1Decode b
then'ASN1Decode f :: ASN1Decode a
f x :: ASN1Decode b
x
= $WASN1Decode :: forall x.
Set Tag
-> Bool -> Card -> (Maybe TL -> Get (ASN1Res x)) -> ASN1Decode x
ASN1Decode { asn1dAny :: Bool
asn1dAny = if Bool
fMaySkip then ASN1Decode a -> Bool
forall x. ASN1Decode x -> Bool
asn1dAny ASN1Decode a
f Bool -> Bool -> Bool
|| ASN1Decode b -> Bool
forall x. ASN1Decode x -> Bool
asn1dAny ASN1Decode b
x else ASN1Decode a -> Bool
forall x. ASN1Decode x -> Bool
asn1dAny ASN1Decode a
f
, asn1dTags :: Set Tag
asn1dTags = if Bool
fMaySkip then ASN1Decode a -> Set Tag
forall x. ASN1Decode x -> Set Tag
asn1dTags ASN1Decode a
f Set Tag -> Set Tag -> Set Tag
forall a. Semigroup a => a -> a -> a
<> ASN1Decode b -> Set Tag
forall x. ASN1Decode x -> Set Tag
asn1dTags ASN1Decode b
x else ASN1Decode a -> Set Tag
forall x. ASN1Decode x -> Set Tag
asn1dTags ASN1Decode a
f
, asn1dCard :: Card
asn1dCard = ASN1Decode a -> Card
forall x. ASN1Decode x -> Card
asn1dCard ASN1Decode a
f Card -> Card -> Card
forall a. Semigroup a => a -> a -> a
<> ASN1Decode b -> Card
forall x. ASN1Decode x -> Card
asn1dCard ASN1Decode b
x
, asn1dContent :: Maybe TL -> Get (ASN1Res b)
asn1dContent = \mtl :: Maybe TL
mtl -> do
ASN1Res a
res <- ASN1Decode a -> Maybe TL -> Get (ASN1Res a)
forall x. ASN1Decode x -> Maybe TL -> Get (ASN1Res x)
getASN1Decode ASN1Decode a
f Maybe TL
mtl
case ASN1Res a
res of
Consumed (Just tl' :: TL
tl') _ -> do
ASN1Decode b -> Maybe TL -> Get (ASN1Res b)
forall x. ASN1Decode x -> Maybe TL -> Get (ASN1Res x)
getASN1Decode ASN1Decode b
x (TL -> Maybe TL
forall a. a -> Maybe a
Just TL
tl')
Consumed Nothing _ -> do
Maybe TL
mtl' <- EncodingRule -> Get (Maybe TL)
getTagLength EncodingRule
BER
ASN1Decode b -> Maybe TL -> Get (ASN1Res b)
forall x. ASN1Decode x -> Maybe TL -> Get (ASN1Res x)
getASN1Decode ASN1Decode b
x Maybe TL
mtl'
Unexpected (t :: Tag
t,_,_) ->
[Char] -> Get (ASN1Res b)
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail ("then'ASN1Decode: Unexpected " [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ Tag -> [Char]
forall a. Show a => a -> [Char]
show Tag
t)
UnexpectedEOF ->
[Char] -> Get (ASN1Res b)
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail ("then'ASN1Decode: UnexpectedEOF")
}
where
fMaySkip :: Bool
fMaySkip = Card -> Bool
cardMaySkip (ASN1Decode a -> Card
forall x. ASN1Decode x -> Card
asn1dCard ASN1Decode a
f)
asn1fail :: String -> ASN1Decode a
asn1fail :: [Char] -> ASN1Decode a
asn1fail s :: [Char]
s = ASN1Decode Any
forall (f :: * -> *) a. Alternative f => f a
empty { asn1dAny :: Bool
asn1dAny = Bool
True
, asn1dContent :: Maybe TL -> Get (ASN1Res a)
asn1dContent = \_ -> [Char] -> Get (ASN1Res a)
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail [Char]
s
}
toBinaryGet :: ASN1Decode x -> Get x
toBinaryGet :: ASN1Decode x -> Get x
toBinaryGet dec :: ASN1Decode x
dec
= EncodingRule -> Get (Maybe TL)
getTagLength EncodingRule
BER Get (Maybe TL) -> (Maybe TL -> Get (ASN1Res x)) -> Get (ASN1Res x)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ASN1Decode x -> Maybe TL -> Get (ASN1Res x)
forall x. ASN1Decode x -> Maybe TL -> Get (ASN1Res x)
getASN1Decode ASN1Decode x
dec Get (ASN1Res x) -> (ASN1Res x -> Get x) -> Get x
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Unexpected tl :: TL
tl -> [Char] -> Get x
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail ("ASN1Decode: unexpected " [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ TL -> [Char]
forall a. Show a => a -> [Char]
show TL
tl)
UnexpectedEOF -> [Char] -> Get x
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail "ASN1Decode: premature end of stream"
Consumed (Just tl :: TL
tl) _ -> [Char] -> Get x
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail ("ASN1Decode: leftover " [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ TL -> [Char]
forall a. Show a => a -> [Char]
show TL
tl)
Consumed Nothing x :: x
x -> x -> Get x
forall (f :: * -> *) a. Applicative f => a -> f a
pure x
x
transformVia :: ASN1Decode x -> (x -> Either String y) -> ASN1Decode y
transformVia :: ASN1Decode x -> (x -> Either [Char] y) -> ASN1Decode y
transformVia old :: ASN1Decode x
old f :: x -> Either [Char] y
f
= ASN1Decode x
old { asn1dContent :: Maybe TL -> Get (ASN1Res y)
asn1dContent = \mtl :: Maybe TL
mtl -> do
ASN1Decode x -> Maybe TL -> Get (ASN1Res x)
forall x. ASN1Decode x -> Maybe TL -> Get (ASN1Res x)
asn1dContent ASN1Decode x
old Maybe TL
mtl Get (ASN1Res x)
-> (ASN1Res x -> Get (ASN1Res y)) -> Get (ASN1Res y)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Consumed lo :: Maybe TL
lo x :: x
x -> case x -> Either [Char] y
f x
x of
Left e :: [Char]
e -> [Char] -> Get (ASN1Res y)
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail [Char]
e
Right y :: y
y -> ASN1Res y -> Get (ASN1Res y)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe TL -> y -> ASN1Res y
forall x. Maybe TL -> x -> ASN1Res x
Consumed Maybe TL
lo y
y)
Unexpected u :: TL
u -> ASN1Res y -> Get (ASN1Res y)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (TL -> ASN1Res y
forall x. TL -> ASN1Res x
Unexpected TL
u)
UnexpectedEOF -> ASN1Res y -> Get (ASN1Res y)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ASN1Res y
forall x. ASN1Res x
UnexpectedEOF
}
explicit :: Tag -> ASN1Decode x -> ASN1Decode x
explicit :: Tag -> ASN1Decode x -> ASN1Decode x
explicit t :: Tag
t body :: ASN1Decode x
body = [Char] -> Tag -> ASN1Decode x -> ASN1Decode x
forall x. [Char] -> Tag -> ASN1Decode x -> ASN1Decode x
dec'Constructed (Tag -> [Char]
forall a. Show a => a -> [Char]
show Tag
t [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ " EXPLICIT") Tag
t ASN1Decode x
body
implicit :: Tag -> ASN1Decode x -> ASN1Decode x
implicit :: Tag -> ASN1Decode x -> ASN1Decode x
implicit newtag :: Tag
newtag old :: ASN1Decode x
old
| Just oldtag :: Tag
oldtag <- ASN1Decode x -> Maybe Tag
forall x. ASN1Decode x -> Maybe Tag
asn1decodeIsMono ASN1Decode x
old
= ASN1Decode Any
forall (f :: * -> *) a. Alternative f => f a
empty { asn1dTags :: Set Tag
asn1dTags = Tag -> Set Tag
forall a. a -> Set a
Set.singleton Tag
newtag
, asn1dCard :: Card
asn1dCard = ASN1Decode x -> Card
forall x. ASN1Decode x -> Card
asn1dCard ASN1Decode x
old
, asn1dContent :: Maybe TL -> Get (ASN1Res x)
asn1dContent = \case
Just tl :: TL
tl@(curtag :: Tag
curtag,_,_) | Tag
newtag Tag -> Tag -> Bool
forall a. Eq a => a -> a -> Bool
/= Tag
curtag -> ASN1Res x -> Get (ASN1Res x)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (TL -> ASN1Res x
forall x. TL -> ASN1Res x
Unexpected TL
tl)
Just (_,pc :: TagPC
pc,sz :: Maybe Word64
sz) -> ASN1Decode x -> Maybe TL -> Get (ASN1Res x)
forall x. ASN1Decode x -> Maybe TL -> Get (ASN1Res x)
asn1dContent ASN1Decode x
old (TL -> Maybe TL
forall a. a -> Maybe a
Just (Tag
oldtag,TagPC
pc,Maybe Word64
sz))
Nothing -> ASN1Decode x -> Maybe TL -> Get (ASN1Res x)
forall x. ASN1Decode x -> Maybe TL -> Get (ASN1Res x)
asn1dContent ASN1Decode x
old Maybe TL
forall a. Maybe a
Nothing
}
| Bool
otherwise = [Char] -> ASN1Decode x
forall a. HasCallStack => [Char] -> a
error "IMPLICIT applied to non-monomorphic ASN1Decode"
dec'CHOICE :: [ASN1Decode x] -> ASN1Decode x
dec'CHOICE :: [ASN1Decode x] -> ASN1Decode x
dec'CHOICE [] = [Char] -> ASN1Decode x
forall a. HasCallStack => [Char] -> a
error "CHOICE over no choices"
dec'CHOICE xs :: [ASN1Decode x]
xs = [ASN1Decode x] -> ASN1Decode x
forall x. [ASN1Decode x] -> ASN1Decode x
asum'ASN1Decode [ASN1Decode x]
xs
dec'Constructed :: forall x . String -> Tag -> ASN1Decode x -> ASN1Decode x
dec'Constructed :: [Char] -> Tag -> ASN1Decode x -> ASN1Decode x
dec'Constructed l :: [Char]
l tag :: Tag
tag body :: ASN1Decode x
body = Tag -> (TL -> Get (ASN1Res x)) -> ASN1Decode x
forall x. Tag -> (TL -> Get (ASN1Res x)) -> ASN1Decode x
asn1DecodeSingleton' Tag
tag TL -> Get (ASN1Res x)
go
where
go :: TL -> Get (ASN1Res x)
go :: TL -> Get (ASN1Res x)
go (_,Primitive,_) = [Char] -> Get (ASN1Res x)
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail ([Char]
l [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ " with primitive encoding")
go (_,Constructed,Nothing) = [Char] -> Get (ASN1Res x)
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail ([Char]
l [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ " with indef length not supported yet")
go (_,Constructed,Just sz :: Word64
sz) = Word64 -> Get (ASN1Res x) -> Get (ASN1Res x)
forall a. Word64 -> Get a -> Get a
isolate64 Word64
sz (Get (ASN1Res x) -> Get (ASN1Res x))
-> Get (ASN1Res x) -> Get (ASN1Res x)
forall a b. (a -> b) -> a -> b
$ do
Maybe TL
tl' <- EncodingRule -> Get (Maybe TL)
getTagLength EncodingRule
BER
ASN1Decode x -> Maybe TL -> Get (ASN1Res x)
forall x. ASN1Decode x -> Maybe TL -> Get (ASN1Res x)
getASN1Decode ASN1Decode x
body Maybe TL
tl'
dec'SEQUENCE :: forall x . ASN1Decode x -> ASN1Decode x
dec'SEQUENCE :: ASN1Decode x -> ASN1Decode x
dec'SEQUENCE = [Char] -> Tag -> ASN1Decode x -> ASN1Decode x
forall x. [Char] -> Tag -> ASN1Decode x -> ASN1Decode x
dec'Constructed "SEQUENCE" (Word64 -> Tag
Universal 16)
dec'SEQUENCE_OF :: forall x . ASN1Decode x -> ASN1Decode [x]
dec'SEQUENCE_OF :: ASN1Decode x -> ASN1Decode [x]
dec'SEQUENCE_OF body :: ASN1Decode x
body = Tag -> (TL -> Get (ASN1Res [x])) -> ASN1Decode [x]
forall x. Tag -> (TL -> Get (ASN1Res x)) -> ASN1Decode x
asn1DecodeSingleton' (Word64 -> Tag
Universal 16) TL -> Get (ASN1Res [x])
go
where
go :: TL -> Get (ASN1Res [x])
go :: TL -> Get (ASN1Res [x])
go (_,Primitive,_) = [Char] -> Get (ASN1Res [x])
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail "SEQUENCE OF with primitive encoding"
go (_,Constructed,Nothing) = [Char] -> Get (ASN1Res [x])
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail "indef SEQUENCE OF not implemented yet"
go (_,Constructed,Just sz :: Word64
sz) = Word64 -> Get (ASN1Res [x]) -> Get (ASN1Res [x])
forall a. Word64 -> Get a -> Get a
isolate64 Word64
sz (Get (ASN1Res [x]) -> Get (ASN1Res [x]))
-> Get (ASN1Res [x]) -> Get (ASN1Res [x])
forall a b. (a -> b) -> a -> b
$ do
let loop :: [x] -> Maybe TL -> Get [x]
loop :: [x] -> Maybe TL -> Get [x]
loop acc :: [x]
acc tl0 :: Maybe TL
tl0 = do
Maybe TL
tl' <- case Maybe TL
tl0 of
Just _ -> Maybe TL -> Get (Maybe TL)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe TL
tl0
Nothing -> EncodingRule -> Get (Maybe TL)
getTagLength EncodingRule
BER
case Maybe TL
tl' of
Nothing -> [x] -> Get [x]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([x] -> [x]
forall a. [a] -> [a]
reverse [x]
acc)
Just _ -> do
ASN1Res x
tmp <- ASN1Decode x -> Maybe TL -> Get (ASN1Res x)
forall x. ASN1Decode x -> Maybe TL -> Get (ASN1Res x)
getASN1Decode ASN1Decode x
body Maybe TL
tl'
case ASN1Res x
tmp of
Consumed tl'' :: Maybe TL
tl'' v :: x
v -> [x] -> Maybe TL -> Get [x]
loop (x
vx -> [x] -> [x]
forall a. a -> [a] -> [a]
:[x]
acc) Maybe TL
tl''
UnexpectedEOF -> [Char] -> Get [x]
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail "dec'SEQUENCE_OF: unexpected EOF"
Unexpected t :: TL
t -> [Char] -> Get [x]
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail ("dec'SEQUENCE_OF: unexpected " [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ TL -> [Char]
forall a. Show a => a -> [Char]
show TL
t)
Maybe TL -> [x] -> ASN1Res [x]
forall x. Maybe TL -> x -> ASN1Res x
Consumed Maybe TL
forall a. Maybe a
Nothing ([x] -> ASN1Res [x]) -> Get [x] -> Get (ASN1Res [x])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [x] -> Maybe TL -> Get [x]
loop [] Maybe TL
forall a. Maybe a
Nothing
dec'SET_OF :: forall x . ASN1Decode x -> ASN1Decode [x]
dec'SET_OF :: ASN1Decode x -> ASN1Decode [x]
dec'SET_OF body :: ASN1Decode x
body = Tag -> (TL -> Get (ASN1Res [x])) -> ASN1Decode [x]
forall x. Tag -> (TL -> Get (ASN1Res x)) -> ASN1Decode x
asn1DecodeSingleton' (Word64 -> Tag
Universal 17) TL -> Get (ASN1Res [x])
go
where
go :: TL -> Get (ASN1Res [x])
go :: TL -> Get (ASN1Res [x])
go (_,Primitive,_) = [Char] -> Get (ASN1Res [x])
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail "SET OF with primitive encoding"
go (_,Constructed,Nothing) = [Char] -> Get (ASN1Res [x])
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail "indef SET OF not implemented yet"
go (_,Constructed,Just sz :: Word64
sz) = Word64 -> Get (ASN1Res [x]) -> Get (ASN1Res [x])
forall a. Word64 -> Get a -> Get a
isolate64 Word64
sz (Get (ASN1Res [x]) -> Get (ASN1Res [x]))
-> Get (ASN1Res [x]) -> Get (ASN1Res [x])
forall a b. (a -> b) -> a -> b
$ do
let loop :: [x] -> Maybe TL -> Get [x]
loop :: [x] -> Maybe TL -> Get [x]
loop acc :: [x]
acc tl0 :: Maybe TL
tl0 = do
Maybe TL
tl' <- case Maybe TL
tl0 of
Just _ -> Maybe TL -> Get (Maybe TL)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe TL
tl0
Nothing -> EncodingRule -> Get (Maybe TL)
getTagLength EncodingRule
BER
case Maybe TL
tl' of
Nothing -> [x] -> Get [x]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([x] -> [x]
forall a. [a] -> [a]
reverse [x]
acc)
Just _ -> do
ASN1Res x
tmp <- ASN1Decode x -> Maybe TL -> Get (ASN1Res x)
forall x. ASN1Decode x -> Maybe TL -> Get (ASN1Res x)
getASN1Decode ASN1Decode x
body Maybe TL
tl'
case ASN1Res x
tmp of
Consumed tl'' :: Maybe TL
tl'' v :: x
v -> [x] -> Maybe TL -> Get [x]
loop (x
vx -> [x] -> [x]
forall a. a -> [a] -> [a]
:[x]
acc) Maybe TL
tl''
UnexpectedEOF -> [Char] -> Get [x]
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail "dec'SET_OF: unexpected EOF"
Unexpected t :: TL
t -> [Char] -> Get [x]
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail ("dec'SET_OF: unexpected " [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ TL -> [Char]
forall a. Show a => a -> [Char]
show TL
t)
Maybe TL -> [x] -> ASN1Res [x]
forall x. Maybe TL -> x -> ASN1Res x
Consumed Maybe TL
forall a. Maybe a
Nothing ([x] -> ASN1Res [x]) -> Get [x] -> Get (ASN1Res [x])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [x] -> Maybe TL -> Get [x]
loop [] Maybe TL
forall a. Maybe a
Nothing
dec'BOOLEAN :: ASN1Decode Bool
dec'BOOLEAN :: ASN1Decode Bool
dec'BOOLEAN = Tag -> (TL -> Get Bool) -> ASN1Decode Bool
forall x. Tag -> (TL -> Get x) -> ASN1Decode x
asn1DecodeSingleton (Word64 -> Tag
Universal 1) ((TL -> Get Bool) -> ASN1Decode Bool)
-> (TL -> Get Bool) -> ASN1Decode Bool
forall a b. (a -> b) -> a -> b
$ (Word64 -> Get Bool) -> TL -> Get Bool
forall x. (Word64 -> Get x) -> TL -> Get x
asPrimitive Word64 -> Get Bool
forall a. (Eq a, Num a) => a -> Get Bool
go
where
go :: a -> Get Bool
go 1 = do
Word8
x <- Get Word8
getWord8
case Word8
x of
0x00 -> Bool -> Get Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
False
0xff -> Bool -> Get Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
True
_ -> [Char] -> Get Bool
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail "BOOLEAN must be encoded as either 0x00 or 0xFF"
go _ = [Char] -> Get Bool
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail "BOOLEAN with content-length not equal 1"
enc'BOOLEAN :: Bool -> ASN1Encode Word64
enc'BOOLEAN :: Bool -> ASN1Encode Word64
enc'BOOLEAN v :: Bool
v = (Maybe Tag -> PutM Word64) -> ASN1Encode Word64
forall a. (Maybe Tag -> PutM a) -> ASN1Encode a
ASN1Encode ((Maybe Tag -> PutM Word64) -> ASN1Encode Word64)
-> (Maybe Tag -> PutM Word64) -> ASN1Encode Word64
forall a b. (a -> b) -> a -> b
$ \mt :: Maybe Tag
mt -> do
Word64
_ <- TL -> PutM Word64
putTagLength (Word64 -> Tag
Universal 1 Tag -> Maybe Tag -> Tag
forall a. a -> Maybe a -> a
`fromMaybe` Maybe Tag
mt, TagPC
Primitive, Word64 -> Maybe Word64
forall a. a -> Maybe a
Just 1)
Word8 -> Put
putWord8 (if Bool
v then 0xff else 0x00)
Word64 -> PutM Word64
forall (f :: * -> *) a. Applicative f => a -> f a
pure 3
dec'INTEGER :: ASN1Decode Integer
dec'INTEGER :: ASN1Decode Integer
dec'INTEGER = Tag -> (TL -> Get Integer) -> ASN1Decode Integer
forall x. Tag -> (TL -> Get x) -> ASN1Decode x
asn1DecodeSingleton (Word64 -> Tag
Universal 2) ((TL -> Get Integer) -> ASN1Decode Integer)
-> (TL -> Get Integer) -> ASN1Decode Integer
forall a b. (a -> b) -> a -> b
$ (Word64 -> Get Integer) -> TL -> Get Integer
forall x. (Word64 -> Get x) -> TL -> Get x
asPrimitive Word64 -> Get Integer
getVarInteger
enc'INTEGER :: Integer -> ASN1Encode Word64
enc'INTEGER :: Integer -> ASN1Encode Word64
enc'INTEGER i :: Integer
i = Tag -> TagPC -> PutM Word64 -> ASN1Encode Word64
wrap'DEFINITE (Word64 -> Tag
Universal 2) TagPC
Primitive (Integer -> PutM Word64
putVarInteger Integer
i)
dec'UInt :: forall lb ub t . (UIntBounds lb ub t, Num t) => ASN1Decode (UInt lb ub t)
dec'UInt :: ASN1Decode (UInt lb ub t)
dec'UInt = ASN1Decode Integer
-> (Integer -> Either [Char] (UInt lb ub t))
-> ASN1Decode (UInt lb ub t)
forall x y. ASN1Decode x -> (x -> Either [Char] y) -> ASN1Decode y
transformVia ASN1Decode Integer
dec'INTEGER ((Integer -> Either [Char] (UInt lb ub t))
-> ASN1Decode (UInt lb ub t))
-> (Integer -> Either [Char] (UInt lb ub t))
-> ASN1Decode (UInt lb ub t)
forall a b. (a -> b) -> a -> b
$ \i :: Integer
i ->
case Integer -> Either ArithException (UInt lb ub t)
forall (lb :: Nat) (ub :: Nat) t.
(UIntBounds lb ub t, Num t) =>
Integer -> Either ArithException (UInt lb ub t)
uintFromInteger (Integer -> Integer
forall a. Integral a => a -> Integer
toInteger Integer
i) of
Left Underflow -> [Char] -> Either [Char] (UInt lb ub t)
forall a b. a -> Either a b
Left "INTEGER below lower bound"
Left Overflow -> [Char] -> Either [Char] (UInt lb ub t)
forall a b. a -> Either a b
Left "INTEGER above upper bound"
Left _ -> [Char] -> Either [Char] (UInt lb ub t)
forall a b. a -> Either a b
Left "INTEGER"
Right v :: UInt lb ub t
v -> UInt lb ub t -> Either [Char] (UInt lb ub t)
forall a b. b -> Either a b
Right UInt lb ub t
v
enc'UInt :: forall lb ub t . (UIntBounds lb ub t, Num t, Integral t) => UInt lb ub t -> ASN1Encode Word64
enc'UInt :: UInt lb ub t -> ASN1Encode Word64
enc'UInt = Integer -> ASN1Encode Word64
enc'INTEGER (Integer -> ASN1Encode Word64)
-> (UInt lb ub t -> Integer) -> UInt lb ub t -> ASN1Encode Word64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. t -> Integer
forall a. Integral a => a -> Integer
toInteger (t -> Integer) -> (UInt lb ub t -> t) -> UInt lb ub t -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UInt lb ub t -> t
forall (lb :: Nat) (ub :: Nat) t. UInt lb ub t -> t
fromUInt
dec'Int64 :: ASN1Decode Int64
dec'Int64 :: ASN1Decode Int64
dec'Int64 = Tag -> (TL -> Get Int64) -> ASN1Decode Int64
forall x. Tag -> (TL -> Get x) -> ASN1Decode x
asn1DecodeSingleton (Word64 -> Tag
Universal 2) ((TL -> Get Int64) -> ASN1Decode Int64)
-> (TL -> Get Int64) -> ASN1Decode Int64
forall a b. (a -> b) -> a -> b
$ (Word64 -> Get Int64) -> TL -> Get Int64
forall x. (Word64 -> Get x) -> TL -> Get x
asPrimitive Word64 -> Get Int64
getVarInt64
enc'Int64 :: Int64 -> ASN1Encode Word64
enc'Int64 :: Int64 -> ASN1Encode Word64
enc'Int64 i :: Int64
i = Tag -> TagPC -> PutM Word64 -> ASN1Encode Word64
wrap'DEFINITE (Word64 -> Tag
Universal 2) TagPC
Primitive (Int64 -> PutM Word64
putVarInt64 Int64
i)
dec'ENUMERATED :: Enumerated enum => ASN1Decode enum
dec'ENUMERATED :: ASN1Decode enum
dec'ENUMERATED = Tag -> (TL -> Get enum) -> ASN1Decode enum
forall x. Tag -> (TL -> Get x) -> ASN1Decode x
asn1DecodeSingleton (Word64 -> Tag
Universal 10) ((TL -> Get enum) -> ASN1Decode enum)
-> (TL -> Get enum) -> ASN1Decode enum
forall a b. (a -> b) -> a -> b
$ (Word64 -> Get enum) -> TL -> Get enum
forall x. (Word64 -> Get x) -> TL -> Get x
asPrimitive ((Word64 -> Get enum) -> TL -> Get enum)
-> (Word64 -> Get enum) -> TL -> Get enum
forall a b. (a -> b) -> a -> b
$ \sz :: Word64
sz -> do
Int64
i <- Word64 -> Get Int64
go Word64
sz
Get enum -> (enum -> Get enum) -> Maybe enum -> Get enum
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ([Char] -> Get enum
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail "invalid ENUMERATED value") enum -> Get enum
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int64 -> Maybe enum
forall x. Enumerated x => Int64 -> Maybe x
toEnumerated Int64
i)
where
go :: Word64 -> Get Int64
go 0 = [Char] -> Get Int64
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail "ENUMERATED with empty content"
go sz :: Word64
sz
| Word64
sz Word64 -> Word64 -> Bool
forall a. Ord a => a -> a -> Bool
<= 8 = Word64 -> Get Int64
getVarInt64 Word64
sz
| Bool
otherwise = [Char] -> Get Int64
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail "invalid ENUMERATED value"
enc'ENUMERATED :: Enumerated enum => enum -> ASN1Encode Word64
enc'ENUMERATED :: enum -> ASN1Encode Word64
enc'ENUMERATED = Tag -> ASN1Encode Word64 -> ASN1Encode Word64
forall a. Tag -> ASN1Encode a -> ASN1Encode a
retag (Word64 -> Tag
Universal 10) (ASN1Encode Word64 -> ASN1Encode Word64)
-> (enum -> ASN1Encode Word64) -> enum -> ASN1Encode Word64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int64 -> ASN1Encode Word64
enc'Int64 (Int64 -> ASN1Encode Word64)
-> (enum -> Int64) -> enum -> ASN1Encode Word64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. enum -> Int64
forall x. Enumerated x => x -> Int64
fromEnumerated
dec'BoundedEnum :: forall enum . (Bounded enum, Enum enum) => ASN1Decode enum
dec'BoundedEnum :: ASN1Decode enum
dec'BoundedEnum = ASN1Decode Int -> (Int -> Either [Char] enum) -> ASN1Decode enum
forall x y. ASN1Decode x -> (x -> Either [Char] y) -> ASN1Decode y
transformVia ASN1Decode Int
forall enum. Enumerated enum => ASN1Decode enum
dec'ENUMERATED ((Int -> Either [Char] enum) -> ASN1Decode enum)
-> (Int -> Either [Char] enum) -> ASN1Decode enum
forall a b. (a -> b) -> a -> b
$ \i :: Int
i ->
if (Int
i Int -> (Int, Int) -> Bool
forall a. Ord a => a -> (a, a) -> Bool
`inside` (Int
lb,Int
ub))
then enum -> Either [Char] enum
forall a b. b -> Either a b
Right (Int -> enum
forall a. Enum a => Int -> a
toEnum Int
i)
else [Char] -> Either [Char] enum
forall a b. a -> Either a b
Left "invalid ENUMERATED value"
where
lb :: Int
lb = enum -> Int
forall a. Enum a => a -> Int
fromEnum (enum
forall a. Bounded a => a
minBound :: enum)
ub :: Int
ub = enum -> Int
forall a. Enum a => a -> Int
fromEnum (enum
forall a. Bounded a => a
maxBound :: enum)
enc'BoundedEnum :: Enum enum => enum -> ASN1Encode Word64
enc'BoundedEnum :: enum -> ASN1Encode Word64
enc'BoundedEnum v :: enum
v = Int64 -> ASN1Encode Word64
forall enum. Enumerated enum => enum -> ASN1Encode Word64
enc'ENUMERATED (Int -> Int64
forall a b.
(Integral a, Integral b, IsIntSubType a b ~ 'True) =>
a -> b
intCast (enum -> Int
forall a. Enum a => a -> Int
fromEnum enum
v) :: Int64)
dec'NULL :: ASN1Decode ()
dec'NULL :: ASN1Decode ()
dec'NULL = Tag -> (TL -> Get ()) -> ASN1Decode ()
forall x. Tag -> (TL -> Get x) -> ASN1Decode x
asn1DecodeSingleton (Word64 -> Tag
Universal 5) ((TL -> Get ()) -> ASN1Decode ())
-> (TL -> Get ()) -> ASN1Decode ()
forall a b. (a -> b) -> a -> b
$ (Word64 -> Get ()) -> TL -> Get ()
forall x. (Word64 -> Get x) -> TL -> Get x
asPrimitive Word64 -> Get ()
forall a (f :: * -> *). (Eq a, Num a, MonadFail f) => a -> f ()
go
where
go :: a -> f ()
go 0 = () -> f ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
go _ = [Char] -> f ()
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail "NULL with content-length not equal 0"
enc'NULL :: ASN1Encode Word64
enc'NULL :: ASN1Encode Word64
enc'NULL = (Maybe Tag -> PutM Word64) -> ASN1Encode Word64
forall a. (Maybe Tag -> PutM a) -> ASN1Encode a
ASN1Encode ((Maybe Tag -> PutM Word64) -> ASN1Encode Word64)
-> (Maybe Tag -> PutM Word64) -> ASN1Encode Word64
forall a b. (a -> b) -> a -> b
$ \mt :: Maybe Tag
mt -> TL -> PutM Word64
putTagLength (Word64 -> Tag
Universal 5 Tag -> Maybe Tag -> Tag
forall a. a -> Maybe a -> a
`fromMaybe` Maybe Tag
mt, TagPC
Primitive, Word64 -> Maybe Word64
forall a. a -> Maybe a
Just 0)
dec'OCTETSTRING :: ASN1Decode ByteString
dec'OCTETSTRING :: ASN1Decode ByteString
dec'OCTETSTRING = Tag -> (TL -> Get ByteString) -> ASN1Decode ByteString
forall x. Tag -> (TL -> Get x) -> ASN1Decode x
asn1DecodeSingleton (Word64 -> Tag
Universal 4) ((TL -> Get ByteString) -> ASN1Decode ByteString)
-> (TL -> Get ByteString) -> ASN1Decode ByteString
forall a b. (a -> b) -> a -> b
$ (Word64 -> Get ByteString) -> TL -> Get ByteString
forall x. (Word64 -> Get x) -> TL -> Get x
asPrimitive Word64 -> Get ByteString
forall a. (Integral a, Bits a) => a -> Get ByteString
go
where
go :: a -> Get ByteString
go sz :: a
sz
| Just sz' :: Int
sz' <- a -> Maybe Int
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
intCastMaybe a
sz = Int -> Get ByteString
Bin.getByteString Int
sz'
| Bool
otherwise = [Char] -> Get ByteString
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail "OCTET STRING too large for this implementation"
enc'OCTETSTRING :: ByteString -> ASN1Encode Word64
enc'OCTETSTRING :: ByteString -> ASN1Encode Word64
enc'OCTETSTRING bs :: ByteString
bs = (Maybe Tag -> PutM Word64) -> ASN1Encode Word64
forall a. (Maybe Tag -> PutM a) -> ASN1Encode a
ASN1Encode ((Maybe Tag -> PutM Word64) -> ASN1Encode Word64)
-> (Maybe Tag -> PutM Word64) -> ASN1Encode Word64
forall a b. (a -> b) -> a -> b
$ \mt :: Maybe Tag
mt -> do
let cl :: Word64
cl = Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (ByteString -> Int
BS.length ByteString
bs)
Word64
hl <- TL -> PutM Word64
putTagLength (Word64 -> Tag
Universal 4 Tag -> Maybe Tag -> Tag
forall a. a -> Maybe a -> a
`fromMaybe` Maybe Tag
mt, TagPC
Primitive, Word64 -> Maybe Word64
forall a. a -> Maybe a
Just Word64
cl)
ByteString -> Put
Bin.putByteString ByteString
bs
Word64 -> PutM Word64
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Word64
hl Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
+ Word64
cl)
wrap'DEFINITE :: Tag -> TagPC -> PutM Word64 -> ASN1Encode Word64
wrap'DEFINITE :: Tag -> TagPC -> PutM Word64 -> ASN1Encode Word64
wrap'DEFINITE t0 :: Tag
t0 pc :: TagPC
pc body :: PutM Word64
body = (Maybe Tag -> PutM Word64) -> ASN1Encode Word64
forall a. (Maybe Tag -> PutM a) -> ASN1Encode a
ASN1Encode ((Maybe Tag -> PutM Word64) -> ASN1Encode Word64)
-> (Maybe Tag -> PutM Word64) -> ASN1Encode Word64
forall a b. (a -> b) -> a -> b
$ \mt :: Maybe Tag
mt -> do
let (cl :: Word64
cl, lbs :: ByteString
lbs) = PutM Word64 -> (Word64, ByteString)
forall a. PutM a -> (a, ByteString)
Bin.runPutM PutM Word64
body
Word64
hl <- TL -> PutM Word64
putTagLength (Tag -> Maybe Tag -> Tag
forall a. a -> Maybe a -> a
fromMaybe Tag
t0 Maybe Tag
mt, TagPC
pc, Word64 -> Maybe Word64
forall a. a -> Maybe a
Just Word64
cl)
ByteString -> Put
Bin.putLazyByteString ByteString
lbs
Word64 -> PutM Word64
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Word64
hlWord64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
+Word64
cl)
retag :: Tag -> ASN1Encode a -> ASN1Encode a
retag :: Tag -> ASN1Encode a -> ASN1Encode a
retag newtag :: Tag
newtag (ASN1Encode old :: Maybe Tag -> PutM a
old) = (Maybe Tag -> PutM a) -> ASN1Encode a
forall a. (Maybe Tag -> PutM a) -> ASN1Encode a
ASN1Encode (\mt :: Maybe Tag
mt -> Maybe Tag -> PutM a
old (Maybe Tag
mt Maybe Tag -> Maybe Tag -> Maybe Tag
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Tag -> Maybe Tag
forall a. a -> Maybe a
Just Tag
newtag))
wraptag :: Tag -> ASN1Encode Word64 -> ASN1Encode Word64
wraptag :: Tag -> ASN1Encode Word64 -> ASN1Encode Word64
wraptag newtag :: Tag
newtag (ASN1Encode old :: Maybe Tag -> PutM Word64
old) = Tag -> TagPC -> PutM Word64 -> ASN1Encode Word64
wrap'DEFINITE Tag
newtag TagPC
Constructed (Maybe Tag -> PutM Word64
old Maybe Tag
forall a. Maybe a
Nothing)
newtype IMPLICIT (tag :: TagK) x = IMPLICIT x
deriving ((forall x. IMPLICIT tag x -> Rep (IMPLICIT tag x) x)
-> (forall x. Rep (IMPLICIT tag x) x -> IMPLICIT tag x)
-> Generic (IMPLICIT tag x)
forall x. Rep (IMPLICIT tag x) x -> IMPLICIT tag x
forall x. IMPLICIT tag x -> Rep (IMPLICIT tag x) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (tag :: TagK) x x. Rep (IMPLICIT tag x) x -> IMPLICIT tag x
forall (tag :: TagK) x x. IMPLICIT tag x -> Rep (IMPLICIT tag x) x
$cto :: forall (tag :: TagK) x x. Rep (IMPLICIT tag x) x -> IMPLICIT tag x
$cfrom :: forall (tag :: TagK) x x. IMPLICIT tag x -> Rep (IMPLICIT tag x) x
Generic,IMPLICIT tag x -> ()
(IMPLICIT tag x -> ()) -> NFData (IMPLICIT tag x)
forall a. (a -> ()) -> NFData a
forall (tag :: TagK) x. NFData x => IMPLICIT tag x -> ()
rnf :: IMPLICIT tag x -> ()
$crnf :: forall (tag :: TagK) x. NFData x => IMPLICIT tag x -> ()
NFData,[Char] -> IMPLICIT tag x
([Char] -> IMPLICIT tag x) -> IsString (IMPLICIT tag x)
forall a. ([Char] -> a) -> IsString a
forall (tag :: TagK) x. IsString x => [Char] -> IMPLICIT tag x
fromString :: [Char] -> IMPLICIT tag x
$cfromString :: forall (tag :: TagK) x. IsString x => [Char] -> IMPLICIT tag x
IsString,Integer -> IMPLICIT tag x
IMPLICIT tag x -> IMPLICIT tag x
IMPLICIT tag x -> IMPLICIT tag x -> IMPLICIT tag x
(IMPLICIT tag x -> IMPLICIT tag x -> IMPLICIT tag x)
-> (IMPLICIT tag x -> IMPLICIT tag x -> IMPLICIT tag x)
-> (IMPLICIT tag x -> IMPLICIT tag x -> IMPLICIT tag x)
-> (IMPLICIT tag x -> IMPLICIT tag x)
-> (IMPLICIT tag x -> IMPLICIT tag x)
-> (IMPLICIT tag x -> IMPLICIT tag x)
-> (Integer -> IMPLICIT tag x)
-> Num (IMPLICIT tag x)
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
forall (tag :: TagK) x. Num x => Integer -> IMPLICIT tag x
forall (tag :: TagK) x. Num x => IMPLICIT tag x -> IMPLICIT tag x
forall (tag :: TagK) x.
Num x =>
IMPLICIT tag x -> IMPLICIT tag x -> IMPLICIT tag x
fromInteger :: Integer -> IMPLICIT tag x
$cfromInteger :: forall (tag :: TagK) x. Num x => Integer -> IMPLICIT tag x
signum :: IMPLICIT tag x -> IMPLICIT tag x
$csignum :: forall (tag :: TagK) x. Num x => IMPLICIT tag x -> IMPLICIT tag x
abs :: IMPLICIT tag x -> IMPLICIT tag x
$cabs :: forall (tag :: TagK) x. Num x => IMPLICIT tag x -> IMPLICIT tag x
negate :: IMPLICIT tag x -> IMPLICIT tag x
$cnegate :: forall (tag :: TagK) x. Num x => IMPLICIT tag x -> IMPLICIT tag x
* :: IMPLICIT tag x -> IMPLICIT tag x -> IMPLICIT tag x
$c* :: forall (tag :: TagK) x.
Num x =>
IMPLICIT tag x -> IMPLICIT tag x -> IMPLICIT tag x
- :: IMPLICIT tag x -> IMPLICIT tag x -> IMPLICIT tag x
$c- :: forall (tag :: TagK) x.
Num x =>
IMPLICIT tag x -> IMPLICIT tag x -> IMPLICIT tag x
+ :: IMPLICIT tag x -> IMPLICIT tag x -> IMPLICIT tag x
$c+ :: forall (tag :: TagK) x.
Num x =>
IMPLICIT tag x -> IMPLICIT tag x -> IMPLICIT tag x
Num,Int -> IMPLICIT tag x -> ShowS
[IMPLICIT tag x] -> ShowS
IMPLICIT tag x -> [Char]
(Int -> IMPLICIT tag x -> ShowS)
-> (IMPLICIT tag x -> [Char])
-> ([IMPLICIT tag x] -> ShowS)
-> Show (IMPLICIT tag x)
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
forall (tag :: TagK) x. Show x => Int -> IMPLICIT tag x -> ShowS
forall (tag :: TagK) x. Show x => [IMPLICIT tag x] -> ShowS
forall (tag :: TagK) x. Show x => IMPLICIT tag x -> [Char]
showList :: [IMPLICIT tag x] -> ShowS
$cshowList :: forall (tag :: TagK) x. Show x => [IMPLICIT tag x] -> ShowS
show :: IMPLICIT tag x -> [Char]
$cshow :: forall (tag :: TagK) x. Show x => IMPLICIT tag x -> [Char]
showsPrec :: Int -> IMPLICIT tag x -> ShowS
$cshowsPrec :: forall (tag :: TagK) x. Show x => Int -> IMPLICIT tag x -> ShowS
Show,IMPLICIT tag x -> IMPLICIT tag x -> Bool
(IMPLICIT tag x -> IMPLICIT tag x -> Bool)
-> (IMPLICIT tag x -> IMPLICIT tag x -> Bool)
-> Eq (IMPLICIT tag x)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (tag :: TagK) x.
Eq x =>
IMPLICIT tag x -> IMPLICIT tag x -> Bool
/= :: IMPLICIT tag x -> IMPLICIT tag x -> Bool
$c/= :: forall (tag :: TagK) x.
Eq x =>
IMPLICIT tag x -> IMPLICIT tag x -> Bool
== :: IMPLICIT tag x -> IMPLICIT tag x -> Bool
$c== :: forall (tag :: TagK) x.
Eq x =>
IMPLICIT tag x -> IMPLICIT tag x -> Bool
Eq,Eq (IMPLICIT tag x)
Eq (IMPLICIT tag x) =>
(IMPLICIT tag x -> IMPLICIT tag x -> Ordering)
-> (IMPLICIT tag x -> IMPLICIT tag x -> Bool)
-> (IMPLICIT tag x -> IMPLICIT tag x -> Bool)
-> (IMPLICIT tag x -> IMPLICIT tag x -> Bool)
-> (IMPLICIT tag x -> IMPLICIT tag x -> Bool)
-> (IMPLICIT tag x -> IMPLICIT tag x -> IMPLICIT tag x)
-> (IMPLICIT tag x -> IMPLICIT tag x -> IMPLICIT tag x)
-> Ord (IMPLICIT tag x)
IMPLICIT tag x -> IMPLICIT tag x -> Bool
IMPLICIT tag x -> IMPLICIT tag x -> Ordering
IMPLICIT tag x -> IMPLICIT tag x -> IMPLICIT tag x
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 (tag :: TagK) x. Ord x => Eq (IMPLICIT tag x)
forall (tag :: TagK) x.
Ord x =>
IMPLICIT tag x -> IMPLICIT tag x -> Bool
forall (tag :: TagK) x.
Ord x =>
IMPLICIT tag x -> IMPLICIT tag x -> Ordering
forall (tag :: TagK) x.
Ord x =>
IMPLICIT tag x -> IMPLICIT tag x -> IMPLICIT tag x
min :: IMPLICIT tag x -> IMPLICIT tag x -> IMPLICIT tag x
$cmin :: forall (tag :: TagK) x.
Ord x =>
IMPLICIT tag x -> IMPLICIT tag x -> IMPLICIT tag x
max :: IMPLICIT tag x -> IMPLICIT tag x -> IMPLICIT tag x
$cmax :: forall (tag :: TagK) x.
Ord x =>
IMPLICIT tag x -> IMPLICIT tag x -> IMPLICIT tag x
>= :: IMPLICIT tag x -> IMPLICIT tag x -> Bool
$c>= :: forall (tag :: TagK) x.
Ord x =>
IMPLICIT tag x -> IMPLICIT tag x -> Bool
> :: IMPLICIT tag x -> IMPLICIT tag x -> Bool
$c> :: forall (tag :: TagK) x.
Ord x =>
IMPLICIT tag x -> IMPLICIT tag x -> Bool
<= :: IMPLICIT tag x -> IMPLICIT tag x -> Bool
$c<= :: forall (tag :: TagK) x.
Ord x =>
IMPLICIT tag x -> IMPLICIT tag x -> Bool
< :: IMPLICIT tag x -> IMPLICIT tag x -> Bool
$c< :: forall (tag :: TagK) x.
Ord x =>
IMPLICIT tag x -> IMPLICIT tag x -> Bool
compare :: IMPLICIT tag x -> IMPLICIT tag x -> Ordering
$ccompare :: forall (tag :: TagK) x.
Ord x =>
IMPLICIT tag x -> IMPLICIT tag x -> Ordering
$cp1Ord :: forall (tag :: TagK) x. Ord x => Eq (IMPLICIT tag x)
Ord,Int -> IMPLICIT tag x
IMPLICIT tag x -> Int
IMPLICIT tag x -> [IMPLICIT tag x]
IMPLICIT tag x -> IMPLICIT tag x
IMPLICIT tag x -> IMPLICIT tag x -> [IMPLICIT tag x]
IMPLICIT tag x
-> IMPLICIT tag x -> IMPLICIT tag x -> [IMPLICIT tag x]
(IMPLICIT tag x -> IMPLICIT tag x)
-> (IMPLICIT tag x -> IMPLICIT tag x)
-> (Int -> IMPLICIT tag x)
-> (IMPLICIT tag x -> Int)
-> (IMPLICIT tag x -> [IMPLICIT tag x])
-> (IMPLICIT tag x -> IMPLICIT tag x -> [IMPLICIT tag x])
-> (IMPLICIT tag x -> IMPLICIT tag x -> [IMPLICIT tag x])
-> (IMPLICIT tag x
-> IMPLICIT tag x -> IMPLICIT tag x -> [IMPLICIT tag x])
-> Enum (IMPLICIT tag x)
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
forall (tag :: TagK) x. Enum x => Int -> IMPLICIT tag x
forall (tag :: TagK) x. Enum x => IMPLICIT tag x -> Int
forall (tag :: TagK) x.
Enum x =>
IMPLICIT tag x -> [IMPLICIT tag x]
forall (tag :: TagK) x. Enum x => IMPLICIT tag x -> IMPLICIT tag x
forall (tag :: TagK) x.
Enum x =>
IMPLICIT tag x -> IMPLICIT tag x -> [IMPLICIT tag x]
forall (tag :: TagK) x.
Enum x =>
IMPLICIT tag x
-> IMPLICIT tag x -> IMPLICIT tag x -> [IMPLICIT tag x]
enumFromThenTo :: IMPLICIT tag x
-> IMPLICIT tag x -> IMPLICIT tag x -> [IMPLICIT tag x]
$cenumFromThenTo :: forall (tag :: TagK) x.
Enum x =>
IMPLICIT tag x
-> IMPLICIT tag x -> IMPLICIT tag x -> [IMPLICIT tag x]
enumFromTo :: IMPLICIT tag x -> IMPLICIT tag x -> [IMPLICIT tag x]
$cenumFromTo :: forall (tag :: TagK) x.
Enum x =>
IMPLICIT tag x -> IMPLICIT tag x -> [IMPLICIT tag x]
enumFromThen :: IMPLICIT tag x -> IMPLICIT tag x -> [IMPLICIT tag x]
$cenumFromThen :: forall (tag :: TagK) x.
Enum x =>
IMPLICIT tag x -> IMPLICIT tag x -> [IMPLICIT tag x]
enumFrom :: IMPLICIT tag x -> [IMPLICIT tag x]
$cenumFrom :: forall (tag :: TagK) x.
Enum x =>
IMPLICIT tag x -> [IMPLICIT tag x]
fromEnum :: IMPLICIT tag x -> Int
$cfromEnum :: forall (tag :: TagK) x. Enum x => IMPLICIT tag x -> Int
toEnum :: Int -> IMPLICIT tag x
$ctoEnum :: forall (tag :: TagK) x. Enum x => Int -> IMPLICIT tag x
pred :: IMPLICIT tag x -> IMPLICIT tag x
$cpred :: forall (tag :: TagK) x. Enum x => IMPLICIT tag x -> IMPLICIT tag x
succ :: IMPLICIT tag x -> IMPLICIT tag x
$csucc :: forall (tag :: TagK) x. Enum x => IMPLICIT tag x -> IMPLICIT tag x
Enum)
instance Newtype (IMPLICIT tag x) x
instance forall tag t . (KnownTag tag, ASN1 t) => ASN1 (IMPLICIT tag t) where
asn1defTag :: Proxy (IMPLICIT tag t) -> Tag
asn1defTag _ = Proxy tag -> Tag
forall (tag :: TagK). KnownTag tag => Proxy tag -> Tag
tagVal (Proxy tag
forall k (t :: k). Proxy t
Proxy :: Proxy tag)
asn1decode :: ASN1Decode (IMPLICIT tag t)
asn1decode = t -> IMPLICIT tag t
forall (tag :: TagK) x. x -> IMPLICIT tag x
IMPLICIT (t -> IMPLICIT tag t)
-> ASN1Decode t -> ASN1Decode (IMPLICIT tag t)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Tag -> ASN1Decode t -> ASN1Decode t
forall x. Tag -> ASN1Decode x -> ASN1Decode x
implicit (Proxy tag -> Tag
forall (tag :: TagK). KnownTag tag => Proxy tag -> Tag
tagVal (Proxy tag
forall k (t :: k). Proxy t
Proxy :: Proxy tag)) ASN1Decode t
forall t. ASN1 t => ASN1Decode t
asn1decode
asn1encode :: IMPLICIT tag t -> ASN1Encode Word64
asn1encode (IMPLICIT v :: t
v) = Tag -> ASN1Encode Word64 -> ASN1Encode Word64
forall a. Tag -> ASN1Encode a -> ASN1Encode a
retag (Proxy tag -> Tag
forall (tag :: TagK). KnownTag tag => Proxy tag -> Tag
tagVal (Proxy tag
forall k (t :: k). Proxy t
Proxy :: Proxy tag)) (t -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t
v)
newtype EXPLICIT (tag :: TagK) x = EXPLICIT x
deriving ((forall x. EXPLICIT tag x -> Rep (EXPLICIT tag x) x)
-> (forall x. Rep (EXPLICIT tag x) x -> EXPLICIT tag x)
-> Generic (EXPLICIT tag x)
forall x. Rep (EXPLICIT tag x) x -> EXPLICIT tag x
forall x. EXPLICIT tag x -> Rep (EXPLICIT tag x) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (tag :: TagK) x x. Rep (EXPLICIT tag x) x -> EXPLICIT tag x
forall (tag :: TagK) x x. EXPLICIT tag x -> Rep (EXPLICIT tag x) x
$cto :: forall (tag :: TagK) x x. Rep (EXPLICIT tag x) x -> EXPLICIT tag x
$cfrom :: forall (tag :: TagK) x x. EXPLICIT tag x -> Rep (EXPLICIT tag x) x
Generic,EXPLICIT tag x -> ()
(EXPLICIT tag x -> ()) -> NFData (EXPLICIT tag x)
forall a. (a -> ()) -> NFData a
forall (tag :: TagK) x. NFData x => EXPLICIT tag x -> ()
rnf :: EXPLICIT tag x -> ()
$crnf :: forall (tag :: TagK) x. NFData x => EXPLICIT tag x -> ()
NFData,[Char] -> EXPLICIT tag x
([Char] -> EXPLICIT tag x) -> IsString (EXPLICIT tag x)
forall a. ([Char] -> a) -> IsString a
forall (tag :: TagK) x. IsString x => [Char] -> EXPLICIT tag x
fromString :: [Char] -> EXPLICIT tag x
$cfromString :: forall (tag :: TagK) x. IsString x => [Char] -> EXPLICIT tag x
IsString,Integer -> EXPLICIT tag x
EXPLICIT tag x -> EXPLICIT tag x
EXPLICIT tag x -> EXPLICIT tag x -> EXPLICIT tag x
(EXPLICIT tag x -> EXPLICIT tag x -> EXPLICIT tag x)
-> (EXPLICIT tag x -> EXPLICIT tag x -> EXPLICIT tag x)
-> (EXPLICIT tag x -> EXPLICIT tag x -> EXPLICIT tag x)
-> (EXPLICIT tag x -> EXPLICIT tag x)
-> (EXPLICIT tag x -> EXPLICIT tag x)
-> (EXPLICIT tag x -> EXPLICIT tag x)
-> (Integer -> EXPLICIT tag x)
-> Num (EXPLICIT tag x)
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
forall (tag :: TagK) x. Num x => Integer -> EXPLICIT tag x
forall (tag :: TagK) x. Num x => EXPLICIT tag x -> EXPLICIT tag x
forall (tag :: TagK) x.
Num x =>
EXPLICIT tag x -> EXPLICIT tag x -> EXPLICIT tag x
fromInteger :: Integer -> EXPLICIT tag x
$cfromInteger :: forall (tag :: TagK) x. Num x => Integer -> EXPLICIT tag x
signum :: EXPLICIT tag x -> EXPLICIT tag x
$csignum :: forall (tag :: TagK) x. Num x => EXPLICIT tag x -> EXPLICIT tag x
abs :: EXPLICIT tag x -> EXPLICIT tag x
$cabs :: forall (tag :: TagK) x. Num x => EXPLICIT tag x -> EXPLICIT tag x
negate :: EXPLICIT tag x -> EXPLICIT tag x
$cnegate :: forall (tag :: TagK) x. Num x => EXPLICIT tag x -> EXPLICIT tag x
* :: EXPLICIT tag x -> EXPLICIT tag x -> EXPLICIT tag x
$c* :: forall (tag :: TagK) x.
Num x =>
EXPLICIT tag x -> EXPLICIT tag x -> EXPLICIT tag x
- :: EXPLICIT tag x -> EXPLICIT tag x -> EXPLICIT tag x
$c- :: forall (tag :: TagK) x.
Num x =>
EXPLICIT tag x -> EXPLICIT tag x -> EXPLICIT tag x
+ :: EXPLICIT tag x -> EXPLICIT tag x -> EXPLICIT tag x
$c+ :: forall (tag :: TagK) x.
Num x =>
EXPLICIT tag x -> EXPLICIT tag x -> EXPLICIT tag x
Num,Int -> EXPLICIT tag x -> ShowS
[EXPLICIT tag x] -> ShowS
EXPLICIT tag x -> [Char]
(Int -> EXPLICIT tag x -> ShowS)
-> (EXPLICIT tag x -> [Char])
-> ([EXPLICIT tag x] -> ShowS)
-> Show (EXPLICIT tag x)
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
forall (tag :: TagK) x. Show x => Int -> EXPLICIT tag x -> ShowS
forall (tag :: TagK) x. Show x => [EXPLICIT tag x] -> ShowS
forall (tag :: TagK) x. Show x => EXPLICIT tag x -> [Char]
showList :: [EXPLICIT tag x] -> ShowS
$cshowList :: forall (tag :: TagK) x. Show x => [EXPLICIT tag x] -> ShowS
show :: EXPLICIT tag x -> [Char]
$cshow :: forall (tag :: TagK) x. Show x => EXPLICIT tag x -> [Char]
showsPrec :: Int -> EXPLICIT tag x -> ShowS
$cshowsPrec :: forall (tag :: TagK) x. Show x => Int -> EXPLICIT tag x -> ShowS
Show,EXPLICIT tag x -> EXPLICIT tag x -> Bool
(EXPLICIT tag x -> EXPLICIT tag x -> Bool)
-> (EXPLICIT tag x -> EXPLICIT tag x -> Bool)
-> Eq (EXPLICIT tag x)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (tag :: TagK) x.
Eq x =>
EXPLICIT tag x -> EXPLICIT tag x -> Bool
/= :: EXPLICIT tag x -> EXPLICIT tag x -> Bool
$c/= :: forall (tag :: TagK) x.
Eq x =>
EXPLICIT tag x -> EXPLICIT tag x -> Bool
== :: EXPLICIT tag x -> EXPLICIT tag x -> Bool
$c== :: forall (tag :: TagK) x.
Eq x =>
EXPLICIT tag x -> EXPLICIT tag x -> Bool
Eq,Eq (EXPLICIT tag x)
Eq (EXPLICIT tag x) =>
(EXPLICIT tag x -> EXPLICIT tag x -> Ordering)
-> (EXPLICIT tag x -> EXPLICIT tag x -> Bool)
-> (EXPLICIT tag x -> EXPLICIT tag x -> Bool)
-> (EXPLICIT tag x -> EXPLICIT tag x -> Bool)
-> (EXPLICIT tag x -> EXPLICIT tag x -> Bool)
-> (EXPLICIT tag x -> EXPLICIT tag x -> EXPLICIT tag x)
-> (EXPLICIT tag x -> EXPLICIT tag x -> EXPLICIT tag x)
-> Ord (EXPLICIT tag x)
EXPLICIT tag x -> EXPLICIT tag x -> Bool
EXPLICIT tag x -> EXPLICIT tag x -> Ordering
EXPLICIT tag x -> EXPLICIT tag x -> EXPLICIT tag x
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 (tag :: TagK) x. Ord x => Eq (EXPLICIT tag x)
forall (tag :: TagK) x.
Ord x =>
EXPLICIT tag x -> EXPLICIT tag x -> Bool
forall (tag :: TagK) x.
Ord x =>
EXPLICIT tag x -> EXPLICIT tag x -> Ordering
forall (tag :: TagK) x.
Ord x =>
EXPLICIT tag x -> EXPLICIT tag x -> EXPLICIT tag x
min :: EXPLICIT tag x -> EXPLICIT tag x -> EXPLICIT tag x
$cmin :: forall (tag :: TagK) x.
Ord x =>
EXPLICIT tag x -> EXPLICIT tag x -> EXPLICIT tag x
max :: EXPLICIT tag x -> EXPLICIT tag x -> EXPLICIT tag x
$cmax :: forall (tag :: TagK) x.
Ord x =>
EXPLICIT tag x -> EXPLICIT tag x -> EXPLICIT tag x
>= :: EXPLICIT tag x -> EXPLICIT tag x -> Bool
$c>= :: forall (tag :: TagK) x.
Ord x =>
EXPLICIT tag x -> EXPLICIT tag x -> Bool
> :: EXPLICIT tag x -> EXPLICIT tag x -> Bool
$c> :: forall (tag :: TagK) x.
Ord x =>
EXPLICIT tag x -> EXPLICIT tag x -> Bool
<= :: EXPLICIT tag x -> EXPLICIT tag x -> Bool
$c<= :: forall (tag :: TagK) x.
Ord x =>
EXPLICIT tag x -> EXPLICIT tag x -> Bool
< :: EXPLICIT tag x -> EXPLICIT tag x -> Bool
$c< :: forall (tag :: TagK) x.
Ord x =>
EXPLICIT tag x -> EXPLICIT tag x -> Bool
compare :: EXPLICIT tag x -> EXPLICIT tag x -> Ordering
$ccompare :: forall (tag :: TagK) x.
Ord x =>
EXPLICIT tag x -> EXPLICIT tag x -> Ordering
$cp1Ord :: forall (tag :: TagK) x. Ord x => Eq (EXPLICIT tag x)
Ord,Int -> EXPLICIT tag x
EXPLICIT tag x -> Int
EXPLICIT tag x -> [EXPLICIT tag x]
EXPLICIT tag x -> EXPLICIT tag x
EXPLICIT tag x -> EXPLICIT tag x -> [EXPLICIT tag x]
EXPLICIT tag x
-> EXPLICIT tag x -> EXPLICIT tag x -> [EXPLICIT tag x]
(EXPLICIT tag x -> EXPLICIT tag x)
-> (EXPLICIT tag x -> EXPLICIT tag x)
-> (Int -> EXPLICIT tag x)
-> (EXPLICIT tag x -> Int)
-> (EXPLICIT tag x -> [EXPLICIT tag x])
-> (EXPLICIT tag x -> EXPLICIT tag x -> [EXPLICIT tag x])
-> (EXPLICIT tag x -> EXPLICIT tag x -> [EXPLICIT tag x])
-> (EXPLICIT tag x
-> EXPLICIT tag x -> EXPLICIT tag x -> [EXPLICIT tag x])
-> Enum (EXPLICIT tag x)
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
forall (tag :: TagK) x. Enum x => Int -> EXPLICIT tag x
forall (tag :: TagK) x. Enum x => EXPLICIT tag x -> Int
forall (tag :: TagK) x.
Enum x =>
EXPLICIT tag x -> [EXPLICIT tag x]
forall (tag :: TagK) x. Enum x => EXPLICIT tag x -> EXPLICIT tag x
forall (tag :: TagK) x.
Enum x =>
EXPLICIT tag x -> EXPLICIT tag x -> [EXPLICIT tag x]
forall (tag :: TagK) x.
Enum x =>
EXPLICIT tag x
-> EXPLICIT tag x -> EXPLICIT tag x -> [EXPLICIT tag x]
enumFromThenTo :: EXPLICIT tag x
-> EXPLICIT tag x -> EXPLICIT tag x -> [EXPLICIT tag x]
$cenumFromThenTo :: forall (tag :: TagK) x.
Enum x =>
EXPLICIT tag x
-> EXPLICIT tag x -> EXPLICIT tag x -> [EXPLICIT tag x]
enumFromTo :: EXPLICIT tag x -> EXPLICIT tag x -> [EXPLICIT tag x]
$cenumFromTo :: forall (tag :: TagK) x.
Enum x =>
EXPLICIT tag x -> EXPLICIT tag x -> [EXPLICIT tag x]
enumFromThen :: EXPLICIT tag x -> EXPLICIT tag x -> [EXPLICIT tag x]
$cenumFromThen :: forall (tag :: TagK) x.
Enum x =>
EXPLICIT tag x -> EXPLICIT tag x -> [EXPLICIT tag x]
enumFrom :: EXPLICIT tag x -> [EXPLICIT tag x]
$cenumFrom :: forall (tag :: TagK) x.
Enum x =>
EXPLICIT tag x -> [EXPLICIT tag x]
fromEnum :: EXPLICIT tag x -> Int
$cfromEnum :: forall (tag :: TagK) x. Enum x => EXPLICIT tag x -> Int
toEnum :: Int -> EXPLICIT tag x
$ctoEnum :: forall (tag :: TagK) x. Enum x => Int -> EXPLICIT tag x
pred :: EXPLICIT tag x -> EXPLICIT tag x
$cpred :: forall (tag :: TagK) x. Enum x => EXPLICIT tag x -> EXPLICIT tag x
succ :: EXPLICIT tag x -> EXPLICIT tag x
$csucc :: forall (tag :: TagK) x. Enum x => EXPLICIT tag x -> EXPLICIT tag x
Enum)
instance Newtype (EXPLICIT tag x) x
instance forall tag t . (KnownTag tag, ASN1 t) => ASN1 (EXPLICIT tag t) where
asn1defTag :: Proxy (EXPLICIT tag t) -> Tag
asn1defTag _ = Proxy tag -> Tag
forall (tag :: TagK). KnownTag tag => Proxy tag -> Tag
tagVal (Proxy tag
forall k (t :: k). Proxy t
Proxy :: Proxy tag)
asn1decode :: ASN1Decode (EXPLICIT tag t)
asn1decode = t -> EXPLICIT tag t
forall (tag :: TagK) x. x -> EXPLICIT tag x
EXPLICIT (t -> EXPLICIT tag t)
-> ASN1Decode t -> ASN1Decode (EXPLICIT tag t)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Tag -> ASN1Decode t -> ASN1Decode t
forall x. Tag -> ASN1Decode x -> ASN1Decode x
explicit (Proxy tag -> Tag
forall (tag :: TagK). KnownTag tag => Proxy tag -> Tag
tagVal (Proxy tag
forall k (t :: k). Proxy t
Proxy :: Proxy tag)) ASN1Decode t
forall t. ASN1 t => ASN1Decode t
asn1decode
asn1encode :: EXPLICIT tag t -> ASN1Encode Word64
asn1encode (EXPLICIT v :: t
v) = Tag -> ASN1Encode Word64 -> ASN1Encode Word64
wraptag (Proxy tag -> Tag
forall (tag :: TagK). KnownTag tag => Proxy tag -> Tag
tagVal (Proxy tag
forall k (t :: k). Proxy t
Proxy :: Proxy tag)) (t -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t
v)
newtype ENUMERATED x = ENUMERATED x
deriving ((forall x. ENUMERATED x -> Rep (ENUMERATED x) x)
-> (forall x. Rep (ENUMERATED x) x -> ENUMERATED x)
-> Generic (ENUMERATED x)
forall x. Rep (ENUMERATED x) x -> ENUMERATED x
forall x. ENUMERATED x -> Rep (ENUMERATED x) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall x x. Rep (ENUMERATED x) x -> ENUMERATED x
forall x x. ENUMERATED x -> Rep (ENUMERATED x) x
$cto :: forall x x. Rep (ENUMERATED x) x -> ENUMERATED x
$cfrom :: forall x x. ENUMERATED x -> Rep (ENUMERATED x) x
Generic,ENUMERATED x -> ()
(ENUMERATED x -> ()) -> NFData (ENUMERATED x)
forall x. NFData x => ENUMERATED x -> ()
forall a. (a -> ()) -> NFData a
rnf :: ENUMERATED x -> ()
$crnf :: forall x. NFData x => ENUMERATED x -> ()
NFData,Integer -> ENUMERATED x
ENUMERATED x -> ENUMERATED x
ENUMERATED x -> ENUMERATED x -> ENUMERATED x
(ENUMERATED x -> ENUMERATED x -> ENUMERATED x)
-> (ENUMERATED x -> ENUMERATED x -> ENUMERATED x)
-> (ENUMERATED x -> ENUMERATED x -> ENUMERATED x)
-> (ENUMERATED x -> ENUMERATED x)
-> (ENUMERATED x -> ENUMERATED x)
-> (ENUMERATED x -> ENUMERATED x)
-> (Integer -> ENUMERATED x)
-> Num (ENUMERATED x)
forall x. Num x => Integer -> ENUMERATED x
forall x. Num x => ENUMERATED x -> ENUMERATED x
forall x. Num x => ENUMERATED x -> ENUMERATED x -> ENUMERATED x
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> ENUMERATED x
$cfromInteger :: forall x. Num x => Integer -> ENUMERATED x
signum :: ENUMERATED x -> ENUMERATED x
$csignum :: forall x. Num x => ENUMERATED x -> ENUMERATED x
abs :: ENUMERATED x -> ENUMERATED x
$cabs :: forall x. Num x => ENUMERATED x -> ENUMERATED x
negate :: ENUMERATED x -> ENUMERATED x
$cnegate :: forall x. Num x => ENUMERATED x -> ENUMERATED x
* :: ENUMERATED x -> ENUMERATED x -> ENUMERATED x
$c* :: forall x. Num x => ENUMERATED x -> ENUMERATED x -> ENUMERATED x
- :: ENUMERATED x -> ENUMERATED x -> ENUMERATED x
$c- :: forall x. Num x => ENUMERATED x -> ENUMERATED x -> ENUMERATED x
+ :: ENUMERATED x -> ENUMERATED x -> ENUMERATED x
$c+ :: forall x. Num x => ENUMERATED x -> ENUMERATED x -> ENUMERATED x
Num,Int -> ENUMERATED x -> ShowS
[ENUMERATED x] -> ShowS
ENUMERATED x -> [Char]
(Int -> ENUMERATED x -> ShowS)
-> (ENUMERATED x -> [Char])
-> ([ENUMERATED x] -> ShowS)
-> Show (ENUMERATED x)
forall x. Show x => Int -> ENUMERATED x -> ShowS
forall x. Show x => [ENUMERATED x] -> ShowS
forall x. Show x => ENUMERATED x -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [ENUMERATED x] -> ShowS
$cshowList :: forall x. Show x => [ENUMERATED x] -> ShowS
show :: ENUMERATED x -> [Char]
$cshow :: forall x. Show x => ENUMERATED x -> [Char]
showsPrec :: Int -> ENUMERATED x -> ShowS
$cshowsPrec :: forall x. Show x => Int -> ENUMERATED x -> ShowS
Show,ENUMERATED x -> ENUMERATED x -> Bool
(ENUMERATED x -> ENUMERATED x -> Bool)
-> (ENUMERATED x -> ENUMERATED x -> Bool) -> Eq (ENUMERATED x)
forall x. Eq x => ENUMERATED x -> ENUMERATED x -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ENUMERATED x -> ENUMERATED x -> Bool
$c/= :: forall x. Eq x => ENUMERATED x -> ENUMERATED x -> Bool
== :: ENUMERATED x -> ENUMERATED x -> Bool
$c== :: forall x. Eq x => ENUMERATED x -> ENUMERATED x -> Bool
Eq,Eq (ENUMERATED x)
Eq (ENUMERATED x) =>
(ENUMERATED x -> ENUMERATED x -> Ordering)
-> (ENUMERATED x -> ENUMERATED x -> Bool)
-> (ENUMERATED x -> ENUMERATED x -> Bool)
-> (ENUMERATED x -> ENUMERATED x -> Bool)
-> (ENUMERATED x -> ENUMERATED x -> Bool)
-> (ENUMERATED x -> ENUMERATED x -> ENUMERATED x)
-> (ENUMERATED x -> ENUMERATED x -> ENUMERATED x)
-> Ord (ENUMERATED x)
ENUMERATED x -> ENUMERATED x -> Bool
ENUMERATED x -> ENUMERATED x -> Ordering
ENUMERATED x -> ENUMERATED x -> ENUMERATED x
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 x. Ord x => Eq (ENUMERATED x)
forall x. Ord x => ENUMERATED x -> ENUMERATED x -> Bool
forall x. Ord x => ENUMERATED x -> ENUMERATED x -> Ordering
forall x. Ord x => ENUMERATED x -> ENUMERATED x -> ENUMERATED x
min :: ENUMERATED x -> ENUMERATED x -> ENUMERATED x
$cmin :: forall x. Ord x => ENUMERATED x -> ENUMERATED x -> ENUMERATED x
max :: ENUMERATED x -> ENUMERATED x -> ENUMERATED x
$cmax :: forall x. Ord x => ENUMERATED x -> ENUMERATED x -> ENUMERATED x
>= :: ENUMERATED x -> ENUMERATED x -> Bool
$c>= :: forall x. Ord x => ENUMERATED x -> ENUMERATED x -> Bool
> :: ENUMERATED x -> ENUMERATED x -> Bool
$c> :: forall x. Ord x => ENUMERATED x -> ENUMERATED x -> Bool
<= :: ENUMERATED x -> ENUMERATED x -> Bool
$c<= :: forall x. Ord x => ENUMERATED x -> ENUMERATED x -> Bool
< :: ENUMERATED x -> ENUMERATED x -> Bool
$c< :: forall x. Ord x => ENUMERATED x -> ENUMERATED x -> Bool
compare :: ENUMERATED x -> ENUMERATED x -> Ordering
$ccompare :: forall x. Ord x => ENUMERATED x -> ENUMERATED x -> Ordering
$cp1Ord :: forall x. Ord x => Eq (ENUMERATED x)
Ord,Int -> ENUMERATED x
ENUMERATED x -> Int
ENUMERATED x -> [ENUMERATED x]
ENUMERATED x -> ENUMERATED x
ENUMERATED x -> ENUMERATED x -> [ENUMERATED x]
ENUMERATED x -> ENUMERATED x -> ENUMERATED x -> [ENUMERATED x]
(ENUMERATED x -> ENUMERATED x)
-> (ENUMERATED x -> ENUMERATED x)
-> (Int -> ENUMERATED x)
-> (ENUMERATED x -> Int)
-> (ENUMERATED x -> [ENUMERATED x])
-> (ENUMERATED x -> ENUMERATED x -> [ENUMERATED x])
-> (ENUMERATED x -> ENUMERATED x -> [ENUMERATED x])
-> (ENUMERATED x -> ENUMERATED x -> ENUMERATED x -> [ENUMERATED x])
-> Enum (ENUMERATED x)
forall x. Enum x => Int -> ENUMERATED x
forall x. Enum x => ENUMERATED x -> Int
forall x. Enum x => ENUMERATED x -> [ENUMERATED x]
forall x. Enum x => ENUMERATED x -> ENUMERATED x
forall x. Enum x => ENUMERATED x -> ENUMERATED x -> [ENUMERATED x]
forall x.
Enum x =>
ENUMERATED x -> ENUMERATED x -> ENUMERATED x -> [ENUMERATED x]
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 :: ENUMERATED x -> ENUMERATED x -> ENUMERATED x -> [ENUMERATED x]
$cenumFromThenTo :: forall x.
Enum x =>
ENUMERATED x -> ENUMERATED x -> ENUMERATED x -> [ENUMERATED x]
enumFromTo :: ENUMERATED x -> ENUMERATED x -> [ENUMERATED x]
$cenumFromTo :: forall x. Enum x => ENUMERATED x -> ENUMERATED x -> [ENUMERATED x]
enumFromThen :: ENUMERATED x -> ENUMERATED x -> [ENUMERATED x]
$cenumFromThen :: forall x. Enum x => ENUMERATED x -> ENUMERATED x -> [ENUMERATED x]
enumFrom :: ENUMERATED x -> [ENUMERATED x]
$cenumFrom :: forall x. Enum x => ENUMERATED x -> [ENUMERATED x]
fromEnum :: ENUMERATED x -> Int
$cfromEnum :: forall x. Enum x => ENUMERATED x -> Int
toEnum :: Int -> ENUMERATED x
$ctoEnum :: forall x. Enum x => Int -> ENUMERATED x
pred :: ENUMERATED x -> ENUMERATED x
$cpred :: forall x. Enum x => ENUMERATED x -> ENUMERATED x
succ :: ENUMERATED x -> ENUMERATED x
$csucc :: forall x. Enum x => ENUMERATED x -> ENUMERATED x
Enum)
instance Newtype (ENUMERATED x) x
instance Enumerated t => ASN1 (ENUMERATED t) where
asn1defTag :: Proxy (ENUMERATED t) -> Tag
asn1defTag _ = Word64 -> Tag
Universal 10
asn1decode :: ASN1Decode (ENUMERATED t)
asn1decode = t -> ENUMERATED t
forall x. x -> ENUMERATED x
ENUMERATED (t -> ENUMERATED t) -> ASN1Decode t -> ASN1Decode (ENUMERATED t)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ASN1Decode t
forall enum. Enumerated enum => ASN1Decode enum
dec'ENUMERATED
asn1encode :: ENUMERATED t -> ASN1Encode Word64
asn1encode (ENUMERATED v :: t
v) = t -> ASN1Encode Word64
forall enum. Enumerated enum => enum -> ASN1Encode Word64
enc'ENUMERATED t
v
newtype COMPONENTS_OF x = COMPONENTS_OF x
deriving ((forall x. COMPONENTS_OF x -> Rep (COMPONENTS_OF x) x)
-> (forall x. Rep (COMPONENTS_OF x) x -> COMPONENTS_OF x)
-> Generic (COMPONENTS_OF x)
forall x. Rep (COMPONENTS_OF x) x -> COMPONENTS_OF x
forall x. COMPONENTS_OF x -> Rep (COMPONENTS_OF x) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall x x. Rep (COMPONENTS_OF x) x -> COMPONENTS_OF x
forall x x. COMPONENTS_OF x -> Rep (COMPONENTS_OF x) x
$cto :: forall x x. Rep (COMPONENTS_OF x) x -> COMPONENTS_OF x
$cfrom :: forall x x. COMPONENTS_OF x -> Rep (COMPONENTS_OF x) x
Generic,COMPONENTS_OF x -> ()
(COMPONENTS_OF x -> ()) -> NFData (COMPONENTS_OF x)
forall x. NFData x => COMPONENTS_OF x -> ()
forall a. (a -> ()) -> NFData a
rnf :: COMPONENTS_OF x -> ()
$crnf :: forall x. NFData x => COMPONENTS_OF x -> ()
NFData,Int -> COMPONENTS_OF x -> ShowS
[COMPONENTS_OF x] -> ShowS
COMPONENTS_OF x -> [Char]
(Int -> COMPONENTS_OF x -> ShowS)
-> (COMPONENTS_OF x -> [Char])
-> ([COMPONENTS_OF x] -> ShowS)
-> Show (COMPONENTS_OF x)
forall x. Show x => Int -> COMPONENTS_OF x -> ShowS
forall x. Show x => [COMPONENTS_OF x] -> ShowS
forall x. Show x => COMPONENTS_OF x -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [COMPONENTS_OF x] -> ShowS
$cshowList :: forall x. Show x => [COMPONENTS_OF x] -> ShowS
show :: COMPONENTS_OF x -> [Char]
$cshow :: forall x. Show x => COMPONENTS_OF x -> [Char]
showsPrec :: Int -> COMPONENTS_OF x -> ShowS
$cshowsPrec :: forall x. Show x => Int -> COMPONENTS_OF x -> ShowS
Show,COMPONENTS_OF x -> COMPONENTS_OF x -> Bool
(COMPONENTS_OF x -> COMPONENTS_OF x -> Bool)
-> (COMPONENTS_OF x -> COMPONENTS_OF x -> Bool)
-> Eq (COMPONENTS_OF x)
forall x. Eq x => COMPONENTS_OF x -> COMPONENTS_OF x -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: COMPONENTS_OF x -> COMPONENTS_OF x -> Bool
$c/= :: forall x. Eq x => COMPONENTS_OF x -> COMPONENTS_OF x -> Bool
== :: COMPONENTS_OF x -> COMPONENTS_OF x -> Bool
$c== :: forall x. Eq x => COMPONENTS_OF x -> COMPONENTS_OF x -> Bool
Eq,Eq (COMPONENTS_OF x)
Eq (COMPONENTS_OF x) =>
(COMPONENTS_OF x -> COMPONENTS_OF x -> Ordering)
-> (COMPONENTS_OF x -> COMPONENTS_OF x -> Bool)
-> (COMPONENTS_OF x -> COMPONENTS_OF x -> Bool)
-> (COMPONENTS_OF x -> COMPONENTS_OF x -> Bool)
-> (COMPONENTS_OF x -> COMPONENTS_OF x -> Bool)
-> (COMPONENTS_OF x -> COMPONENTS_OF x -> COMPONENTS_OF x)
-> (COMPONENTS_OF x -> COMPONENTS_OF x -> COMPONENTS_OF x)
-> Ord (COMPONENTS_OF x)
COMPONENTS_OF x -> COMPONENTS_OF x -> Bool
COMPONENTS_OF x -> COMPONENTS_OF x -> Ordering
COMPONENTS_OF x -> COMPONENTS_OF x -> COMPONENTS_OF x
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 x. Ord x => Eq (COMPONENTS_OF x)
forall x. Ord x => COMPONENTS_OF x -> COMPONENTS_OF x -> Bool
forall x. Ord x => COMPONENTS_OF x -> COMPONENTS_OF x -> Ordering
forall x.
Ord x =>
COMPONENTS_OF x -> COMPONENTS_OF x -> COMPONENTS_OF x
min :: COMPONENTS_OF x -> COMPONENTS_OF x -> COMPONENTS_OF x
$cmin :: forall x.
Ord x =>
COMPONENTS_OF x -> COMPONENTS_OF x -> COMPONENTS_OF x
max :: COMPONENTS_OF x -> COMPONENTS_OF x -> COMPONENTS_OF x
$cmax :: forall x.
Ord x =>
COMPONENTS_OF x -> COMPONENTS_OF x -> COMPONENTS_OF x
>= :: COMPONENTS_OF x -> COMPONENTS_OF x -> Bool
$c>= :: forall x. Ord x => COMPONENTS_OF x -> COMPONENTS_OF x -> Bool
> :: COMPONENTS_OF x -> COMPONENTS_OF x -> Bool
$c> :: forall x. Ord x => COMPONENTS_OF x -> COMPONENTS_OF x -> Bool
<= :: COMPONENTS_OF x -> COMPONENTS_OF x -> Bool
$c<= :: forall x. Ord x => COMPONENTS_OF x -> COMPONENTS_OF x -> Bool
< :: COMPONENTS_OF x -> COMPONENTS_OF x -> Bool
$c< :: forall x. Ord x => COMPONENTS_OF x -> COMPONENTS_OF x -> Bool
compare :: COMPONENTS_OF x -> COMPONENTS_OF x -> Ordering
$ccompare :: forall x. Ord x => COMPONENTS_OF x -> COMPONENTS_OF x -> Ordering
$cp1Ord :: forall x. Ord x => Eq (COMPONENTS_OF x)
Ord)
instance Newtype (COMPONENTS_OF x) x
instance ASN1Constructed t => ASN1 (COMPONENTS_OF t) where
asn1defTag :: Proxy (COMPONENTS_OF t) -> Tag
asn1defTag _ = Proxy t -> Tag
forall t. ASN1 t => Proxy t -> Tag
asn1defTag (Proxy t
forall k (t :: k). Proxy t
Proxy :: Proxy t)
asn1decode :: ASN1Decode (COMPONENTS_OF t)
asn1decode = t -> COMPONENTS_OF t
forall x. x -> COMPONENTS_OF x
COMPONENTS_OF (t -> COMPONENTS_OF t)
-> ASN1Decode t -> ASN1Decode (COMPONENTS_OF t)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ASN1Decode t
forall t. ASN1Constructed t => ASN1Decode t
asn1decodeCompOf
asn1encode :: COMPONENTS_OF t -> ASN1Encode Word64
asn1encode (COMPONENTS_OF v :: t
v) = t -> ASN1Encode Word64
forall t. ASN1Constructed t => t -> ASN1Encode Word64
asn1encodeCompOf t
v
newtype CHOICE x = CHOICE x
deriving ((forall x. CHOICE x -> Rep (CHOICE x) x)
-> (forall x. Rep (CHOICE x) x -> CHOICE x) -> Generic (CHOICE x)
forall x. Rep (CHOICE x) x -> CHOICE x
forall x. CHOICE x -> Rep (CHOICE x) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall x x. Rep (CHOICE x) x -> CHOICE x
forall x x. CHOICE x -> Rep (CHOICE x) x
$cto :: forall x x. Rep (CHOICE x) x -> CHOICE x
$cfrom :: forall x x. CHOICE x -> Rep (CHOICE x) x
Generic,CHOICE x -> ()
(CHOICE x -> ()) -> NFData (CHOICE x)
forall x. NFData x => CHOICE x -> ()
forall a. (a -> ()) -> NFData a
rnf :: CHOICE x -> ()
$crnf :: forall x. NFData x => CHOICE x -> ()
NFData,Int -> CHOICE x -> ShowS
[CHOICE x] -> ShowS
CHOICE x -> [Char]
(Int -> CHOICE x -> ShowS)
-> (CHOICE x -> [Char]) -> ([CHOICE x] -> ShowS) -> Show (CHOICE x)
forall x. Show x => Int -> CHOICE x -> ShowS
forall x. Show x => [CHOICE x] -> ShowS
forall x. Show x => CHOICE x -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [CHOICE x] -> ShowS
$cshowList :: forall x. Show x => [CHOICE x] -> ShowS
show :: CHOICE x -> [Char]
$cshow :: forall x. Show x => CHOICE x -> [Char]
showsPrec :: Int -> CHOICE x -> ShowS
$cshowsPrec :: forall x. Show x => Int -> CHOICE x -> ShowS
Show,CHOICE x -> CHOICE x -> Bool
(CHOICE x -> CHOICE x -> Bool)
-> (CHOICE x -> CHOICE x -> Bool) -> Eq (CHOICE x)
forall x. Eq x => CHOICE x -> CHOICE x -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CHOICE x -> CHOICE x -> Bool
$c/= :: forall x. Eq x => CHOICE x -> CHOICE x -> Bool
== :: CHOICE x -> CHOICE x -> Bool
$c== :: forall x. Eq x => CHOICE x -> CHOICE x -> Bool
Eq,Eq (CHOICE x)
Eq (CHOICE x) =>
(CHOICE x -> CHOICE x -> Ordering)
-> (CHOICE x -> CHOICE x -> Bool)
-> (CHOICE x -> CHOICE x -> Bool)
-> (CHOICE x -> CHOICE x -> Bool)
-> (CHOICE x -> CHOICE x -> Bool)
-> (CHOICE x -> CHOICE x -> CHOICE x)
-> (CHOICE x -> CHOICE x -> CHOICE x)
-> Ord (CHOICE x)
CHOICE x -> CHOICE x -> Bool
CHOICE x -> CHOICE x -> Ordering
CHOICE x -> CHOICE x -> CHOICE x
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 x. Ord x => Eq (CHOICE x)
forall x. Ord x => CHOICE x -> CHOICE x -> Bool
forall x. Ord x => CHOICE x -> CHOICE x -> Ordering
forall x. Ord x => CHOICE x -> CHOICE x -> CHOICE x
min :: CHOICE x -> CHOICE x -> CHOICE x
$cmin :: forall x. Ord x => CHOICE x -> CHOICE x -> CHOICE x
max :: CHOICE x -> CHOICE x -> CHOICE x
$cmax :: forall x. Ord x => CHOICE x -> CHOICE x -> CHOICE x
>= :: CHOICE x -> CHOICE x -> Bool
$c>= :: forall x. Ord x => CHOICE x -> CHOICE x -> Bool
> :: CHOICE x -> CHOICE x -> Bool
$c> :: forall x. Ord x => CHOICE x -> CHOICE x -> Bool
<= :: CHOICE x -> CHOICE x -> Bool
$c<= :: forall x. Ord x => CHOICE x -> CHOICE x -> Bool
< :: CHOICE x -> CHOICE x -> Bool
$c< :: forall x. Ord x => CHOICE x -> CHOICE x -> Bool
compare :: CHOICE x -> CHOICE x -> Ordering
$ccompare :: forall x. Ord x => CHOICE x -> CHOICE x -> Ordering
$cp1Ord :: forall x. Ord x => Eq (CHOICE x)
Ord)
instance Newtype (CHOICE x) x
instance (Generic t, GASN1EncodeChoice (Rep t), GASN1DecodeChoice (Rep t)) => ASN1 (CHOICE t) where
asn1defTag :: Proxy (CHOICE t) -> Tag
asn1defTag _ = Tag
forall a. HasCallStack => a
undefined
asn1decode :: ASN1Decode (CHOICE t)
asn1decode = t -> CHOICE t
forall x. x -> CHOICE x
CHOICE (t -> CHOICE t) -> ASN1Decode t -> ASN1Decode (CHOICE t)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ASN1Decode t
forall t. (Generic t, GASN1DecodeChoice (Rep t)) => ASN1Decode t
gasn1decodeChoice
asn1encode :: CHOICE t -> ASN1Encode Word64
asn1encode (CHOICE v :: t
v) = t -> ASN1Encode Word64
forall t.
(Generic t, GASN1EncodeChoice (Rep t)) =>
t -> ASN1Encode Word64
gasn1encodeChoice t
v
class ASN1 t where
asn1defTag :: Proxy t -> Tag
asn1defTag _ = Word64 -> Tag
Universal 16
asn1decode :: ASN1Decode t
default asn1decode :: ASN1Constructed t => ASN1Decode t
asn1decode = [Char] -> Tag -> ASN1Decode t -> ASN1Decode t
forall x. [Char] -> Tag -> ASN1Decode x -> ASN1Decode x
dec'Constructed "SEQUENCE" (Proxy t -> Tag
forall t. ASN1 t => Proxy t -> Tag
asn1defTag (Proxy t
forall k (t :: k). Proxy t
Proxy :: Proxy t)) ASN1Decode t
forall t. ASN1Constructed t => ASN1Decode t
asn1decodeCompOf
asn1encode :: t -> ASN1Encode Word64
default asn1encode :: ASN1Constructed t => t -> ASN1Encode Word64
asn1encode = Tag -> ASN1Encode Word64 -> ASN1Encode Word64
wraptag (Proxy t -> Tag
forall t. ASN1 t => Proxy t -> Tag
asn1defTag (Proxy t
forall k (t :: k). Proxy t
Proxy :: Proxy t)) (ASN1Encode Word64 -> ASN1Encode Word64)
-> (t -> ASN1Encode Word64) -> t -> ASN1Encode Word64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. t -> ASN1Encode Word64
forall t. ASN1Constructed t => t -> ASN1Encode Word64
asn1encodeCompOf
class ASN1 t => ASN1Constructed t where
asn1encodeCompOf :: t -> ASN1Encode Word64
default asn1encodeCompOf :: (Generic t, GASN1EncodeCompOf (Rep t)) => t -> ASN1Encode Word64
asn1encodeCompOf = t -> ASN1Encode Word64
forall t.
(Generic t, GASN1EncodeCompOf (Rep t)) =>
t -> ASN1Encode Word64
gasn1encodeCompOf
asn1decodeCompOf :: ASN1Decode t
default asn1decodeCompOf :: (Generic t, GASN1DecodeCompOf (Rep t)) => ASN1Decode t
asn1decodeCompOf = ASN1Decode t
forall t. (Generic t, GASN1DecodeCompOf (Rep t)) => ASN1Decode t
gasn1decodeCompOf
gasn1encodeCompOf :: (Generic t, GASN1EncodeCompOf (Rep t)) => t -> ASN1Encode Word64
gasn1encodeCompOf :: t -> ASN1Encode Word64
gasn1encodeCompOf v :: t
v = Rep t Any -> ASN1Encode Word64
forall (t :: * -> *) p.
GASN1EncodeCompOf t =>
t p -> ASN1Encode Word64
gasn1encodeCompOf' (t -> Rep t Any
forall a x. Generic a => a -> Rep a x
from t
v)
gasn1decodeCompOf :: (Generic t, GASN1DecodeCompOf (Rep t)) => ASN1Decode t
gasn1decodeCompOf :: ASN1Decode t
gasn1decodeCompOf = Rep t Any -> t
forall a x. Generic a => Rep a x -> a
to (Rep t Any -> t) -> ASN1Decode (Rep t Any) -> ASN1Decode t
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ASN1Decode (Rep t Any)
forall (t :: * -> *) p. GASN1DecodeCompOf t => ASN1Decode (t p)
gasn1decodeCompOf'
instance (ASN1 t1, ASN1 t2) => ASN1 (t1,t2)
instance (ASN1 t1, ASN1 t2) => ASN1Constructed (t1,t2) where
asn1encodeCompOf :: (t1, t2) -> ASN1Encode Word64
asn1encodeCompOf (v1 :: t1
v1,v2 :: t2
v2) = [ASN1Encode Word64] -> ASN1Encode Word64
enc'SEQUENCE_COMPS [t1 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t1
v1, t2 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t2
v2]
asn1decodeCompOf :: ASN1Decode (t1, t2)
asn1decodeCompOf = (,) (t1 -> t2 -> (t1, t2))
-> ASN1Decode t1 -> ASN1Decode (t2 -> (t1, t2))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ASN1Decode t1
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode (t2 -> (t1, t2)) -> ASN1Decode t2 -> ASN1Decode (t1, t2)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t2
forall t. ASN1 t => ASN1Decode t
asn1decode
instance (ASN1 t1, ASN1 t2, ASN1 t3) => ASN1 (t1,t2,t3)
instance (ASN1 t1, ASN1 t2, ASN1 t3) => ASN1Constructed (t1,t2,t3) where
asn1encodeCompOf :: (t1, t2, t3) -> ASN1Encode Word64
asn1encodeCompOf (v1 :: t1
v1,v2 :: t2
v2,v3 :: t3
v3) = [ASN1Encode Word64] -> ASN1Encode Word64
enc'SEQUENCE_COMPS [t1 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t1
v1, t2 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t2
v2, t3 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t3
v3]
asn1decodeCompOf :: ASN1Decode (t1, t2, t3)
asn1decodeCompOf = (,,) (t1 -> t2 -> t3 -> (t1, t2, t3))
-> ASN1Decode t1 -> ASN1Decode (t2 -> t3 -> (t1, t2, t3))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ASN1Decode t1
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode (t2 -> t3 -> (t1, t2, t3))
-> ASN1Decode t2 -> ASN1Decode (t3 -> (t1, t2, t3))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t2
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode (t3 -> (t1, t2, t3))
-> ASN1Decode t3 -> ASN1Decode (t1, t2, t3)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t3
forall t. ASN1 t => ASN1Decode t
asn1decode
instance (ASN1 t1, ASN1 t2, ASN1 t3, ASN1 t4) => ASN1 (t1,t2,t3,t4)
instance (ASN1 t1, ASN1 t2, ASN1 t3, ASN1 t4) => ASN1Constructed (t1,t2,t3,t4) where
asn1encodeCompOf :: (t1, t2, t3, t4) -> ASN1Encode Word64
asn1encodeCompOf (v1 :: t1
v1,v2 :: t2
v2,v3 :: t3
v3,v4 :: t4
v4) = [ASN1Encode Word64] -> ASN1Encode Word64
enc'SEQUENCE_COMPS [t1 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t1
v1, t2 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t2
v2, t3 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t3
v3, t4 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t4
v4]
asn1decodeCompOf :: ASN1Decode (t1, t2, t3, t4)
asn1decodeCompOf = (,,,) (t1 -> t2 -> t3 -> t4 -> (t1, t2, t3, t4))
-> ASN1Decode t1 -> ASN1Decode (t2 -> t3 -> t4 -> (t1, t2, t3, t4))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ASN1Decode t1
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode (t2 -> t3 -> t4 -> (t1, t2, t3, t4))
-> ASN1Decode t2 -> ASN1Decode (t3 -> t4 -> (t1, t2, t3, t4))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t2
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode (t3 -> t4 -> (t1, t2, t3, t4))
-> ASN1Decode t3 -> ASN1Decode (t4 -> (t1, t2, t3, t4))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t3
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode (t4 -> (t1, t2, t3, t4))
-> ASN1Decode t4 -> ASN1Decode (t1, t2, t3, t4)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t4
forall t. ASN1 t => ASN1Decode t
asn1decode
instance (ASN1 t1, ASN1 t2, ASN1 t3, ASN1 t4, ASN1 t5) => ASN1 (t1,t2,t3,t4,t5)
instance (ASN1 t1, ASN1 t2, ASN1 t3, ASN1 t4, ASN1 t5) => ASN1Constructed (t1,t2,t3,t4,t5) where
asn1encodeCompOf :: (t1, t2, t3, t4, t5) -> ASN1Encode Word64
asn1encodeCompOf (v1 :: t1
v1,v2 :: t2
v2,v3 :: t3
v3,v4 :: t4
v4,v5 :: t5
v5) = [ASN1Encode Word64] -> ASN1Encode Word64
enc'SEQUENCE_COMPS [t1 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t1
v1, t2 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t2
v2, t3 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t3
v3, t4 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t4
v4, t5 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t5
v5]
asn1decodeCompOf :: ASN1Decode (t1, t2, t3, t4, t5)
asn1decodeCompOf = (,,,,) (t1 -> t2 -> t3 -> t4 -> t5 -> (t1, t2, t3, t4, t5))
-> ASN1Decode t1
-> ASN1Decode (t2 -> t3 -> t4 -> t5 -> (t1, t2, t3, t4, t5))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ASN1Decode t1
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode (t2 -> t3 -> t4 -> t5 -> (t1, t2, t3, t4, t5))
-> ASN1Decode t2
-> ASN1Decode (t3 -> t4 -> t5 -> (t1, t2, t3, t4, t5))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t2
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode (t3 -> t4 -> t5 -> (t1, t2, t3, t4, t5))
-> ASN1Decode t3 -> ASN1Decode (t4 -> t5 -> (t1, t2, t3, t4, t5))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t3
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode (t4 -> t5 -> (t1, t2, t3, t4, t5))
-> ASN1Decode t4 -> ASN1Decode (t5 -> (t1, t2, t3, t4, t5))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t4
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode (t5 -> (t1, t2, t3, t4, t5))
-> ASN1Decode t5 -> ASN1Decode (t1, t2, t3, t4, t5)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t5
forall t. ASN1 t => ASN1Decode t
asn1decode
instance (ASN1 t1, ASN1 t2, ASN1 t3, ASN1 t4, ASN1 t5, ASN1 t6) => ASN1 (t1,t2,t3,t4,t5,t6)
instance (ASN1 t1, ASN1 t2, ASN1 t3, ASN1 t4, ASN1 t5, ASN1 t6) => ASN1Constructed (t1,t2,t3,t4,t5,t6) where
asn1encodeCompOf :: (t1, t2, t3, t4, t5, t6) -> ASN1Encode Word64
asn1encodeCompOf (v1 :: t1
v1,v2 :: t2
v2,v3 :: t3
v3,v4 :: t4
v4,v5 :: t5
v5,v6 :: t6
v6) = [ASN1Encode Word64] -> ASN1Encode Word64
enc'SEQUENCE_COMPS [t1 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t1
v1, t2 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t2
v2, t3 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t3
v3, t4 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t4
v4, t5 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t5
v5, t6 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t6
v6]
asn1decodeCompOf :: ASN1Decode (t1, t2, t3, t4, t5, t6)
asn1decodeCompOf = (,,,,,) (t1 -> t2 -> t3 -> t4 -> t5 -> t6 -> (t1, t2, t3, t4, t5, t6))
-> ASN1Decode t1
-> ASN1Decode
(t2 -> t3 -> t4 -> t5 -> t6 -> (t1, t2, t3, t4, t5, t6))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ASN1Decode t1
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode (t2 -> t3 -> t4 -> t5 -> t6 -> (t1, t2, t3, t4, t5, t6))
-> ASN1Decode t2
-> ASN1Decode (t3 -> t4 -> t5 -> t6 -> (t1, t2, t3, t4, t5, t6))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t2
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode (t3 -> t4 -> t5 -> t6 -> (t1, t2, t3, t4, t5, t6))
-> ASN1Decode t3
-> ASN1Decode (t4 -> t5 -> t6 -> (t1, t2, t3, t4, t5, t6))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t3
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode (t4 -> t5 -> t6 -> (t1, t2, t3, t4, t5, t6))
-> ASN1Decode t4
-> ASN1Decode (t5 -> t6 -> (t1, t2, t3, t4, t5, t6))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t4
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode (t5 -> t6 -> (t1, t2, t3, t4, t5, t6))
-> ASN1Decode t5 -> ASN1Decode (t6 -> (t1, t2, t3, t4, t5, t6))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t5
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode (t6 -> (t1, t2, t3, t4, t5, t6))
-> ASN1Decode t6 -> ASN1Decode (t1, t2, t3, t4, t5, t6)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t6
forall t. ASN1 t => ASN1Decode t
asn1decode
instance (ASN1 t1, ASN1 t2, ASN1 t3, ASN1 t4, ASN1 t5, ASN1 t6, ASN1 t7) => ASN1 (t1,t2,t3,t4,t5,t6,t7)
instance (ASN1 t1, ASN1 t2, ASN1 t3, ASN1 t4, ASN1 t5, ASN1 t6, ASN1 t7) => ASN1Constructed (t1,t2,t3,t4,t5,t6,t7) where
asn1encodeCompOf :: (t1, t2, t3, t4, t5, t6, t7) -> ASN1Encode Word64
asn1encodeCompOf (v1 :: t1
v1,v2 :: t2
v2,v3 :: t3
v3,v4 :: t4
v4,v5 :: t5
v5,v6 :: t6
v6,v7 :: t7
v7) = [ASN1Encode Word64] -> ASN1Encode Word64
enc'SEQUENCE_COMPS [t1 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t1
v1, t2 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t2
v2, t3 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t3
v3, t4 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t4
v4, t5 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t5
v5, t6 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t6
v6, t7 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t7
v7]
asn1decodeCompOf :: ASN1Decode (t1, t2, t3, t4, t5, t6, t7)
asn1decodeCompOf = (,,,,,,) (t1
-> t2
-> t3
-> t4
-> t5
-> t6
-> t7
-> (t1, t2, t3, t4, t5, t6, t7))
-> ASN1Decode t1
-> ASN1Decode
(t2 -> t3 -> t4 -> t5 -> t6 -> t7 -> (t1, t2, t3, t4, t5, t6, t7))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ASN1Decode t1
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t2 -> t3 -> t4 -> t5 -> t6 -> t7 -> (t1, t2, t3, t4, t5, t6, t7))
-> ASN1Decode t2
-> ASN1Decode
(t3 -> t4 -> t5 -> t6 -> t7 -> (t1, t2, t3, t4, t5, t6, t7))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t2
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t3 -> t4 -> t5 -> t6 -> t7 -> (t1, t2, t3, t4, t5, t6, t7))
-> ASN1Decode t3
-> ASN1Decode
(t4 -> t5 -> t6 -> t7 -> (t1, t2, t3, t4, t5, t6, t7))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t3
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode (t4 -> t5 -> t6 -> t7 -> (t1, t2, t3, t4, t5, t6, t7))
-> ASN1Decode t4
-> ASN1Decode (t5 -> t6 -> t7 -> (t1, t2, t3, t4, t5, t6, t7))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t4
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode (t5 -> t6 -> t7 -> (t1, t2, t3, t4, t5, t6, t7))
-> ASN1Decode t5
-> ASN1Decode (t6 -> t7 -> (t1, t2, t3, t4, t5, t6, t7))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t5
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode (t6 -> t7 -> (t1, t2, t3, t4, t5, t6, t7))
-> ASN1Decode t6 -> ASN1Decode (t7 -> (t1, t2, t3, t4, t5, t6, t7))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t6
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode (t7 -> (t1, t2, t3, t4, t5, t6, t7))
-> ASN1Decode t7 -> ASN1Decode (t1, t2, t3, t4, t5, t6, t7)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t7
forall t. ASN1 t => ASN1Decode t
asn1decode
instance (ASN1 t1, ASN1 t2, ASN1 t3, ASN1 t4, ASN1 t5, ASN1 t6, ASN1 t7, ASN1 t8) => ASN1 (t1,t2,t3,t4,t5,t6,t7,t8)
instance (ASN1 t1, ASN1 t2, ASN1 t3, ASN1 t4, ASN1 t5, ASN1 t6, ASN1 t7, ASN1 t8) => ASN1Constructed (t1,t2,t3,t4,t5,t6,t7,t8) where
asn1encodeCompOf :: (t1, t2, t3, t4, t5, t6, t7, t8) -> ASN1Encode Word64
asn1encodeCompOf (v1 :: t1
v1,v2 :: t2
v2,v3 :: t3
v3,v4 :: t4
v4,v5 :: t5
v5,v6 :: t6
v6,v7 :: t7
v7,v8 :: t8
v8) = [ASN1Encode Word64] -> ASN1Encode Word64
enc'SEQUENCE_COMPS [t1 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t1
v1, t2 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t2
v2, t3 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t3
v3, t4 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t4
v4, t5 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t5
v5, t6 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t6
v6, t7 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t7
v7, t8 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t8
v8]
asn1decodeCompOf :: ASN1Decode (t1, t2, t3, t4, t5, t6, t7, t8)
asn1decodeCompOf = (,,,,,,,) (t1
-> t2
-> t3
-> t4
-> t5
-> t6
-> t7
-> t8
-> (t1, t2, t3, t4, t5, t6, t7, t8))
-> ASN1Decode t1
-> ASN1Decode
(t2
-> t3
-> t4
-> t5
-> t6
-> t7
-> t8
-> (t1, t2, t3, t4, t5, t6, t7, t8))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ASN1Decode t1
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t2
-> t3
-> t4
-> t5
-> t6
-> t7
-> t8
-> (t1, t2, t3, t4, t5, t6, t7, t8))
-> ASN1Decode t2
-> ASN1Decode
(t3
-> t4 -> t5 -> t6 -> t7 -> t8 -> (t1, t2, t3, t4, t5, t6, t7, t8))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t2
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t3
-> t4 -> t5 -> t6 -> t7 -> t8 -> (t1, t2, t3, t4, t5, t6, t7, t8))
-> ASN1Decode t3
-> ASN1Decode
(t4 -> t5 -> t6 -> t7 -> t8 -> (t1, t2, t3, t4, t5, t6, t7, t8))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t3
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t4 -> t5 -> t6 -> t7 -> t8 -> (t1, t2, t3, t4, t5, t6, t7, t8))
-> ASN1Decode t4
-> ASN1Decode
(t5 -> t6 -> t7 -> t8 -> (t1, t2, t3, t4, t5, t6, t7, t8))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t4
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t5 -> t6 -> t7 -> t8 -> (t1, t2, t3, t4, t5, t6, t7, t8))
-> ASN1Decode t5
-> ASN1Decode (t6 -> t7 -> t8 -> (t1, t2, t3, t4, t5, t6, t7, t8))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t5
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode (t6 -> t7 -> t8 -> (t1, t2, t3, t4, t5, t6, t7, t8))
-> ASN1Decode t6
-> ASN1Decode (t7 -> t8 -> (t1, t2, t3, t4, t5, t6, t7, t8))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t6
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode (t7 -> t8 -> (t1, t2, t3, t4, t5, t6, t7, t8))
-> ASN1Decode t7
-> ASN1Decode (t8 -> (t1, t2, t3, t4, t5, t6, t7, t8))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t7
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode (t8 -> (t1, t2, t3, t4, t5, t6, t7, t8))
-> ASN1Decode t8 -> ASN1Decode (t1, t2, t3, t4, t5, t6, t7, t8)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t8
forall t. ASN1 t => ASN1Decode t
asn1decode
instance (ASN1 t1, ASN1 t2, ASN1 t3, ASN1 t4, ASN1 t5, ASN1 t6, ASN1 t7, ASN1 t8, ASN1 t9) => ASN1 (t1,t2,t3,t4,t5,t6,t7,t8,t9)
instance (ASN1 t1, ASN1 t2, ASN1 t3, ASN1 t4, ASN1 t5, ASN1 t6, ASN1 t7, ASN1 t8, ASN1 t9) => ASN1Constructed (t1,t2,t3,t4,t5,t6,t7,t8,t9) where
asn1encodeCompOf :: (t1, t2, t3, t4, t5, t6, t7, t8, t9) -> ASN1Encode Word64
asn1encodeCompOf (v1 :: t1
v1,v2 :: t2
v2,v3 :: t3
v3,v4 :: t4
v4,v5 :: t5
v5,v6 :: t6
v6,v7 :: t7
v7,v8 :: t8
v8,v9 :: t9
v9) = [ASN1Encode Word64] -> ASN1Encode Word64
enc'SEQUENCE_COMPS [t1 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t1
v1, t2 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t2
v2, t3 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t3
v3, t4 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t4
v4, t5 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t5
v5, t6 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t6
v6, t7 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t7
v7, t8 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t8
v8, t9 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t9
v9]
asn1decodeCompOf :: ASN1Decode (t1, t2, t3, t4, t5, t6, t7, t8, t9)
asn1decodeCompOf = (,,,,,,,,) (t1
-> t2
-> t3
-> t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9))
-> ASN1Decode t1
-> ASN1Decode
(t2
-> t3
-> t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ASN1Decode t1
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t2
-> t3
-> t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9))
-> ASN1Decode t2
-> ASN1Decode
(t3
-> t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t2
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t3
-> t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9))
-> ASN1Decode t3
-> ASN1Decode
(t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t3
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9))
-> ASN1Decode t4
-> ASN1Decode
(t5
-> t6 -> t7 -> t8 -> t9 -> (t1, t2, t3, t4, t5, t6, t7, t8, t9))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t4
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t5
-> t6 -> t7 -> t8 -> t9 -> (t1, t2, t3, t4, t5, t6, t7, t8, t9))
-> ASN1Decode t5
-> ASN1Decode
(t6 -> t7 -> t8 -> t9 -> (t1, t2, t3, t4, t5, t6, t7, t8, t9))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t5
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t6 -> t7 -> t8 -> t9 -> (t1, t2, t3, t4, t5, t6, t7, t8, t9))
-> ASN1Decode t6
-> ASN1Decode
(t7 -> t8 -> t9 -> (t1, t2, t3, t4, t5, t6, t7, t8, t9))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t6
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode (t7 -> t8 -> t9 -> (t1, t2, t3, t4, t5, t6, t7, t8, t9))
-> ASN1Decode t7
-> ASN1Decode (t8 -> t9 -> (t1, t2, t3, t4, t5, t6, t7, t8, t9))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t7
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode (t8 -> t9 -> (t1, t2, t3, t4, t5, t6, t7, t8, t9))
-> ASN1Decode t8
-> ASN1Decode (t9 -> (t1, t2, t3, t4, t5, t6, t7, t8, t9))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t8
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode (t9 -> (t1, t2, t3, t4, t5, t6, t7, t8, t9))
-> ASN1Decode t9 -> ASN1Decode (t1, t2, t3, t4, t5, t6, t7, t8, t9)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t9
forall t. ASN1 t => ASN1Decode t
asn1decode
instance (ASN1 t1, ASN1 t2, ASN1 t3, ASN1 t4, ASN1 t5, ASN1 t6, ASN1 t7, ASN1 t8, ASN1 t9, ASN1 t10) => ASN1 (t1,t2,t3,t4,t5,t6,t7,t8,t9,t10)
instance (ASN1 t1, ASN1 t2, ASN1 t3, ASN1 t4, ASN1 t5, ASN1 t6, ASN1 t7, ASN1 t8, ASN1 t9, ASN1 t10) => ASN1Constructed (t1,t2,t3,t4,t5,t6,t7,t8,t9,t10) where
asn1encodeCompOf :: (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10) -> ASN1Encode Word64
asn1encodeCompOf (v1 :: t1
v1,v2 :: t2
v2,v3 :: t3
v3,v4 :: t4
v4,v5 :: t5
v5,v6 :: t6
v6,v7 :: t7
v7,v8 :: t8
v8,v9 :: t9
v9,v10 :: t10
v10) = [ASN1Encode Word64] -> ASN1Encode Word64
enc'SEQUENCE_COMPS [t1 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t1
v1, t2 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t2
v2, t3 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t3
v3, t4 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t4
v4, t5 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t5
v5, t6 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t6
v6, t7 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t7
v7, t8 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t8
v8, t9 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t9
v9, t10 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t10
v10]
asn1decodeCompOf :: ASN1Decode (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10)
asn1decodeCompOf = (,,,,,,,,,) (t1
-> t2
-> t3
-> t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10))
-> ASN1Decode t1
-> ASN1Decode
(t2
-> t3
-> t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ASN1Decode t1
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t2
-> t3
-> t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10))
-> ASN1Decode t2
-> ASN1Decode
(t3
-> t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t2
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t3
-> t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10))
-> ASN1Decode t3
-> ASN1Decode
(t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t3
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10))
-> ASN1Decode t4
-> ASN1Decode
(t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t4
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10))
-> ASN1Decode t5
-> ASN1Decode
(t6
-> t7
-> t8
-> t9
-> t10
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t5
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t6
-> t7
-> t8
-> t9
-> t10
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10))
-> ASN1Decode t6
-> ASN1Decode
(t7
-> t8 -> t9 -> t10 -> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t6
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t7
-> t8 -> t9 -> t10 -> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10))
-> ASN1Decode t7
-> ASN1Decode
(t8 -> t9 -> t10 -> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t7
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t8 -> t9 -> t10 -> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10))
-> ASN1Decode t8
-> ASN1Decode
(t9 -> t10 -> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t8
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode (t9 -> t10 -> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10))
-> ASN1Decode t9
-> ASN1Decode (t10 -> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t9
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode (t10 -> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10))
-> ASN1Decode t10
-> ASN1Decode (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t10
forall t. ASN1 t => ASN1Decode t
asn1decode
instance (ASN1 t1, ASN1 t2, ASN1 t3, ASN1 t4, ASN1 t5, ASN1 t6, ASN1 t7, ASN1 t8, ASN1 t9, ASN1 t10, ASN1 t11) => ASN1 (t1,t2,t3,t4,t5,t6,t7,t8,t9,t10,t11)
instance (ASN1 t1, ASN1 t2, ASN1 t3, ASN1 t4, ASN1 t5, ASN1 t6, ASN1 t7, ASN1 t8, ASN1 t9, ASN1 t10, ASN1 t11) => ASN1Constructed (t1,t2,t3,t4,t5,t6,t7,t8,t9,t10,t11) where
asn1encodeCompOf :: (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11) -> ASN1Encode Word64
asn1encodeCompOf (v1 :: t1
v1,v2 :: t2
v2,v3 :: t3
v3,v4 :: t4
v4,v5 :: t5
v5,v6 :: t6
v6,v7 :: t7
v7,v8 :: t8
v8,v9 :: t9
v9,v10 :: t10
v10,v11 :: t11
v11) = [ASN1Encode Word64] -> ASN1Encode Word64
enc'SEQUENCE_COMPS [t1 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t1
v1, t2 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t2
v2, t3 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t3
v3, t4 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t4
v4, t5 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t5
v5, t6 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t6
v6, t7 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t7
v7, t8 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t8
v8, t9 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t9
v9, t10 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t10
v10, t11 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t11
v11]
asn1decodeCompOf :: ASN1Decode (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11)
asn1decodeCompOf = (,,,,,,,,,,) (t1
-> t2
-> t3
-> t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11))
-> ASN1Decode t1
-> ASN1Decode
(t2
-> t3
-> t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ASN1Decode t1
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t2
-> t3
-> t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11))
-> ASN1Decode t2
-> ASN1Decode
(t3
-> t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t2
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t3
-> t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11))
-> ASN1Decode t3
-> ASN1Decode
(t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t3
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11))
-> ASN1Decode t4
-> ASN1Decode
(t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t4
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11))
-> ASN1Decode t5
-> ASN1Decode
(t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t5
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11))
-> ASN1Decode t6
-> ASN1Decode
(t7
-> t8
-> t9
-> t10
-> t11
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t6
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t7
-> t8
-> t9
-> t10
-> t11
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11))
-> ASN1Decode t7
-> ASN1Decode
(t8
-> t9
-> t10
-> t11
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t7
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t8
-> t9
-> t10
-> t11
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11))
-> ASN1Decode t8
-> ASN1Decode
(t9
-> t10 -> t11 -> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t8
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t9
-> t10 -> t11 -> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11))
-> ASN1Decode t9
-> ASN1Decode
(t10 -> t11 -> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t9
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t10 -> t11 -> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11))
-> ASN1Decode t10
-> ASN1Decode
(t11 -> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t10
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode (t11 -> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11))
-> ASN1Decode t11
-> ASN1Decode (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t11
forall t. ASN1 t => ASN1Decode t
asn1decode
instance (ASN1 t1, ASN1 t2, ASN1 t3, ASN1 t4, ASN1 t5, ASN1 t6, ASN1 t7, ASN1 t8, ASN1 t9, ASN1 t10, ASN1 t11, ASN1 t12) => ASN1 (t1,t2,t3,t4,t5,t6,t7,t8,t9,t10,t11,t12)
instance (ASN1 t1, ASN1 t2, ASN1 t3, ASN1 t4, ASN1 t5, ASN1 t6, ASN1 t7, ASN1 t8, ASN1 t9, ASN1 t10, ASN1 t11, ASN1 t12) => ASN1Constructed (t1,t2,t3,t4,t5,t6,t7,t8,t9,t10,t11,t12) where
asn1encodeCompOf :: (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12)
-> ASN1Encode Word64
asn1encodeCompOf (v1 :: t1
v1,v2 :: t2
v2,v3 :: t3
v3,v4 :: t4
v4,v5 :: t5
v5,v6 :: t6
v6,v7 :: t7
v7,v8 :: t8
v8,v9 :: t9
v9,v10 :: t10
v10,v11 :: t11
v11,v12 :: t12
v12) = [ASN1Encode Word64] -> ASN1Encode Word64
enc'SEQUENCE_COMPS [t1 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t1
v1, t2 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t2
v2, t3 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t3
v3, t4 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t4
v4, t5 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t5
v5, t6 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t6
v6, t7 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t7
v7, t8 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t8
v8, t9 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t9
v9, t10 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t10
v10, t11 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t11
v11, t12 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t12
v12]
asn1decodeCompOf :: ASN1Decode (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12)
asn1decodeCompOf = (,,,,,,,,,,,) (t1
-> t2
-> t3
-> t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12))
-> ASN1Decode t1
-> ASN1Decode
(t2
-> t3
-> t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ASN1Decode t1
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t2
-> t3
-> t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12))
-> ASN1Decode t2
-> ASN1Decode
(t3
-> t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t2
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t3
-> t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12))
-> ASN1Decode t3
-> ASN1Decode
(t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t3
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12))
-> ASN1Decode t4
-> ASN1Decode
(t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t4
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12))
-> ASN1Decode t5
-> ASN1Decode
(t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t5
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12))
-> ASN1Decode t6
-> ASN1Decode
(t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t6
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12))
-> ASN1Decode t7
-> ASN1Decode
(t8
-> t9
-> t10
-> t11
-> t12
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t7
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t8
-> t9
-> t10
-> t11
-> t12
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12))
-> ASN1Decode t8
-> ASN1Decode
(t9
-> t10
-> t11
-> t12
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t8
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t9
-> t10
-> t11
-> t12
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12))
-> ASN1Decode t9
-> ASN1Decode
(t10
-> t11
-> t12
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t9
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t10
-> t11
-> t12
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12))
-> ASN1Decode t10
-> ASN1Decode
(t11 -> t12 -> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t10
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t11 -> t12 -> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12))
-> ASN1Decode t11
-> ASN1Decode
(t12 -> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t11
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t12 -> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12))
-> ASN1Decode t12
-> ASN1Decode (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t12
forall t. ASN1 t => ASN1Decode t
asn1decode
instance (ASN1 t1, ASN1 t2, ASN1 t3, ASN1 t4, ASN1 t5, ASN1 t6, ASN1 t7, ASN1 t8, ASN1 t9, ASN1 t10, ASN1 t11, ASN1 t12, ASN1 t13) => ASN1 (t1,t2,t3,t4,t5,t6,t7,t8,t9,t10,t11,t12,t13)
instance (ASN1 t1, ASN1 t2, ASN1 t3, ASN1 t4, ASN1 t5, ASN1 t6, ASN1 t7, ASN1 t8, ASN1 t9, ASN1 t10, ASN1 t11, ASN1 t12, ASN1 t13) => ASN1Constructed (t1,t2,t3,t4,t5,t6,t7,t8,t9,t10,t11,t12,t13) where
asn1encodeCompOf :: (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13)
-> ASN1Encode Word64
asn1encodeCompOf (v1 :: t1
v1,v2 :: t2
v2,v3 :: t3
v3,v4 :: t4
v4,v5 :: t5
v5,v6 :: t6
v6,v7 :: t7
v7,v8 :: t8
v8,v9 :: t9
v9,v10 :: t10
v10,v11 :: t11
v11,v12 :: t12
v12,v13 :: t13
v13) = [ASN1Encode Word64] -> ASN1Encode Word64
enc'SEQUENCE_COMPS [t1 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t1
v1, t2 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t2
v2, t3 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t3
v3, t4 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t4
v4, t5 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t5
v5, t6 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t6
v6, t7 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t7
v7, t8 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t8
v8, t9 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t9
v9, t10 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t10
v10, t11 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t11
v11, t12 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t12
v12, t13 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t13
v13]
asn1decodeCompOf :: ASN1Decode (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13)
asn1decodeCompOf = (,,,,,,,,,,,,) (t1
-> t2
-> t3
-> t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> t13
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13))
-> ASN1Decode t1
-> ASN1Decode
(t2
-> t3
-> t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> t13
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ASN1Decode t1
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t2
-> t3
-> t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> t13
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13))
-> ASN1Decode t2
-> ASN1Decode
(t3
-> t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> t13
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t2
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t3
-> t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> t13
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13))
-> ASN1Decode t3
-> ASN1Decode
(t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> t13
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t3
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> t13
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13))
-> ASN1Decode t4
-> ASN1Decode
(t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> t13
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t4
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> t13
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13))
-> ASN1Decode t5
-> ASN1Decode
(t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> t13
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t5
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> t13
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13))
-> ASN1Decode t6
-> ASN1Decode
(t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> t13
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t6
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> t13
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13))
-> ASN1Decode t7
-> ASN1Decode
(t8
-> t9
-> t10
-> t11
-> t12
-> t13
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t7
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t8
-> t9
-> t10
-> t11
-> t12
-> t13
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13))
-> ASN1Decode t8
-> ASN1Decode
(t9
-> t10
-> t11
-> t12
-> t13
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t8
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t9
-> t10
-> t11
-> t12
-> t13
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13))
-> ASN1Decode t9
-> ASN1Decode
(t10
-> t11
-> t12
-> t13
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t9
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t10
-> t11
-> t12
-> t13
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13))
-> ASN1Decode t10
-> ASN1Decode
(t11
-> t12
-> t13
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t10
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t11
-> t12
-> t13
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13))
-> ASN1Decode t11
-> ASN1Decode
(t12
-> t13 -> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t11
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t12
-> t13 -> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13))
-> ASN1Decode t12
-> ASN1Decode
(t13 -> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t12
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t13 -> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13))
-> ASN1Decode t13
-> ASN1Decode
(t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t13
forall t. ASN1 t => ASN1Decode t
asn1decode
instance (ASN1 t1, ASN1 t2, ASN1 t3, ASN1 t4, ASN1 t5, ASN1 t6, ASN1 t7, ASN1 t8, ASN1 t9, ASN1 t10, ASN1 t11, ASN1 t12, ASN1 t13, ASN1 t14) => ASN1 (t1,t2,t3,t4,t5,t6,t7,t8,t9,t10,t11,t12,t13,t14)
instance (ASN1 t1, ASN1 t2, ASN1 t3, ASN1 t4, ASN1 t5, ASN1 t6, ASN1 t7, ASN1 t8, ASN1 t9, ASN1 t10, ASN1 t11, ASN1 t12, ASN1 t13, ASN1 t14) => ASN1Constructed (t1,t2,t3,t4,t5,t6,t7,t8,t9,t10,t11,t12,t13,t14) where
asn1encodeCompOf :: (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14)
-> ASN1Encode Word64
asn1encodeCompOf (v1 :: t1
v1,v2 :: t2
v2,v3 :: t3
v3,v4 :: t4
v4,v5 :: t5
v5,v6 :: t6
v6,v7 :: t7
v7,v8 :: t8
v8,v9 :: t9
v9,v10 :: t10
v10,v11 :: t11
v11,v12 :: t12
v12,v13 :: t13
v13,v14 :: t14
v14) = [ASN1Encode Word64] -> ASN1Encode Word64
enc'SEQUENCE_COMPS [t1 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t1
v1, t2 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t2
v2, t3 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t3
v3, t4 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t4
v4, t5 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t5
v5, t6 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t6
v6, t7 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t7
v7, t8 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t8
v8, t9 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t9
v9, t10 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t10
v10, t11 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t11
v11, t12 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t12
v12, t13 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t13
v13, t14 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t14
v14]
asn1decodeCompOf :: ASN1Decode
(t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14)
asn1decodeCompOf = (,,,,,,,,,,,,,) (t1
-> t2
-> t3
-> t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> t13
-> t14
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14))
-> ASN1Decode t1
-> ASN1Decode
(t2
-> t3
-> t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> t13
-> t14
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ASN1Decode t1
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t2
-> t3
-> t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> t13
-> t14
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14))
-> ASN1Decode t2
-> ASN1Decode
(t3
-> t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> t13
-> t14
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t2
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t3
-> t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> t13
-> t14
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14))
-> ASN1Decode t3
-> ASN1Decode
(t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> t13
-> t14
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t3
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> t13
-> t14
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14))
-> ASN1Decode t4
-> ASN1Decode
(t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> t13
-> t14
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t4
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> t13
-> t14
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14))
-> ASN1Decode t5
-> ASN1Decode
(t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> t13
-> t14
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t5
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> t13
-> t14
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14))
-> ASN1Decode t6
-> ASN1Decode
(t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> t13
-> t14
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t6
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> t13
-> t14
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14))
-> ASN1Decode t7
-> ASN1Decode
(t8
-> t9
-> t10
-> t11
-> t12
-> t13
-> t14
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t7
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t8
-> t9
-> t10
-> t11
-> t12
-> t13
-> t14
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14))
-> ASN1Decode t8
-> ASN1Decode
(t9
-> t10
-> t11
-> t12
-> t13
-> t14
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t8
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t9
-> t10
-> t11
-> t12
-> t13
-> t14
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14))
-> ASN1Decode t9
-> ASN1Decode
(t10
-> t11
-> t12
-> t13
-> t14
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t9
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t10
-> t11
-> t12
-> t13
-> t14
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14))
-> ASN1Decode t10
-> ASN1Decode
(t11
-> t12
-> t13
-> t14
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t10
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t11
-> t12
-> t13
-> t14
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14))
-> ASN1Decode t11
-> ASN1Decode
(t12
-> t13
-> t14
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t11
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t12
-> t13
-> t14
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14))
-> ASN1Decode t12
-> ASN1Decode
(t13
-> t14
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t12
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t13
-> t14
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14))
-> ASN1Decode t13
-> ASN1Decode
(t14
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t13
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t14
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14))
-> ASN1Decode t14
-> ASN1Decode
(t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t14
forall t. ASN1 t => ASN1Decode t
asn1decode
instance (ASN1 t1, ASN1 t2, ASN1 t3, ASN1 t4, ASN1 t5, ASN1 t6, ASN1 t7, ASN1 t8, ASN1 t9, ASN1 t10, ASN1 t11, ASN1 t12, ASN1 t13, ASN1 t14, ASN1 t15) => ASN1 (t1,t2,t3,t4,t5,t6,t7,t8,t9,t10,t11,t12,t13,t14,t15)
instance (ASN1 t1, ASN1 t2, ASN1 t3, ASN1 t4, ASN1 t5, ASN1 t6, ASN1 t7, ASN1 t8, ASN1 t9, ASN1 t10, ASN1 t11, ASN1 t12, ASN1 t13, ASN1 t14, ASN1 t15) => ASN1Constructed (t1,t2,t3,t4,t5,t6,t7,t8,t9,t10,t11,t12,t13,t14,t15) where
asn1encodeCompOf :: (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15)
-> ASN1Encode Word64
asn1encodeCompOf (v1 :: t1
v1,v2 :: t2
v2,v3 :: t3
v3,v4 :: t4
v4,v5 :: t5
v5,v6 :: t6
v6,v7 :: t7
v7,v8 :: t8
v8,v9 :: t9
v9,v10 :: t10
v10,v11 :: t11
v11,v12 :: t12
v12,v13 :: t13
v13,v14 :: t14
v14,v15 :: t15
v15) = [ASN1Encode Word64] -> ASN1Encode Word64
enc'SEQUENCE_COMPS [t1 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t1
v1, t2 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t2
v2, t3 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t3
v3, t4 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t4
v4, t5 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t5
v5, t6 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t6
v6, t7 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t7
v7, t8 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t8
v8, t9 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t9
v9, t10 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t10
v10, t11 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t11
v11, t12 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t12
v12, t13 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t13
v13, t14 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t14
v14, t15 -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t15
v15]
asn1decodeCompOf :: ASN1Decode
(t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15)
asn1decodeCompOf = (,,,,,,,,,,,,,,) (t1
-> t2
-> t3
-> t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> t13
-> t14
-> t15
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14,
t15))
-> ASN1Decode t1
-> ASN1Decode
(t2
-> t3
-> t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> t13
-> t14
-> t15
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14,
t15))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ASN1Decode t1
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t2
-> t3
-> t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> t13
-> t14
-> t15
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14,
t15))
-> ASN1Decode t2
-> ASN1Decode
(t3
-> t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> t13
-> t14
-> t15
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14,
t15))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t2
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t3
-> t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> t13
-> t14
-> t15
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14,
t15))
-> ASN1Decode t3
-> ASN1Decode
(t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> t13
-> t14
-> t15
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14,
t15))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t3
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t4
-> t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> t13
-> t14
-> t15
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14,
t15))
-> ASN1Decode t4
-> ASN1Decode
(t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> t13
-> t14
-> t15
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14,
t15))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t4
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t5
-> t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> t13
-> t14
-> t15
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14,
t15))
-> ASN1Decode t5
-> ASN1Decode
(t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> t13
-> t14
-> t15
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14,
t15))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t5
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t6
-> t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> t13
-> t14
-> t15
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14,
t15))
-> ASN1Decode t6
-> ASN1Decode
(t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> t13
-> t14
-> t15
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14,
t15))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t6
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t7
-> t8
-> t9
-> t10
-> t11
-> t12
-> t13
-> t14
-> t15
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14,
t15))
-> ASN1Decode t7
-> ASN1Decode
(t8
-> t9
-> t10
-> t11
-> t12
-> t13
-> t14
-> t15
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14,
t15))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t7
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t8
-> t9
-> t10
-> t11
-> t12
-> t13
-> t14
-> t15
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14,
t15))
-> ASN1Decode t8
-> ASN1Decode
(t9
-> t10
-> t11
-> t12
-> t13
-> t14
-> t15
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14,
t15))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t8
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t9
-> t10
-> t11
-> t12
-> t13
-> t14
-> t15
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14,
t15))
-> ASN1Decode t9
-> ASN1Decode
(t10
-> t11
-> t12
-> t13
-> t14
-> t15
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14,
t15))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t9
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t10
-> t11
-> t12
-> t13
-> t14
-> t15
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14,
t15))
-> ASN1Decode t10
-> ASN1Decode
(t11
-> t12
-> t13
-> t14
-> t15
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14,
t15))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t10
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t11
-> t12
-> t13
-> t14
-> t15
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14,
t15))
-> ASN1Decode t11
-> ASN1Decode
(t12
-> t13
-> t14
-> t15
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14,
t15))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t11
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t12
-> t13
-> t14
-> t15
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14,
t15))
-> ASN1Decode t12
-> ASN1Decode
(t13
-> t14
-> t15
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14,
t15))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t12
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t13
-> t14
-> t15
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14,
t15))
-> ASN1Decode t13
-> ASN1Decode
(t14
-> t15
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14,
t15))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t13
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t14
-> t15
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14,
t15))
-> ASN1Decode t14
-> ASN1Decode
(t15
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14,
t15))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t14
forall t. ASN1 t => ASN1Decode t
asn1decode ASN1Decode
(t15
-> (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14,
t15))
-> ASN1Decode t15
-> ASN1Decode
(t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode t15
forall t. ASN1 t => ASN1Decode t
asn1decode
type OCTET_STRING = ByteString
instance ASN1 ByteString where
asn1defTag :: Proxy ByteString -> Tag
asn1defTag _ = Word64 -> Tag
Universal 4
asn1decode :: ASN1Decode ByteString
asn1decode = ASN1Decode ByteString
dec'OCTETSTRING
asn1encode :: ByteString -> ASN1Encode Word64
asn1encode = ByteString -> ASN1Encode Word64
enc'OCTETSTRING
instance ASN1 SBS.ShortByteString where
asn1defTag :: Proxy ShortByteString -> Tag
asn1defTag _ = Word64 -> Tag
Universal 4
asn1decode :: ASN1Decode ShortByteString
asn1decode = ByteString -> ShortByteString
SBS.toShort (ByteString -> ShortByteString)
-> ASN1Decode ByteString -> ASN1Decode ShortByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ASN1Decode ByteString
dec'OCTETSTRING
asn1encode :: ShortByteString -> ASN1Encode Word64
asn1encode = ByteString -> ASN1Encode Word64
enc'OCTETSTRING (ByteString -> ASN1Encode Word64)
-> (ShortByteString -> ByteString)
-> ShortByteString
-> ASN1Encode Word64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> ByteString
SBS.fromShort
instance ASN1 ShortText where
asn1defTag :: Proxy ShortText -> Tag
asn1defTag _ = Word64 -> Tag
Universal 4
asn1decode :: ASN1Decode ShortText
asn1decode = ASN1Decode ByteString
dec'OCTETSTRING ASN1Decode ByteString
-> (ByteString -> Either [Char] ShortText) -> ASN1Decode ShortText
forall x y. ASN1Decode x -> (x -> Either [Char] y) -> ASN1Decode y
`transformVia`
(Either [Char] ShortText
-> (ShortText -> Either [Char] ShortText)
-> Maybe ShortText
-> Either [Char] ShortText
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ([Char] -> Either [Char] ShortText
forall a b. a -> Either a b
Left "OCTECT STRING contained invalid UTF-8") ShortText -> Either [Char] ShortText
forall a b. b -> Either a b
Right (Maybe ShortText -> Either [Char] ShortText)
-> (ByteString -> Maybe ShortText)
-> ByteString
-> Either [Char] ShortText
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Maybe ShortText
TS.fromByteString)
asn1encode :: ShortText -> ASN1Encode Word64
asn1encode = ShortByteString -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode (ShortByteString -> ASN1Encode Word64)
-> (ShortText -> ShortByteString) -> ShortText -> ASN1Encode Word64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> ShortByteString
TS.toShortByteString
type BOOLEAN = Bool
instance ASN1 Bool where
asn1defTag :: Proxy Bool -> Tag
asn1defTag _ = Word64 -> Tag
Universal 1
asn1decode :: ASN1Decode Bool
asn1decode = ASN1Decode Bool
dec'BOOLEAN
asn1encode :: Bool -> ASN1Encode Word64
asn1encode = Bool -> ASN1Encode Word64
enc'BOOLEAN
type OPTIONAL x = Maybe x
instance ASN1 t => ASN1 (Maybe t) where
asn1defTag :: Proxy (Maybe t) -> Tag
asn1defTag _ = Proxy t -> Tag
forall t. ASN1 t => Proxy t -> Tag
asn1defTag (Proxy t
forall k (t :: k). Proxy t
Proxy :: Proxy t)
asn1decode :: ASN1Decode (Maybe t)
asn1decode = ASN1Decode t -> ASN1Decode (Maybe t)
forall x. ASN1Decode x -> ASN1Decode (Maybe x)
dec'OPTIONAL ASN1Decode t
forall t. ASN1 t => ASN1Decode t
asn1decode
asn1encode :: Maybe t -> ASN1Encode Word64
asn1encode Nothing = ASN1Encode Word64
empty'ASN1Encode
asn1encode (Just v :: t
v) = t -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode t
v
instance ASN1 t => ASN1 [t] where
asn1decode :: ASN1Decode [t]
asn1decode = ASN1Decode t -> ASN1Decode [t]
forall a. ASN1Decode a -> ASN1Decode [a]
dec'SEQUENCE_OF ASN1Decode t
forall t. ASN1 t => ASN1Decode t
asn1decode
asn1encode :: [t] -> ASN1Encode Word64
asn1encode = [ASN1Encode Word64] -> ASN1Encode Word64
enc'SEQUENCE ([ASN1Encode Word64] -> ASN1Encode Word64)
-> ([t] -> [ASN1Encode Word64]) -> [t] -> ASN1Encode Word64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (t -> ASN1Encode Word64) -> [t] -> [ASN1Encode Word64]
forall a b. (a -> b) -> [a] -> [b]
map t -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode
instance ASN1 t => ASN1 (NonEmpty t) where
asn1decode :: ASN1Decode (NonEmpty t)
asn1decode = ASN1Decode [t]
-> ([t] -> Either [Char] (NonEmpty t)) -> ASN1Decode (NonEmpty t)
forall x y. ASN1Decode x -> (x -> Either [Char] y) -> ASN1Decode y
transformVia ASN1Decode [t]
forall t. ASN1 t => ASN1Decode t
asn1decode (([t] -> Either [Char] (NonEmpty t)) -> ASN1Decode (NonEmpty t))
-> ([t] -> Either [Char] (NonEmpty t)) -> ASN1Decode (NonEmpty t)
forall a b. (a -> b) -> a -> b
$ \case
[] -> [Char] -> Either [Char] (NonEmpty t)
forall a b. a -> Either a b
Left "SEQUENCE (1..n) must be non-empty"
x :: t
x:xs :: [t]
xs -> NonEmpty t -> Either [Char] (NonEmpty t)
forall a b. b -> Either a b
Right (t
x t -> [t] -> NonEmpty t
forall a. a -> [a] -> NonEmpty a
:| [t]
xs)
asn1encode :: NonEmpty t -> ASN1Encode Word64
asn1encode (x :: t
x :| xs :: [t]
xs) = [t] -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode (t
xt -> [t] -> [t]
forall a. a -> [a] -> [a]
:[t]
xs)
newtype SET1 x = SET1 (NonEmpty x)
deriving ((forall x. SET1 x -> Rep (SET1 x) x)
-> (forall x. Rep (SET1 x) x -> SET1 x) -> Generic (SET1 x)
forall x. Rep (SET1 x) x -> SET1 x
forall x. SET1 x -> Rep (SET1 x) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall x x. Rep (SET1 x) x -> SET1 x
forall x x. SET1 x -> Rep (SET1 x) x
$cto :: forall x x. Rep (SET1 x) x -> SET1 x
$cfrom :: forall x x. SET1 x -> Rep (SET1 x) x
Generic,SET1 x -> ()
(SET1 x -> ()) -> NFData (SET1 x)
forall x. NFData x => SET1 x -> ()
forall a. (a -> ()) -> NFData a
rnf :: SET1 x -> ()
$crnf :: forall x. NFData x => SET1 x -> ()
NFData,Int -> SET1 x -> ShowS
[SET1 x] -> ShowS
SET1 x -> [Char]
(Int -> SET1 x -> ShowS)
-> (SET1 x -> [Char]) -> ([SET1 x] -> ShowS) -> Show (SET1 x)
forall x. Show x => Int -> SET1 x -> ShowS
forall x. Show x => [SET1 x] -> ShowS
forall x. Show x => SET1 x -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [SET1 x] -> ShowS
$cshowList :: forall x. Show x => [SET1 x] -> ShowS
show :: SET1 x -> [Char]
$cshow :: forall x. Show x => SET1 x -> [Char]
showsPrec :: Int -> SET1 x -> ShowS
$cshowsPrec :: forall x. Show x => Int -> SET1 x -> ShowS
Show,SET1 x -> SET1 x -> Bool
(SET1 x -> SET1 x -> Bool)
-> (SET1 x -> SET1 x -> Bool) -> Eq (SET1 x)
forall x. Eq x => SET1 x -> SET1 x -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SET1 x -> SET1 x -> Bool
$c/= :: forall x. Eq x => SET1 x -> SET1 x -> Bool
== :: SET1 x -> SET1 x -> Bool
$c== :: forall x. Eq x => SET1 x -> SET1 x -> Bool
Eq,Eq (SET1 x)
Eq (SET1 x) =>
(SET1 x -> SET1 x -> Ordering)
-> (SET1 x -> SET1 x -> Bool)
-> (SET1 x -> SET1 x -> Bool)
-> (SET1 x -> SET1 x -> Bool)
-> (SET1 x -> SET1 x -> Bool)
-> (SET1 x -> SET1 x -> SET1 x)
-> (SET1 x -> SET1 x -> SET1 x)
-> Ord (SET1 x)
SET1 x -> SET1 x -> Bool
SET1 x -> SET1 x -> Ordering
SET1 x -> SET1 x -> SET1 x
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 x. Ord x => Eq (SET1 x)
forall x. Ord x => SET1 x -> SET1 x -> Bool
forall x. Ord x => SET1 x -> SET1 x -> Ordering
forall x. Ord x => SET1 x -> SET1 x -> SET1 x
min :: SET1 x -> SET1 x -> SET1 x
$cmin :: forall x. Ord x => SET1 x -> SET1 x -> SET1 x
max :: SET1 x -> SET1 x -> SET1 x
$cmax :: forall x. Ord x => SET1 x -> SET1 x -> SET1 x
>= :: SET1 x -> SET1 x -> Bool
$c>= :: forall x. Ord x => SET1 x -> SET1 x -> Bool
> :: SET1 x -> SET1 x -> Bool
$c> :: forall x. Ord x => SET1 x -> SET1 x -> Bool
<= :: SET1 x -> SET1 x -> Bool
$c<= :: forall x. Ord x => SET1 x -> SET1 x -> Bool
< :: SET1 x -> SET1 x -> Bool
$c< :: forall x. Ord x => SET1 x -> SET1 x -> Bool
compare :: SET1 x -> SET1 x -> Ordering
$ccompare :: forall x. Ord x => SET1 x -> SET1 x -> Ordering
$cp1Ord :: forall x. Ord x => Eq (SET1 x)
Ord)
instance Newtype (SET1 x) (NonEmpty x)
instance ASN1 t => ASN1 (SET1 t) where
asn1defTag :: Proxy (SET1 t) -> Tag
asn1defTag _ = Word64 -> Tag
Universal 17
asn1decode :: ASN1Decode (SET1 t)
asn1decode = ASN1Decode (SET t)
-> (SET t -> Either [Char] (SET1 t)) -> ASN1Decode (SET1 t)
forall x y. ASN1Decode x -> (x -> Either [Char] y) -> ASN1Decode y
transformVia ASN1Decode (SET t)
forall t. ASN1 t => ASN1Decode t
asn1decode ((SET t -> Either [Char] (SET1 t)) -> ASN1Decode (SET1 t))
-> (SET t -> Either [Char] (SET1 t)) -> ASN1Decode (SET1 t)
forall a b. (a -> b) -> a -> b
$ \case
SET [] -> [Char] -> Either [Char] (SET1 t)
forall a b. a -> Either a b
Left "SET (1..n) must be non-empty"
SET (x :: t
x:xs :: [t]
xs) -> SET1 t -> Either [Char] (SET1 t)
forall a b. b -> Either a b
Right (NonEmpty t -> SET1 t
forall x. NonEmpty x -> SET1 x
SET1 (t
x t -> [t] -> NonEmpty t
forall a. a -> [a] -> NonEmpty a
:| [t]
xs))
asn1encode :: SET1 t -> ASN1Encode Word64
asn1encode (SET1 (x :: t
x :| xs :: [t]
xs)) = SET t -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode ([t] -> SET t
forall x. [x] -> SET x
SET (t
xt -> [t] -> [t]
forall a. a -> [a] -> [a]
:[t]
xs))
newtype SET x = SET [x]
deriving ((forall x. SET x -> Rep (SET x) x)
-> (forall x. Rep (SET x) x -> SET x) -> Generic (SET x)
forall x. Rep (SET x) x -> SET x
forall x. SET x -> Rep (SET x) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall x x. Rep (SET x) x -> SET x
forall x x. SET x -> Rep (SET x) x
$cto :: forall x x. Rep (SET x) x -> SET x
$cfrom :: forall x x. SET x -> Rep (SET x) x
Generic,SET x -> ()
(SET x -> ()) -> NFData (SET x)
forall x. NFData x => SET x -> ()
forall a. (a -> ()) -> NFData a
rnf :: SET x -> ()
$crnf :: forall x. NFData x => SET x -> ()
NFData,Int -> SET x -> ShowS
[SET x] -> ShowS
SET x -> [Char]
(Int -> SET x -> ShowS)
-> (SET x -> [Char]) -> ([SET x] -> ShowS) -> Show (SET x)
forall x. Show x => Int -> SET x -> ShowS
forall x. Show x => [SET x] -> ShowS
forall x. Show x => SET x -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [SET x] -> ShowS
$cshowList :: forall x. Show x => [SET x] -> ShowS
show :: SET x -> [Char]
$cshow :: forall x. Show x => SET x -> [Char]
showsPrec :: Int -> SET x -> ShowS
$cshowsPrec :: forall x. Show x => Int -> SET x -> ShowS
Show,SET x -> SET x -> Bool
(SET x -> SET x -> Bool) -> (SET x -> SET x -> Bool) -> Eq (SET x)
forall x. Eq x => SET x -> SET x -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SET x -> SET x -> Bool
$c/= :: forall x. Eq x => SET x -> SET x -> Bool
== :: SET x -> SET x -> Bool
$c== :: forall x. Eq x => SET x -> SET x -> Bool
Eq,Eq (SET x)
Eq (SET x) =>
(SET x -> SET x -> Ordering)
-> (SET x -> SET x -> Bool)
-> (SET x -> SET x -> Bool)
-> (SET x -> SET x -> Bool)
-> (SET x -> SET x -> Bool)
-> (SET x -> SET x -> SET x)
-> (SET x -> SET x -> SET x)
-> Ord (SET x)
SET x -> SET x -> Bool
SET x -> SET x -> Ordering
SET x -> SET x -> SET x
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 x. Ord x => Eq (SET x)
forall x. Ord x => SET x -> SET x -> Bool
forall x. Ord x => SET x -> SET x -> Ordering
forall x. Ord x => SET x -> SET x -> SET x
min :: SET x -> SET x -> SET x
$cmin :: forall x. Ord x => SET x -> SET x -> SET x
max :: SET x -> SET x -> SET x
$cmax :: forall x. Ord x => SET x -> SET x -> SET x
>= :: SET x -> SET x -> Bool
$c>= :: forall x. Ord x => SET x -> SET x -> Bool
> :: SET x -> SET x -> Bool
$c> :: forall x. Ord x => SET x -> SET x -> Bool
<= :: SET x -> SET x -> Bool
$c<= :: forall x. Ord x => SET x -> SET x -> Bool
< :: SET x -> SET x -> Bool
$c< :: forall x. Ord x => SET x -> SET x -> Bool
compare :: SET x -> SET x -> Ordering
$ccompare :: forall x. Ord x => SET x -> SET x -> Ordering
$cp1Ord :: forall x. Ord x => Eq (SET x)
Ord)
instance Newtype (SET x) [x]
instance ASN1 t => ASN1 (SET t) where
asn1defTag :: Proxy (SET t) -> Tag
asn1defTag _ = Word64 -> Tag
Universal 17
asn1decode :: ASN1Decode (SET t)
asn1decode = [t] -> SET t
forall x. [x] -> SET x
SET ([t] -> SET t) -> ASN1Decode [t] -> ASN1Decode (SET t)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ASN1Decode t -> ASN1Decode [t]
forall a. ASN1Decode a -> ASN1Decode [a]
dec'SET_OF ASN1Decode t
forall t. ASN1 t => ASN1Decode t
asn1decode
asn1encode :: SET t -> ASN1Encode Word64
asn1encode (SET vs :: [t]
vs) = [ASN1Encode Word64] -> ASN1Encode Word64
enc'SET ((t -> ASN1Encode Word64) -> [t] -> [ASN1Encode Word64]
forall a b. (a -> b) -> [a] -> [b]
map t -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode [t]
vs)
instance ASN1 Integer where
asn1defTag :: Proxy Integer -> Tag
asn1defTag _ = Word64 -> Tag
Universal 2
asn1decode :: ASN1Decode Integer
asn1decode = ASN1Decode Integer
dec'INTEGER
asn1encode :: Integer -> ASN1Encode Word64
asn1encode = Integer -> ASN1Encode Word64
enc'INTEGER
instance ASN1 Int64 where
asn1defTag :: Proxy Int64 -> Tag
asn1defTag _ = Word64 -> Tag
Universal 2
asn1decode :: ASN1Decode Int64
asn1decode = ASN1Decode Int64
dec'Int64
asn1encode :: Int64 -> ASN1Encode Word64
asn1encode = Int64 -> ASN1Encode Word64
enc'Int64
instance (UIntBounds lb ub t, Integral t) => ASN1 (UInt lb ub t) where
asn1defTag :: Proxy (UInt lb ub t) -> Tag
asn1defTag _ = Word64 -> Tag
Universal 2
asn1decode :: ASN1Decode (UInt lb ub t)
asn1decode = ASN1Decode (UInt lb ub t)
forall (lb :: Nat) (ub :: Nat) t.
(UIntBounds lb ub t, Num t) =>
ASN1Decode (UInt lb ub t)
dec'UInt
asn1encode :: UInt lb ub t -> ASN1Encode Word64
asn1encode = UInt lb ub t -> ASN1Encode Word64
forall (lb :: Nat) (ub :: Nat) t.
(UIntBounds lb ub t, Num t, Integral t) =>
UInt lb ub t -> ASN1Encode Word64
enc'UInt
type NULL = ()
instance ASN1 () where
asn1defTag :: Proxy () -> Tag
asn1defTag _ = Word64 -> Tag
Universal 5
asn1decode :: ASN1Decode ()
asn1decode = ASN1Decode ()
dec'NULL
asn1encode :: () -> ASN1Encode Word64
asn1encode () = ASN1Encode Word64
enc'NULL
newtype BOOLEAN_DEFAULT (def :: Bool) = BOOLEAN Bool
deriving (BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def -> Bool
(BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def -> Bool)
-> (BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def -> Bool)
-> Eq (BOOLEAN_DEFAULT def)
forall (def :: Bool).
BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def -> Bool
$c/= :: forall (def :: Bool).
BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def -> Bool
== :: BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def -> Bool
$c== :: forall (def :: Bool).
BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def -> Bool
Eq,Eq (BOOLEAN_DEFAULT def)
Eq (BOOLEAN_DEFAULT def) =>
(BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def -> Ordering)
-> (BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def -> Bool)
-> (BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def -> Bool)
-> (BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def -> Bool)
-> (BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def -> Bool)
-> (BOOLEAN_DEFAULT def
-> BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def)
-> (BOOLEAN_DEFAULT def
-> BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def)
-> Ord (BOOLEAN_DEFAULT def)
BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def -> Bool
BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def -> Ordering
BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def
forall (def :: Bool). Eq (BOOLEAN_DEFAULT def)
forall (def :: Bool).
BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def -> Bool
forall (def :: Bool).
BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def -> Ordering
forall (def :: Bool).
BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def
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 :: BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def
$cmin :: forall (def :: Bool).
BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def
max :: BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def
$cmax :: forall (def :: Bool).
BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def
>= :: BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def -> Bool
$c>= :: forall (def :: Bool).
BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def -> Bool
> :: BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def -> Bool
$c> :: forall (def :: Bool).
BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def -> Bool
<= :: BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def -> Bool
$c<= :: forall (def :: Bool).
BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def -> Bool
< :: BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def -> Bool
$c< :: forall (def :: Bool).
BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def -> Bool
compare :: BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def -> Ordering
$ccompare :: forall (def :: Bool).
BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def -> Ordering
$cp1Ord :: forall (def :: Bool). Eq (BOOLEAN_DEFAULT def)
Ord,BOOLEAN_DEFAULT def
BOOLEAN_DEFAULT def
-> BOOLEAN_DEFAULT def -> Bounded (BOOLEAN_DEFAULT def)
forall (def :: Bool). BOOLEAN_DEFAULT def
forall a. a -> a -> Bounded a
maxBound :: BOOLEAN_DEFAULT def
$cmaxBound :: forall (def :: Bool). BOOLEAN_DEFAULT def
minBound :: BOOLEAN_DEFAULT def
$cminBound :: forall (def :: Bool). BOOLEAN_DEFAULT def
Bounded,Int -> BOOLEAN_DEFAULT def
BOOLEAN_DEFAULT def -> Int
BOOLEAN_DEFAULT def -> [BOOLEAN_DEFAULT def]
BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def
BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def -> [BOOLEAN_DEFAULT def]
BOOLEAN_DEFAULT def
-> BOOLEAN_DEFAULT def
-> BOOLEAN_DEFAULT def
-> [BOOLEAN_DEFAULT def]
(BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def)
-> (BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def)
-> (Int -> BOOLEAN_DEFAULT def)
-> (BOOLEAN_DEFAULT def -> Int)
-> (BOOLEAN_DEFAULT def -> [BOOLEAN_DEFAULT def])
-> (BOOLEAN_DEFAULT def
-> BOOLEAN_DEFAULT def -> [BOOLEAN_DEFAULT def])
-> (BOOLEAN_DEFAULT def
-> BOOLEAN_DEFAULT def -> [BOOLEAN_DEFAULT def])
-> (BOOLEAN_DEFAULT def
-> BOOLEAN_DEFAULT def
-> BOOLEAN_DEFAULT def
-> [BOOLEAN_DEFAULT def])
-> Enum (BOOLEAN_DEFAULT def)
forall (def :: Bool). Int -> BOOLEAN_DEFAULT def
forall (def :: Bool). BOOLEAN_DEFAULT def -> Int
forall (def :: Bool). BOOLEAN_DEFAULT def -> [BOOLEAN_DEFAULT def]
forall (def :: Bool). BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def
forall (def :: Bool).
BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def -> [BOOLEAN_DEFAULT def]
forall (def :: Bool).
BOOLEAN_DEFAULT def
-> BOOLEAN_DEFAULT def
-> BOOLEAN_DEFAULT def
-> [BOOLEAN_DEFAULT def]
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 :: BOOLEAN_DEFAULT def
-> BOOLEAN_DEFAULT def
-> BOOLEAN_DEFAULT def
-> [BOOLEAN_DEFAULT def]
$cenumFromThenTo :: forall (def :: Bool).
BOOLEAN_DEFAULT def
-> BOOLEAN_DEFAULT def
-> BOOLEAN_DEFAULT def
-> [BOOLEAN_DEFAULT def]
enumFromTo :: BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def -> [BOOLEAN_DEFAULT def]
$cenumFromTo :: forall (def :: Bool).
BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def -> [BOOLEAN_DEFAULT def]
enumFromThen :: BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def -> [BOOLEAN_DEFAULT def]
$cenumFromThen :: forall (def :: Bool).
BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def -> [BOOLEAN_DEFAULT def]
enumFrom :: BOOLEAN_DEFAULT def -> [BOOLEAN_DEFAULT def]
$cenumFrom :: forall (def :: Bool). BOOLEAN_DEFAULT def -> [BOOLEAN_DEFAULT def]
fromEnum :: BOOLEAN_DEFAULT def -> Int
$cfromEnum :: forall (def :: Bool). BOOLEAN_DEFAULT def -> Int
toEnum :: Int -> BOOLEAN_DEFAULT def
$ctoEnum :: forall (def :: Bool). Int -> BOOLEAN_DEFAULT def
pred :: BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def
$cpred :: forall (def :: Bool). BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def
succ :: BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def
$csucc :: forall (def :: Bool). BOOLEAN_DEFAULT def -> BOOLEAN_DEFAULT def
Enum,(forall x. BOOLEAN_DEFAULT def -> Rep (BOOLEAN_DEFAULT def) x)
-> (forall x. Rep (BOOLEAN_DEFAULT def) x -> BOOLEAN_DEFAULT def)
-> Generic (BOOLEAN_DEFAULT def)
forall (def :: Bool) x.
Rep (BOOLEAN_DEFAULT def) x -> BOOLEAN_DEFAULT def
forall (def :: Bool) x.
BOOLEAN_DEFAULT def -> Rep (BOOLEAN_DEFAULT def) x
forall x. Rep (BOOLEAN_DEFAULT def) x -> BOOLEAN_DEFAULT def
forall x. BOOLEAN_DEFAULT def -> Rep (BOOLEAN_DEFAULT def) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall (def :: Bool) x.
Rep (BOOLEAN_DEFAULT def) x -> BOOLEAN_DEFAULT def
$cfrom :: forall (def :: Bool) x.
BOOLEAN_DEFAULT def -> Rep (BOOLEAN_DEFAULT def) x
Generic,Int -> BOOLEAN_DEFAULT def -> ShowS
[BOOLEAN_DEFAULT def] -> ShowS
BOOLEAN_DEFAULT def -> [Char]
(Int -> BOOLEAN_DEFAULT def -> ShowS)
-> (BOOLEAN_DEFAULT def -> [Char])
-> ([BOOLEAN_DEFAULT def] -> ShowS)
-> Show (BOOLEAN_DEFAULT def)
forall (def :: Bool). Int -> BOOLEAN_DEFAULT def -> ShowS
forall (def :: Bool). [BOOLEAN_DEFAULT def] -> ShowS
forall (def :: Bool). BOOLEAN_DEFAULT def -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [BOOLEAN_DEFAULT def] -> ShowS
$cshowList :: forall (def :: Bool). [BOOLEAN_DEFAULT def] -> ShowS
show :: BOOLEAN_DEFAULT def -> [Char]
$cshow :: forall (def :: Bool). BOOLEAN_DEFAULT def -> [Char]
showsPrec :: Int -> BOOLEAN_DEFAULT def -> ShowS
$cshowsPrec :: forall (def :: Bool). Int -> BOOLEAN_DEFAULT def -> ShowS
Show,ReadPrec [BOOLEAN_DEFAULT def]
ReadPrec (BOOLEAN_DEFAULT def)
Int -> ReadS (BOOLEAN_DEFAULT def)
ReadS [BOOLEAN_DEFAULT def]
(Int -> ReadS (BOOLEAN_DEFAULT def))
-> ReadS [BOOLEAN_DEFAULT def]
-> ReadPrec (BOOLEAN_DEFAULT def)
-> ReadPrec [BOOLEAN_DEFAULT def]
-> Read (BOOLEAN_DEFAULT def)
forall (def :: Bool). ReadPrec [BOOLEAN_DEFAULT def]
forall (def :: Bool). ReadPrec (BOOLEAN_DEFAULT def)
forall (def :: Bool). Int -> ReadS (BOOLEAN_DEFAULT def)
forall (def :: Bool). ReadS [BOOLEAN_DEFAULT def]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BOOLEAN_DEFAULT def]
$creadListPrec :: forall (def :: Bool). ReadPrec [BOOLEAN_DEFAULT def]
readPrec :: ReadPrec (BOOLEAN_DEFAULT def)
$creadPrec :: forall (def :: Bool). ReadPrec (BOOLEAN_DEFAULT def)
readList :: ReadS [BOOLEAN_DEFAULT def]
$creadList :: forall (def :: Bool). ReadS [BOOLEAN_DEFAULT def]
readsPrec :: Int -> ReadS (BOOLEAN_DEFAULT def)
$creadsPrec :: forall (def :: Bool). Int -> ReadS (BOOLEAN_DEFAULT def)
Read,BOOLEAN_DEFAULT def -> ()
(BOOLEAN_DEFAULT def -> ()) -> NFData (BOOLEAN_DEFAULT def)
forall (def :: Bool). BOOLEAN_DEFAULT def -> ()
forall a. (a -> ()) -> NFData a
rnf :: BOOLEAN_DEFAULT def -> ()
$crnf :: forall (def :: Bool). BOOLEAN_DEFAULT def -> ()
NFData)
instance forall def . KnownBool def => ASN1 (BOOLEAN_DEFAULT def) where
asn1defTag :: Proxy (BOOLEAN_DEFAULT def) -> Tag
asn1defTag _ = Word64 -> Tag
Universal 1
asn1encode :: BOOLEAN_DEFAULT def -> ASN1Encode Word64
asn1encode (BOOLEAN b :: Bool
b)
| Bool
b Bool -> Bool -> Bool
forall a. Eq a => a -> a -> Bool
== Proxy def -> Bool
forall (b :: Bool). KnownBool b => Proxy b -> Bool
boolVal (Proxy def
forall k (t :: k). Proxy t
Proxy :: Proxy def) = (Maybe Tag -> PutM Word64) -> ASN1Encode Word64
forall a. (Maybe Tag -> PutM a) -> ASN1Encode a
ASN1Encode ((Maybe Tag -> PutM Word64) -> ASN1Encode Word64)
-> (Maybe Tag -> PutM Word64) -> ASN1Encode Word64
forall a b. (a -> b) -> a -> b
$ \_ -> Word64 -> PutM Word64
forall (f :: * -> *) a. Applicative f => a -> f a
pure 0
| Bool
otherwise = Bool -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode Bool
b
asn1decode :: ASN1Decode (BOOLEAN_DEFAULT def)
asn1decode = ASN1Decode (Maybe Bool)
-> (Maybe Bool -> Either [Char] (BOOLEAN_DEFAULT def))
-> ASN1Decode (BOOLEAN_DEFAULT def)
forall x y. ASN1Decode x -> (x -> Either [Char] y) -> ASN1Decode y
transformVia (ASN1Decode Bool -> ASN1Decode (Maybe Bool)
forall x. ASN1Decode x -> ASN1Decode (Maybe x)
dec'OPTIONAL ASN1Decode Bool
dec'BOOLEAN) ((Maybe Bool -> Either [Char] (BOOLEAN_DEFAULT def))
-> ASN1Decode (BOOLEAN_DEFAULT def))
-> (Maybe Bool -> Either [Char] (BOOLEAN_DEFAULT def))
-> ASN1Decode (BOOLEAN_DEFAULT def)
forall a b. (a -> b) -> a -> b
$ \case
Just True | Bool
defbool -> [Char] -> Either [Char] (BOOLEAN_DEFAULT def)
forall a b. a -> Either a b
Left "encoded TRUE encountered despite 'BOOLEAN DEFAULT TRUE'"
Just False | Bool -> Bool
not Bool
defbool -> [Char] -> Either [Char] (BOOLEAN_DEFAULT def)
forall a b. a -> Either a b
Left "encoded FALSE encountered despite 'BOOLEAN DEFAULT FALSE'"
Just b :: Bool
b -> BOOLEAN_DEFAULT def -> Either [Char] (BOOLEAN_DEFAULT def)
forall a b. b -> Either a b
Right (Bool -> BOOLEAN_DEFAULT def
forall (def :: Bool). Bool -> BOOLEAN_DEFAULT def
BOOLEAN Bool
b)
Nothing -> BOOLEAN_DEFAULT def -> Either [Char] (BOOLEAN_DEFAULT def)
forall a b. b -> Either a b
Right (Bool -> BOOLEAN_DEFAULT def
forall (def :: Bool). Bool -> BOOLEAN_DEFAULT def
BOOLEAN Bool
defbool)
where
defbool :: Bool
defbool = Proxy def -> Bool
forall (b :: Bool). KnownBool b => Proxy b -> Bool
boolVal (Proxy def
forall k (t :: k). Proxy t
Proxy :: Proxy def)
class KnownBool (b :: Bool) where boolVal :: Proxy b -> Bool
instance KnownBool 'True where boolVal :: Proxy 'True -> Bool
boolVal _ = Bool
True
instance KnownBool 'False where boolVal :: Proxy 'False -> Bool
boolVal _ = Bool
False
class GASN1EncodeCompOf (t :: * -> *) where
gasn1encodeCompOf' :: t p -> ASN1Encode Word64
instance ASN1 a => GASN1EncodeCompOf (K1 i a) where
gasn1encodeCompOf' :: K1 i a p -> ASN1Encode Word64
gasn1encodeCompOf' (K1 v :: a
v) = a -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode a
v
instance GASN1EncodeCompOf f => GASN1EncodeCompOf (M1 i c f) where
gasn1encodeCompOf' :: M1 i c f p -> ASN1Encode Word64
gasn1encodeCompOf' (M1 x :: f p
x) = f p -> ASN1Encode Word64
forall (t :: * -> *) p.
GASN1EncodeCompOf t =>
t p -> ASN1Encode Word64
gasn1encodeCompOf' f p
x
instance (GASN1EncodeCompOf f, GASN1EncodeCompOf g) => GASN1EncodeCompOf (f :*: g) where
gasn1encodeCompOf' :: (:*:) f g p -> ASN1Encode Word64
gasn1encodeCompOf' (x1 :: f p
x1 :*: x2 :: g p
x2) = f p -> ASN1Encode Word64
forall (t :: * -> *) p.
GASN1EncodeCompOf t =>
t p -> ASN1Encode Word64
gasn1encodeCompOf' f p
x1 ASN1Encode Word64 -> ASN1Encode Word64 -> ASN1Encode Word64
forall a. Semigroup a => a -> a -> a
<> g p -> ASN1Encode Word64
forall (t :: * -> *) p.
GASN1EncodeCompOf t =>
t p -> ASN1Encode Word64
gasn1encodeCompOf' g p
x2
class GASN1DecodeCompOf (t :: * -> *) where
gasn1decodeCompOf' :: ASN1Decode (t p)
instance ASN1 a => GASN1DecodeCompOf (K1 i a) where
gasn1decodeCompOf' :: ASN1Decode (K1 i a p)
gasn1decodeCompOf' = a -> K1 i a p
forall k i c (p :: k). c -> K1 i c p
K1 (a -> K1 i a p) -> ASN1Decode a -> ASN1Decode (K1 i a p)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ASN1Decode a
forall t. ASN1 t => ASN1Decode t
asn1decode
instance GASN1DecodeCompOf f => GASN1DecodeCompOf (M1 i c f) where
gasn1decodeCompOf' :: ASN1Decode (M1 i c f p)
gasn1decodeCompOf' = f p -> M1 i c f p
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 (f p -> M1 i c f p) -> ASN1Decode (f p) -> ASN1Decode (M1 i c f p)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ASN1Decode (f p)
forall (t :: * -> *) p. GASN1DecodeCompOf t => ASN1Decode (t p)
gasn1decodeCompOf'
instance (GASN1DecodeCompOf f, GASN1DecodeCompOf g) => GASN1DecodeCompOf (f :*: g) where
gasn1decodeCompOf' :: ASN1Decode ((:*:) f g p)
gasn1decodeCompOf' = f p -> g p -> (:*:) f g p
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
(:*:) (f p -> g p -> (:*:) f g p)
-> ASN1Decode (f p) -> ASN1Decode (g p -> (:*:) f g p)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ASN1Decode (f p)
forall (t :: * -> *) p. GASN1DecodeCompOf t => ASN1Decode (t p)
gasn1decodeCompOf' ASN1Decode (g p -> (:*:) f g p)
-> ASN1Decode (g p) -> ASN1Decode ((:*:) f g p)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ASN1Decode (g p)
forall (t :: * -> *) p. GASN1DecodeCompOf t => ASN1Decode (t p)
gasn1decodeCompOf'
gasn1encodeChoice :: (Generic t, GASN1EncodeChoice (Rep t)) => t -> ASN1Encode Word64
gasn1encodeChoice :: t -> ASN1Encode Word64
gasn1encodeChoice x :: t
x = Rep t Any -> ASN1Encode Word64
forall (t :: * -> *) p.
GASN1EncodeChoice t =>
t p -> ASN1Encode Word64
gchoice (t -> Rep t Any
forall a x. Generic a => a -> Rep a x
from t
x)
class GASN1EncodeChoice (t :: * -> *) where
gchoice :: t p -> ASN1Encode Word64
instance GASN1EncodeChoice V1 where
gchoice :: V1 p -> ASN1Encode Word64
gchoice _ = ASN1Encode Word64
empty'ASN1Encode
instance GASN1EncodeChoice f => GASN1EncodeChoice (M1 i c f) where
gchoice :: M1 i c f p -> ASN1Encode Word64
gchoice (M1 x :: f p
x) = f p -> ASN1Encode Word64
forall (t :: * -> *) p.
GASN1EncodeChoice t =>
t p -> ASN1Encode Word64
gchoice f p
x
instance ASN1 a => GASN1EncodeChoice (K1 i a) where
gchoice :: K1 i a p -> ASN1Encode Word64
gchoice (K1 x :: a
x) = a -> ASN1Encode Word64
forall t. ASN1 t => t -> ASN1Encode Word64
asn1encode a
x
instance (GASN1EncodeChoice x, GASN1EncodeChoice y) => GASN1EncodeChoice (x :+: y) where
gchoice :: (:+:) x y p -> ASN1Encode Word64
gchoice (L1 x :: x p
x) = x p -> ASN1Encode Word64
forall (t :: * -> *) p.
GASN1EncodeChoice t =>
t p -> ASN1Encode Word64
gchoice x p
x
gchoice (R1 x :: y p
x) = y p -> ASN1Encode Word64
forall (t :: * -> *) p.
GASN1EncodeChoice t =>
t p -> ASN1Encode Word64
gchoice y p
x
gasn1decodeChoice :: (Generic t, GASN1DecodeChoice (Rep t)) => ASN1Decode t
gasn1decodeChoice :: ASN1Decode t
gasn1decodeChoice = Rep t Any -> t
forall a x. Generic a => Rep a x -> a
to (Rep t Any -> t) -> ASN1Decode (Rep t Any) -> ASN1Decode t
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ASN1Decode (Rep t Any)
forall (t :: * -> *) p. GASN1DecodeChoice t => ASN1Decode (t p)
gunchoice
class GASN1DecodeChoice (t :: * -> *) where
gunchoice :: ASN1Decode (t p)
instance GASN1DecodeChoice V1 where
gunchoice :: ASN1Decode (V1 p)
gunchoice = ASN1Decode (V1 p)
forall (f :: * -> *) a. Alternative f => f a
empty
instance GASN1DecodeChoice f => GASN1DecodeChoice (M1 i c f) where
gunchoice :: ASN1Decode (M1 i c f p)
gunchoice = f p -> M1 i c f p
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 (f p -> M1 i c f p) -> ASN1Decode (f p) -> ASN1Decode (M1 i c f p)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ASN1Decode (f p)
forall (t :: * -> *) p. GASN1DecodeChoice t => ASN1Decode (t p)
gunchoice
instance ASN1 a => GASN1DecodeChoice (K1 i a) where
gunchoice :: ASN1Decode (K1 i a p)
gunchoice = a -> K1 i a p
forall k i c (p :: k). c -> K1 i c p
K1 (a -> K1 i a p) -> ASN1Decode a -> ASN1Decode (K1 i a p)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ASN1Decode a
forall t. ASN1 t => ASN1Decode t
asn1decode
instance (GASN1DecodeChoice x, GASN1DecodeChoice y) => GASN1DecodeChoice (x :+: y) where
gunchoice :: ASN1Decode ((:+:) x y p)
gunchoice = (x p -> (:+:) x y p
forall k (f :: k -> *) (g :: k -> *) (p :: k). f p -> (:+:) f g p
L1 (x p -> (:+:) x y p)
-> ASN1Decode (x p) -> ASN1Decode ((:+:) x y p)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ASN1Decode (x p)
forall (t :: * -> *) p. GASN1DecodeChoice t => ASN1Decode (t p)
gunchoice) ASN1Decode ((:+:) x y p)
-> ASN1Decode ((:+:) x y p) -> ASN1Decode ((:+:) x y p)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (y p -> (:+:) x y p
forall k (f :: k -> *) (g :: k -> *) (p :: k). g p -> (:+:) f g p
R1 (y p -> (:+:) x y p)
-> ASN1Decode (y p) -> ASN1Decode ((:+:) x y p)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ASN1Decode (y p)
forall (t :: * -> *) p. GASN1DecodeChoice t => ASN1Decode (t p)
gunchoice)