Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
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.)
LdapMessage | |
|
Instances
Eq op => Eq (LdapMessage op) Source # | |
Defined in Ldap.Asn1.Type (==) :: LdapMessage op -> LdapMessage op -> Bool # (/=) :: LdapMessage op -> LdapMessage op -> Bool # | |
Show op => Show (LdapMessage op) Source # | |
Defined in Ldap.Asn1.Type showsPrec :: Int -> LdapMessage op -> ShowS # show :: LdapMessage op -> String # showList :: [LdapMessage op] -> ShowS # | |
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 | |
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 fromAsn1 :: Parser [ASN1] (LdapMessage op) |
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.
Instances
Eq ProtocolClientOp Source # | |
Defined in Ldap.Asn1.Type (==) :: ProtocolClientOp -> ProtocolClientOp -> Bool # (/=) :: ProtocolClientOp -> ProtocolClientOp -> Bool # | |
Show ProtocolClientOp Source # | |
Defined in Ldap.Asn1.Type showsPrec :: Int -> ProtocolClientOp -> ShowS # show :: ProtocolClientOp -> String # showList :: [ProtocolClientOp] -> ShowS # | |
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.
Instances
Eq ProtocolServerOp Source # | |
Defined in Ldap.Asn1.Type (==) :: ProtocolServerOp -> ProtocolServerOp -> Bool # (/=) :: ProtocolServerOp -> ProtocolServerOp -> Bool # | |
Show ProtocolServerOp Source # | |
Defined in Ldap.Asn1.Type showsPrec :: Int -> ProtocolServerOp -> ShowS # show :: ProtocolServerOp -> String # showList :: [ProtocolServerOp] -> ShowS # | |
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 fromAsn1 :: Parser [ASN1] ProtocolServerOp |
data AuthenticationChoice Source #
Not really a choice until SASL is supported.
Instances
Eq AuthenticationChoice Source # | |
Defined in Ldap.Asn1.Type (==) :: AuthenticationChoice -> AuthenticationChoice -> Bool # (/=) :: AuthenticationChoice -> AuthenticationChoice -> Bool # | |
Show AuthenticationChoice Source # | |
Defined in Ldap.Asn1.Type showsPrec :: Int -> AuthenticationChoice -> ShowS # show :: AuthenticationChoice -> String # showList :: [AuthenticationChoice] -> ShowS # | |
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
Instances
Eq SaslMechanism Source # | |
Defined in Ldap.Asn1.Type (==) :: SaslMechanism -> SaslMechanism -> Bool # (/=) :: SaslMechanism -> SaslMechanism -> Bool # | |
Show SaslMechanism Source # | |
Defined in Ldap.Asn1.Type showsPrec :: Int -> SaslMechanism -> ShowS # show :: SaslMechanism -> String # showList :: [SaslMechanism] -> ShowS # |
Scope of the search to be performed.
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.
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 # | |
Defined in Ldap.Asn1.Type (==) :: DerefAliases -> DerefAliases -> Bool # (/=) :: DerefAliases -> DerefAliases -> Bool # | |
Show DerefAliases Source # | |
Defined in Ldap.Asn1.Type showsPrec :: Int -> DerefAliases -> ShowS # show :: DerefAliases -> String # showList :: [DerefAliases] -> ShowS # |
Conditions that must be fulfilled in order for the Search to match a given entry.
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
Eq Filter Source # | |
Show 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 #
Instances
Eq SubstringFilter Source # | |
Defined in Ldap.Asn1.Type (==) :: SubstringFilter -> SubstringFilter -> Bool # (/=) :: SubstringFilter -> SubstringFilter -> Bool # | |
Show SubstringFilter Source # | |
Defined in Ldap.Asn1.Type showsPrec :: Int -> SubstringFilter -> ShowS # show :: SubstringFilter -> String # showList :: [SubstringFilter] -> ShowS # | |
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 |
data MatchingRuleAssertion Source #
Instances
Eq MatchingRuleAssertion Source # | |
Defined in Ldap.Asn1.Type (==) :: MatchingRuleAssertion -> MatchingRuleAssertion -> Bool # (/=) :: MatchingRuleAssertion -> MatchingRuleAssertion -> Bool # | |
Show MatchingRuleAssertion Source # | |
Defined in Ldap.Asn1.Type showsPrec :: Int -> MatchingRuleAssertion -> ShowS # show :: MatchingRuleAssertion -> String # showList :: [MatchingRuleAssertion] -> ShowS # | |
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.)
Instances
Eq MatchingRuleId Source # | |
Defined in Ldap.Asn1.Type (==) :: MatchingRuleId -> MatchingRuleId -> Bool # (/=) :: MatchingRuleId -> MatchingRuleId -> Bool # | |
Show MatchingRuleId Source # | |
Defined in Ldap.Asn1.Type showsPrec :: Int -> MatchingRuleId -> ShowS # show :: MatchingRuleId -> String # showList :: [MatchingRuleId] -> ShowS # | |
ToAsn1 MatchingRuleId Source # | MatchingRuleId ::= LDAPString |
Defined in Ldap.Asn1.ToAsn1 |
newtype AttributeSelection Source #
Instances
Eq AttributeSelection Source # | |
Defined in Ldap.Asn1.Type (==) :: AttributeSelection -> AttributeSelection -> Bool # (/=) :: AttributeSelection -> AttributeSelection -> Bool # | |
Show AttributeSelection Source # | |
Defined in Ldap.Asn1.Type showsPrec :: Int -> AttributeSelection -> ShowS # show :: AttributeSelection -> String # showList :: [AttributeSelection] -> ShowS # | |
ToAsn1 AttributeSelection Source # | AttributeSelection ::= SEQUENCE OF selector LDAPString |
Defined in Ldap.Asn1.ToAsn1 |
newtype AttributeList Source #
Instances
Eq AttributeList Source # | |
Defined in Ldap.Asn1.Type (==) :: AttributeList -> AttributeList -> Bool # (/=) :: AttributeList -> AttributeList -> Bool # | |
Show AttributeList Source # | |
Defined in Ldap.Asn1.Type showsPrec :: Int -> AttributeList -> ShowS # show :: AttributeList -> String # showList :: [AttributeList] -> ShowS # | |
ToAsn1 AttributeList Source # | AttributeList ::= SEQUENCE OF attribute Attribute |
Defined in Ldap.Asn1.ToAsn1 |
newtype PartialAttributeList Source #
Instances
Eq PartialAttributeList Source # | |
Defined in Ldap.Asn1.Type (==) :: PartialAttributeList -> PartialAttributeList -> Bool # (/=) :: PartialAttributeList -> PartialAttributeList -> Bool # | |
Show PartialAttributeList Source # | |
Defined in Ldap.Asn1.Type showsPrec :: Int -> PartialAttributeList -> ShowS # show :: PartialAttributeList -> String # showList :: [PartialAttributeList] -> ShowS # | |
FromAsn1 PartialAttributeList Source # | PartialAttributeList ::= SEQUENCE OF partialAttribute PartialAttribute |
Defined in Ldap.Asn1.FromAsn1 fromAsn1 :: Parser [ASN1] PartialAttributeList |
Control !LdapOid !Bool !(Maybe ByteString) |
data LdapResult Source #
Instances
Eq LdapResult Source # | |
Defined in Ldap.Asn1.Type (==) :: LdapResult -> LdapResult -> Bool # (/=) :: LdapResult -> LdapResult -> Bool # | |
Show LdapResult Source # | |
Defined in Ldap.Asn1.Type showsPrec :: Int -> LdapResult -> ShowS # show :: LdapResult -> String # showList :: [LdapResult] -> ShowS # | |
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 fromAsn1 :: Parser [ASN1] LdapResult |
data ResultCode Source #
LDAP operation's result.
Instances
Eq ResultCode Source # | |
Defined in Ldap.Asn1.Type (==) :: ResultCode -> ResultCode -> Bool # (/=) :: ResultCode -> ResultCode -> Bool # | |
Show ResultCode Source # | |
Defined in Ldap.Asn1.Type showsPrec :: Int -> ResultCode -> ShowS # show :: ResultCode -> String # showList :: [ResultCode] -> ShowS # |
newtype AttributeDescription Source #
Instances
Eq AttributeDescription Source # | |
Defined in Ldap.Asn1.Type (==) :: AttributeDescription -> AttributeDescription -> Bool # (/=) :: AttributeDescription -> AttributeDescription -> Bool # | |
Show AttributeDescription Source # | |
Defined in Ldap.Asn1.Type showsPrec :: Int -> AttributeDescription -> ShowS # show :: AttributeDescription -> String # showList :: [AttributeDescription] -> ShowS # | |
ToAsn1 AttributeDescription Source # | AttributeDescription ::= LDAPString |
Defined in Ldap.Asn1.ToAsn1 | |
FromAsn1 AttributeDescription Source # | AttributeDescription ::= LDAPString |
Defined in Ldap.Asn1.FromAsn1 fromAsn1 :: Parser [ASN1] AttributeDescription |
newtype AttributeValue Source #
Instances
Eq AttributeValue Source # | |
Defined in Ldap.Asn1.Type (==) :: AttributeValue -> AttributeValue -> Bool # (/=) :: AttributeValue -> AttributeValue -> Bool # | |
Show AttributeValue Source # | |
Defined in Ldap.Asn1.Type showsPrec :: Int -> AttributeValue -> ShowS # show :: AttributeValue -> String # showList :: [AttributeValue] -> ShowS # | |
ToAsn1 AttributeValue Source # | AttributeValue ::= OCTET STRING |
Defined in Ldap.Asn1.ToAsn1 | |
FromAsn1 AttributeValue Source # | AttributeValue ::= OCTET STRING |
Defined in Ldap.Asn1.FromAsn1 fromAsn1 :: Parser [ASN1] AttributeValue |
data AttributeValueAssertion Source #
Instances
Eq AttributeValueAssertion Source # | |
Defined in Ldap.Asn1.Type | |
Show AttributeValueAssertion Source # | |
Defined in Ldap.Asn1.Type showsPrec :: Int -> AttributeValueAssertion -> ShowS # show :: AttributeValueAssertion -> String # showList :: [AttributeValueAssertion] -> ShowS # | |
ToAsn1 AttributeValueAssertion Source # | AttributeValueAssertion ::= SEQUENCE { attributeDesc AttributeDescription, assertionValue AssertionValue } |
Defined in Ldap.Asn1.ToAsn1 |
newtype AssertionValue Source #
Instances
Eq AssertionValue Source # | |
Defined in Ldap.Asn1.Type (==) :: AssertionValue -> AssertionValue -> Bool # (/=) :: AssertionValue -> AssertionValue -> Bool # | |
Show AssertionValue Source # | |
Defined in Ldap.Asn1.Type showsPrec :: Int -> AssertionValue -> ShowS # show :: AssertionValue -> String # showList :: [AssertionValue] -> ShowS # | |
ToAsn1 AssertionValue Source # | AssertionValue ::= OCTET STRING |
Defined in Ldap.Asn1.ToAsn1 |
data PartialAttribute Source #
Instances
Eq PartialAttribute Source # | |
Defined in Ldap.Asn1.Type (==) :: PartialAttribute -> PartialAttribute -> Bool # (/=) :: PartialAttribute -> PartialAttribute -> Bool # | |
Show PartialAttribute Source # | |
Defined in Ldap.Asn1.Type showsPrec :: Int -> PartialAttribute -> ShowS # show :: PartialAttribute -> String # showList :: [PartialAttribute] -> ShowS # | |
ToAsn1 PartialAttribute Source # | PartialAttribute ::= SEQUENCE { type AttributeDescription, vals SET OF value AttributeValue } |
Defined in Ldap.Asn1.ToAsn1 | |
FromAsn1 PartialAttribute Source # | PartialAttribute ::= SEQUENCE { type AttributeDescription, vals SET OF value AttributeValue } |
Defined in Ldap.Asn1.FromAsn1 fromAsn1 :: Parser [ASN1] PartialAttribute |
An LDAPDN is defined to be the representation of a Distinguished Name (DN) after encoding according to the specification in [RFC4514].
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 # | |
Defined in Ldap.Asn1.Type (==) :: RelativeLdapDn -> RelativeLdapDn -> Bool # (/=) :: RelativeLdapDn -> RelativeLdapDn -> Bool # | |
Show RelativeLdapDn Source # | |
Defined in Ldap.Asn1.Type showsPrec :: Int -> RelativeLdapDn -> ShowS # show :: RelativeLdapDn -> String # showList :: [RelativeLdapDn] -> ShowS # | |
ToAsn1 RelativeLdapDn Source # | RelativeLDAPDN ::= LDAPString -- Constrained to <name-component> |
Defined in Ldap.Asn1.ToAsn1 |
newtype ReferralUris Source #
Instances
Eq ReferralUris Source # | |
Defined in Ldap.Asn1.Type (==) :: ReferralUris -> ReferralUris -> Bool # (/=) :: ReferralUris -> ReferralUris -> Bool # | |
Show ReferralUris Source # | |
Defined in Ldap.Asn1.Type showsPrec :: Int -> ReferralUris -> ShowS # show :: ReferralUris -> String # showList :: [ReferralUris] -> ShowS # | |
FromAsn1 ReferralUris Source # | Referral ::= SEQUENCE SIZE (1..MAX) OF uri URI |
Defined in Ldap.Asn1.FromAsn1 fromAsn1 :: Parser [ASN1] ReferralUris |
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.)
Instances
Eq LdapString Source # | |
Defined in Ldap.Asn1.Type (==) :: LdapString -> LdapString -> Bool # (/=) :: LdapString -> LdapString -> Bool # | |
Show LdapString Source # | |
Defined in Ldap.Asn1.Type showsPrec :: Int -> LdapString -> ShowS # show :: LdapString -> String # showList :: [LdapString] -> ShowS # | |
ToAsn1 LdapString Source # | LDAPString ::= OCTET STRING -- UTF-8 encoded |
Defined in Ldap.Asn1.ToAsn1 | |
FromAsn1 LdapString Source # | LDAPString ::= OCTET STRING -- UTF-8 encoded, |
Defined in Ldap.Asn1.FromAsn1 fromAsn1 :: Parser [ASN1] LdapString |
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].