Safe Haskell | Trustworthy |
---|---|
Language | Haskell2010 |
LDAPv3.Message
Contents
- LDAPv3 Protocol data structures
- Common Elements (RFC4511 Section 4.1)
- Bind Operation (RFC4511 Section 4.2)
- Unbind Operation (RFC4511 Section 4.3)
- Unsolicited Notification (RFC4511 Section 4.4)
- Search Operation (RFC4511 Section 4.5)
- Modify Operation (RFC4511 Section 4.6)
- Add Operation (RFC4511 Section 4.7)
- Delete Operation (RFC4511 Section 4.8)
- Modify DN Operation (RFC4511 Section 4.9)
- Compare Operation (RFC4511 Section 4.10)
- Abandon Operation (RFC4511 Section 4.11)
- Extended Operation (RFC4511 Section 4.12)
- Intermediate Response (RFC4511 Section 4.13)
- ASN.1 Helpers
- Unsigned integer sub-type
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
- data LDAPMessage = LDAPMessage {}
- newtype MessageID = MessageID (UInt 0 MaxInt Int32)
- type MaxInt = 2147483647
- data ProtocolOp
- = ProtocolOp'bindRequest BindRequest
- | ProtocolOp'bindResponse BindResponse
- | ProtocolOp'unbindRequest UnbindRequest
- | ProtocolOp'searchRequest SearchRequest
- | ProtocolOp'searchResEntry SearchResultEntry
- | ProtocolOp'searchResDone SearchResultDone
- | ProtocolOp'searchResRef SearchResultReference
- | ProtocolOp'modifyRequest ModifyRequest
- | ProtocolOp'modifyResponse ModifyResponse
- | ProtocolOp'addRequest AddRequest
- | ProtocolOp'addResponse AddResponse
- | ProtocolOp'delRequest DelRequest
- | ProtocolOp'delResponse DelResponse
- | ProtocolOp'modDNRequest ModifyDNRequest
- | ProtocolOp'modDNResponse ModifyDNResponse
- | ProtocolOp'compareRequest CompareRequest
- | ProtocolOp'compareResponse CompareResponse
- | ProtocolOp'abandonRequest AbandonRequest
- | ProtocolOp'extendedReq ExtendedRequest
- | ProtocolOp'extendedResp ExtendedResponse
- | ProtocolOp'intermediateResponse IntermediateResponse
- type LDAPString = ShortText
- type LDAPOID = OCTET_STRING
- type LDAPDN = LDAPString
- type RelativeLDAPDN = LDAPString
- type AttributeDescription = LDAPString
- type AttributeValue = OCTET_STRING
- data AttributeValueAssertion = AttributeValueAssertion {}
- type AssertionValue = OCTET_STRING
- data PartialAttribute = PartialAttribute {}
- data Attribute = Attribute {}
- type MatchingRuleId = LDAPString
- data LDAPResult = LDAPResult {}
- data ResultCode
- = ResultCode'success
- | ResultCode'operationsError
- | ResultCode'protocolError
- | ResultCode'timeLimitExceeded
- | ResultCode'sizeLimitExceeded
- | ResultCode'compareFalse
- | ResultCode'compareTrue
- | ResultCode'authMethodNotSupported
- | ResultCode'strongerAuthRequired
- | ResultCode'referral
- | ResultCode'adminLimitExceeded
- | ResultCode'unavailableCriticalExtension
- | ResultCode'confidentialityRequired
- | ResultCode'saslBindInProgress
- | ResultCode'noSuchAttribute
- | ResultCode'undefinedAttributeType
- | ResultCode'inappropriateMatching
- | ResultCode'constraintViolation
- | ResultCode'attributeOrValueExists
- | ResultCode'invalidAttributeSyntax
- | ResultCode'noSuchObject
- | ResultCode'aliasProblem
- | ResultCode'invalidDNSyntax
- | ResultCode'aliasDereferencingProblem
- | ResultCode'inappropriateAuthentication
- | ResultCode'invalidCredentials
- | ResultCode'insufficientAccessRights
- | ResultCode'busy
- | ResultCode'unavailable
- | ResultCode'unwillingToPerform
- | ResultCode'loopDetect
- | ResultCode'namingViolation
- | ResultCode'objectClassViolation
- | ResultCode'notAllowedOnNonLeaf
- | ResultCode'notAllowedOnRDN
- | ResultCode'entryAlreadyExists
- | ResultCode'objectClassModsProhibited
- | ResultCode'affectsMultipleDSAs
- | ResultCode'other
- type Referral = 'CONTEXTUAL 3 `IMPLICIT` NonEmpty URI
- type URI = LDAPString
- type Controls = [Control]
- data Control = Control {}
- data BindRequest = BindRequest {}
- data AuthenticationChoice
- data SaslCredentials = SaslCredentials {}
- data BindResponse = BindResponse {}
- type UnbindRequest = 'APPLICATION 2 `IMPLICIT` NULL
- data SearchRequest = SearchRequest {
- _SearchRequest'baseObject :: LDAPDN
- _SearchRequest'scope :: ENUMERATED Scope
- _SearchRequest'derefAliases :: ENUMERATED DerefAliases
- _SearchRequest'sizeLimit :: UInt 0 MaxInt Int32
- _SearchRequest'timeLimit :: UInt 0 MaxInt Int32
- _SearchRequest'typesOnly :: Bool
- _SearchRequest'filter :: Filter
- _SearchRequest'attributes :: AttributeSelection
- data Scope
- data DerefAliases
- type AttributeSelection = [LDAPString]
- data Filter
- = Filter'and ('CONTEXTUAL 0 `IMPLICIT` SET1 Filter)
- | Filter'or ('CONTEXTUAL 1 `IMPLICIT` SET1 Filter)
- | Filter'not ('CONTEXTUAL 2 `EXPLICIT` Filter)
- | Filter'equalityMatch ('CONTEXTUAL 3 `IMPLICIT` AttributeValueAssertion)
- | Filter'substrings ('CONTEXTUAL 4 `IMPLICIT` SubstringFilter)
- | Filter'greaterOrEqual ('CONTEXTUAL 5 `IMPLICIT` AttributeValueAssertion)
- | Filter'lessOrEqual ('CONTEXTUAL 6 `IMPLICIT` AttributeValueAssertion)
- | Filter'present ('CONTEXTUAL 7 `IMPLICIT` AttributeDescription)
- | Filter'approxMatch ('CONTEXTUAL 8 `IMPLICIT` AttributeValueAssertion)
- | Filter'extensibleMatch ('CONTEXTUAL 9 `IMPLICIT` MatchingRuleAssertion)
- data SubstringFilter = SubstringFilter {}
- data Substring
- data MatchingRuleAssertion = MatchingRuleAssertion {
- _MatchingRuleAssertion'matchingRule :: Maybe ('CONTEXTUAL 1 `IMPLICIT` MatchingRuleId)
- _MatchingRuleAssertion'type :: Maybe ('CONTEXTUAL 2 `IMPLICIT` AttributeDescription)
- _MatchingRuleAssertion'matchValue :: 'CONTEXTUAL 3 `IMPLICIT` AssertionValue
- _MatchingRuleAssertion'dnAttributes :: 'CONTEXTUAL 4 `IMPLICIT` BOOLEAN_DEFAULT 'False
- data SearchResultEntry = SearchResultEntry {}
- type PartialAttributeList = [PartialAttribute]
- newtype SearchResultReference = SearchResultReference ('APPLICATION 19 `IMPLICIT` NonEmpty URI)
- type SearchResultDone = 'APPLICATION 5 `IMPLICIT` LDAPResult
- data ModifyRequest = ModifyRequest {}
- data Change = Change {}
- data Operation
- type ModifyResponse = 'APPLICATION 7 `IMPLICIT` LDAPResult
- data AddRequest = AddRequest {}
- type AttributeList = [Attribute]
- type AddResponse = 'APPLICATION 9 `IMPLICIT` LDAPResult
- type DelRequest = 'APPLICATION 10 `IMPLICIT` LDAPDN
- type DelResponse = 'APPLICATION 11 `IMPLICIT` LDAPResult
- data ModifyDNRequest = ModifyDNRequest {}
- type ModifyDNResponse = 'APPLICATION 13 `IMPLICIT` LDAPResult
- data CompareRequest = CompareRequest {}
- type CompareResponse = 'APPLICATION 15 `IMPLICIT` LDAPResult
- type AbandonRequest = 'APPLICATION 16 `IMPLICIT` MessageID
- data ExtendedRequest = ExtendedRequest {}
- data ExtendedResponse = ExtendedResponse {}
- data IntermediateResponse = IntermediateResponse {}
- type NULL = ()
- type OCTET_STRING = ByteString
- type BOOLEAN_DEFAULT (def :: Bool) = Bool
- newtype SET x = SET [x]
- newtype SET1 x = SET1 (NonEmpty x)
- type COMPONENTS_OF x = x
- type EXPLICIT (tag :: TagK) x = x
- type IMPLICIT (tag :: TagK) x = x
- type ENUMERATED x = x
- type CHOICE x = x
- data TagK
- type UIntBounds lb ub t = (KnownNat lb, KnownNat ub, lb <= ub, IsBelowMaxBound ub (IntBaseType t) ~ 'True)
- data UInt (lb :: Nat) (ub :: Nat) t
- fromUInt :: UInt lb ub t -> t
- toUInt :: forall lb ub t. (UIntBounds lb ub t, Num t, Ord t) => t -> Either ArithException (UInt lb ub t)
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 }
Constructors
LDAPMessage | |
Instances
Message ID (RFC4511 Section 4.1.1.1)
MessageID ::= INTEGER (0 .. maxInt)
Instances
Bounded MessageID Source # | |
Eq MessageID Source # | |
Ord MessageID Source # | |
Show MessageID Source # | |
Generic MessageID Source # | |
NFData MessageID Source # | |
Defined in LDAPv3.Message | |
type Rep MessageID Source # | |
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)
Constructors
Instances
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 }
Constructors
AttributeValueAssertion | |
Instances
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 }
Constructors
PartialAttribute | |
Instances
Attribute (RFC4511 Section 4.1.7)
Attribute ::= PartialAttribute(WITH COMPONENTS { ..., vals (SIZE(1..MAX))})
Constructors
Attribute | |
Instances
Eq Attribute Source # | |
Show Attribute Source # | |
Generic Attribute Source # | |
NFData Attribute Source # | |
Defined in LDAPv3.Message | |
type Rep Attribute Source # | |
Defined in LDAPv3.Message type Rep Attribute = D1 ('MetaData "Attribute" "LDAPv3.Message" "LDAPv3-0.1.0.0-inplace" '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 }
Constructors
LDAPResult | |
Instances
data ResultCode Source #
LDAPResult
Result Code
Constructors
Instances
Bounded ResultCode Source # | |
Defined in LDAPv3.ResultCode | |
Enum ResultCode Source # | |
Defined in LDAPv3.ResultCode Methods succ :: ResultCode -> ResultCode # pred :: ResultCode -> ResultCode # toEnum :: Int -> ResultCode # fromEnum :: ResultCode -> Int # enumFrom :: ResultCode -> [ResultCode] # enumFromThen :: ResultCode -> ResultCode -> [ResultCode] # enumFromTo :: ResultCode -> ResultCode -> [ResultCode] # enumFromThenTo :: ResultCode -> ResultCode -> ResultCode -> [ResultCode] # | |
Eq ResultCode Source # | |
Defined in LDAPv3.ResultCode | |
Ord ResultCode Source # | |
Defined in LDAPv3.ResultCode Methods compare :: ResultCode -> ResultCode -> Ordering # (<) :: ResultCode -> ResultCode -> Bool # (<=) :: ResultCode -> ResultCode -> Bool # (>) :: ResultCode -> ResultCode -> Bool # (>=) :: ResultCode -> ResultCode -> Bool # max :: ResultCode -> ResultCode -> ResultCode # min :: ResultCode -> ResultCode -> ResultCode # | |
Show ResultCode Source # | |
Defined in LDAPv3.ResultCode Methods showsPrec :: Int -> ResultCode -> ShowS # show :: ResultCode -> String # showList :: [ResultCode] -> ShowS # | |
Generic ResultCode Source # | |
Defined in LDAPv3.ResultCode Associated Types type Rep ResultCode :: Type -> Type # | |
NFData ResultCode Source # | |
Defined in LDAPv3.ResultCode Methods rnf :: ResultCode -> () # | |
type Rep ResultCode Source # | |
Defined in LDAPv3.ResultCode type Rep ResultCode = D1 ('MetaData "ResultCode" "LDAPv3.ResultCode" "LDAPv3-0.1.0.0-inplace" '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
Control Entry (RFC4511 Section 4.1.11)
Control ::= SEQUENCE { controlType LDAPOID, criticality BOOLEAN DEFAULT FALSE, controlValue OCTET STRING OPTIONAL }
Constructors
Control | |
Instances
Eq Control Source # | |
Show Control Source # | |
Generic Control Source # | |
NFData Control Source # | |
Defined in LDAPv3.Message | |
type Rep Control Source # | |
Defined in LDAPv3.Message type Rep Control = D1 ('MetaData "Control" "LDAPv3.Message" "LDAPv3-0.1.0.0-inplace" '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 (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 }
Constructors
BindRequest | |
Fields |
Instances
Eq BindRequest Source # | |
Defined in LDAPv3.Message | |
Show BindRequest Source # | |
Defined in LDAPv3.Message Methods showsPrec :: Int -> BindRequest -> ShowS # show :: BindRequest -> String # showList :: [BindRequest] -> ShowS # | |
Generic BindRequest Source # | |
Defined in LDAPv3.Message Associated Types type Rep BindRequest :: Type -> Type # | |
NFData BindRequest Source # | |
Defined in LDAPv3.Message Methods rnf :: BindRequest -> () # | |
type Rep BindRequest Source # | |
Defined in LDAPv3.Message type Rep BindRequest = D1 ('MetaData "BindRequest" "LDAPv3.Message" "LDAPv3-0.1.0.0-inplace" '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, ... }
Constructors
AuthenticationChoice'simple ('CONTEXTUAL 0 `IMPLICIT` OCTET_STRING) | |
AuthenticationChoice'sasl ('CONTEXTUAL 3 `IMPLICIT` SaslCredentials) |
Instances
data SaslCredentials Source #
SaslCredentials ::= SEQUENCE { mechanism LDAPString, credentials OCTET STRING OPTIONAL }
Constructors
SaslCredentials | |
Instances
data BindResponse Source #
Bind Response (RFC4511 Section 4.2)
BindResponse ::= [APPLICATION 1] SEQUENCE { COMPONENTS OF LDAPResult, serverSaslCreds [7] OCTET STRING OPTIONAL }
Constructors
BindResponse | |
Instances
Eq BindResponse Source # | |
Defined in LDAPv3.Message | |
Show BindResponse Source # | |
Defined in LDAPv3.Message Methods showsPrec :: Int -> BindResponse -> ShowS # show :: BindResponse -> String # showList :: [BindResponse] -> ShowS # | |
Generic BindResponse Source # | |
Defined in LDAPv3.Message Associated Types type Rep BindResponse :: Type -> Type # | |
NFData BindResponse Source # | |
Defined in LDAPv3.Message Methods rnf :: BindResponse -> () # | |
type Rep BindResponse Source # | |
Defined in LDAPv3.Message type Rep BindResponse = D1 ('MetaData "BindResponse" "LDAPv3.Message" "LDAPv3-0.1.0.0-inplace" 'False) (C1 ('MetaCons "BindResponse" 'PrefixI 'True) (S1 ('MetaSel ('Just "_BindResponse'LDAPResult") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (COMPONENTS_OF 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 }
Constructors
Instances
Constructors
Scope'baseObject | |
Scope'singleLevel | |
Scope'wholeSubtree |
Instances
Bounded Scope Source # | |
Enum Scope Source # | |
Eq Scope Source # | |
Show Scope Source # | |
Generic Scope Source # | |
NFData Scope Source # | |
Defined in LDAPv3.Message | |
type Rep Scope Source # | |
Defined in LDAPv3.Message type Rep Scope = D1 ('MetaData "Scope" "LDAPv3.Message" "LDAPv3-0.1.0.0-inplace" '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 #
Constructors
DerefAliases'neverDerefAliases | |
DerefAliases'derefInSearching | |
DerefAliases'derefFindingBaseObj | |
DerefAliases'derefAlways |
Instances
type AttributeSelection = [LDAPString] Source #
See SearchRequest
AttributeSelection ::= SEQUENCE OF selector LDAPString -- The LDAPString is constrained to -- <attributeSelector> in Section 4.5.1.8
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, ... }
Constructors
Instances
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
.
Constructors
SubstringFilter | |
Instances
See SubstringFilter
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 # | |
Show Substring Source # | |
Generic Substring Source # | |
NFData Substring Source # | |
Defined in LDAPv3.Message | |
type Rep Substring Source # | |
Defined in LDAPv3.Message type Rep Substring = D1 ('MetaData "Substring" "LDAPv3.Message" "LDAPv3-0.1.0.0-inplace" 'False) (C1 ('MetaCons "Substring'initial" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (IMPLICIT ('CONTEXTUAL 0) AssertionValue))) :+: (C1 ('MetaCons "Substring'any" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (IMPLICIT ('CONTEXTUAL 1) AssertionValue))) :+: C1 ('MetaCons "Substring'final" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (IMPLICIT ('CONTEXTUAL 2) AssertionValue))))) |
data MatchingRuleAssertion Source #
See SearchRequest
Filter
MatchingRuleAssertion ::= SEQUENCE { matchingRule [1] MatchingRuleId OPTIONAL, type [2] AttributeDescription OPTIONAL, matchValue [3] AssertionValue, dnAttributes [4] BOOLEAN DEFAULT FALSE }
Constructors
Instances
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 }
Constructors
SearchResultEntry | |
Instances
type PartialAttributeList = [PartialAttribute] Source #
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
Constructors
SearchResultReference ('APPLICATION 19 `IMPLICIT` NonEmpty URI) |
Instances
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 } }
Constructors
ModifyRequest | |
Fields |
Instances
Eq ModifyRequest Source # | |
Defined in LDAPv3.Message Methods (==) :: ModifyRequest -> ModifyRequest -> Bool # (/=) :: ModifyRequest -> ModifyRequest -> Bool # | |
Show ModifyRequest Source # | |
Defined in LDAPv3.Message Methods showsPrec :: Int -> ModifyRequest -> ShowS # show :: ModifyRequest -> String # showList :: [ModifyRequest] -> ShowS # | |
Generic ModifyRequest Source # | |
Defined in LDAPv3.Message Associated Types type Rep ModifyRequest :: Type -> Type # | |
NFData ModifyRequest Source # | |
Defined in LDAPv3.Message Methods rnf :: ModifyRequest -> () # | |
type Rep ModifyRequest Source # | |
Defined in LDAPv3.Message type Rep ModifyRequest = D1 ('MetaData "ModifyRequest" "LDAPv3.Message" "LDAPv3-0.1.0.0-inplace" '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]))) |
See ModifyRequest
Constructors
Change | |
Instances
Eq Change Source # | |
Show Change Source # | |
Generic Change Source # | |
NFData Change Source # | |
Defined in LDAPv3.Message | |
type Rep Change Source # | |
Defined in LDAPv3.Message type Rep Change = D1 ('MetaData "Change" "LDAPv3.Message" "LDAPv3-0.1.0.0-inplace" 'False) (C1 ('MetaCons "Change" 'PrefixI 'True) (S1 ('MetaSel ('Just "_Change'operation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ENUMERATED Operation)) :*: S1 ('MetaSel ('Just "_Change'modification") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PartialAttribute))) |
See ModifyRequest
and Change
Constructors
Operation'add | |
Operation'delete | |
Operation'replace |
Instances
Bounded Operation Source # | |
Enum Operation Source # | |
Defined in LDAPv3.Message Methods succ :: Operation -> Operation # pred :: Operation -> Operation # fromEnum :: Operation -> Int # enumFrom :: Operation -> [Operation] # enumFromThen :: Operation -> Operation -> [Operation] # enumFromTo :: Operation -> Operation -> [Operation] # enumFromThenTo :: Operation -> Operation -> Operation -> [Operation] # | |
Eq Operation Source # | |
Show Operation Source # | |
Generic Operation Source # | |
NFData Operation Source # | |
Defined in LDAPv3.Message | |
type Rep Operation Source # | |
Defined in LDAPv3.Message type Rep Operation = D1 ('MetaData "Operation" "LDAPv3.Message" "LDAPv3-0.1.0.0-inplace" '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 }
Constructors
AddRequest | |
Fields |
Instances
Eq AddRequest Source # | |
Defined in LDAPv3.Message | |
Show AddRequest Source # | |
Defined in LDAPv3.Message Methods showsPrec :: Int -> AddRequest -> ShowS # show :: AddRequest -> String # showList :: [AddRequest] -> ShowS # | |
Generic AddRequest Source # | |
Defined in LDAPv3.Message Associated Types type Rep AddRequest :: Type -> Type # | |
NFData AddRequest Source # | |
Defined in LDAPv3.Message Methods rnf :: AddRequest -> () # | |
type Rep AddRequest Source # | |
Defined in LDAPv3.Message type Rep AddRequest = D1 ('MetaData "AddRequest" "LDAPv3.Message" "LDAPv3-0.1.0.0-inplace" '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 }
Constructors
ModifyDNRequest | |
Instances
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 }
Constructors
CompareRequest | |
Instances
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 }
Constructors
ExtendedRequest | |
Instances
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 }
Constructors
ExtendedResponse | |
Instances
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 }
Constructors
IntermediateResponse | |
Instances
ASN.1 Helpers
type OCTET_STRING = ByteString Source #
ASN.1 OCTET STRING
type
type BOOLEAN_DEFAULT (def :: Bool) = Bool Source #
Helper representing a BOOLEAN DEFAULT (TRUE|FALSE)
ASN.1 type annotation
ASN.1 SET OF
type
Constructors
SET [x] |
ASN.1 SET SIZE (1..MAX) OF
type
type COMPONENTS_OF x = x Source #
ASN.1 COMPONENTS OF
Annotation
ASN.1 type-level tagging
type ENUMERATED x = x Source #
ASN.1 ENUMERATED
Annotation
Type-level promoted Tag
Constructors
UNIVERSAL Nat | |
APPLICATION Nat | |
CONTEXTUAL Nat | |
PRIVATE Nat |
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 # | |
Eq t => Eq (UInt lb ub t) Source # | |
(UIntBounds lb ub t, Integral t, Ord t) => Num (UInt lb ub t) Source # | |
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 # | |
Defined in Data.Int.Subtypes | |
Show t => Show (UInt lb ub t) Source # | |
NFData t => NFData (UInt lb ub t) Source # | |
Defined in Data.Int.Subtypes |