ldap-client-0.4.1: Pure Haskell LDAP Client Library

Safe HaskellSafe
LanguageHaskell2010

Ldap.Asn1.Type

Synopsis

Documentation

data LdapMessage op Source #

Message envelope. (Section 4.1.1.)

Instances
Eq op => Eq (LdapMessage op) Source # 
Instance details

Defined in Ldap.Asn1.Type

Methods

(==) :: LdapMessage op -> LdapMessage op -> Bool #

(/=) :: LdapMessage op -> LdapMessage op -> Bool #

Show op => Show (LdapMessage op) Source # 
Instance details

Defined in Ldap.Asn1.Type

ToAsn1 op => ToAsn1 (LdapMessage op) Source #
LDAPMessage ::= SEQUENCE {
     messageID       MessageID,
     protocolOp      CHOICE {
          bindRequest           BindRequest,
          bindResponse          BindResponse,
          unbindRequest         UnbindRequest,
          searchRequest         SearchRequest,
          searchResEntry        SearchResultEntry,
          searchResDone         SearchResultDone,
          searchResRef          SearchResultReference,
          addRequest            AddRequest,
          addResponse           AddResponse,
          ... },
     controls       [0] Controls OPTIONAL }
Instance details

Defined in Ldap.Asn1.ToAsn1

Methods

toAsn1 :: LdapMessage op -> Endo [ASN1] Source #

FromAsn1 op => FromAsn1 (LdapMessage op) Source #
LDAPMessage ::= SEQUENCE {
     messageID       MessageID,
     protocolOp      CHOICE {
          bindRequest           BindRequest,
          bindResponse          BindResponse,
          unbindRequest         UnbindRequest,
          searchRequest         SearchRequest,
          searchResEntry        SearchResultEntry,
          searchResDone         SearchResultDone,
          searchResRef          SearchResultReference,
          addRequest            AddRequest,
          addResponse           AddResponse,
          ... },
     controls       [0] Controls OPTIONAL }
Instance details

Defined in Ldap.Asn1.FromAsn1

Methods

fromAsn1 :: Parser [ASN1] (LdapMessage op)

newtype Id Source #

Every message being processed has a unique non-zero integer ID. (Section 4.1.1.1.)

Constructors

Id 

Fields

Instances
Eq Id Source # 
Instance details

Defined in Ldap.Asn1.Type

Methods

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

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

Ord Id Source # 
Instance details

Defined in Ldap.Asn1.Type

Methods

compare :: Id -> Id -> Ordering #

(<) :: Id -> Id -> Bool #

(<=) :: Id -> Id -> Bool #

(>) :: Id -> Id -> Bool #

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

max :: Id -> Id -> Id #

min :: Id -> Id -> Id #

Show Id Source # 
Instance details

Defined in Ldap.Asn1.Type

Methods

showsPrec :: Int -> Id -> ShowS #

show :: Id -> String #

showList :: [Id] -> ShowS #

ToAsn1 Id Source #
MessageID ::= INTEGER (0 ..  maxInt)
Instance details

Defined in Ldap.Asn1.ToAsn1

Methods

toAsn1 :: Id -> Endo [ASN1] Source #

FromAsn1 Id Source #
MessageID ::= INTEGER (0 ..  maxInt)
Instance details

Defined in Ldap.Asn1.FromAsn1

Methods

fromAsn1 :: Parser [ASN1] Id

data ProtocolClientOp Source #

Client requests. The RFC doesn't make a difference between ProtocolClientOp and ProtocolServerOp but it's useful to distinguish between them in Haskell.

Instances
Eq ProtocolClientOp Source # 
Instance details

Defined in Ldap.Asn1.Type

Show ProtocolClientOp Source # 
Instance details

Defined in Ldap.Asn1.Type

ToAsn1 ProtocolClientOp Source #
BindRequest ::= [APPLICATION 0] SEQUENCE {
     version                 INTEGER (1 ..  127),
     name                    LDAPDN,
     authentication          AuthenticationChoice }
UnbindRequest ::= [APPLICATION 2] NULL
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 }
ModifyRequest ::= [APPLICATION 6] SEQUENCE {
     object          LDAPDN,
     changes         SEQUENCE OF change SEQUENCE {
          operation       ENUMERATED {
               add     (0),
               delete  (1),
               replace (2),
               ...  },
          modification    PartialAttribute } }
