| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Ldap.Asn1.Type
Synopsis
- data LdapMessage op = LdapMessage {
- ldapMessageId :: !Id
 - ldapMessageOp :: !op
 - ldapMessageControls :: !(Maybe Controls)
 
 - newtype Id = Id {}
 - data ProtocolClientOp
- = BindRequest !Int8 !LdapDn !AuthenticationChoice
 - | UnbindRequest
 - | SearchRequest !LdapDn !Scope !DerefAliases !Int32 !Int32 !Bool !Filter !AttributeSelection
 - | ModifyRequest !LdapDn ![(Operation, PartialAttribute)]
 - | AddRequest !LdapDn !AttributeList
 - | DeleteRequest !LdapDn
 - | ModifyDnRequest !LdapDn !RelativeLdapDn !Bool !(Maybe LdapDn)
 - | CompareRequest !LdapDn !AttributeValueAssertion
 - | ExtendedRequest !LdapOid !(Maybe ByteString)
 
 - data ProtocolServerOp
- = BindResponse !LdapResult !(Maybe ByteString)
 - | SearchResultEntry !LdapDn !PartialAttributeList
 - | SearchResultReference !(NonEmpty Uri)
 - | SearchResultDone !LdapResult
 - | ModifyResponse !LdapResult
 - | AddResponse !LdapResult
 - | DeleteResponse !LdapResult
 - | ModifyDnResponse !LdapResult
 - | CompareResponse !LdapResult
 - | ExtendedResponse !LdapResult !(Maybe LdapOid) !(Maybe ByteString)
 - | IntermediateResponse !(Maybe LdapOid) !(Maybe ByteString)
 
 - data AuthenticationChoice
- = Simple !ByteString
 - | Sasl !SaslMechanism !(Maybe Text)
 
 - data SaslMechanism = External
 - data Scope
 - data DerefAliases
 - data Filter
- = And !(NonEmpty Filter)
 - | Or !(NonEmpty Filter)
 - | Not !Filter
 - | EqualityMatch !AttributeValueAssertion
 - | Substrings !SubstringFilter
 - | GreaterOrEqual !AttributeValueAssertion
 - | LessOrEqual !AttributeValueAssertion
 - | Present !AttributeDescription
 - | ApproxMatch !AttributeValueAssertion
 - | ExtensibleMatch !MatchingRuleAssertion
 
 - data SubstringFilter = SubstringFilter !AttributeDescription !(NonEmpty Substring)
 - data Substring
 - data MatchingRuleAssertion = MatchingRuleAssertion !(Maybe MatchingRuleId) !(Maybe AttributeDescription) !AssertionValue !Bool
 - newtype MatchingRuleId = MatchingRuleId LdapString
 - newtype AttributeSelection = AttributeSelection [LdapString]
 - newtype AttributeList = AttributeList [Attribute]
 - newtype PartialAttributeList = PartialAttributeList [PartialAttribute]
 - newtype Controls = Controls [Control]
 - data Control = Control !LdapOid !Bool !(Maybe ByteString)
 - data LdapResult = LdapResult !ResultCode !LdapDn !LdapString !(Maybe ReferralUris)
 - data ResultCode
- = Success
 - | OperationError
 - | ProtocolError
 - | TimeLimitExceeded
 - | SizeLimitExceeded
 - | CompareFalse
 - | CompareTrue
 - | AuthMethodNotSupported
 - | StrongerAuthRequired
 - | Referral
 - | AdminLimitExceeded
 - | UnavailableCriticalExtension
 - | ConfidentialityRequired
 - | SaslBindInProgress
 - | NoSuchAttribute
 - | UndefinedAttributeType
 - | InappropriateMatching
 - | ConstraintViolation
 - | AttributeOrValueExists
 - | InvalidAttributeSyntax
 - | NoSuchObject
 - | AliasProblem
 - | InvalidDNSyntax
 - | AliasDereferencingProblem
 - | InappropriateAuthentication
 - | InvalidCredentials
 - | InsufficientAccessRights
 - | Busy
 - | Unavailable
 - | UnwillingToPerform
 - | LoopDetect
 - | NamingViolation
 - | ObjectClassViolation
 - | NotAllowedOnNonLeaf
 - | NotAllowedOnRDN
 - | EntryAlreadyExists
 - | ObjectClassModsProhibited
 - | AffectsMultipleDSAs
 - | Other
 
 - newtype AttributeDescription = AttributeDescription LdapString
 - newtype AttributeValue = AttributeValue ByteString
 - data AttributeValueAssertion = AttributeValueAssertion !AttributeDescription !AssertionValue
 - newtype AssertionValue = AssertionValue ByteString
 - data Attribute = Attribute !AttributeDescription !(NonEmpty AttributeValue)
 - data PartialAttribute = PartialAttribute !AttributeDescription ![AttributeValue]
 - newtype LdapDn = LdapDn LdapString
 - newtype RelativeLdapDn = RelativeLdapDn LdapString
 - newtype ReferralUris = ReferralUris (NonEmpty Uri)
 - newtype Uri = Uri LdapString
 - data Operation
 - newtype LdapString = LdapString Text
 - newtype LdapOid = LdapOid Text
 
Documentation
data LdapMessage op Source #
Message envelope. (Section 4.1.1.)
Constructors
| LdapMessage | |
Fields 
  | |
Instances
| Show op => Show (LdapMessage op) Source # | |
Defined in Ldap.Asn1.Type Methods showsPrec :: Int -> LdapMessage op -> ShowS # show :: LdapMessage op -> String # showList :: [LdapMessage op] -> ShowS #  | |
| Eq op => Eq (LdapMessage op) Source # | |
Defined in Ldap.Asn1.Type Methods (==) :: LdapMessage op -> LdapMessage op -> Bool # (/=) :: LdapMessage op -> LdapMessage op -> Bool #  | |
| 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 }
 | 
