LDAPv3-0.0.0.0: Lightweight Directory Access Protocol (LDAP) version 3

Safe HaskellNone
LanguageHaskell2010

LDAPv3

Contents

Description

This module provides a pure Haskell implementation of the Lightweight Directory Access Protocol (LDAP) version 3 as specified in RFC4511.

Serializing and deserializing to and from the wire ASN.1 encoding is provided via the Binary instance of LDAPMessage. For the purpose of implementing network clients and servers, the operations

are most useful.

Synopsis

LDAPv3 Protocol data structures

The Haskell data structures defined in this module closely follow the protocol specification as laid out in RFC4511.

For convenience, the normative ASN.1 definitions for each Haskell data type are quoted.

Common Elements (RFC4511 Section 4.1)

data LDAPMessage Source #

Message Envelope (RFC4511 Section 4.1.1)

LDAPMessage ::= SEQUENCE {
     messageID       MessageID,
     protocolOp      CHOICE {
          bindRequest           BindRequest,
          bindResponse          BindResponse,
          unbindRequest         UnbindRequest,
          searchRequest         SearchRequest,
          searchResEntry        SearchResultEntry,
          searchResDone         SearchResultDone,
          searchResRef          SearchResultReference,
          modifyRequest         ModifyRequest,
          modifyResponse        ModifyResponse,
          addRequest            AddRequest,
          addResponse           AddResponse,
          delRequest            DelRequest,
          delResponse           DelResponse,
          modDNRequest          ModifyDNRequest,
          modDNResponse         ModifyDNResponse,
          compareRequest        CompareRequest,
          compareResponse       CompareResponse,
          abandonRequest        AbandonRequest,
          extendedReq           ExtendedRequest,
          extendedResp          ExtendedResponse,
          ...,
          intermediateResponse  IntermediateResponse },
     controls       [0] Controls OPTIONAL }
Instances
Eq LDAPMessage Source # 
Instance details

Defined in LDAPv3

Show LDAPMessage Source # 
Instance details

Defined in LDAPv3

Generic LDAPMessage Source # 
Instance details

Defined in LDAPv3

Associated Types

type Rep LDAPMessage :: Type -> Type #

Binary LDAPMessage Source #

Encodes to/from ASN.1 as per RFC4511 Section 5.1

Instance details

Defined in LDAPv3

type Rep LDAPMessage Source # 
Instance details

Defined in LDAPv3

type Rep LDAPMessage = D1 (MetaData "LDAPMessage" "LDAPv3" "LDAPv3-0.0.0.0-L06NoWaj9ma4LMfw7dYZJc" False) (C1 (MetaCons "LDAPMessage" PrefixI True) (S1 (MetaSel (Just "_LDAPMessage'messageID") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MessageID) :*: (S1 (MetaSel (Just "_LDAPMessage'protocolOp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ProtocolOp) :*: S1 (MetaSel (Just "_LDAPMessage'controls") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (IMPLICIT (CONTEXTUAL 0) Controls))))))

newtype MessageID Source #

Message ID (RFC4511 Section 4.1.1.1)

MessageID ::= INTEGER (0 ..  maxInt)

Constructors

MessageID (UInt 0 MaxInt Int32) 
Instances
Bounded MessageID Source # 
Instance details

Defined in LDAPv3

Eq MessageID Source # 
Instance details

Defined in LDAPv3

Ord MessageID Source # 
Instance details

Defined in LDAPv3

Show MessageID Source # 
Instance details

Defined in LDAPv3

Generic MessageID Source # 
Instance details

Defined in LDAPv3

Associated Types

type Rep MessageID :: Type -> Type #

NFData MessageID Source # 
Instance details

Defined in LDAPv3

Methods

rnf :: MessageID -> () #

type Rep MessageID Source # 
Instance details

Defined in LDAPv3

type Rep MessageID = D1 (MetaData "MessageID" "LDAPv3" "LDAPv3-0.0.0.0-L06NoWaj9ma4LMfw7dYZJc" True) (C1 (MetaCons "MessageID" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (UInt 0 MaxInt Int32))))

type MaxInt = 2147483647 Source #

LDAPv3 protocol ASN.1 constant as per RFC4511 Section 4.1.1

maxInt INTEGER ::= 2147483647 -- (2^^31 - 1)

data ProtocolOp Source #

CHOICE type inlined in LDAPMessage.protocolOp (RFC4511 Section 4.1.1)

Instances
Eq ProtocolOp Source # 
Instance details

Defined in LDAPv3

Show ProtocolOp Source # 
Instance details

Defined in LDAPv3

Generic ProtocolOp Source # 
Instance details

Defined in LDAPv3

Associated Types

type Rep ProtocolOp :: Type -> Type #

NFData ProtocolOp Source # 
Instance details

Defined in LDAPv3

Methods

rnf :: ProtocolOp -> () #

type Rep ProtocolOp Source # 
Instance details

Defined in LDAPv3

type Rep ProtocolOp = D1 (MetaData "ProtocolOp" "LDAPv3" "LDAPv3-0.0.0.0-L06NoWaj9ma4LMfw7dYZJc" False) ((((C1 (MetaCons "ProtocolOp'bindRequest" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 BindRequest)) :+: C1 (MetaCons "ProtocolOp'bindResponse" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 BindResponse))) :+: (C1 (MetaCons "ProtocolOp'unbindRequest" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UnbindRequest)) :+: (C1 (MetaCons "ProtocolOp'searchRequest" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SearchRequest)) :+: C1 (MetaCons "ProtocolOp'searchResEntry" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SearchResultEntry))))) :+: ((C1 (MetaCons "ProtocolOp'searchResDone" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SearchResultDone)) :+: C1 (MetaCons "ProtocolOp'searchResRef" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SearchResultReference))) :+: (C1 (MetaCons "ProtocolOp'modifyRequest" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ModifyRequest)) :+: (C1 (MetaCons "ProtocolOp'modifyResponse" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ModifyResponse)) :+: C1 (MetaCons "ProtocolOp'addRequest" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AddRequest)))))) :+: (((C1 (MetaCons "ProtocolOp'addResponse" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AddResponse)) :+: C1 (MetaCons "ProtocolOp'delRequest" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DelRequest))) :+: (C1 (MetaCons "ProtocolOp'delResponse" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DelResponse)) :+: (C1 (MetaCons "ProtocolOp'modDNRequest" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ModifyDNRequest)) :+: C1 (MetaCons "ProtocolOp'modDNResponse" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ModifyDNResponse))))) :+: ((C1 (MetaCons "ProtocolOp'compareRequest" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CompareRequest)) :+: (C1 (MetaCons "ProtocolOp'compareResponse" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CompareResponse)) :+: C1 (MetaCons "ProtocolOp'abandonRequest" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AbandonRequest)))) :+: (C1 (MetaCons "ProtocolOp'extendedReq" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ExtendedRequest)) :+: (C1 (MetaCons "ProtocolOp'extendedResp" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ExtendedResponse)) :+: C1 (MetaCons "ProtocolOp'intermediateResponse" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 IntermediateResponse)))))))

type LDAPString = ShortText Source #

String Type (RFC4511 Section 4.1.2)

LDAPString ::= OCTET STRING -- UTF-8 encoded,
                            -- [ISO10646] characters

type LDAPOID = OCTET_STRING Source #

Object identifier (RFC4511 Section 4.1.2)

LDAPOID ::= OCTET STRING -- Constrained to <numericoid>
                         -- [RFC4512]

type LDAPDN = LDAPString Source #

Distinguished Name (RFC4511 Section 4.1.3)

LDAPDN ::= LDAPString -- Constrained to <distinguishedName>
                      -- [RFC4514]

type RelativeLDAPDN = LDAPString Source #

Relative Distinguished Name (RFC4511 Section 4.1.3)

RelativeLDAPDN ::= LDAPString -- Constrained to <name-component>
                              -- [RFC4514]

type AttributeDescription = LDAPString Source #

Attribute Descriptions (RFC4511 Section 4.1.4)

AttributeDescription ::= LDAPString
                        -- Constrained to <attributedescription>
                        -- [RFC4512]

type AttributeValue = OCTET_STRING Source #

Attribute Value (RFC4511 Section 4.1.5)

AttributeValue ::= OCTET STRING

data AttributeValueAssertion Source #

Attribute Value Assertion (RFC4511 Section 4.1.6)