AddRequest ::= [APPLICATION 8] SEQUENCE {
     entry           LDAPDN,
     attributes      AttributeList }
DelRequest ::= [APPLICATION 10] LDAPDN
ModifyDNRequest ::= [APPLICATION 12] SEQUENCE {
     entry           LDAPDN,
     newrdn          RelativeLDAPDN,
     deleteoldrdn    BOOLEAN,
     newSuperior     [0] LDAPDN OPTIONAL }
CompareRequest ::= [APPLICATION 14] SEQUENCE {
     entry           LDAPDN,
     ava             AttributeValueAssertion }
ExtendedRequest ::= [APPLICATION 23] SEQUENCE {
     requestName      [0] LDAPOID,
     requestValue     [1] OCTET STRING OPTIONAL }
Instance details

Defined in Ldap.Asn1.ToAsn1

data ProtocolServerOp Source #

Server responses. The RFC doesn't make a difference between ProtocolClientOp and ProtocolServerOp but it's useful to distinguish between them in Haskell.

Instances
Eq ProtocolServerOp Source # 
Instance details

Defined in Ldap.Asn1.Type

Show ProtocolServerOp Source # 
Instance details

Defined in Ldap.Asn1.Type

FromAsn1 ProtocolServerOp Source #
BindResponse ::= [APPLICATION 1] SEQUENCE {
     COMPONENTS OF LDAPResult,
     serverSaslCreds    [7] OCTET STRING OPTIONAL }
SearchResultEntry ::= [APPLICATION 4] SEQUENCE {
     objectName      LDAPDN,
     attributes      PartialAttributeList }
SearchResultReference ::= [APPLICATION 19] SEQUENCE
                          SIZE (1..MAX) OF uri URI
SearchResultDone ::= [APPLICATION 5] LDAPResult
ModifyResponse ::= [APPLICATION 7] LDAPResult
AddResponse ::= [APPLICATION 9] LDAPResult
DelResponse ::= [APPLICATION 11] LDAPResult
ModifyDNResponse ::= [APPLICATION 13] LDAPResult
CompareResponse ::= [APPLICATION 15] LDAPResult
ExtendedResponse ::= [APPLICATION 24] SEQUENCE {
     COMPONENTS OF LDAPResult,
     responseName     [10] LDAPOID OPTIONAL,
     responseValue    [11] OCTET STRING OPTIONAL }
IntermediateResponse ::= [APPLICATION 25] SEQUENCE {
     responseName     [0] LDAPOID OPTIONAL,
     responseValue    [1] OCTET STRING OPTIONAL }
Instance details

Defined in Ldap.Asn1.FromAsn1

Methods

fromAsn1 :: Parser [ASN1] ProtocolServerOp

data AuthenticationChoice Source #

Not really a choice until SASL is supported.

Instances
Eq AuthenticationChoice Source # 
Instance details

Defined in Ldap.Asn1.Type

Show AuthenticationChoice Source # 
Instance details

Defined in Ldap.Asn1.Type

ToAsn1 AuthenticationChoice Source #
AuthenticationChoice ::= CHOICE {
     simple                  [0] OCTET STRING,
     sasl                    [3] SaslCredentials,
     ...  }


SaslCredentials ::= SEQUENCE {
     mechanism               LDAPString,
     credentials             OCTET STRING OPTIONAL }
Instance details

Defined in Ldap.Asn1.ToAsn1

data SaslMechanism Source #

SASL Mechanism, for now only SASL EXTERNAL is supported

Constructors

External 

data Scope Source #

Scope of the search to be performed.

Constructors

BaseObject

Constrained to the entry named by baseObject.

SingleLevel

Constrained to the immediate subordinates of the entry named by baseObject.

WholeSubtree

Constrained to the entry named by baseObject and to all its subordinates.

Instances
Eq Scope Source # 
Instance details

Defined in Ldap.Asn1.Type

Methods

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

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

Show Scope Source # 
Instance details

Defined in Ldap.Asn1.Type

Methods

showsPrec :: Int -> Scope -> ShowS #

show :: Scope -> String #

showList :: [Scope] -> ShowS #

data DerefAliases Source #

An indicator as to whether or not alias entries (as defined in [RFC4512]) are to be dereferenced during stages of the Search operation.

Constructors

NeverDerefAliases

Do not dereference aliases in searching or in locating the base object of the Search.