Defined in Ldap.Asn1.FromAsn1 Methods fromAsn1 :: Parser [ASN1] (LdapMessage op)  | |
| 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 }
 | 
Defined in Ldap.Asn1.ToAsn1  | |
Every message being processed has a unique non-zero integer ID. (Section 4.1.1.1.)
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.
Constructors
Instances
| Show ProtocolClientOp Source # | |
Defined in Ldap.Asn1.Type Methods showsPrec :: Int -> ProtocolClientOp -> ShowS # show :: ProtocolClientOp -> String # showList :: [ProtocolClientOp] -> ShowS #  | |
| Eq ProtocolClientOp Source # | |
Defined in Ldap.Asn1.Type Methods (==) :: ProtocolClientOp -> ProtocolClientOp -> Bool # (/=) :: ProtocolClientOp -> ProtocolClientOp -> Bool #  | |
| 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 }
 | 
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.
Constructors
Instances
| Show ProtocolServerOp Source # | |
Defined in Ldap.Asn1.Type Methods showsPrec :: Int -> ProtocolServerOp -> ShowS # show :: ProtocolServerOp -> String # showList :: [ProtocolServerOp] -> ShowS #  | |
| Eq ProtocolServerOp Source # | |
Defined in Ldap.Asn1.Type Methods (==) :: ProtocolServerOp -> ProtocolServerOp -> Bool # (/=) :: ProtocolServerOp -> ProtocolServerOp -> Bool #  | |
| 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 }
 | 
Defined in Ldap.Asn1.FromAsn1 Methods fromAsn1 :: Parser [ASN1] ProtocolServerOp  | |
data AuthenticationChoice Source #
Not really a choice until SASL is supported.
Constructors
| Simple !ByteString | |
| Sasl !SaslMechanism !(Maybe Text) | 
Instances
| Show AuthenticationChoice Source # | |
Defined in Ldap.Asn1.Type Methods showsPrec :: Int -> AuthenticationChoice -> ShowS # show :: AuthenticationChoice -> String # showList :: [AuthenticationChoice] -> ShowS #  | |
| Eq AuthenticationChoice Source # | |
Defined in Ldap.Asn1.Type Methods (==) :: AuthenticationChoice -> AuthenticationChoice -> Bool # (/=) :: AuthenticationChoice -> AuthenticationChoice -> Bool #  | |
| ToAsn1 AuthenticationChoice Source # | AuthenticationChoice ::= CHOICE {
     simple                  [0] OCTET STRING,
     sasl                    [3] SaslCredentials,
     ...  }