AttributeValueAssertion ::= SEQUENCE {
     attributeDesc   AttributeDescription,
     assertionValue  AssertionValue }
Instances
Eq AttributeValueAssertion Source # 
Instance details

Defined in LDAPv3

Show AttributeValueAssertion Source # 
Instance details

Defined in LDAPv3

Generic AttributeValueAssertion Source # 
Instance details

Defined in LDAPv3

Associated Types

type Rep AttributeValueAssertion :: Type -> Type #

NFData AttributeValueAssertion Source # 
Instance details

Defined in LDAPv3

Methods

rnf :: AttributeValueAssertion -> () #

type Rep AttributeValueAssertion Source # 
Instance details

Defined in LDAPv3

type Rep AttributeValueAssertion = D1 (MetaData "AttributeValueAssertion" "LDAPv3" "LDAPv3-0.0.0.0-L06NoWaj9ma4LMfw7dYZJc" False) (C1 (MetaCons "AttributeValueAssertion" PrefixI True) (S1 (MetaSel (Just "_AttributeValueAssertion'attributeDesc") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AttributeDescription) :*: S1 (MetaSel (Just "_AttributeValueAssertion'assertionValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AssertionValue)))

type AssertionValue = OCTET_STRING Source #

AssertionValue ::= OCTET STRING

data PartialAttribute Source #

Partial Attribute (RFC4511 Section 4.1.7)

PartialAttribute ::= SEQUENCE {
     type       AttributeDescription,
     vals       SET OF value AttributeValue }
Instances
Eq PartialAttribute Source # 
Instance details

Defined in LDAPv3

Show PartialAttribute Source # 
Instance details

Defined in LDAPv3

Generic PartialAttribute Source # 
Instance details

Defined in LDAPv3

Associated Types

type Rep PartialAttribute :: Type -> Type #

NFData PartialAttribute Source # 
Instance details

Defined in LDAPv3

Methods

rnf :: PartialAttribute -> () #

type Rep PartialAttribute Source # 
Instance details

Defined in LDAPv3

type Rep PartialAttribute = D1 (MetaData "PartialAttribute" "LDAPv3" "LDAPv3-0.0.0.0-L06NoWaj9ma4LMfw7dYZJc" False) (C1 (MetaCons "PartialAttribute" PrefixI True) (S1 (MetaSel (Just "_PartialAttribute'type") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AttributeDescription) :*: S1 (MetaSel (Just "_PartialAttribute'vals") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SET AttributeValue))))

data Attribute Source #

Attribute (RFC4511 Section 4.1.7)

Attribute ::= PartialAttribute(WITH COMPONENTS {
     ...,
     vals (SIZE(1..MAX))})
Instances
Eq Attribute Source # 
Instance details

Defined in LDAPv3

Show Attribute Source # 
Instance details

Defined in LDAPv3

Generic Attribute Source # 
Instance details

Defined in LDAPv3

Associated Types

type Rep Attribute :: Type -> Type #

NFData Attribute Source # 
Instance details

Defined in LDAPv3

Methods

rnf :: Attribute -> () #

type Rep Attribute Source # 
Instance details

Defined in LDAPv3

type Rep Attribute = D1 (MetaData "Attribute" "LDAPv3" "LDAPv3-0.0.0.0-L06NoWaj9ma4LMfw7dYZJc" False) (C1 (MetaCons "Attribute" PrefixI True) (S1 (MetaSel (Just "_Attribute'type") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AttributeDescription) :*: S1 (MetaSel (Just "_Attribute'vals") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SET1 AttributeValue))))

type MatchingRuleId = LDAPString Source #

Matching Rule Identifier (RFC4511 Section 4.1.8)

MatchingRuleId ::= LDAPString

data LDAPResult Source #

Result Message (RFC4511 Section 4.1.9)

LDAPResult ::= SEQUENCE {
     resultCode         ENUMERATED {
          success                      (0),
          operationsError              (1),
          protocolError                (2),
          timeLimitExceeded            (3),
          sizeLimitExceeded            (4),
          compareFalse                 (5),
          compareTrue                  (6),
          authMethodNotSupported       (7),
          strongerAuthRequired         (8),
               -- 9 reserved --
          referral                     (10),
          adminLimitExceeded           (11),
          unavailableCriticalExtension (12),
          confidentialityRequired      (13),
          saslBindInProgress           (14),
          noSuchAttribute              (16),
          undefinedAttributeType       (17),
          inappropriateMatching        (18),
          constraintViolation          (19),
          attributeOrValueExists       (20),
          invalidAttributeSyntax       (21),
               -- 22-31 unused --
          noSuchObject                 (32),
          aliasProblem                 (33),
          invalidDNSyntax              (34),
               -- 35 reserved for undefined isLeaf --
          aliasDereferencingProblem    (36),
               -- 37-47 unused --
          inappropriateAuthentication  (48),
          invalidCredentials           (49),
          insufficientAccessRights     (50),
          busy                         (51),
          unavailable                  (52),
          unwillingToPerform           (53),
          loopDetect                   (54),
               -- 55-63 unused --
          namingViolation              (64),
          objectClassViolation         (65),
          notAllowedOnNonLeaf          (66),
          notAllowedOnRDN              (67),
          entryAlreadyExists           (68),
          objectClassModsProhibited    (69),
               -- 70 reserved for CLDAP --
          affectsMultipleDSAs          (71),
               -- 72-79 unused --
          other                        (80),
          ...  },
     matchedDN          LDAPDN,
     diagnosticMessage  LDAPString,
     referral           [3] Referral OPTIONAL }
Instances
Eq LDAPResult Source # 
Instance details

Defined in LDAPv3

Show LDAPResult Source # 
Instance details

Defined in LDAPv3

Generic LDAPResult Source # 
Instance details

Defined in LDAPv3

Associated Types

type Rep LDAPResult :: Type -> Type #

NFData LDAPResult Source # 
Instance details

Defined in LDAPv3

Methods

rnf :: LDAPResult -> () #

type Rep LDAPResult Source # 
Instance details

Defined in LDAPv3

type Rep LDAPResult = D1 (MetaData "LDAPResult" "LDAPv3" "LDAPv3-0.0.0.0-L06NoWaj9ma4LMfw7dYZJc" False) (C1 (MetaCons "LDAPResult" PrefixI True) ((S1 (MetaSel (Just "_LDAPResult'resultCode") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ResultCode) :*: S1 (MetaSel (Just "_LDAPResult'matchedDN") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 LDAPDN)) :*: (S1 (MetaSel (Just "_LDAPResult'diagnosticMessage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 LDAPString) :*: S1 (MetaSel (Just "_LDAPResult'referral") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (IMPLICIT (CONTEXTUAL 3) Referral))))))

data ResultCode Source #

LDAPResult Result Code

Instances
Bounded ResultCode Source # 
Instance details

Defined in LDAPv3.ResultCode

Enum ResultCode Source # 
Instance details

Defined in LDAPv3.ResultCode

Eq ResultCode Source # 
Instance details

Defined in LDAPv3.ResultCode

Ord ResultCode Source # 
Instance details

Defined in LDAPv3.ResultCode

Show ResultCode Source # 
Instance details

Defined in LDAPv3.ResultCode

Generic ResultCode Source # 
Instance details

Defined in LDAPv3.ResultCode

Associated Types

type Rep ResultCode :: Type -> Type #

NFData ResultCode Source # 
Instance details

Defined in LDAPv3.ResultCode

Methods

rnf :: ResultCode -> () #

type Rep ResultCode Source # 
Instance details

Defined in LDAPv3.ResultCode

type Rep ResultCode = D1 (MetaData "ResultCode" "LDAPv3.ResultCode" "LDAPv3-0.0.0.0-L06NoWaj9ma4LMfw7dYZJc" False) (((((C1 (MetaCons "ResultCode'success" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ResultCode'operationsError" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "ResultCode'protocolError" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ResultCode'timeLimitExceeded" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "ResultCode'sizeLimitExceeded" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ResultCode'compareFalse" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "ResultCode'compareTrue" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "ResultCode'authMethodNotSupported" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ResultCode'strongerAuthRequired" PrefixI False) (U1 :: Type -> Type))))) :+: (((C1 (MetaCons "ResultCode'referral" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ResultCode'adminLimitExceeded" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "ResultCode'unavailableCriticalExtension" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "ResultCode'confidentialityRequired" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ResultCode'saslBindInProgress" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "ResultCode'noSuchAttribute" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ResultCode'undefinedAttributeType" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "ResultCode'inappropriateMatching" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "ResultCode'constraintViolation" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ResultCode'attributeOrValueExists" PrefixI False) (U1 :: Type -> Type)))))) :+: ((((C1 (MetaCons "ResultCode'invalidAttributeSyntax" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ResultCode'noSuchObject" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "ResultCode'aliasProblem" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "ResultCode'invalidDNSyntax" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ResultCode'aliasDereferencingProblem" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "ResultCode'inappropriateAuthentication" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ResultCode'invalidCredentials" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "ResultCode'insufficientAccessRights" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "ResultCode'busy" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ResultCode'unavailable" PrefixI False) (U1 :: Type -> Type))))) :+: (((C1 (MetaCons "ResultCode'unwillingToPerform" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ResultCode'loopDetect" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "ResultCode'namingViolation" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "ResultCode'objectClassViolation" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ResultCode'notAllowedOnNonLeaf" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "ResultCode'notAllowedOnRDN" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ResultCode'entryAlreadyExists" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "ResultCode'objectClassModsProhibited" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "ResultCode'affectsMultipleDSAs" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ResultCode'other" PrefixI False) (U1 :: Type -> Type)))))))

type Referral = CONTEXTUAL 3 `IMPLICIT` NonEmpty URI Source #

Referral result code (RFC4511 Section 4.1.10)

Referral ::= SEQUENCE SIZE (1..MAX) OF uri URI

type URI = LDAPString Source #

URI ::= LDAPString     -- limited to characters permitted in
                       -- URIs

type Controls = [Control] Source #

Controls (RFC4511 Section 4.1.11)

Controls ::= SEQUENCE OF control Control

data Control Source #

Control Entry (RFC4511 Section 4.1.11)

Control ::= SEQUENCE {
     controlType             LDAPOID,
     criticality             BOOLEAN DEFAULT FALSE,
     controlValue            OCTET STRING OPTIONAL }
Instances
Eq Control Source # 
Instance details

Defined in LDAPv3

Methods

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

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

Show Control Source # 
Instance details

Defined in LDAPv3

Generic Control Source # 
Instance details

Defined in LDAPv3

Associated Types

type Rep Control :: Type -> Type #

Methods

from :: Control -> Rep Control x #

to :: Rep Control x -> Control #

NFData Control Source # 
Instance details

Defined in LDAPv3

Methods

rnf :: Control -> () #

type Rep Control Source # 
Instance details

Defined in LDAPv3

type Rep Control = D1 (MetaData "Control" "LDAPv3" "LDAPv3-0.0.0.0-L06NoWaj9ma4LMfw7dYZJc" False) (C1 (MetaCons "Control" PrefixI True) (S1 (MetaSel (Just "_Control'controlType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 LDAPOID) :*: (S1 (MetaSel (Just "_Control'criticality") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe BOOLEAN_DEFAULT_FALSE)) :*: S1 (MetaSel (Just "_Control'controlValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe OCTET_STRING)))))

Bind Operation (RFC4511 Section 4.2)

data BindRequest Source #

Bind Request (RFC4511 Section 4.2)

BindRequest ::= [APPLICATION 0] SEQUENCE {
     version                 INTEGER (1 ..  127),
     name                    LDAPDN,
     authentication          AuthenticationChoice }
Instances
Eq BindRequest Source # 
Instance details

Defined in LDAPv3

Show BindRequest Source # 
Instance details

Defined in LDAPv3

Generic BindRequest Source # 
Instance details

Defined in LDAPv3

Associated Types

type Rep BindRequest :: Type -> Type #

NFData BindRequest Source # 
Instance details

Defined in LDAPv3

Methods

rnf :: BindRequest -> () #

type Rep BindRequest Source # 
Instance details

Defined in LDAPv3

type Rep BindRequest = D1 (MetaData "BindRequest" "LDAPv3" "LDAPv3-0.0.0.0-L06NoWaj9ma4LMfw7dYZJc" False) (C1 (MetaCons "BindRequest" PrefixI True) (S1 (MetaSel (Just "bindRequest'version") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (UInt 1 127 Int8)) :*: (S1 (MetaSel (Just "bindRequest'name") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 LDAPDN) :*: S1 (MetaSel (Just "bindRequest'authentication") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AuthenticationChoice))))

data AuthenticationChoice Source #

See BindRequest

AuthenticationChoice ::= CHOICE {
     simple                  [0] OCTET STRING,
                             -- 1 and 2 reserved
     sasl                    [3] SaslCredentials,
     ...  }

data SaslCredentials Source #

See AuthenticationChoice

SaslCredentials ::= SEQUENCE {
     mechanism               LDAPString,
     credentials             OCTET STRING OPTIONAL }
Instances
Eq SaslCredentials Source # 
Instance details

Defined in LDAPv3

Show SaslCredentials Source # 
Instance details

Defined in LDAPv3

Generic SaslCredentials Source # 
Instance details

Defined in LDAPv3

Associated Types

type Rep SaslCredentials :: Type -> Type #

NFData SaslCredentials Source # 
Instance details

Defined in LDAPv3

Methods

rnf :: SaslCredentials -> () #

type Rep SaslCredentials Source # 
Instance details

Defined in LDAPv3

type Rep SaslCredentials = D1 (MetaData "SaslCredentials" "LDAPv3" "LDAPv3-0.0.0.0-L06NoWaj9ma4LMfw7dYZJc" False) (C1 (MetaCons "SaslCredentials" PrefixI True) (S1 (MetaSel (Just "_SaslCredentials'mechanism") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 LDAPString) :*: S1 (MetaSel (Just "_SaslCredentials'credentials") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe OCTET_STRING))))

data BindResponse Source #

Bind Response (RFC4511 Section 4.2)

BindResponse ::= [APPLICATION 1] SEQUENCE {
     COMPONENTS OF LDAPResult,
     serverSaslCreds    [7] OCTET STRING OPTIONAL }
Instances
Eq BindResponse Source # 
Instance details

Defined in LDAPv3

Show BindResponse Source # 
Instance details

Defined in LDAPv3

Generic BindResponse Source # 
Instance details

Defined in LDAPv3

Associated Types

type Rep BindResponse :: Type -> Type #

NFData BindResponse Source # 
Instance details

Defined in LDAPv3

Methods

rnf :: BindResponse -> () #

type Rep BindResponse Source # 
Instance details

Defined in LDAPv3

type Rep BindResponse = D1 (MetaData "BindResponse" "LDAPv3" "LDAPv3-0.0.0.0-L06NoWaj9ma4LMfw7dYZJc" False) (C1 (MetaCons "BindResponse" PrefixI True) (S1 (MetaSel (Just "_BindResponse'LDAPResult") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 LDAPResult) :*: S1 (MetaSel (Just "_BindResponse'serverSaslCreds") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (IMPLICIT (CONTEXTUAL 7) OCTET_STRING)))))

Unbind Operation (RFC4511 Section 4.3)

type UnbindRequest = APPLICATION 2 `IMPLICIT` NULL Source #

Unbind Operation (RFC4511 Section 4.3)

UnbindRequest ::= [APPLICATION 2] NULL

Unsolicited Notification (RFC4511 Section 4.4)

Unsolicited notifications are represented by an ExtendedResponse message with its MessageID set to 0.

Search Operation (RFC4511 Section 4.5)

data SearchRequest Source #

Search Request (RFC4511 Section 4.5.1)

SearchRequest ::= [APPLICATION 3] SEQUENCE {
     baseObject      LDAPDN,
     scope           ENUMERATED {
          baseObject              (0),
          singleLevel             (1),
          wholeSubtree            (2),
          ...  },
     derefAliases    ENUMERATED {
          neverDerefAliases       (0),
          derefInSearching        (1),
          derefFindingBaseObj     (2),
          derefAlways             (3) },
     sizeLimit       INTEGER (0 ..  maxInt),
     timeLimit       INTEGER (0 ..  maxInt),
     typesOnly       BOOLEAN,
     filter          Filter,
     attributes      AttributeSelection }
Instances
Eq SearchRequest Source # 
Instance details

Defined in LDAPv3

Show SearchRequest Source # 
Instance details

Defined in LDAPv3

Generic SearchRequest Source # 
Instance details

Defined in LDAPv3

Associated Types

type Rep SearchRequest :: Type -> Type #

NFData SearchRequest Source # 
Instance details

Defined in LDAPv3

Methods

rnf :: SearchRequest -> () #

type Rep SearchRequest Source # 
Instance details

Defined in LDAPv3

type Rep SearchRequest = D1 (MetaData "SearchRequest" "LDAPv3" "LDAPv3-0.0.0.0-L06NoWaj9ma4LMfw7dYZJc" False) (C1 (MetaCons "SearchRequest" PrefixI True) (((S1 (MetaSel (Just "_SearchRequest'baseObject") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 LDAPDN) :*: S1 (MetaSel (Just "_SearchRequest'scope") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Scope)) :*: (S1 (MetaSel (Just "_SearchRequest'derefAliases") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DerefAliases) :*: S1 (MetaSel (Just "_SearchRequest'sizeLimit") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (UInt 0 MaxInt Int32)))) :*: ((S1 (MetaSel (Just "_SearchRequest'timeLimit") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (UInt 0 MaxInt Int32)) :*: S1 (MetaSel (Just "_SearchRequest'typesOnly") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) :*: (S1 (MetaSel (Just "_SearchRequest'filter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Filter) :*: S1 (MetaSel (Just "_SearchRequest'attributes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AttributeSelection)))))

data Scope Source #

Instances
Bounded Scope Source # 
Instance details

Defined in LDAPv3

Enum Scope Source # 
Instance details

Defined in LDAPv3

Eq Scope Source # 
Instance details

Defined in LDAPv3

Methods

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

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

Show Scope Source # 
Instance details

Defined in LDAPv3

Methods

showsPrec :: Int -> Scope -> ShowS #

show :: Scope -> String #

showList :: [Scope] -> ShowS #

Generic Scope Source # 
Instance details

Defined in LDAPv3

Associated Types

type Rep Scope :: Type -> Type #

Methods

from :: Scope -> Rep Scope x #

to :: Rep Scope x -> Scope #

NFData Scope Source # 
Instance details

Defined in LDAPv3

Methods

rnf :: Scope -> () #

type Rep Scope Source # 
Instance details

Defined in LDAPv3

type Rep Scope = D1 (MetaData "Scope" "LDAPv3" "LDAPv3-0.0.0.0-L06NoWaj9ma4LMfw7dYZJc" False) (C1 (MetaCons "Scope'baseObject" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Scope'singleLevel" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Scope'wholeSubtree" PrefixI False) (U1 :: Type -> Type)))

data DerefAliases Source #

Instances
Bounded DerefAliases Source # 
Instance details

Defined in LDAPv3

Enum DerefAliases Source # 
Instance details

Defined in LDAPv3

Eq DerefAliases Source # 
Instance details

Defined in LDAPv3

Show DerefAliases Source # 
Instance details

Defined in LDAPv3

Generic DerefAliases Source # 
Instance details

Defined in LDAPv3

Associated Types

type Rep DerefAliases :: Type -> Type #

NFData DerefAliases Source # 
Instance details

Defined in LDAPv3

Methods

rnf :: DerefAliases -> () #

type Rep DerefAliases Source # 
Instance details

Defined in LDAPv3

type Rep DerefAliases = D1 (MetaData "DerefAliases" "LDAPv3" "LDAPv3-0.0.0.0-L06NoWaj9ma4LMfw7dYZJc" False) ((C1 (MetaCons "DerefAliases'neverDerefAliases" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "DerefAliases'derefInSearching" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "DerefAliases'derefFindingBaseObj" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "DerefAliases'derefAlways" PrefixI False) (U1 :: Type -> Type)))

type AttributeSelection = [LDAPString] Source #

See SearchRequest

AttributeSelection ::= SEQUENCE OF selector LDAPString
               -- The LDAPString is constrained to
               -- <attributeSelector> in Section 4.5.1.8

data Filter Source #

Search Filter (RFC4511 Section 4.5.1.7)

Filter ::= CHOICE {
     and             [0] SET SIZE (1..MAX) OF filter Filter,
     or              [1] SET SIZE (1..MAX) OF filter Filter,
     not             [2] Filter,
     equalityMatch   [3] AttributeValueAssertion,
     substrings      [4] SubstringFilter,
     greaterOrEqual  [5] AttributeValueAssertion,
     lessOrEqual     [6] AttributeValueAssertion,
     present         [7] AttributeDescription,
     approxMatch     [8] AttributeValueAssertion,
     extensibleMatch [9] MatchingRuleAssertion,
     ...  }
Instances
Eq Filter Source # 
Instance details

Defined in LDAPv3

Methods

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

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

Show Filter Source # 
Instance details

Defined in LDAPv3

Generic Filter Source # 
Instance details

Defined in LDAPv3

Associated Types

type Rep Filter :: Type -> Type #

Methods

from :: Filter -> Rep Filter x #

to :: Rep Filter x -> Filter #

NFData Filter Source # 
Instance details

Defined in LDAPv3

Methods

rnf :: Filter -> () #

type Rep Filter Source # 
Instance details

Defined in LDAPv3

type Rep Filter = D1 (MetaData "Filter" "LDAPv3" "LDAPv3-0.0.0.0-L06NoWaj9ma4LMfw7dYZJc" False) (((C1 (MetaCons "Filter'and" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (IMPLICIT (CONTEXTUAL 0) (SET1 Filter)))) :+: C1 (MetaCons "Filter'or" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (IMPLICIT (CONTEXTUAL 1) (SET1 Filter))))) :+: (C1 (MetaCons "Filter'not" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (EXPLICIT (CONTEXTUAL 2) Filter))) :+: (C1 (MetaCons "Filter'equalityMatch" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (IMPLICIT (CONTEXTUAL 3) AttributeValueAssertion))) :+: C1 (MetaCons "Filter'substrings" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (IMPLICIT (CONTEXTUAL 4) SubstringFilter)))))) :+: ((C1 (MetaCons "Filter'greaterOrEqual" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (IMPLICIT (CONTEXTUAL 5) AttributeValueAssertion))) :+: C1 (MetaCons "Filter'lessOrEqual" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (IMPLICIT (CONTEXTUAL 6) AttributeValueAssertion)))) :+: (C1 (MetaCons "Filter'present" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (IMPLICIT (CONTEXTUAL 7) AttributeDescription))) :+: (C1 (MetaCons "Filter'approxMatch" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (IMPLICIT (CONTEXTUAL 8) AttributeValueAssertion))) :+: C1 (MetaCons "Filter'extensibleMatch" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (IMPLICIT (CONTEXTUAL 9) MatchingRuleAssertion)))))))

data SubstringFilter Source #

Substring Filter (RFC4511 Section 4.5.1.7.2)

SubstringFilter ::= SEQUENCE {
     type           AttributeDescription,
     substrings     SEQUENCE SIZE (1..MAX) OF substring CHOICE {
          initial [0] AssertionValue,  -- can occur at most once
          any     [1] AssertionValue,
          final   [2] AssertionValue } -- can occur at most once
     }

NOTE: The additional invariants imposed on the ordering and occurence counts of the initial and final entries MUST currently be enforced by the consumer of this library. Future versions of this library might change to enforce these invariants at the type-level.

Specifically, the invariant stated by the specification is:

There SHALL be at most one initial and at most one final in the substrings of a SubstringFilter. If initial is present, it SHALL be the first element of substrings. If final is present, it SHALL be the last element of substrings.

Instances
Eq SubstringFilter Source # 
Instance details

Defined in LDAPv3

Show SubstringFilter Source # 
Instance details

Defined in LDAPv3

Generic SubstringFilter Source # 
Instance details

Defined in LDAPv3

Associated Types

type Rep SubstringFilter :: Type -> Type #

NFData SubstringFilter Source # 
Instance details

Defined in LDAPv3

Methods

rnf :: SubstringFilter -> () #

type Rep SubstringFilter Source # 
Instance details

Defined in LDAPv3

type Rep SubstringFilter = D1 (MetaData "SubstringFilter" "LDAPv3" "LDAPv3-0.0.0.0-L06NoWaj9ma4LMfw7dYZJc" False) (C1 (MetaCons "SubstringFilter" PrefixI True) (S1 (MetaSel (Just "_SubstringFilter'type") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AttributeDescription) :*: S1 (MetaSel (Just "_SubstringFilter'substrings") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty Substring))))

data Substring Source #

Constructors

Substring'initial (CONTEXTUAL 0 `IMPLICIT` AssertionValue)

may occur at most once; must be first element if present

Substring'any (CONTEXTUAL 1 `IMPLICIT` AssertionValue) 
Substring'final (CONTEXTUAL 2 `IMPLICIT` AssertionValue)

may occur at most once; must be last element if present

Instances
Eq Substring Source # 
Instance details

Defined in LDAPv3

Show Substring Source # 
Instance details

Defined in LDAPv3

Generic Substring Source # 
Instance details

Defined in LDAPv3

Associated Types

type Rep Substring :: Type -> Type #

NFData Substring Source # 
Instance details

Defined in LDAPv3

Methods

rnf :: Substring -> () #

type Rep Substring Source # 
Instance details

Defined in LDAPv3

data MatchingRuleAssertion Source #

See SearchRequest Filter

MatchingRuleAssertion ::= SEQUENCE {
     matchingRule    [1] MatchingRuleId OPTIONAL,
     type            [2] AttributeDescription OPTIONAL,
     matchValue      [3] AssertionValue,
     dnAttributes    [4] BOOLEAN DEFAULT FALSE }
Instances
Eq MatchingRuleAssertion Source # 
Instance details

Defined in LDAPv3

Show MatchingRuleAssertion Source # 
Instance details

Defined in LDAPv3

Generic MatchingRuleAssertion Source # 
Instance details

Defined in LDAPv3

Associated Types

type Rep MatchingRuleAssertion :: Type -> Type #

NFData MatchingRuleAssertion Source # 
Instance details

Defined in LDAPv3

Methods

rnf :: MatchingRuleAssertion -> () #

type Rep MatchingRuleAssertion Source # 
Instance details

Defined in LDAPv3

type Rep MatchingRuleAssertion = D1 (MetaData "MatchingRuleAssertion" "LDAPv3" "LDAPv3-0.0.0.0-L06NoWaj9ma4LMfw7dYZJc" False) (C1 (MetaCons "MatchingRuleAssertion" PrefixI True) ((S1 (MetaSel (Just "_MatchingRuleAssertion'matchingRule") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (IMPLICIT (CONTEXTUAL 1) MatchingRuleId))) :*: S1 (MetaSel (Just "_MatchingRuleAssertion'type") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (IMPLICIT (CONTEXTUAL 2) AttributeDescription)))) :*: (S1 (MetaSel (Just "_MatchingRuleAssertion'matchValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (IMPLICIT (CONTEXTUAL 3) AssertionValue)) :*: S1 (MetaSel (Just "_MatchingRuleAssertion'dnAttributes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (IMPLICIT (CONTEXTUAL 4) BOOLEAN_DEFAULT_FALSE))))))

Search Result (RFC4511 Section 4.5.2)

data SearchResultEntry Source #

Search Result Entry (RFC4511 Section 4.5.2)

SearchResultEntry ::= [APPLICATION 4] SEQUENCE {
     objectName      LDAPDN,
     attributes      PartialAttributeList }
Instances
Eq SearchResultEntry Source # 
Instance details

Defined in LDAPv3

Show SearchResultEntry Source # 
Instance details

Defined in LDAPv3

Generic SearchResultEntry Source # 
Instance details

Defined in LDAPv3

Associated Types

type Rep SearchResultEntry :: Type -> Type #

NFData SearchResultEntry Source # 
Instance details

Defined in LDAPv3

Methods

rnf :: SearchResultEntry -> () #

type Rep SearchResultEntry Source # 
Instance details

Defined in LDAPv3

type Rep SearchResultEntry = D1 (MetaData "SearchResultEntry" "LDAPv3" "LDAPv3-0.0.0.0-L06NoWaj9ma4LMfw7dYZJc" False) (C1 (MetaCons "SearchResultEntry" PrefixI True) (S1 (MetaSel (Just "_SearchResultEntry'objectName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 LDAPDN) :*: S1 (MetaSel (Just "_SearchResultEntry'attributes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PartialAttributeList)))

type PartialAttributeList = [PartialAttribute] Source #

See SearchResultEntry

PartialAttributeList ::= SEQUENCE OF
                     partialAttribute PartialAttribute

newtype SearchResultReference Source #

Search Result Continuation Reference (RFC4511 Section 4.5.3)

SearchResultReference ::= [APPLICATION 19] SEQUENCE
                          SIZE (1..MAX) OF uri URI
Instances
Eq SearchResultReference Source # 
Instance details

Defined in LDAPv3

Show SearchResultReference Source # 
Instance details

Defined in LDAPv3

Generic SearchResultReference Source # 
Instance details

Defined in LDAPv3

Associated Types

type Rep SearchResultReference :: Type -> Type #

NFData SearchResultReference Source # 
Instance details

Defined in LDAPv3

Methods

rnf :: SearchResultReference -> () #

type Rep SearchResultReference Source # 
Instance details

Defined in LDAPv3

type Rep SearchResultReference = D1 (MetaData "SearchResultReference" "LDAPv3" "LDAPv3-0.0.0.0-L06NoWaj9ma4LMfw7dYZJc" True) (C1 (MetaCons "SearchResultReference" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty URI))))

type SearchResultDone = APPLICATION 5 `IMPLICIT` LDAPResult Source #

Search Result Done (RFC4511 Section 4.5.2)

SearchResultDone ::= [APPLICATION 5] LDAPResult

Modify Operation (RFC4511 Section 4.6)

data ModifyRequest Source #

Modify Operation (RFC4511 Section 4.6)

ModifyRequest ::= [APPLICATION 6] SEQUENCE {
     object          LDAPDN,
     changes         SEQUENCE OF change SEQUENCE {
          operation       ENUMERATED {
               add     (0),
               delete  (1),
               replace (2),
               ...  },
          modification    PartialAttribute } }
Instances
Eq ModifyRequest Source # 
Instance details

Defined in LDAPv3

Show ModifyRequest Source # 
Instance details

Defined in LDAPv3

Generic ModifyRequest Source # 
Instance details

Defined in LDAPv3

Associated Types

type Rep ModifyRequest :: Type -> Type #

NFData ModifyRequest Source # 
Instance details

Defined in LDAPv3

Methods

rnf :: ModifyRequest -> () #

type Rep ModifyRequest Source # 
Instance details

Defined in LDAPv3

type Rep ModifyRequest = D1 (MetaData "ModifyRequest" "LDAPv3" "LDAPv3-0.0.0.0-L06NoWaj9ma4LMfw7dYZJc" False) (C1 (MetaCons "ModifyRequest" PrefixI True) (S1 (MetaSel (Just "_ModifyRequest'object") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 LDAPDN) :*: S1 (MetaSel (Just "_ModifyRequest'changes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Change])))

data Change Source #

Instances
Eq Change Source # 
Instance details

Defined in LDAPv3

Methods

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

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

Show Change Source # 
Instance details

Defined in LDAPv3

Generic Change Source # 
Instance details

Defined in LDAPv3

Associated Types

type Rep Change :: Type -> Type #

Methods

from :: Change -> Rep Change x #

to :: Rep Change x -> Change #

NFData Change Source # 
Instance details

Defined in LDAPv3

Methods

rnf :: Change -> () #

type Rep Change Source # 
Instance details

Defined in LDAPv3

type Rep Change = D1 (MetaData "Change" "LDAPv3" "LDAPv3-0.0.0.0-L06NoWaj9ma4LMfw7dYZJc" False) (C1 (MetaCons "Change" PrefixI True) (S1 (MetaSel (Just "_Change'operation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Operation) :*: S1 (MetaSel (Just "_Change'modification") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PartialAttribute)))

data Operation Source #

Instances
Bounded Operation Source # 
Instance details

Defined in LDAPv3

Enum Operation Source # 
Instance details

Defined in LDAPv3

Eq Operation Source # 
Instance details

Defined in LDAPv3

Show Operation Source # 
Instance details

Defined in LDAPv3

Generic Operation Source # 
Instance details

Defined in LDAPv3

Associated Types

type Rep Operation :: Type -> Type #

NFData Operation Source # 
Instance details

Defined in LDAPv3

Methods

rnf :: Operation -> () #

type Rep Operation Source # 
Instance details

Defined in LDAPv3

type Rep Operation = D1 (MetaData "Operation" "LDAPv3" "LDAPv3-0.0.0.0-L06NoWaj9ma4LMfw7dYZJc" False) (C1 (MetaCons "Operation'add" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Operation'delete" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Operation'replace" PrefixI False) (U1 :: Type -> Type)))

type ModifyResponse = APPLICATION 7 `IMPLICIT` LDAPResult Source #

Modify Response (RFC4511 Section 4.6)

ModifyResponse ::= [APPLICATION 7] LDAPResult

Add Operation (RFC4511 Section 4.7)

data AddRequest Source #

Add Operation (RFC4511 Section 4.7)

AddRequest ::= [APPLICATION 8] SEQUENCE {
     entry           LDAPDN,
     attributes      AttributeList }
Instances
Eq AddRequest Source # 
Instance details

Defined in LDAPv3

Show AddRequest Source # 
Instance details

Defined in LDAPv3

Generic AddRequest Source # 
Instance details

Defined in LDAPv3

Associated Types

type Rep AddRequest :: Type -> Type #

NFData AddRequest Source # 
Instance details

Defined in LDAPv3

Methods

rnf :: AddRequest -> () #

type Rep AddRequest Source # 
Instance details

Defined in LDAPv3

type Rep AddRequest = D1 (MetaData "AddRequest" "LDAPv3" "LDAPv3-0.0.0.0-L06NoWaj9ma4LMfw7dYZJc" False) (C1 (MetaCons "AddRequest" PrefixI True) (S1 (MetaSel (Just "_AddRequest'entry") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 LDAPDN) :*: S1 (MetaSel (Just "_AddRequest'attributes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AttributeList)))

type AttributeList = [Attribute] Source #

Attribute List

AttributeList ::= SEQUENCE OF attribute Attribute

type AddResponse = APPLICATION 9 `IMPLICIT` LDAPResult Source #

Add Response (RFC4511 Section 4.7)

AddResponse ::= [APPLICATION 9] LDAPResult

Delete Operation (RFC4511 Section 4.8)

type DelRequest = APPLICATION 10 `IMPLICIT` LDAPDN Source #

Delete Operation (RFC4511 Section 4.8)

DelRequest ::= [APPLICATION 10] LDAPDN

type DelResponse = APPLICATION 11 `IMPLICIT` LDAPResult Source #

Delete Response (RFC4511 Section 4.8)

DelResponse ::= [APPLICATION 11] LDAPResult

Modify DN Operation (RFC4511 Section 4.9)

data ModifyDNRequest Source #

Modify DN Operation (RFC4511 Section 4.9)

ModifyDNRequest ::= [APPLICATION 12] SEQUENCE { entry LDAPDN, newrdn RelativeLDAPDN, deleteoldrdn BOOLEAN, newSuperior [0] LDAPDN OPTIONAL }

Instances
Eq ModifyDNRequest Source # 
Instance details

Defined in LDAPv3

Show ModifyDNRequest Source # 
Instance details

Defined in LDAPv3

Generic ModifyDNRequest Source # 
Instance details

Defined in LDAPv3

Associated Types

type Rep ModifyDNRequest :: Type -> Type #

NFData ModifyDNRequest Source # 
Instance details

Defined in LDAPv3

Methods

rnf :: ModifyDNRequest -> () #

type Rep ModifyDNRequest Source # 
Instance details

Defined in LDAPv3

type Rep ModifyDNRequest = D1 (MetaData "ModifyDNRequest" "LDAPv3" "LDAPv3-0.0.0.0-L06NoWaj9ma4LMfw7dYZJc" False) (C1 (MetaCons "ModifyDNRequest" PrefixI True) ((S1 (MetaSel (Just "_ModifyDNRequest'entry") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 LDAPDN) :*: S1 (MetaSel (Just "_ModifyDNRequest'newrdn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RelativeLDAPDN)) :*: (S1 (MetaSel (Just "_ModifyDNRequest'deleteoldrdn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: S1 (MetaSel (Just "_ModifyDNRequest'newSuperior") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (IMPLICIT (CONTEXTUAL 0) LDAPDN))))))

type ModifyDNResponse = APPLICATION 13 `IMPLICIT` LDAPResult Source #

Modify DN Response (RFC4511 Section 4.9)

ModifyDNResponse ::= [APPLICATION 13] LDAPResult

Compare Operation (RFC4511 Section 4.10)

data CompareRequest Source #

Compare Operation (RFC4511 Section 4.10)

CompareRequest ::= [APPLICATION 14] SEQUENCE {
     entry           LDAPDN,
     ava             AttributeValueAssertion }
Instances
Eq CompareRequest Source # 
Instance details

Defined in LDAPv3

Show CompareRequest Source # 
Instance details

Defined in LDAPv3

Generic CompareRequest Source # 
Instance details

Defined in LDAPv3

Associated Types

type Rep CompareRequest :: Type -> Type #

NFData CompareRequest Source # 
Instance details

Defined in LDAPv3

Methods

rnf :: CompareRequest -> () #

type Rep CompareRequest Source # 
Instance details

Defined in LDAPv3

type Rep CompareRequest = D1 (MetaData "CompareRequest" "LDAPv3" "LDAPv3-0.0.0.0-L06NoWaj9ma4LMfw7dYZJc" False) (C1 (MetaCons "CompareRequest" PrefixI True) (S1 (MetaSel (Just "_CompareRequest'entry") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 LDAPDN) :*: S1 (MetaSel (Just "_CompareRequest'ava") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AttributeValueAssertion)))

type CompareResponse = APPLICATION 15 `IMPLICIT` LDAPResult Source #

Compare Response (RFC4511 Section 4.10)

CompareResponse ::= [APPLICATION 15] LDAPResult

Abandon Operation (RFC4511 Section 4.11)

type AbandonRequest = APPLICATION 16 `IMPLICIT` MessageID Source #

Abandon Operation (RFC4511 Section 4.11)

AbandonRequest ::= [APPLICATION 16] MessageID

Extended Operation (RFC4511 Section 4.12)

data ExtendedRequest Source #

Extended Request (RFC4511 Section 4.12)

ExtendedRequest ::= [APPLICATION 23] SEQUENCE {
     requestName      [0] LDAPOID,
     requestValue     [1] OCTET STRING OPTIONAL }
Instances
Eq ExtendedRequest Source # 
Instance details

Defined in LDAPv3

Show ExtendedRequest Source # 
Instance details

Defined in LDAPv3

Generic ExtendedRequest Source # 
Instance details

Defined in LDAPv3

Associated Types

type Rep ExtendedRequest :: Type -> Type #

NFData ExtendedRequest Source # 
Instance details

Defined in LDAPv3

Methods

rnf :: ExtendedRequest -> () #

type Rep ExtendedRequest Source # 
Instance details

Defined in LDAPv3

type Rep ExtendedRequest = D1 (MetaData "ExtendedRequest" "LDAPv3" "LDAPv3-0.0.0.0-L06NoWaj9ma4LMfw7dYZJc" False) (C1 (MetaCons "ExtendedRequest" PrefixI True) (S1 (MetaSel (Just "_ExtendedRequest'responseName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (IMPLICIT (CONTEXTUAL 0) LDAPOID)) :*: S1 (MetaSel (Just "_ExtendedRequest'responseValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (IMPLICIT (CONTEXTUAL 1) OCTET_STRING)))))

data ExtendedResponse Source #

Extended Response (RFC4511 Section 4.12)

ExtendedResponse ::= [APPLICATION 24] SEQUENCE {
     COMPONENTS OF LDAPResult,
     responseName     [10] LDAPOID OPTIONAL,
     responseValue    [11] OCTET STRING OPTIONAL }
Instances
Eq ExtendedResponse Source # 
Instance details

Defined in LDAPv3

Show ExtendedResponse Source # 
Instance details

Defined in LDAPv3

Generic ExtendedResponse Source # 
Instance details

Defined in LDAPv3

Associated Types

type Rep ExtendedResponse :: Type -> Type #

NFData ExtendedResponse Source # 
Instance details

Defined in LDAPv3

Methods

rnf :: ExtendedResponse -> () #

type Rep ExtendedResponse Source # 
Instance details

Defined in LDAPv3

type Rep ExtendedResponse = D1 (MetaData "ExtendedResponse" "LDAPv3" "LDAPv3-0.0.0.0-L06NoWaj9ma4LMfw7dYZJc" False) (C1 (MetaCons "ExtendedResponse" PrefixI True) (S1 (MetaSel (Just "_ExtendedResponse'LDAPResult") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 LDAPResult) :*: (S1 (MetaSel (Just "_ExtendedResponse'responseName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (IMPLICIT (CONTEXTUAL 10) LDAPOID))) :*: S1 (MetaSel (Just "_ExtendedResponse'responseValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (IMPLICIT (CONTEXTUAL 11) OCTET_STRING))))))

Intermediate Response (RFC4511 Section 4.13)

data IntermediateResponse Source #

Intermediate Response (RFC4511 Section 4.13)

IntermediateResponse ::= [APPLICATION 25] SEQUENCE {
        responseName     [0] LDAPOID OPTIONAL,
        responseValue    [1] OCTET STRING OPTIONAL }
Instances
Eq IntermediateResponse Source # 
Instance details

Defined in LDAPv3

Show IntermediateResponse Source # 
Instance details

Defined in LDAPv3

Generic IntermediateResponse Source # 
Instance details

Defined in LDAPv3

Associated Types

type Rep IntermediateResponse :: Type -> Type #

NFData IntermediateResponse Source # 
Instance details

Defined in LDAPv3

Methods

rnf :: IntermediateResponse -> () #

type Rep IntermediateResponse Source # 
Instance details

Defined in LDAPv3

type Rep IntermediateResponse = D1 (MetaData "IntermediateResponse" "LDAPv3" "LDAPv3-0.0.0.0-L06NoWaj9ma4LMfw7dYZJc" False) (C1 (MetaCons "IntermediateResponse" PrefixI True) (S1 (MetaSel (Just "_IntermediateResponse'responseName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (IMPLICIT (CONTEXTUAL 0) LDAPOID))) :*: S1 (MetaSel (Just "_IntermediateResponse'responseValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (IMPLICIT (CONTEXTUAL 1) OCTET_STRING)))))

ASN.1 Helpers

type NULL = () Source #

ASN.1 NULL type

type OCTET_STRING = ByteString Source #

ASN.1 OCTET STRING type

data BOOLEAN_DEFAULT_FALSE Source #

This represents a BOOLEAN DEFAULT FALSE that is only ever serialized as True (hence why its only inhabitant is a true value)

This must be Maybe-wrapped to make any sense; the table below shows the mapping between Bool values and this construct.

Bool Maybe BOOLEAN_DEFAULT_FALSE
False Nothing
True Just BOOL_TRUE

Constructors

BOOL_TRUE 
Instances
Eq BOOLEAN_DEFAULT_FALSE Source # 
Instance details

Defined in Data.ASN1

Ord BOOLEAN_DEFAULT_FALSE Source # 
Instance details

Defined in Data.ASN1

Show BOOLEAN_DEFAULT_FALSE Source # 
Instance details

Defined in Data.ASN1

Generic BOOLEAN_DEFAULT_FALSE Source # 
Instance details

Defined in Data.ASN1

Associated Types

type Rep BOOLEAN_DEFAULT_FALSE :: Type -> Type #

NFData BOOLEAN_DEFAULT_FALSE Source # 
Instance details

Defined in Data.ASN1

Methods

rnf :: BOOLEAN_DEFAULT_FALSE -> () #

type Rep BOOLEAN_DEFAULT_FALSE Source # 
Instance details

Defined in Data.ASN1

type Rep BOOLEAN_DEFAULT_FALSE = D1 (MetaData "BOOLEAN_DEFAULT_FALSE" "Data.ASN1" "LDAPv3-0.0.0.0-L06NoWaj9ma4LMfw7dYZJc" False) (C1 (MetaCons "BOOL_TRUE" PrefixI False) (U1 :: Type -> Type))

newtype SET x Source #

ASN.1 SET OF type

Constructors

SET [x] 
Instances
Eq x => Eq (SET x) Source # 
Instance details

Defined in Data.ASN1

Methods

(==) :: SET x -> SET x -> Bool #

(/=) :: SET x -> SET x -> Bool #

Ord x => Ord (SET x) Source # 
Instance details

Defined in Data.ASN1

Methods

compare :: 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 #

max :: SET x -> SET x -> SET x #

min :: SET x -> SET x -> SET x #

Show x => Show (SET x) Source # 
Instance details

Defined in Data.ASN1

Methods

showsPrec :: Int -> SET x -> ShowS #

show :: SET x -> String #

showList :: [SET x] -> ShowS #

Generic (SET x) Source # 
Instance details

Defined in Data.ASN1

Associated Types

type Rep (SET x) :: Type -> Type #

Methods

from :: SET x -> Rep (SET x) x0 #

to :: Rep (SET x) x0 -> SET x #

NFData x => NFData (SET x) Source # 
Instance details

Defined in Data.ASN1

Methods

rnf :: SET x -> () #

Newtype (SET x) [x] Source # 
Instance details

Defined in Data.ASN1

Methods

pack :: [x] -> SET x #

unpack :: SET x -> [x] #

type Rep (SET x) Source # 
Instance details

Defined in Data.ASN1

type Rep (SET x) = D1 (MetaData "SET" "Data.ASN1" "LDAPv3-0.0.0.0-L06NoWaj9ma4LMfw7dYZJc" True) (C1 (MetaCons "SET" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [x])))

newtype SET1 x Source #

ASN.1 SET SIZE (1..MAX) OF type

Constructors

SET1 (NonEmpty x) 
Instances
Eq x => Eq (SET1 x) Source # 
Instance details

Defined in Data.ASN1

Methods

(==) :: SET1 x -> SET1 x -> Bool #

(/=) :: SET1 x -> SET1 x -> Bool #

Ord x => Ord (SET1 x) Source # 
Instance details

Defined in Data.ASN1

Methods

compare :: 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 #

max :: SET1 x -> SET1 x -> SET1 x #

min :: SET1 x -> SET1 x -> SET1 x #

Show x => Show (SET1 x) Source # 
Instance details

Defined in Data.ASN1

Methods

showsPrec :: Int -> SET1 x -> ShowS #

show :: SET1 x -> String #

showList :: [SET1 x] -> ShowS #

Generic (SET1 x) Source # 
Instance details

Defined in Data.ASN1

Associated Types

type Rep (SET1 x) :: Type -> Type #

Methods

from :: SET1 x -> Rep (SET1 x) x0 #

to :: Rep (SET1 x) x0 -> SET1 x #

NFData x => NFData (SET1 x) Source # 
Instance details

Defined in Data.ASN1

Methods

rnf :: SET1 x -> () #

Newtype (SET1 x) (NonEmpty x) Source # 
Instance details

Defined in Data.ASN1

Methods

pack :: NonEmpty x -> SET1 x #

unpack :: SET1 x -> NonEmpty x #

type Rep (SET1 x) Source # 
Instance details

Defined in Data.ASN1

type Rep (SET1 x) = D1 (MetaData "SET1" "Data.ASN1" "LDAPv3-0.0.0.0-L06NoWaj9ma4LMfw7dYZJc" True) (C1 (MetaCons "SET1" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty x))))

ASN.1 type-level tagging

newtype EXPLICIT (tag :: TagK) x Source #

ASN.1 EXPLICIT Annotation

Constructors

EXPLICIT x 
Instances
Enum x => Enum (EXPLICIT tag x) Source # 
Instance details

Defined in Data.ASN1

Methods

succ :: EXPLICIT tag x -> EXPLICIT tag x #

pred :: EXPLICIT tag x -> EXPLICIT tag x #

toEnum :: Int -> EXPLICIT tag x #

fromEnum :: EXPLICIT tag x -> Int #

enumFrom :: EXPLICIT tag x -> [EXPLICIT tag x] #

enumFromThen :: EXPLICIT tag x -> EXPLICIT tag x -> [EXPLICIT tag x] #

enumFromTo :: EXPLICIT tag x -> EXPLICIT tag x -> [EXPLICIT tag x] #

enumFromThenTo :: EXPLICIT tag x -> EXPLICIT tag x -> EXPLICIT tag x -> [EXPLICIT tag x] #

Eq x => Eq (EXPLICIT tag x) Source # 
Instance details

Defined in Data.ASN1

Methods

(==) :: EXPLICIT tag x -> EXPLICIT tag x -> Bool #

(/=) :: EXPLICIT tag x -> EXPLICIT tag x -> Bool #

Num x => Num (EXPLICIT tag x) Source # 
Instance details

Defined in Data.ASN1

Methods

(+) :: 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 #

negate :: EXPLICIT tag x -> EXPLICIT tag x #

abs :: EXPLICIT tag x -> EXPLICIT tag x #

signum :: EXPLICIT tag x -> EXPLICIT tag x #

fromInteger :: Integer -> EXPLICIT tag x #

Ord x => Ord (EXPLICIT tag x) Source # 
Instance details

Defined in Data.ASN1

Methods

compare :: 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 #

max :: EXPLICIT tag x -> EXPLICIT tag x -> EXPLICIT tag x #

min :: EXPLICIT tag x -> EXPLICIT tag x -> EXPLICIT tag x #

Show x => Show (EXPLICIT tag x) Source # 
Instance details

Defined in Data.ASN1

Methods

showsPrec :: Int -> EXPLICIT tag x -> ShowS #

show :: EXPLICIT tag x -> String #

showList :: [EXPLICIT tag x] -> ShowS #

IsString x => IsString (EXPLICIT tag x) Source # 
Instance details

Defined in Data.ASN1

Methods

fromString :: String -> EXPLICIT tag x #

Generic (EXPLICIT tag x) Source # 
Instance details

Defined in Data.ASN1

Associated Types

type Rep (EXPLICIT tag x) :: Type -> Type #

Methods

from :: EXPLICIT tag x -> Rep (EXPLICIT tag x) x0 #

to :: Rep (EXPLICIT tag x) x0 -> EXPLICIT tag x #

NFData x => NFData (EXPLICIT tag x) Source # 
Instance details

Defined in Data.ASN1

Methods

rnf :: EXPLICIT tag x -> () #

Newtype (EXPLICIT tag x) x Source # 
Instance details

Defined in Data.ASN1

Methods

pack :: x -> EXPLICIT tag x #

unpack :: EXPLICIT tag x -> x #

type Rep (EXPLICIT tag x) Source # 
Instance details

Defined in Data.ASN1

type Rep (EXPLICIT tag x) = D1 (MetaData "EXPLICIT" "Data.ASN1" "LDAPv3-0.0.0.0-L06NoWaj9ma4LMfw7dYZJc" True) (C1 (MetaCons "EXPLICIT" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 x)))

newtype IMPLICIT (tag :: TagK) x Source #

ASN.1 IMPLICIT Annotation

Constructors

IMPLICIT x 
Instances
Enum x => Enum (IMPLICIT tag x) Source # 
Instance details

Defined in Data.ASN1

Methods

succ :: IMPLICIT tag x -> IMPLICIT tag x #

pred :: IMPLICIT tag x -> IMPLICIT tag x #

toEnum :: Int -> IMPLICIT tag x #

fromEnum :: IMPLICIT tag x -> Int #

enumFrom :: IMPLICIT tag x -> [IMPLICIT tag x] #

enumFromThen :: IMPLICIT tag x -> IMPLICIT tag x -> [IMPLICIT tag x] #

enumFromTo :: IMPLICIT tag x -> IMPLICIT tag x -> [IMPLICIT tag x] #

enumFromThenTo :: IMPLICIT tag x -> IMPLICIT tag x -> IMPLICIT tag x -> [IMPLICIT tag x] #

Eq x => Eq (IMPLICIT tag x) Source # 
Instance details

Defined in Data.ASN1

Methods

(==) :: IMPLICIT tag x -> IMPLICIT tag x -> Bool #

(/=) :: IMPLICIT tag x -> IMPLICIT tag x -> Bool #

Num x => Num (IMPLICIT tag x) Source # 
Instance details

Defined in Data.ASN1

Methods

(+) :: 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 #

negate :: IMPLICIT tag x -> IMPLICIT tag x #

abs :: IMPLICIT tag x -> IMPLICIT tag x #

signum :: IMPLICIT tag x -> IMPLICIT tag x #

fromInteger :: Integer -> IMPLICIT tag x #

Ord x => Ord (IMPLICIT tag x) Source # 
Instance details

Defined in Data.ASN1

Methods

compare :: 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 #

max :: IMPLICIT tag x -> IMPLICIT tag x -> IMPLICIT tag x #

min :: IMPLICIT tag x -> IMPLICIT tag x -> IMPLICIT tag x #

Show x => Show (IMPLICIT tag x) Source # 
Instance details

Defined in Data.ASN1

Methods

showsPrec :: Int -> IMPLICIT tag x -> ShowS #

show :: IMPLICIT tag x -> String #

showList :: [IMPLICIT tag x] -> ShowS #

IsString x => IsString (IMPLICIT tag x) Source # 
Instance details

Defined in Data.ASN1

Methods

fromString :: String -> IMPLICIT tag x #

Generic (IMPLICIT tag x) Source # 
Instance details

Defined in Data.ASN1

Associated Types

type Rep (IMPLICIT tag x) :: Type -> Type #

Methods

from :: IMPLICIT tag x -> Rep (IMPLICIT tag x) x0 #

to :: Rep (IMPLICIT tag x) x0 -> IMPLICIT tag x #

NFData x => NFData (IMPLICIT tag x) Source # 
Instance details

Defined in Data.ASN1

Methods

rnf :: IMPLICIT tag x -> () #

Newtype (IMPLICIT tag x) x Source # 
Instance details

Defined in Data.ASN1

Methods

pack :: x -> IMPLICIT tag x #

unpack :: IMPLICIT tag x -> x #

type Rep (IMPLICIT tag x) Source # 
Instance details

Defined in Data.ASN1

type Rep (IMPLICIT tag x) = D1 (MetaData "IMPLICIT" "Data.ASN1" "LDAPv3-0.0.0.0-L06NoWaj9ma4LMfw7dYZJc" True) (C1 (MetaCons "IMPLICIT" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 x)))

data TagK Source #

Type-level promoted Tag

Unsigned integer sub-type

type UIntBounds lb ub t = (KnownNat lb, KnownNat ub, lb <= ub, IsBelowMaxBound ub (IntBaseType t) ~ True) Source #

Constraint encoding type-level invariants for UInt

data UInt (lb :: Nat) (ub :: Nat) t Source #

Unsigned integer sub-type

Instances
(UIntBounds lb ub t, Num t) => Bounded (UInt lb ub t) Source # 
Instance details

Defined in Data.Int.Subtypes

Methods

minBound :: UInt lb ub t #

maxBound :: UInt lb ub t #

Eq t => Eq (UInt lb ub t) Source # 
Instance details

Defined in Data.Int.Subtypes

Methods

(==) :: UInt lb ub t -> UInt lb ub t -> Bool #

(/=) :: UInt lb ub t -> UInt lb ub t -> Bool #

(UIntBounds lb ub t, Integral t, Ord t) => Num (UInt lb ub t) Source # 
Instance details

Defined in Data.Int.Subtypes

Methods

(+) :: UInt lb ub t -> UInt lb ub t -> UInt lb ub t #

(-) :: UInt lb ub t -> UInt lb ub t -> UInt lb ub t #

(*) :: UInt lb ub t -> UInt lb ub t -> UInt lb ub t #

negate :: UInt lb ub t -> UInt lb ub t #

abs :: UInt lb ub t -> UInt lb ub t #

signum :: UInt lb ub t -> UInt lb ub t #

fromInteger :: Integer -> UInt lb ub t #

Ord t => Ord (UInt lb ub t) Source # 
Instance details

Defined in Data.Int.Subtypes

Methods

compare :: UInt lb ub t -> UInt lb ub t -> Ordering #

(<) :: UInt lb ub t -> UInt lb ub t -> Bool #

(<=) :: UInt lb ub t -> UInt lb ub t -> Bool #

(>) :: UInt lb ub t -> UInt lb ub t -> Bool #

(>=) :: UInt lb ub t -> UInt lb ub t -> Bool #

max :: UInt lb ub t -> UInt lb ub t -> UInt lb ub t #

min :: UInt lb ub t -> UInt lb ub t -> UInt lb ub t #

Show t => Show (UInt lb ub t) Source # 
Instance details

Defined in Data.Int.Subtypes

Methods

showsPrec :: Int -> UInt lb ub t -> ShowS #

show :: UInt lb ub t -> String #

showList :: [UInt lb ub t] -> ShowS #

NFData t => NFData (UInt lb ub t) Source # 
Instance details

Defined in Data.Int.Subtypes

Methods

rnf :: UInt lb ub t -> () #

fromUInt :: UInt lb ub t -> t Source #

Coerce integer sub-type into its base-type

toUInt :: forall lb ub t. (UIntBounds lb ub t, Num t, Ord t) => t -> Either ArithException (UInt lb ub t) Source #

Try to coerce a base-type into its UInt sub-type

If out of range, Left Underflow or Right Overflow will be returned.