DerefInSearching

While searching subordinates of the base object, dereference any alias within the search scope.

DerefFindingBaseObject

Dereference aliases in locating the base object of the Search.

DerefAlways

Dereference aliases both in searching and in locating the base object of the Search.

Instances
Eq DerefAliases Source # 
Instance details

Defined in Ldap.Asn1.Type

Show DerefAliases Source # 
Instance details

Defined in Ldap.Asn1.Type

data Filter Source #

Conditions that must be fulfilled in order for the Search to match a given entry.

Constructors

And !(NonEmpty Filter)

All filters evaluate to TRUE

Or !(NonEmpty Filter)

Any filter evaluates to TRUE

Not !Filter

Filter evaluates to FALSE

EqualityMatch !AttributeValueAssertion

EQUALITY rule returns TRUE

Substrings !SubstringFilter

SUBSTR rule returns TRUE

GreaterOrEqual !AttributeValueAssertion

ORDERING rule returns FALSE

LessOrEqual !AttributeValueAssertion

ORDERING or EQUALITY rule returns TRUE

Present !AttributeDescription

Attribute is present in the entry

ApproxMatch !AttributeValueAssertion

Same as EqualityMatch for most servers

ExtensibleMatch !MatchingRuleAssertion 
Instances
Eq Filter Source # 
Instance details

Defined in Ldap.Asn1.Type

Methods

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

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

Show Filter Source # 
Instance details

Defined in Ldap.Asn1.Type

ToAsn1 Filter Source #
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,
     ...  }
Instance details

Defined in Ldap.Asn1.ToAsn1

Methods

toAsn1 :: Filter -> Endo [ASN1] Source #

data SubstringFilter Source #

Instances
Eq SubstringFilter Source # 
Instance details

Defined in Ldap.Asn1.Type

Show SubstringFilter Source # 
Instance details

Defined in Ldap.Asn1.Type

ToAsn1 SubstringFilter Source #
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
     }
Instance details

Defined in Ldap.Asn1.ToAsn1

data Substring Source #

Instances
Eq Substring Source # 
Instance details

Defined in Ldap.Asn1.Type

Show Substring Source # 
Instance details

Defined in Ldap.Asn1.Type

data MatchingRuleAssertion Source #

Instances
Eq MatchingRuleAssertion Source # 
Instance details

Defined in Ldap.Asn1.Type

Show MatchingRuleAssertion Source # 
Instance details

Defined in Ldap.Asn1.Type

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

Defined in Ldap.Asn1.ToAsn1

newtype MatchingRuleId Source #

Matching rules are defined in Section 4.1.3 of [RFC4512]. A matching rule is identified in the protocol by the printable representation of either its numericoid or one of its short name descriptors [RFC4512], e.g., caseIgnoreMatch or '2.5.13.2'. (Section 4.1.8.)

Instances
Eq MatchingRuleId Source # 
Instance details

Defined in Ldap.Asn1.Type

Show MatchingRuleId Source # 
Instance details

Defined in Ldap.Asn1.Type

ToAsn1 MatchingRuleId Source #
MatchingRuleId ::= LDAPString
Instance details

Defined in Ldap.Asn1.ToAsn1

newtype AttributeSelection Source #

Instances
Eq AttributeSelection Source # 
Instance details

Defined in Ldap.Asn1.Type

Show AttributeSelection Source # 
Instance details

Defined in Ldap.Asn1.Type

ToAsn1 AttributeSelection Source #
AttributeSelection ::= SEQUENCE OF selector LDAPString
Instance details

Defined in Ldap.Asn1.ToAsn1

newtype AttributeList Source #

Constructors

AttributeList [Attribute] 
Instances
Eq AttributeList Source # 
Instance details

Defined in Ldap.Asn1.Type

Show AttributeList Source # 
Instance details

Defined in Ldap.Asn1.Type

ToAsn1 AttributeList Source #
AttributeList ::= SEQUENCE OF attribute Attribute
Instance details

Defined in Ldap.Asn1.ToAsn1

newtype PartialAttributeList Source #

Instances
Eq PartialAttributeList Source # 
Instance details

Defined in Ldap.Asn1.Type

Show PartialAttributeList Source # 
Instance details

Defined in Ldap.Asn1.Type

FromAsn1 PartialAttributeList Source #
PartialAttributeList ::= SEQUENCE OF partialAttribute PartialAttribute
Instance details