SaslCredentials ::= SEQUENCE {
     mechanism               LDAPString,
     credentials             OCTET STRING OPTIONAL }
 | 
Defined in Ldap.Asn1.ToAsn1  | |
data SaslMechanism Source #
SASL Mechanism, for now only SASL EXTERNAL is supported
Constructors
| External | 
Instances
| Show SaslMechanism Source # | |
Defined in Ldap.Asn1.Type Methods showsPrec :: Int -> SaslMechanism -> ShowS # show :: SaslMechanism -> String # showList :: [SaslMechanism] -> ShowS #  | |
| Eq SaslMechanism Source # | |
Defined in Ldap.Asn1.Type Methods (==) :: SaslMechanism -> SaslMechanism -> Bool # (/=) :: SaslMechanism -> SaslMechanism -> Bool #  | |
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.  | 
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
| Show DerefAliases Source # | |
Defined in Ldap.Asn1.Type Methods showsPrec :: Int -> DerefAliases -> ShowS # show :: DerefAliases -> String # showList :: [DerefAliases] -> ShowS #  | |
| Eq DerefAliases Source # | |
Defined in Ldap.Asn1.Type  | |
Conditions that must be fulfilled in order for the Search to match a given entry.
Constructors
| And !(NonEmpty Filter) | All filters evaluate to   | 
| Or !(NonEmpty Filter) | Any filter evaluates to   | 
| Not !Filter | Filter evaluates to   | 
| EqualityMatch !AttributeValueAssertion | 
  | 
| Substrings !SubstringFilter | 
  | 
| GreaterOrEqual !AttributeValueAssertion | 
  | 
| LessOrEqual !AttributeValueAssertion | 
  | 
| Present !AttributeDescription | Attribute is present in the entry  | 
| ApproxMatch !AttributeValueAssertion | Same as   | 
| ExtensibleMatch !MatchingRuleAssertion | 
Instances
| Show Filter Source # | |
| Eq Filter Source # | |
| 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,
     ...  }
 | 
data SubstringFilter Source #
Constructors
| SubstringFilter !AttributeDescription !(NonEmpty Substring) | 
Instances
| Show SubstringFilter Source # | |
Defined in Ldap.Asn1.Type Methods showsPrec :: Int -> SubstringFilter -> ShowS # show :: SubstringFilter -> String # showList :: [SubstringFilter] -> ShowS #  | |
| Eq SubstringFilter Source # | |
Defined in Ldap.Asn1.Type Methods (==) :: SubstringFilter -> SubstringFilter -> Bool # (/=) :: SubstringFilter -> SubstringFilter -> Bool #  | |
| 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
     }
 | 
