language-asn-0.1.0.0: ASN.1 encoding and decoding

Safe HaskellNone
LanguageHaskell2010

Language.Asn.Types.Internal

Synopsis

Documentation

newtype Subtypes a Source #

Constructors

Subtypes 

Fields

Instances
Semigroup (Subtypes a) Source # 
Instance details

Defined in Language.Asn.Types.Internal

Methods

(<>) :: Subtypes a -> Subtypes a -> Subtypes a #

sconcat :: NonEmpty (Subtypes a) -> Subtypes a #

stimes :: Integral b => b -> Subtypes a -> Subtypes a #

Monoid (Subtypes a) Source # 
Instance details

Defined in Language.Asn.Types.Internal

Methods

mempty :: Subtypes a #

mappend :: Subtypes a -> Subtypes a -> Subtypes a #

mconcat :: [Subtypes a] -> Subtypes a #

newtype ObjectIdentifier Source #

Note: we deviate slightly from the actual definition of an object identifier. Technically, each number of an OID should be allowed to be an integer of unlimited size. However, we are intentionally unfaithful to this specification because in practice, there are no OIDs that use integers above a 32-bit word, so we just use the machine's native word size.

Instances
Eq ObjectIdentifier Source # 
Instance details

Defined in Language.Asn.Types.Internal

Ord ObjectIdentifier Source # 
Instance details

Defined in Language.Asn.Types.Internal

Show ObjectIdentifier Source # 
Instance details

Defined in Language.Asn.Types.Internal

Generic ObjectIdentifier Source # 
Instance details

Defined in Language.Asn.Types.Internal

Associated Types

type Rep ObjectIdentifier :: Type -> Type #

Hashable ObjectIdentifier Source # 
Instance details

Defined in Language.Asn.Types.Internal

type Rep ObjectIdentifier Source # 
Instance details

Defined in Language.Asn.Types.Internal

type Rep ObjectIdentifier = D1 (MetaData "ObjectIdentifier" "Language.Asn.Types.Internal" "language-asn-0.1.0.0-CEYoCnbWRHKC4EXbCHGksq" True) (C1 (MetaCons "ObjectIdentifier" PrefixI True) (S1 (MetaSel (Just "getObjectIdentifier") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (PrimArray Word))))

newtype ObjectIdentifierSuffix Source #

Instances
Eq ObjectIdentifierSuffix Source # 
Instance details

Defined in Language.Asn.Types.Internal

Ord ObjectIdentifierSuffix Source # 
Instance details

Defined in Language.Asn.Types.Internal

Show ObjectIdentifierSuffix Source # 
Instance details

Defined in Language.Asn.Types.Internal

Generic ObjectIdentifierSuffix Source # 
Instance details

Defined in Language.Asn.Types.Internal

Associated Types

type Rep ObjectIdentifierSuffix :: Type -> Type #

Hashable ObjectIdentifierSuffix Source # 
Instance details

Defined in Language.Asn.Types.Internal

type Rep ObjectIdentifierSuffix Source # 
Instance details

Defined in Language.Asn.Types.Internal

type Rep ObjectIdentifierSuffix = D1 (MetaData "ObjectIdentifierSuffix" "Language.Asn.Types.Internal" "language-asn-0.1.0.0-CEYoCnbWRHKC4EXbCHGksq" True) (C1 (MetaCons "ObjectIdentifierSuffix" PrefixI True) (S1 (MetaSel (Just "getObjectIdentifierSuffix") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (PrimArray Word))))

data Choice a Source #

Constructors

Choice (a -> b) [b] (b -> ValueAndEncoding) 
Instances
Contravariant Choice Source # 
Instance details

Defined in Language.Asn.Types.Internal

Methods

contramap :: (a -> b) -> Choice b -> Choice a #

(>$) :: b -> Choice b -> Choice a #

data Field a Source #

Constructors

FieldRequired FieldName (a -> b) (AsnEncoding b) 
FieldOptional FieldName (a -> Maybe b) (AsnEncoding b) 
FieldDefaulted FieldName (a -> b) b (b -> String) (b -> b -> Bool) (AsnEncoding b) 
Instances
Contravariant Field Source # 
Instance details

Defined in Language.Asn.Types.Internal

Methods

contramap :: (a -> b) -> Field b -> Field a #

(>$) :: b -> Field b -> Field a #

newtype FieldName Source #

Constructors

FieldName 

Fields

Instances
IsString FieldName Source # 
Instance details

Defined in Language.Asn.Types.Internal

newtype OptionName Source #

Constructors

OptionName 
Instances
IsString OptionName Source # 
Instance details

Defined in Language.Asn.Types.Internal

data TagClass Source #

Instances
Eq TagClass Source # 
Instance details

Defined in Language.Asn.Types.Internal

Show TagClass Source # 
Instance details

Defined in Language.Asn.Types.Internal

data Tag Source #

Constructors

Tag 
Instances
Eq Tag Source # 
Instance details

Defined in Language.Asn.Types.Internal

Methods

(==) :: Tag -> Tag -> Bool #

(/=) :: Tag -> Tag -> Bool #

Show Tag Source # 
Instance details

Defined in Language.Asn.Types.Internal

Methods

showsPrec :: Int -> Tag -> ShowS #

show :: Tag -> String #

showList :: [Tag] -> ShowS #

data Ap f a where Source #

Constructors

Pure :: a -> Ap f a 
Ap :: f a -> Ap f (a -> b) -> Ap f b 
Instances
Functor (Ap f) Source # 
Instance details

Defined in Language.Asn.Types.Internal

Methods

fmap :: (a -> b) -> Ap f a -> Ap f b #

(<$) :: a -> Ap f b -> Ap f a #

Applicative (Ap f) Source # 
Instance details

Defined in Language.Asn.Types.Internal

Methods

pure :: a -> Ap f a #

(<*>) :: Ap f (a -> b) -> Ap f a -> Ap f b #

liftA2 :: (a -> b -> c) -> Ap f a -> Ap f b -> Ap f c #

(*>) :: Ap f a -> Ap f b -> Ap f b #

(<*) :: Ap f a -> Ap f b -> Ap f a #

data OptionDecoding a Source #

Instances
Functor OptionDecoding Source # 
Instance details

Defined in Language.Asn.Types.Internal

Methods

fmap :: (a -> b) -> OptionDecoding a -> OptionDecoding b #

(<$) :: a -> OptionDecoding b -> OptionDecoding a #

newtype DecodePart a Source #

Constructors

DecodePart 
Instances
Functor DecodePart Source # 
Instance details

Defined in Language.Asn.Types.Internal

Methods

fmap :: (a -> b) -> DecodePart a -> DecodePart b #

(<$) :: a -> DecodePart b -> DecodePart a #

Applicative DecodePart Source # 
Instance details

Defined in Language.Asn.Types.Internal

Methods

pure :: a -> DecodePart a #

(<*>) :: DecodePart (a -> b) -> DecodePart a -> DecodePart b #

liftA2 :: (a -> b -> c) -> DecodePart a -> DecodePart b -> DecodePart c #

(*>) :: DecodePart a -> DecodePart b -> DecodePart b #

(<*) :: DecodePart a -> DecodePart b -> DecodePart a #

runAp :: Applicative g => (forall x. f x -> g x) -> Ap f a -> g a Source #

liftAp :: f a -> Ap f a Source #