Defined in Ldap.Asn1.FromAsn1

newtype Controls Source #

Constructors

Controls [Control] 
Instances
Eq Controls Source # 
Instance details

Defined in Ldap.Asn1.Type

Show Controls Source # 
Instance details

Defined in Ldap.Asn1.Type

ToAsn1 Controls Source #
Controls ::= SEQUENCE OF control Control
Instance details

Defined in Ldap.Asn1.ToAsn1

Methods

toAsn1 :: Controls -> Endo [ASN1] Source #

data Control Source #

Constructors

Control !LdapOid !Bool !(Maybe ByteString) 
Instances
Eq Control Source # 
Instance details

Defined in Ldap.Asn1.Type

Methods

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

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

Show Control Source # 
Instance details

Defined in Ldap.Asn1.Type

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

Defined in Ldap.Asn1.ToAsn1

Methods

toAsn1 :: Control -> Endo [ASN1] Source #

data LdapResult Source #

Instances
Eq LdapResult Source # 
Instance details

Defined in Ldap.Asn1.Type

Show LdapResult Source # 
Instance details

Defined in Ldap.Asn1.Type

FromAsn1 LdapResult Source #
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 }
Instance details

Defined in Ldap.Asn1.FromAsn1

Methods

fromAsn1 :: Parser [ASN1] LdapResult

newtype AttributeDescription Source #

Instances
Eq AttributeDescription Source # 
Instance details

Defined in Ldap.Asn1.Type

Show AttributeDescription Source # 
Instance details

Defined in Ldap.Asn1.Type

ToAsn1 AttributeDescription Source #
AttributeDescription ::= LDAPString
Instance details

Defined in Ldap.Asn1.ToAsn1

FromAsn1 AttributeDescription Source #
AttributeDescription ::= LDAPString
Instance details

Defined in Ldap.Asn1.FromAsn1

newtype AttributeValue Source #

Instances
Eq AttributeValue Source # 
Instance details

Defined in Ldap.Asn1.Type

Show AttributeValue Source # 
Instance details

Defined in Ldap.Asn1.Type

ToAsn1 AttributeValue Source #
AttributeValue ::= OCTET STRING
Instance details

Defined in Ldap.Asn1.ToAsn1

FromAsn1 AttributeValue Source #
AttributeValue ::= OCTET STRING
Instance details

Defined in Ldap.Asn1.FromAsn1

Methods

fromAsn1 :: Parser [ASN1] AttributeValue

data AttributeValueAssertion Source #

Instances
Eq AttributeValueAssertion Source # 
Instance details

Defined in Ldap.Asn1.Type

Show AttributeValueAssertion Source # 
Instance details

Defined in Ldap.Asn1.Type

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

Defined in Ldap.Asn1.ToAsn1

newtype AssertionValue Source #

Instances
Eq AssertionValue Source # 
Instance details

Defined in Ldap.Asn1.Type

Show AssertionValue Source # 
Instance details

Defined in Ldap.Asn1.Type

ToAsn1 AssertionValue Source #
AssertionValue ::= OCTET STRING
Instance details

Defined in Ldap.Asn1.ToAsn1

data Attribute Source #

Instances
Eq Attribute Source # 
Instance details

Defined in Ldap.Asn1.Type

Show Attribute Source # 
Instance details

Defined in Ldap.Asn1.Type

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

Defined in Ldap.Asn1.ToAsn1

Methods

toAsn1 :: Attribute -> Endo [ASN1] Source #

data PartialAttribute Source #

Instances
Eq PartialAttribute Source # 
Instance details

Defined in Ldap.Asn1.Type

Show PartialAttribute Source # 
Instance details

Defined in Ldap.Asn1.Type

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

Defined in Ldap.Asn1.ToAsn1

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

Defined in Ldap.Asn1.FromAsn1

Methods

fromAsn1 :: Parser [ASN1] PartialAttribute

newtype LdapDn Source #

An LDAPDN is defined to be the representation of a Distinguished Name (DN) after encoding according to the specification in [RFC4514].

Constructors

LdapDn LdapString 
Instances
Eq LdapDn Source # 
Instance details

Defined in Ldap.Asn1.Type

Methods

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

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

Show LdapDn Source # 
Instance details

Defined in Ldap.Asn1.Type

ToAsn1 LdapDn Source #
LDAPDN ::= LDAPString -- Constrained to <distinguishedName>
Instance details