Defined in Ldap.Asn1.ToAsn1  | |
Constructors
| Initial !AssertionValue | |
| Any !AssertionValue | |
| Final !AssertionValue | 
Instances
data MatchingRuleAssertion Source #
Constructors
| MatchingRuleAssertion !(Maybe MatchingRuleId) !(Maybe AttributeDescription) !AssertionValue !Bool | 
Instances
| Show MatchingRuleAssertion Source # | |
Defined in Ldap.Asn1.Type Methods showsPrec :: Int -> MatchingRuleAssertion -> ShowS # show :: MatchingRuleAssertion -> String # showList :: [MatchingRuleAssertion] -> ShowS #  | |
| Eq MatchingRuleAssertion Source # | |
Defined in Ldap.Asn1.Type Methods (==) :: MatchingRuleAssertion -> MatchingRuleAssertion -> Bool # (/=) :: MatchingRuleAssertion -> MatchingRuleAssertion -> Bool #  | |
| ToAsn1 MatchingRuleAssertion Source # | MatchingRuleAssertion ::= SEQUENCE {
     matchingRule    [1] MatchingRuleId OPTIONAL,
     type            [2] AttributeDescription OPTIONAL,
     matchValue      [3] AssertionValue,
     dnAttributes    [4] BOOLEAN DEFAULT FALSE }
 | 
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.)
Constructors
| MatchingRuleId LdapString | 
Instances
| Show MatchingRuleId Source # | |
Defined in Ldap.Asn1.Type Methods showsPrec :: Int -> MatchingRuleId -> ShowS # show :: MatchingRuleId -> String # showList :: [MatchingRuleId] -> ShowS #  | |
| Eq MatchingRuleId Source # | |
Defined in Ldap.Asn1.Type Methods (==) :: MatchingRuleId -> MatchingRuleId -> Bool # (/=) :: MatchingRuleId -> MatchingRuleId -> Bool #  | |
| ToAsn1 MatchingRuleId Source # | MatchingRuleId ::= LDAPString  | 
Defined in Ldap.Asn1.ToAsn1  | |
newtype AttributeSelection Source #
Constructors
| AttributeSelection [LdapString] | 
Instances
| Show AttributeSelection Source # | |
Defined in Ldap.Asn1.Type Methods showsPrec :: Int -> AttributeSelection -> ShowS # show :: AttributeSelection -> String # showList :: [AttributeSelection] -> ShowS #  | |
| Eq AttributeSelection Source # | |
Defined in Ldap.Asn1.Type Methods (==) :: AttributeSelection -> AttributeSelection -> Bool # (/=) :: AttributeSelection -> AttributeSelection -> Bool #  | |
| ToAsn1 AttributeSelection Source # | AttributeSelection ::= SEQUENCE OF selector LDAPString  | 
Defined in Ldap.Asn1.ToAsn1  | |
newtype AttributeList Source #
Constructors
| AttributeList [Attribute] | 
Instances
| Show AttributeList Source # | |
Defined in Ldap.Asn1.Type Methods showsPrec :: Int -> AttributeList -> ShowS # show :: AttributeList -> String # showList :: [AttributeList] -> ShowS #  | |
| Eq AttributeList Source # | |
Defined in Ldap.Asn1.Type Methods (==) :: AttributeList -> AttributeList -> Bool # (/=) :: AttributeList -> AttributeList -> Bool #  | |
| ToAsn1 AttributeList Source # | AttributeList ::= SEQUENCE OF attribute Attribute  | 
Defined in Ldap.Asn1.ToAsn1  | |
newtype PartialAttributeList Source #
Constructors
| PartialAttributeList [PartialAttribute] | 
Instances
| Show PartialAttributeList Source # | |
Defined in Ldap.Asn1.Type Methods showsPrec :: Int -> PartialAttributeList -> ShowS # show :: PartialAttributeList -> String # showList :: [PartialAttributeList] -> ShowS #  | |
| Eq PartialAttributeList Source # | |
Defined in Ldap.Asn1.Type Methods (==) :: PartialAttributeList -> PartialAttributeList -> Bool # (/=) :: PartialAttributeList -> PartialAttributeList -> Bool #  | |
| FromAsn1 PartialAttributeList Source # | PartialAttributeList ::= SEQUENCE OF partialAttribute PartialAttribute  | 
Defined in Ldap.Asn1.FromAsn1 Methods fromAsn1 :: Parser [ASN1] PartialAttributeList  | |
Constructors
| Control !LdapOid !Bool !(Maybe ByteString) | 
data LdapResult Source #
Constructors
| LdapResult !ResultCode !LdapDn !LdapString !(Maybe ReferralUris) | 
Instances
| Show LdapResult Source # | |
Defined in Ldap.Asn1.Type Methods showsPrec :: Int -> LdapResult -> ShowS # show :: LdapResult -> String # showList :: [LdapResult] -> ShowS #  | |
| Eq LdapResult Source # | |
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 }
 | 
Defined in Ldap.Asn1.FromAsn1 Methods fromAsn1 :: Parser [ASN1] LdapResult  | |
data ResultCode Source #
LDAP operation's result.
Constructors
Instances
| Show ResultCode Source # | |
Defined in Ldap.Asn1.Type Methods showsPrec :: Int -> ResultCode -> ShowS # show :: ResultCode -> String # showList :: [ResultCode] -> ShowS #  | |
| Eq ResultCode Source # | |
Defined in Ldap.Asn1.Type  | |
newtype AttributeDescription Source #
Constructors
| AttributeDescription LdapString | 
Instances
| Show AttributeDescription Source # | |
Defined in Ldap.Asn1.Type Methods showsPrec :: Int -> AttributeDescription -> ShowS # show :: AttributeDescription -> String # showList :: [AttributeDescription] -> ShowS #  | |
| Eq AttributeDescription Source # | |
Defined in Ldap.Asn1.Type Methods (==) :: AttributeDescription -> AttributeDescription -> Bool # (/=) :: AttributeDescription -> AttributeDescription -> Bool #  | |
| FromAsn1 AttributeDescription Source # | AttributeDescription ::= LDAPString  | 
Defined in Ldap.Asn1.FromAsn1 Methods fromAsn1 :: Parser [ASN1] AttributeDescription  | |
| ToAsn1 AttributeDescription Source # | AttributeDescription ::= LDAPString  | 
Defined in Ldap.Asn1.ToAsn1  | |
newtype AttributeValue Source #
Constructors
| AttributeValue ByteString | 
Instances
| Show AttributeValue Source # | |
Defined in Ldap.Asn1.Type Methods showsPrec :: Int -> AttributeValue -> ShowS # show :: AttributeValue -> String # showList :: [AttributeValue] -> ShowS #  | |
| Eq AttributeValue Source # | |
Defined in Ldap.Asn1.Type Methods (==) :: AttributeValue -> AttributeValue -> Bool # (/=) :: AttributeValue -> AttributeValue -> Bool #  | |
| FromAsn1 AttributeValue Source # | AttributeValue ::= OCTET STRING  | 
Defined in Ldap.Asn1.FromAsn1 Methods fromAsn1 :: Parser [ASN1] AttributeValue  | |
| ToAsn1 AttributeValue Source # | AttributeValue ::= OCTET STRING  | 
Defined in Ldap.Asn1.ToAsn1  | |
data AttributeValueAssertion Source #
Constructors
| AttributeValueAssertion !AttributeDescription !AssertionValue | 
Instances
| Show AttributeValueAssertion Source # | |
Defined in Ldap.Asn1.Type Methods showsPrec :: Int -> AttributeValueAssertion -> ShowS # show :: AttributeValueAssertion -> String # showList :: [AttributeValueAssertion] -> ShowS #  | |
| Eq AttributeValueAssertion Source # | |
Defined in Ldap.Asn1.Type Methods (==) :: AttributeValueAssertion -> AttributeValueAssertion -> Bool # (/=) :: AttributeValueAssertion -> AttributeValueAssertion -> Bool #  | |
| ToAsn1 AttributeValueAssertion Source # | AttributeValueAssertion ::= SEQUENCE {
     attributeDesc   AttributeDescription,
     assertionValue  AssertionValue }
 | 