Defined in Ldap.Asn1.ToAsn1

Methods

toAsn1 :: LdapDn -> Endo [ASN1] Source #

FromAsn1 LdapDn Source #
LDAPDN ::= LDAPString
Instance details

Defined in Ldap.Asn1.FromAsn1

Methods

fromAsn1 :: Parser [ASN1] LdapDn

newtype RelativeLdapDn Source #

A RelativeLDAPDN is defined to be the representation of a Relative Distinguished Name (RDN) after encoding according to the specification in [RFC4514].

Instances
Eq RelativeLdapDn Source # 
Instance details

Defined in Ldap.Asn1.Type

Show RelativeLdapDn Source # 
Instance details

Defined in Ldap.Asn1.Type

ToAsn1 RelativeLdapDn Source #
RelativeLDAPDN ::= LDAPString -- Constrained to <name-component>
Instance details

Defined in Ldap.Asn1.ToAsn1

newtype ReferralUris Source #

Constructors

ReferralUris (NonEmpty Uri) 
Instances
Eq ReferralUris Source # 
Instance details

Defined in Ldap.Asn1.Type

Show ReferralUris Source # 
Instance details

Defined in Ldap.Asn1.Type

FromAsn1 ReferralUris Source #
Referral ::= SEQUENCE SIZE (1..MAX) OF uri URI
Instance details

Defined in Ldap.Asn1.FromAsn1

Methods

fromAsn1 :: Parser [ASN1] ReferralUris

newtype Uri Source #

Constructors

Uri LdapString 
Instances
Eq Uri Source # 
Instance details

Defined in Ldap.Asn1.Type

Methods

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

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

Show Uri Source # 
Instance details

Defined in Ldap.Asn1.Type

Methods

showsPrec :: Int -> Uri -> ShowS #

show :: Uri -> String #

showList :: [Uri] -> ShowS #

FromAsn1 Uri Source #
URI ::= LDAPString
Instance details

Defined in Ldap.Asn1.FromAsn1

Methods

fromAsn1 :: Parser [ASN1] Uri

data Operation Source #

Constructors

Add 
Delete 
Replace 
Instances
Eq Operation Source # 
Instance details

Defined in Ldap.Asn1.Type

Show Operation Source # 
Instance details

Defined in Ldap.Asn1.Type

newtype LdapString Source #

The LDAPString is a notational convenience to indicate that, although strings of LDAPString type encode as ASN.1 OCTET STRING types, the [ISO10646] character set (a superset of [Unicode]) is used, encoded following the UTF-8 [RFC3629] algorithm. (Section 4.1.2.)

Constructors

LdapString Text 
Instances
Eq LdapString Source # 
Instance details

Defined in Ldap.Asn1.Type

Show LdapString Source # 
Instance details

Defined in Ldap.Asn1.Type

ToAsn1 LdapString Source #
LDAPString ::= OCTET STRING -- UTF-8 encoded
Instance details

Defined in Ldap.Asn1.ToAsn1

FromAsn1 LdapString Source #
LDAPString ::= OCTET STRING -- UTF-8 encoded,
Instance details

Defined in Ldap.Asn1.FromAsn1

Methods

fromAsn1 :: Parser [ASN1] LdapString

newtype LdapOid Source #

The LDAPOID is a notational convenience to indicate that the permitted value of this string is a (UTF-8 encoded) dotted-decimal representation of an OBJECT IDENTIFIER. Although an LDAPOID is encoded as an OCTET STRING, values are limited to the definition of <numericoid> given in Section 1.4 of [RFC4512].

Constructors

LdapOid Text 
Instances
Eq LdapOid Source # 
Instance details

Defined in Ldap.Asn1.Type

Methods

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

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

Show LdapOid Source # 
Instance details

Defined in Ldap.Asn1.Type

ToAsn1 LdapOid Source #
LDAPOID ::= OCTET STRING -- Constrained to <numericoid>
Instance details

Defined in Ldap.Asn1.ToAsn1

Methods

toAsn1 :: LdapOid -> Endo [ASN1] Source #

FromAsn1 LdapOid Source #
LDAPOID ::= OCTET STRING -- Constrained to <numericoid>
Instance details

Defined in Ldap.Asn1.FromAsn1

Methods

fromAsn1 :: Parser [ASN1] LdapOid