Defined in Ldap.Asn1.ToAsn1  | |
newtype AssertionValue Source #
Constructors
| AssertionValue ByteString | 
Instances
| Show AssertionValue Source # | |
Defined in Ldap.Asn1.Type Methods showsPrec :: Int -> AssertionValue -> ShowS # show :: AssertionValue -> String # showList :: [AssertionValue] -> ShowS #  | |
| Eq AssertionValue Source # | |
Defined in Ldap.Asn1.Type Methods (==) :: AssertionValue -> AssertionValue -> Bool # (/=) :: AssertionValue -> AssertionValue -> Bool #  | |
| ToAsn1 AssertionValue Source # | AssertionValue ::= OCTET STRING  | 
Defined in Ldap.Asn1.ToAsn1  | |
Constructors
| Attribute !AttributeDescription !(NonEmpty AttributeValue) | 
data PartialAttribute Source #
Constructors
| PartialAttribute !AttributeDescription ![AttributeValue] | 
Instances
| Show PartialAttribute Source # | |
Defined in Ldap.Asn1.Type Methods showsPrec :: Int -> PartialAttribute -> ShowS # show :: PartialAttribute -> String # showList :: [PartialAttribute] -> ShowS #  | |
| Eq PartialAttribute Source # | |
Defined in Ldap.Asn1.Type Methods (==) :: PartialAttribute -> PartialAttribute -> Bool # (/=) :: PartialAttribute -> PartialAttribute -> Bool #  | |
| FromAsn1 PartialAttribute Source # | PartialAttribute ::= SEQUENCE {
     type       AttributeDescription,
     vals       SET OF value AttributeValue }
 | 
Defined in Ldap.Asn1.FromAsn1 Methods fromAsn1 :: Parser [ASN1] PartialAttribute  | |
| ToAsn1 PartialAttribute Source # | PartialAttribute ::= SEQUENCE {
     type       AttributeDescription,
     vals       SET OF value AttributeValue }
 | 
Defined in Ldap.Asn1.ToAsn1  | |
An LDAPDN is defined to be the representation of a Distinguished Name (DN) after encoding according to the specification in [RFC4514].
Constructors
| LdapDn LdapString | 
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].
Constructors
| RelativeLdapDn LdapString | 
Instances
| Show RelativeLdapDn Source # | |
Defined in Ldap.Asn1.Type Methods showsPrec :: Int -> RelativeLdapDn -> ShowS # show :: RelativeLdapDn -> String # showList :: [RelativeLdapDn] -> ShowS #  | |
| Eq RelativeLdapDn Source # | |
Defined in Ldap.Asn1.Type Methods (==) :: RelativeLdapDn -> RelativeLdapDn -> Bool # (/=) :: RelativeLdapDn -> RelativeLdapDn -> Bool #  | |
| ToAsn1 RelativeLdapDn Source # | RelativeLDAPDN ::= LDAPString -- Constrained to <name-component>  | 
Defined in Ldap.Asn1.ToAsn1  | |
newtype ReferralUris Source #
Constructors
| ReferralUris (NonEmpty Uri) | 
Instances
| Show ReferralUris Source # | |
Defined in Ldap.Asn1.Type Methods showsPrec :: Int -> ReferralUris -> ShowS # show :: ReferralUris -> String # showList :: [ReferralUris] -> ShowS #  | |
| Eq ReferralUris Source # | |
Defined in Ldap.Asn1.Type  | |
| FromAsn1 ReferralUris Source # | Referral ::= SEQUENCE SIZE (1..MAX) OF uri URI  | 
Defined in Ldap.Asn1.FromAsn1 Methods fromAsn1 :: Parser [ASN1] ReferralUris  | |
Constructors
| Uri LdapString | 
Instances
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
| Show LdapString Source # | |
Defined in Ldap.Asn1.Type Methods showsPrec :: Int -> LdapString -> ShowS # show :: LdapString -> String # showList :: [LdapString] -> ShowS #  | |
| Eq LdapString Source # | |
Defined in Ldap.Asn1.Type  | |
| FromAsn1 LdapString Source # | LDAPString ::= OCTET STRING -- UTF-8 encoded,  | 
Defined in Ldap.Asn1.FromAsn1 Methods fromAsn1 :: Parser [ASN1] LdapString  | |
| ToAsn1 LdapString Source # | LDAPString ::= OCTET STRING -- UTF-8 encoded  | 
Defined in Ldap.Asn1.ToAsn1  | |
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].