Attachment "ldap.diff" to
ticket [2018141fff]
added by
flatworm
2008-07-15 06:34:00.
diff -ur ldap.orig/ldap.tcl ldap/ldap.tcl
--- ldap.orig/ldap.tcl 2008-03-27 07:21:05.000000000 +0300
+++ ldap/ldap.tcl 2008-07-15 03:30:18.000000000 +0400
@@ -5,7 +5,7 @@
#
# A (partial) LDAPv3 protocol implementation in plain Tcl.
#
-# See RFC 2251 and ASN.1 (X.680) and BER (X.690).
+# See RFC 4510 and ASN.1 (X.680) and BER (X.690).
#
#
# This software is copyrighted by Jochen C. Loewer ([email protected]). The
@@ -1128,109 +1128,6 @@
#-----------------------------------------------------------------------------
-# buildUpFilter - parses the text representation of LDAP search
-# filters and transforms it into the correct
-# marshalled representation for the search request
-# packet
-#
-#-----------------------------------------------------------------------------
-proc ldap::buildUpFilter { filter } {
-
- set first [lindex $filter 0]
- set data ""
- switch -regexp -- $first {
- ^\\&$ { #--- and -------------------------------------------
- foreach term [lrange $filter 1 end] {
- append data [buildUpFilter $term]
- }
- return [asnChoiceConstr 0 $data]
- }
- ^\\|$ { #--- or --------------------------------------------
- foreach term [lrange $filter 1 end] {
- append data [buildUpFilter $term]
- }
- return [asnChoiceConstr 1 $data]
- }
- ^\\!$ { #--- not -------------------------------------------
- return [asnChoiceConstr 2 [buildUpFilter [lindex $filter 1]]]
- }
- =\\*$ { #--- present ---------------------------------------
- set endpos [expr {[string length $first] -3}]
- set attributetype [string range $first 0 $endpos]
- return [asnChoice 7 $attributetype]
- }
- ^[0-9A-z.]*~= { #--- approxMatch --------------------------
- regexp {^([0-9A-z.]*)~=(.*)$} $first all attributetype value
- return [asnChoiceConstr 8 [asnOctetString $attributetype] \
- [asnOctetString $value] ]
- }
- ^[0-9A-z.]*<= { #--- lessOrEqual --------------------------
- regexp {^([0-9A-z.]*)<=(.*)$} $first all attributetype value
- return [asnChoiceConstr 6 [asnOctetString $attributetype] \
- [asnOctetString $value] ]
- }
- ^[0-9A-z.]*>= { #--- greaterOrEqual -----------------------
- regexp {^([0-9A-z.]*)>=(.*)$} $first all attributetype value
- return [asnChoiceConstr 5 [asnOctetString $attributetype] \
- [asnOctetString $value] ]
- }
- ^[0-9A-z.]*=.*\\*.* { #--- substrings -----------------
- regexp {^([0-9A-z.]*)=(.*)$} $first all attributetype value
- regsub -all {\*+} $value {*} value
- set value [split $value "*"]
-
- set firstsubstrtype 0 ;# initial
- set lastsubstrtype 2 ;# final
- if {[string equal [lindex $value 0] ""]} {
- set firstsubstrtype 1 ;# any
- set value [lreplace $value 0 0]
- }
- if {[string equal [lindex $value end] ""]} {
- set lastsubstrtype 1 ;# any
- set value [lreplace $value end end]
- }
-
- set n [llength $value]
-
- set i 1
- set l {}
- set substrtype 0 ;# initial
- foreach str $value {
- if {$i == 1 && $i == $n} {
- if {$firstsubstrtype == 0} {
- set substrtype 0 ;# initial
- } elseif {$lastsubstrtype == 2} {
- set substrtype 2 ;# final
- } else {
- set substrtype 1 ;# any
- }
- } elseif {$i == 1} {
- set substrtype $firstsubstrtype
- } elseif {$i == $n} {
- set substrtype $lastsubstrtype
- } else {
- set substrtype 1 ;# any
- }
- lappend l [asnChoice $substrtype $str]
- incr i
- }
- return [asnChoiceConstr 4 [asnOctetString $attributetype] \
- [asnSequenceFromList $l] ]
- }
- ^[0-9A-z.]*= { #--- equal ---------------------------------
- regexp {^([0-9A-z.]*)=(.*)$} $first all attributetype value
- trace "equal: attributetype='$attributetype' value='$value'"
- return [asnChoiceConstr 3 [asnOctetString $attributetype] \
- [asnOctetString $value] ]
- }
- default {
- return [buildUpFilter $first]
- #error "cant handle $first for filter part"
- }
- }
-}
-
-#-----------------------------------------------------------------------------
# search - performs a LDAP search below the baseObject tree using a
# complex LDAP search expression (like "|(cn=Linus*)(sn=Torvalds*)"
# and returns all matching objects (DNs) with given attributes
@@ -1349,10 +1246,7 @@
#----------------------------------------------------------
# marshal filter and attributes parameter
#----------------------------------------------------------
- regsub -all {\(} $filterString " \{" filterString
- regsub -all {\)} $filterString "\} " filterString
-
- set berFilter [buildUpFilter $filterString]
+ set berFilter [filter::encode $filterString]
set berAttributes ""
foreach attribute $attributes {
@@ -1437,10 +1331,15 @@
-errorcode [list LDAP [resultCode2String $resultCode] $matchedDN $errorMessage] \
"LDAP error [resultCode2String $resultCode] : $errorMessage"
}
- } else {
- error "unexpected application number ($appNum != 4 or 5)"
}
+ # Unknown application type of result set.
+ # We should just ignore it since the only PDU the server
+ # MUST return if it understood our request is the "search response
+ # done" (apptype 5) which we know how to process.
+
+ # TODO we should implement processing of apptype 19 (search reference)
+
return $result
}
@@ -1855,3 +1754,348 @@
}
trace ""
}
+
+#-----------------------------------------------------------------------------
+# ldap::filter -- set of procedures for construction of BER-encoded
+# data defined by ASN.1 type Filter described in RFC 4511
+# from string representations of search filters
+# defined in RFC 4515.
+#-----------------------------------------------------------------------------
+namespace eval ldap::filter {
+ # Regexp which matches strings of type AttribyteType:
+ variable reatype {[A-Za-z][A-Za-z0-9-]*|\d+(?:\.\d+)+}
+
+ # Regexp which matches attribute options in strings
+ # of type AttributeDescription:
+ variable reaopts {(?:;[A-Za-z0-9-]+)*}
+
+ # Regexp which matches strings of type AttributeDescription.
+ # Note that this regexp captures attribute options,
+ # with leading ";", if any.
+ variable readesc (?:$reatype)($reaopts)
+
+ # Two regexps to match strings representing "left hand side" (LHS)
+ # in extensible match assertion.
+ # In fact there could be one regexp with two alterations,
+ # but this would complicate capturing of regexp parts.
+ # The first regexp captures, in this order:
+ # 1. Attribute description.
+ # 2. Attribute options.
+ # 3. ":dn" string, indicating "Use DN attribute types" flag.
+ # 4. Matching rule ID.
+ # The second regexp captures, in this order:
+ # 1. ":dn" string.
+ # 2. Matching rule ID.
+ variable reaextmatch1 ^($readesc)(:dn)?(?::($reatype))?\$
+ variable reaextmatch2 ^(:dn)?:($reatype)\$
+
+ # The only validation proc using this regexp requires it to be
+ # anchored to the boundaries of a string being validated,
+ # so we change it here to allow this regexp to be compiled:
+ set readesc ^$readesc\$
+
+ unset reatype reaopts
+
+ namespace import ::asn::*
+}
+
+# "Public API" function.
+# Parses the string represntation of an LDAP search filter expression
+# and returns its BER-encoded form.
+# NOTE While RFC 4515 strictly defines that any filter expression must
+# be surrounded by parentheses it is customary for LDAP client software
+# to allow specification of simple (i.e. non-compound) filter expressions
+# without enclosing parentheses, so we also do this (in fact, we allow
+# omission of outermost parentheses in any filter expression).
+proc ldap::filter::encode s {
+ if {[string match (*) $s]} {
+ ProcessFilter $s
+ } else {
+ ProcessFilterComp $s
+ }
+}
+
+# Parses the string represntation of an LDAP search filter expression
+# and returns its BER-encoded form.
+proc ldap::filter::ProcessFilter s {
+ if {![string match (*) $s]} {
+ return -code error "Invalid filter: filter expression must be\
+ surrounded by parentheses"
+ }
+ ProcessFilterComp [string range $s 1 end-1]
+}
+
+# Parses "internals" of a filter expression, i.e. what's contained
+# between its enclosing parentheses.
+# It classifies the type of filter expression (compound, negated or
+# simple) and invokes its corresponding handler.
+# Returns a BER-encoded form of the filter expression.
+proc ldap::filter::ProcessFilterComp s {
+ switch -- [string index $s 0] {
+ & {
+ ProcessFilterList 0 [string range $s 1 end]
+ }
+ | {
+ ProcessFilterList 1 [string range $s 1 end]
+ }
+ ! {
+ ProcessNegatedFilter [string range $s 1 end]
+ }
+ default {
+ ProcessMatch $s
+ }
+ }
+}
+
+# Parses string $s containing a chain of one or more filter
+# expressions (as found in compound filter expressions),
+# processes each filter in such chain and returns
+# a BER-encoded form of this chain tagged with specified
+# application type given as $apptype.
+proc ldap::filter::ProcessFilterList {apptype s} {
+ set data ""
+ set rest $s
+ while 1 {
+ foreach {filter rest} [ExtractFilter $rest] break
+ append data [ProcessFilter $filter]
+ if {$rest == ""} break
+ }
+ # TODO looks like it's impossible to hit this condition
+ if {[string length $data] == 0} {
+ return -code error "Invalid filter: filter composition must\
+ consist of at least one element"
+ }
+ asnChoiceConstr $apptype $data
+}
+
+# Parses a string $s representing a filter expression
+# and returns a BER construction representing negation
+# of that filter expression.
+proc ldap::filter::ProcessNegatedFilter s {
+ asnChoiceConstr 2 [ProcessFilter $s]
+}
+
+# Parses a string $s representing an "attribute matching rule"
+# (i.e. the contents of a non-compound filter expression)
+# and returns its BER-encoded form.
+proc ldap::filter::ProcessMatch s {
+ if {![regexp -indices {(=|~=|>=|<=|:=)} $s range]} {
+ return -code error "Invalid filter: no match operator in item"
+ }
+ foreach {a z} $range break
+ set lhs [string range $s 0 [expr {$a - 1}]]
+ set match [string range $s $a $z]
+ set val [string range $s [expr {$z + 1}] end]
+
+ switch -- $match {
+ = {
+ if {$val eq "*"} {
+ ProcessPresenceMatch $lhs
+ } else {
+ if {[regexp {^([^*]*)(\*(?:[^*]*\*)*)([^*]*)$} $val \
+ -> initial any final]} {
+ ProcessSubstringMatch $lhs $initial $any $final
+ } else {
+ ProcessSimpleMatch 3 $lhs $val
+ }
+ }
+ }
+ >= {
+ ProcessSimpleMatch 5 $lhs $val
+ }
+ <= {
+ ProcessSimpleMatch 6 $lhs $val
+ }
+ ~= {
+ ProcessSimpleMatch 8 $lhs $val
+ }
+ := {
+ ProcessExtensibleMatch $lhs $val
+ }
+ }
+}
+
+# From a string $s, containing a chain of filter
+# expressions (as found in compound filter expressions)
+# extracts the first filter expression and returns
+# a two element list composed of the extracted filter
+# expression and the remainder of the source string.
+proc ldap::filter::ExtractFilter s {
+ if {[string index $s 0] ne "("} {
+ return -code error "Invalid filter: malformed compound filter expression"
+ }
+ set pos 1
+ set nopen 1
+ while 1 {
+ if {![regexp -indices -start $pos {\)|\(} $s match]} {
+ return -code error "Invalid filter: unbalanced parenthesis"
+ }
+ set pos [lindex $match 0]
+ if {[string index $s $pos] eq "("} {
+ incr nopen
+ } else {
+ incr nopen -1
+ }
+ if {$nopen == 0} {
+ return [list [string range $s 0 $pos] \
+ [string range $s [incr pos] end]]
+ }
+ incr pos
+ }
+}
+
+# Constructs a BER-encoded form of a "presence" match
+# involving an attribute description string passed in $attrdesc.
+proc ldap::filter::ProcessPresenceMatch attrdesc {
+ ValidateAttributeDescription $attrdesc options
+ asnChoice 7 [LDAPString $attrdesc]
+}
+
+# Constructs a BER-encoded form of a simple match designated
+# by application type $apptype and involving an attribute
+# description $attrdesc and attribute value $val.
+# "Simple" match is one of: equal, less or equal, greater
+# or equal, approximate.
+proc ldap::filter::ProcessSimpleMatch {apptype attrdesc val} {
+ ValidateAttributeDescription $attrdesc options
+ append data [asnOctetString [LDAPString $attrdesc]] \
+ [asnOctetString [AssertionValue $val]]
+ asnChoiceConstr $apptype $data
+}
+
+# Constructs a BER-encoded form of a substrings match
+# involving an attribute description $attrdesc and parts of attribute
+# value -- $initial, $any and $final.
+# A string contained in any may be compound -- several strings
+# concatenated by asterisks ("*"), they are extracted and used as
+# multiple attribute value parts of type "any".
+proc ldap::filter::ProcessSubstringMatch {attrdesc initial any final} {
+ ValidateAttributeDescription $attrdesc options
+
+ set data [asnOctetString [LDAPString $attrdesc]]
+
+ set seq [list]
+ set parts 0
+ if {$initial != ""} {
+ lappend seq [asnChoice 0 [AssertionValue $initial]]
+ incr parts
+ }
+
+ foreach v [split [string trim $any *] *] {
+ if {$v != ""} {
+ lappend seq [asnChoice 1 [AssertionValue $v]]
+ incr parts
+ }
+ }
+
+ if {$final != ""} {
+ lappend seq [asnChoice 2 [AssertionValue $final]]
+ incr parts
+ }
+
+ if {$parts == 0} {
+ return -code error "Invalid filter: substrings match parses to zero parts"
+ }
+
+ append data [asnSequenceFromList $seq]
+
+ asnChoiceConstr 4 $data
+}
+
+# Constructs a BER-encoded form of an extensible match
+# involving an attribute value given in $value and a string
+# containing the matching rule OID, if present a "Use DN attribute
+# types" flag, if present, and an atttibute description, if present,
+# given in $lhs (stands for "Left Hand Side").
+proc ldap::filter::ProcessExtensibleMatch {lhs value} {
+ ParseExtMatchLHS $lhs attrdesc options dn ruleid
+ set data ""
+ foreach {apptype val} [list 1 $ruleid 2 $attrdesc] {
+ if {$val != ""} {
+ append data [asnChoice $apptype [LDAPString $val]]
+ }
+ }
+ append data [asnChoice 3 [AssertionValue $value]]
+ if {$dn} {
+ # [asnRetag] is broken in asn, so we use the trick
+ # to simulate "boolean true" BER-encoding which
+ # is octet 1 of length 1:
+ append data [asnChoice 4 [binary format cc 1 1]]
+ }
+ asnChoiceConstr 9 $data
+}
+
+# Parses a string $s, representing a "left hand side" of an extensible match
+# expression, into several parts: attribute desctiption, options,
+# "Use DN attribute types" flag and rule OID. These parts are
+# assigned to corresponding variables in the caller's scope.
+proc ldap::filter::ParseExtMatchLHS {s attrdescVar optionsVar dnVar ruleidVar} {
+ upvar 1 $attrdescVar attrdesc $optionsVar options $dnVar dn $ruleidVar ruleid
+ variable reaextmatch1
+ variable reaextmatch2
+ if {[regexp $reaextmatch1 $s -> attrdesc opts dnstr ruleid]} {
+ set options [ProcessAttrTypeOptions $opts]
+ set dn [expr {$dnstr != ""}]
+ } elseif {[regexp $reaextmatch2 $s -> dnstr ruleid]} {
+ set attrdesc ""
+ set options [list]
+ set dn [expr {$dnstr != ""}]
+ } else {
+ return -code error "Invalid filter: malformed attribute description"
+ }
+}
+
+# Validates an attribute description passed as $attrdesc.
+# Raises an error if it's ill-formed.
+# Variable in the caller's scope whose name is passed in optionsVar
+# is set to a list of attribute options (which may be empty if
+# there's no options in the attribute type).
+proc ldap::filter::ValidateAttributeDescription {attrdesc optionsVar} {
+ variable readesc
+ if {![regexp $readesc $attrdesc -> opts]} {
+ return -code error "Invalid filter: malformed attribute description"
+ }
+ upvar 1 $optionsVar options
+ set options [ProcessAttrTypeOptions $opts]
+ return
+}
+
+# Parses a string $s containing one or more attribute
+# options, delimited by seimcolons, with the leading semicolon,
+# if non-empty.
+# Returns a list of distinct options, lowercased for normalization
+# purposes.
+proc ldap::filter::ProcessAttrTypeOptions s {
+ set opts [list]
+ foreach opt [split [string trimleft $s \;] \;] {
+ lappend opts [string tolower $opt]
+ }
+ set opts
+}
+
+# Checks an assertion value $s for validity and substitutes
+# any backslash escapes in it with their respective values.
+# Returns canonical form of the attribute value
+# ready to be packed into a BER-encoded stream.
+proc ldap::filter::AssertionValue s {
+ set v [encoding convertto utf-8 $s]
+ if {[regexp {\\(?:[[:xdigit:]])?(?![[:xdigit:]])|[()*\0]} $v]} {
+ return -code error "Invalid filter: malformed assertion value"
+ }
+
+ variable escmap
+ if {![info exists escmap]} {
+ for {set i 0} {$i <= 0xff} {incr i} {
+ lappend escmap [format {\%02x} $i] [format %c $i]
+ }
+ }
+ string map -nocase $escmap $v
+}
+
+# Turns a given Tcl string $s into a binary blob ready to be packed
+# into a BER-encoded stream.
+proc ldap::filter::LDAPString s {
+ encoding convertto utf-8 $s
+}
+
+# vim:ts=8:sw=4:sts=4:noet
diff -ur ldap.orig/ldap.test ldap/ldap.test
--- ldap.orig/ldap.test 2006-10-10 01:41:40.000000000 +0400
+++ ldap/ldap.test 2008-07-14 20:53:19.000000000 +0400
@@ -257,8 +257,607 @@
-errorOutput [tcltest::wrongNumArgs {ldap::disconnect} \
{handle} 0 ]
+# Handling of string representation of filters (RFC 4515):
+package require asn
+namespace import asn::*
+proc glue args {
+ join $args ""
+}
+
+test filter-0.0 {[glue] should concatenate its string arguments} -body {
+ glue a b c d \0 foo
+} -result abcd\0foo
+
+test filter-1.0 {LDAPString produces packed UTF-8} -body {
+ binary scan [ldap::filter::LDAPString \u043a\u0430\u0448\u0430] H* foo
+ set foo
+} -result d0bad0b0d188d0b0 -cleanup { unset foo }
+
+test filter-2.0 {Backslash escaping in attribute values} -body {
+ set a ""
+ set b ""
+ for {set i 0} {$i <= 255} {incr i} {
+ append a [format \\%02x $i] ;# lowercase hex
+ append b [format %c $i]
+ }
+ string equal [ldap::filter::AttributeValue $a] $b
+} -result 1 -cleanup { unset a b i }
+
+test filter-2.1 {Backslash escaping in attribute values} -body {
+ set a ""
+ set b ""
+ for {set i 0} {$i <= 255} {incr i} {
+ append a [format \\%02X $i] ;# uppercase hex
+ append b [format %c $i]
+ }
+ string equal [ldap::filter::AttributeValue $a] $b
+} -result 1 -cleanup { unset a b i }
+
+test filter-3.1 {Malformed backslash escaping in attribute values} -body {
+ ldap::filter::AttributeValue foo\\0
+} -returnCodes error -result {Invalid filter: malformed attribute value}
+
+test filter-3.2 {Malformed backslash escaping in attribute values} -body {
+ ldap::filter::AttributeValue \\foo
+} -returnCodes error -result {Invalid filter: malformed attribute value}
+
+test filter-3.3 {Malformed backslash escaping in attribute values} -body {
+ ldap::filter::AttributeValue hA\\1x0rz
+} -returnCodes error -result {Invalid filter: malformed attribute value}
+
+test filter-3.4 {Malformed backslash escaping in attribute values} -body {
+ ldap::filter::AttributeValue \\value
+} -returnCodes error -result {Invalid filter: malformed attribute value}
+
+test filter-3.5 {Malformed backslash escaping in attribute values} -body {
+ ldap::filter::AttributeValue end\\
+} -returnCodes error -result {Invalid filter: malformed attribute value}
+
+test filter-4.0 {Presence match} -body {
+ ldap::filter::encode (Certificates=*)
+} -result [asnChoice 7 [ldap::filter::LDAPString Certificates]]
+
+test filter-4.1 {Presence match + attribute options} -body {
+ ldap::filter::encode (Certificates\;binary\;X-FooBar=*)
+} -result [asnChoice 7 [ldap::filter::LDAPString Certificates\;binary\;X-FooBar]]
+
+test filter-5.0 {Equality match} -body {
+ ldap::filter::encode (foo=bar)
+} -result [asnChoiceConstr 3 [glue \
+ [asnOctetString [ldap::filter::LDAPString foo]] \
+ [asnOctetString [ldap::filter::LDAPString bar]]]]
+
+test filter-5.1 {Equality match with empty attribute value} -body {
+ ldap::filter::encode (seeAlso=)
+} -result [asnChoiceConstr 3 [glue \
+ [asnOctetString [ldap::filter::LDAPString seeAlso]] \
+ [asnOctetString [ldap::filter::LDAPString ""]]]]
+
+test filter-5.2 {Equality match + attribute options} -body {
+ ldap::filter::encode (foo\;X-option=bar)
+} -result [asnChoiceConstr 3 [glue \
+ [asnOctetString [ldap::filter::LDAPString foo\;X-option]] \
+ [asnOctetString [ldap::filter::LDAPString bar]]]]
+
+test filter-6.0 {Approx match} -body {
+ ldap::filter::encode (descr~=val)
+} -result [asnChoiceConstr 8 [glue \
+ [asnOctetString [ldap::filter::LDAPString descr]] \
+ [asnOctetString [ldap::filter::LDAPString val]]]]
+
+test filter-6.1 {Approx match with empty attribute value} -body {
+ ldap::filter::encode (cn~=)
+} -result [asnChoiceConstr 8 [glue \
+ [asnOctetString [ldap::filter::LDAPString cn]] \
+ [asnOctetString [ldap::filter::LDAPString ""]]]]
+
+test filter-6.2 {Approx match + attribute options} -body {
+ ldap::filter::encode (binaryCert\;binary~=0000)
+} -result [asnChoiceConstr 8 [glue \
+ [asnOctetString [ldap::filter::LDAPString binaryCert\;binary]] \
+ [asnOctetString [ldap::filter::LDAPString 0000]]]]
+
+test filter-7.0 {Less or equal match} -body {
+ ldap::filter::encode (attr<=string)
+} -result [asnChoiceConstr 6 [glue \
+ [asnOctetString [ldap::filter::LDAPString attr]] \
+ [asnOctetString [ldap::filter::LDAPString string]]]]
+
+test filter-7.1 {Less or equal match with empty attribute value} -body {
+ ldap::filter::encode (attr<=)
+} -result [asnChoiceConstr 6 [glue \
+ [asnOctetString [ldap::filter::LDAPString attr]] \
+ [asnOctetString [ldap::filter::LDAPString ""]]]]
+
+test filter-7.2 {Less or equal match + attribute options} -body {
+ ldap::filter::encode (binaryCert\;binary<=01234)
+} -result [asnChoiceConstr 6 [glue \
+ [asnOctetString [ldap::filter::LDAPString binaryCert\;binary]] \
+ [asnOctetString [ldap::filter::LDAPString 01234]]]]
+
+test filter-8.0 {Greater or equal match} -body {
+ ldap::filter::encode (one>=two)
+} -result [asnChoiceConstr 5 [glue \
+ [asnOctetString [ldap::filter::LDAPString one]] \
+ [asnOctetString [ldap::filter::LDAPString two]]]]
+
+test filter-8.1 {Greater or equal match with empty attribute} -body {
+ ldap::filter::encode (one>=)
+} -result [asnChoiceConstr 5 [glue \
+ [asnOctetString [ldap::filter::LDAPString one]] \
+ [asnOctetString [ldap::filter::LDAPString ""]]]]
+
+test filter-8.2 {Greater or equal match + attribute options} -body {
+ ldap::filter::encode (exampleAttr\;X-experimental>=value)
+} -result [asnChoiceConstr 5 [glue \
+ [asnOctetString [ldap::filter::LDAPString exampleAttr\;X-experimental]] \
+ [asnOctetString [ldap::filter::LDAPString value]]]]
+
+test filter-9.0 {Substrings match: only initial string} -body {
+ ldap::filter::encode (sAMAccountName=management-*)
+} -result [asnChoiceConstr 4 [glue \
+ [asnOctetString [ldap::filter::LDAPString sAMAccountName]] \
+ [asnSequence [asnChoice 0 [ldap::filter::LDAPString management-]]]]]
+
+test filter-9.1 {Substrings match: only final string} -body {
+ ldap::filter::encode (User=*ish)
+} -result [asnChoiceConstr 4 [glue \
+ [asnOctetString [ldap::filter::LDAPString User]] \
+ [asnSequence [asnChoice 2 [ldap::filter::LDAPString ish]]]]]
+
+test filter-9.2 {Substrings match: initial and final strings} -body {
+ ldap::filter::encode (OU=F*off)
+} -result [asnChoiceConstr 4 [glue \
+ [asnOctetString [ldap::filter::LDAPString OU]] \
+ [asnSequence \
+ [asnChoice 0 [ldap::filter::LDAPString F]] \
+ [asnChoice 2 [ldap::filter::LDAPString off]]]]]
+
+test filter-9.3 {Substrings match: initial, any and final strings} -body {
+ ldap::filter::encode (mail=Schlenk*@uni-*.de)
+} -result [asnChoiceConstr 4 [glue \
+ [asnOctetString [ldap::filter::LDAPString mail]] \
+ [asnSequence \
+ [asnChoice 0 [ldap::filter::LDAPString Schlenk]] \
+ [asnChoice 1 [ldap::filter::LDAPString @uni-]] \
+ [asnChoice 2 [ldap::filter::LDAPString .de]]]]]
+
+test filter-9.4 {Substrings match: multiple any strings} -body {
+ ldap::filter::encode (Something=a*b*c*d*e)
+} -result [asnChoiceConstr 4 [glue \
+ [asnOctetString [ldap::filter::LDAPString Something]] \
+ [asnSequence \
+ [asnChoice 0 [ldap::filter::LDAPString a]] \
+ [asnChoice 1 [ldap::filter::LDAPString b]] \
+ [asnChoice 1 [ldap::filter::LDAPString c]] \
+ [asnChoice 1 [ldap::filter::LDAPString d]] \
+ [asnChoice 2 [ldap::filter::LDAPString e]]]]]
+
+test filter-9.5 {Substrings match: no initial and final strings} -body {
+ ldap::filter::encode (Whatever=*foo*)
+} -result [asnChoiceConstr 4 [glue \
+ [asnOctetString [ldap::filter::LDAPString Whatever]] \
+ [asnSequence \
+ [asnChoice 1 [ldap::filter::LDAPString foo]]]]]
+
+test filter-9.6 {Substrings match: empty any string prevention} -body {
+ ldap::filter::encode {(Person=J.Ra***m Hacker)}
+} -result [asnChoiceConstr 4 [glue \
+ [asnOctetString [ldap::filter::LDAPString Person]] \
+ [asnSequence \
+ [asnChoice 0 [ldap::filter::LDAPString J.Ra]] \
+ [asnChoice 2 [ldap::filter::LDAPString {m Hacker}]]]]]
+
+test filter-9.7 {Substrings match: empty any string prevention} -body {
+ ldap::filter::encode (SomeType=***foo***bar***baz**********)
+} -result [asnChoiceConstr 4 [glue \
+ [asnOctetString [ldap::filter::LDAPString SomeType]] \
+ [asnSequence \
+ [asnChoice 1 [ldap::filter::LDAPString foo]] \
+ [asnChoice 1 [ldap::filter::LDAPString bar]] \
+ [asnChoice 1 [ldap::filter::LDAPString baz]]]]]
+
+test filter-9.8 {Substrings match: parsing to zero parts} -body {
+ ldap::filter::encode (SomeType=**)
+} -returnCodes error -result {Invalid filter: substrings match parses to zero parts}
+
+test filter-9.10 {Substrings match: parsing to zero parts} -body {
+ ldap::filter::encode (SomeOtherType=*****)
+} -returnCodes error -result {Invalid filter: substrings match parses to zero parts}
+
+test filter-10.0 {Extensible match: only attribute description} -body {
+ ldap::filter::encode (AttrDesc:=10)
+} -result [asnChoiceConstr 9 [glue \
+ [asnChoice 2 [ldap::filter::LDAPString AttrDesc]] \
+ [asnChoice 3 [ldap::filter::LDAPString 10]]]]
+
+test filter-10.1 {Extensible match: attribute description + matching rule} -body {
+ ldap::filter::encode (personKind:caseIgnoreMatch:=bad)
+} -result [asnChoiceConstr 9 [glue \
+ [asnChoice 1 [ldap::filter::LDAPString caseIgnoreMatch]] \
+ [asnChoice 2 [ldap::filter::LDAPString personKind]] \
+ [asnChoice 3 [ldap::filter::LDAPString bad]]]]
+
+test filter-10.2 {Extensible match: attribute description
+ + matching rule in form of numericoid} -body {
+ ldap::filter::encode (personKind:1.3.6.1.4.1.1466.115.121.1.15:=good)
+} -result [asnChoiceConstr 9 [glue \
+ [asnChoice 1 [ldap::filter::LDAPString 1.3.6.1.4.1.1466.115.121.1.15]] \
+ [asnChoice 2 [ldap::filter::LDAPString personKind]] \
+ [asnChoice 3 [ldap::filter::LDAPString good]]]]
+
+test filter-10.3 {Extensible match: attribute description + DN flag} -body {
+ ldap::filter::encode (Foobar:dn:=345)
+} -result [asnChoiceConstr 9 [glue \
+ [asnChoice 2 [ldap::filter::LDAPString Foobar]] \
+ [asnChoice 3 [ldap::filter::LDAPString 345]] \
+ [asnChoice 4 [binary format cc 1 1]]]]
+
+test filter-10.4 {Extensible match: attribute description + DN flag + matching rule} -body {
+ ldap::filter::encode (NamelessOne:dn:caseIgnoreIA5Match:=who)
+} -result [asnChoiceConstr 9 [glue \
+ [asnChoice 1 [ldap::filter::LDAPString caseIgnoreIA5Match]] \
+ [asnChoice 2 [ldap::filter::LDAPString NamelessOne]] \
+ [asnChoice 3 [ldap::filter::LDAPString who]] \
+ [asnChoice 4 [binary format cc 1 1]]]]
+
+test filter-10.5 {Extensible match: attribute description + DN flag
+ + matching rule numericoid} -body {
+ ldap::filter::encode (OU:dn:111.222.333.444:=test)
+} -result [asnChoiceConstr 9 [glue \
+ [asnChoice 1 [ldap::filter::LDAPString 111.222.333.444]] \
+ [asnChoice 2 [ldap::filter::LDAPString OU]] \
+ [asnChoice 3 [ldap::filter::LDAPString test]] \
+ [asnChoice 4 [binary format cc 1 1]]]]
+
+test filter-10.6 {Extensible match: matching rule alone} -body {
+ ldap::filter::encode (:caseIgnoreIA5Match:=they)
+} -result [asnChoiceConstr 9 [glue \
+ [asnChoice 1 [ldap::filter::LDAPString caseIgnoreIA5Match]] \
+ [asnChoice 3 [ldap::filter::LDAPString they]]]]
+
+test filter-10.7 {Extensible match: matching rule alone, in form of numericoid} -body {
+ ldap::filter::encode (:874.274.378.432:=value)
+} -result [asnChoiceConstr 9 [glue \
+ [asnChoice 1 [ldap::filter::LDAPString 874.274.378.432]] \
+ [asnChoice 3 [ldap::filter::LDAPString value]]]]
+
+test filter-10.8 {Extensible match: matching rule + DN flag} -body {
+ ldap::filter::encode (:dn:caseIgnoreIA5Match:=they)
+} -result [asnChoiceConstr 9 [glue \
+ [asnChoice 1 [ldap::filter::LDAPString caseIgnoreIA5Match]] \
+ [asnChoice 3 [ldap::filter::LDAPString they]] \
+ [asnChoice 4 [binary format cc 1 1]]]]
+
+test filter-10.9 {Extensible match: matching rule (numericoid) + DN flag} -body {
+ ldap::filter::encode (:dn:111.222.333.444:=value)
+} -result [asnChoiceConstr 9 [glue \
+ [asnChoice 1 [ldap::filter::LDAPString 111.222.333.444]] \
+ [asnChoice 3 [ldap::filter::LDAPString value]] \
+ [asnChoice 4 [binary format cc 1 1]]]]
+
+test filter-10.10 {Extensible match: empty attribute value} -body {
+ ldap::filter::encode (AttrDesc:=)
+} -result [asnChoiceConstr 9 [glue \
+ [asnChoice 2 [ldap::filter::LDAPString AttrDesc]] \
+ [asnChoice 3 [ldap::filter::LDAPString ""]]]]
+
+test filter-10.11 {Extensible match: empty attribute value, DN flag} -body {
+ ldap::filter::encode (AttrDesc:dn:=)
+} -result [asnChoiceConstr 9 [glue \
+ [asnChoice 2 [ldap::filter::LDAPString AttrDesc]] \
+ [asnChoice 3 [ldap::filter::LDAPString ""]] \
+ [asnChoice 4 [binary format cc 1 1]]]]
+
+test filter-10.11 {Extensible match: matching rule with empty attribute value} -body {
+ ldap::filter::encode (:caseIgnoreIA5Match:=)
+} -result [asnChoiceConstr 9 [glue \
+ [asnChoice 1 [ldap::filter::LDAPString caseIgnoreIA5Match]] \
+ [asnChoice 3 [ldap::filter::LDAPString ""]]]]
+
+test filter-10.12 {Extensible match: empty LHS} -body {
+ ldap::filter::encode (:=foo)
+} -returnCodes error -result {Invalid filter: malformed attribute description}
+
+test filter-10.12 {Extensible match: empty DN flag or matching rule OID} -body {
+ ldap::filter::encode (attrDesc::=bar)
+} -returnCodes error -result {Invalid filter: malformed attribute description}
+
+test filter-10.12 {Extensible match: empty matching rule OID} -body {
+ ldap::filter::encode (attrDesc:dn::=baz)
+} -returnCodes error -result {Invalid filter: malformed attribute description}
+
+test filter-10.13 {Extensible match: empty DN flag} -body {
+ ldap::filter::encode (attrDesc::caseIgnoreMatch:=quux)
+} -returnCodes error -result {Invalid filter: malformed attribute description}
+
+test filter-10.14 {Extensible match: empty DN flag} -body {
+ ldap::filter::encode (::caseIgnoreMatch:=foo)
+} -returnCodes error -result {Invalid filter: malformed attribute description}
+
+test filter-10.15 {Extensible match: empty matching rule OID} -body {
+ ldap::filter::encode (::=bar)
+} -returnCodes error -result {Invalid filter: malformed attribute description}
+
+test filter-10.16 {Extensible match: malformed matching rule numericoid} -body {
+ ldap::filter::encode (:111.222.333.xxx:=baz)
+} -returnCodes error -result {Invalid filter: malformed attribute description}
+
+test filter-10.17 {Extensible match: malformed matching rule numericoid} -body {
+ ldap::filter::encode (userCategory:111.222.333.444\;binary:=baz)
+} -returnCodes error -result {Invalid filter: malformed attribute description}
+
+test filter-10.18 {Extensible match: malformed matching rule numericoid} -body {
+ ldap::filter::encode (userCategory:dn:111.222.333.444\;x-bar:=foo)
+} -returnCodes error -result {Invalid filter: malformed attribute description}
+
+test filter-10.19 {Extensible match: malformed matching rule numericoid} -body {
+ ldap::filter::encode (:caseIgnoreIA5Match\;lang-ru:=quux)
+} -returnCodes error -result {Invalid filter: malformed attribute description}
+
+test filter-10.20 {Extensible match: camel-cased DN flag} -body {
+ ldap::filter::encode (attrDesc:Dn:caseIgnoreMatch:=quux)
+} -returnCodes error -result {Invalid filter: malformed attribute description}
+
+test filter-10.21 {Extensible match: prohibited character in attribute description} -body {
+ ldap::filter::encode (4cast:=foo)
+} -returnCodes error -result {Invalid filter: malformed attribute description}
+
+test filter-10.22 {Extensible match: gibberish in place of DN flag} -body {
+ ldap::filter::encode (OU:gibberish:caseIgnoreIA5Match:=bar)
+} -returnCodes error -result {Invalid filter: malformed attribute description}
+
+test filter-10.23 {Extensible match: options in attribute description} -body {
+ ldap::filter::encode (personAge\;lang-ru\;x-foo:numericMatch:=99)
+} -result [asnChoiceConstr 9 [glue \
+ [asnChoice 1 [ldap::filter::LDAPString numericMatch]] \
+ [asnChoice 2 [ldap::filter::LDAPString personAge\;lang-ru\;x-foo]] \
+ [asnChoice 3 [ldap::filter::LDAPString 99]]]]
+
+test filter-10.24 {Extensible match: options in attribute description} -body {
+ ldap::filter::encode (111.222.333.444\;x-bar:dn:555.666.777.888:=foo)
+} -result [asnChoiceConstr 9 [glue \
+ [asnChoice 1 [ldap::filter::LDAPString 555.666.777.888]] \
+ [asnChoice 2 [ldap::filter::LDAPString 111.222.333.444\;x-bar]] \
+ [asnChoice 3 [ldap::filter::LDAPString foo]] \
+ [asnChoice 4 [binary format cc 1 1]]]]
+
+test filter-11.1 {Prohibited characters in argument value} -body {
+ ldap::filter::encode (foo=bar(and)baz)
+} -returnCodes error -result {Invalid filter: malformed attribute value}
+
+test filter-11.2 {Prohibited characters in argument value} -body {
+ ldap::filter::encode (zero=lurks\0here)
+} -returnCodes error -result {Invalid filter: malformed attribute value}
+
+test filter-11.3 {Prohibited characters in argument value} -body {
+ ldap::filter::encode (extensible:=asterisk*)
+} -returnCodes error -result {Invalid filter: malformed attribute value}
+
+test filter-12.0 {Malformed attribute description: empty} -body {
+ ldap::filter::encode (=foo)
+} -returnCodes error -result {Invalid filter: malformed attribute description}
+
+test filter-12.1 {Malformed attribute description: doesn't start with a letter} -body {
+ ldap::filter::encode (2forTheRoad=bar)
+} -returnCodes error -result {Invalid filter: malformed attribute description}
+
+test filter-12.2 {Malformed attribute description: mix of descr and numericoid} -body {
+ ldap::filter::encode (foo.12.13=bar)
+} -returnCodes error -result {Invalid filter: malformed attribute description}
+
+test filter-12.3 {Malformed attribute description: bad numericoid} -body {
+ ldap::filter::encode (.11.12.13=bar)
+} -returnCodes error -result {Invalid filter: malformed attribute description}
+
+test filter-12.4 {Malformed attribute description: bad numericoid} -body {
+ ldap::filter::encode (11.12.13.=bar)
+} -returnCodes error -result {Invalid filter: malformed attribute description}
+
+test filter-12.5 {Malformed attribute description: prohibited character in descr} -body {
+ ldap::filter::encode (cn_2=bar)
+} -returnCodes error -result {Invalid filter: malformed attribute description}
+
+test filter-12.6 {Malformed attribute description: prohibited character in option} -body {
+ ldap::filter::encode (OU\;lang_en=bar)
+} -returnCodes error -result {Invalid filter: malformed attribute description}
+
+test filter-12.7 {Malformed attribute description:
+ colon in an LHS part of a rule which doesn't represent an extensible match} -body {
+ ldap::filter::encode (phoneNumber:dn=value)
+} -returnCodes error -result {Invalid filter: malformed attribute description}
+
+test filter-12.8 {Malformed attribute description: empty option} -body {
+ ldap::filter::encode (CN\;\;lang-ru=?)
+} -returnCodes error -result {Invalid filter: malformed attribute description}
+
+test filter-15.0 {No match rule operator} -body {
+ ldap::filter::encode ()
+} -returnCodes error -result {Invalid filter: no match operator in item}
+
+test filter-15.1 {No match rule operator} -body {
+ ldap::filter::encode (11.12.14~value)
+} -returnCodes error -result {Invalid filter: no match operator in item}
+
+test filter-16.0 {Duplicated match rule operator} -body {
+ ldap::filter::encode (attrDesc=foo=bar)
+} -result [asnChoiceConstr 3 [glue \
+ [asnOctetString [ldap::filter::LDAPString attrDesc]] \
+ [asnOctetString [ldap::filter::LDAPString foo=bar]]]]
+
+test filter-16.1 {Duplicated match rule operator} -body {
+ ldap::filter::encode (attrDesc~=foo~=)
+} -result [asnChoiceConstr 8 [glue \
+ [asnOctetString [ldap::filter::LDAPString attrDesc]] \
+ [asnOctetString [ldap::filter::LDAPString foo~=]]]]
+
+test filter-16.2 {Duplicated match rule operator} -body {
+ ldap::filter::encode (attrDesc<=<=bar)
+} -result [asnChoiceConstr 6 [glue \
+ [asnOctetString [ldap::filter::LDAPString attrDesc]] \
+ [asnOctetString [ldap::filter::LDAPString <=bar]]]]
+
+test filter-16.3 {Duplicated match rule operator} -body {
+ ldap::filter::encode (attrDesc>=>=>=)
+} -result [asnChoiceConstr 5 [glue \
+ [asnOctetString [ldap::filter::LDAPString attrDesc]] \
+ [asnOctetString [ldap::filter::LDAPString >=>=]]]]
+
+test filter-16.4 {Duplicated match rule operator} -body {
+ ldap::filter::encode (AttrDesc:=:=what?:=)
+} -result [asnChoiceConstr 9 [glue \
+ [asnChoice 2 [ldap::filter::LDAPString AttrDesc]] \
+ [asnChoice 3 [ldap::filter::LDAPString :=what?:=]]]]
+
+test filter-17.0 {Compound filters: negation} -body {
+ ldap::filter::encode (!(foo=bar))
+} -result [asnChoiceConstr 2 [asnChoiceConstr 3 [glue \
+ [asnOctetString [ldap::filter::LDAPString foo]] \
+ [asnOctetString [ldap::filter::LDAPString bar]]]]]
+
+test filter-17.1 {Compound filters: AND} -body {
+ ldap::filter::encode (&(one=two)(three<=four)(five>=six))
+} -result [asnChoiceConstr 0 [glue \
+ [asnChoiceConstr 3 [glue \
+ [asnOctetString [ldap::filter::LDAPString one]] \
+ [asnOctetString [ldap::filter::LDAPString two]]]] \
+ [asnChoiceConstr 6 [glue \
+ [asnOctetString [ldap::filter::LDAPString three]] \
+ [asnOctetString [ldap::filter::LDAPString four]]]] \
+ [asnChoiceConstr 5 [glue \
+ [asnOctetString [ldap::filter::LDAPString five]] \
+ [asnOctetString [ldap::filter::LDAPString six]]]]]]
+
+test filter-17.2 {Compound filters: OR} -body {
+ ldap::filter::encode (|(foo=bar)(baz:fuzzyMatch:=quux)(key~=value))
+} -result [asnChoiceConstr 1 [glue \
+ [asnChoiceConstr 3 [glue \
+ [asnOctetString [ldap::filter::LDAPString foo]] \
+ [asnOctetString [ldap::filter::LDAPString bar]]]] \
+ [asnChoiceConstr 9 [glue \
+ [asnChoice 1 [ldap::filter::LDAPString fuzzyMatch]] \
+ [asnChoice 2 [ldap::filter::LDAPString baz]] \
+ [asnChoice 3 [ldap::filter::LDAPString quux]]]] \
+ [asnChoiceConstr 8 [glue \
+ [asnOctetString [ldap::filter::LDAPString key]] \
+ [asnOctetString [ldap::filter::LDAPString value]]]]]]
+
+test filter-18.1 {Compound filters: unbalanced parenthesis} -body {
+ ldap::filter::encode (&(foo=bar)(baz=quux)
+} -returnCodes error -result {Invalid filter: unbalanced parenthesis}
+
+test filter-18.2 {Compound filters: unbalanced parenthesis} -body {
+ ldap::filter::encode (!(&(a=b)c=d))
+} -returnCodes error -result {Invalid filter: malformed compound filter expression}
+
+test filter-18.2 {Compound filters: unbalanced parenthesis} -body {
+ ldap::filter::encode (!(&(a=b)))c=d))
+} -returnCodes error -result {Invalid filter: malformed compound filter expression}
+
+test filter-18.3 {Compound filters: unbalanced parenthesis} -body {
+ ldap::filter::encode (!()
+} -returnCodes error -result {Invalid filter:\
+ filter expression must be surrounded by parentheses}
+
+test filter-19.1 {Compound filters: junk in expression} -body {
+ ldap::filter::encode {(& (foo=bar)(baz=quux))}
+} -returnCodes error -result {Invalid filter: malformed compound filter expression}
+
+test filter-19.2 {Compound filters: junk in expression} -body {
+ ldap::filter::encode {(&(foo=bar) (baz=quux))}
+} -returnCodes error -result {Invalid filter: malformed compound filter expression}
+
+test filter-19.3 {Compound filters: junk in expression} -body {
+ ldap::filter::encode {(|(foo=bar)(baz=quux) )}
+} -returnCodes error -result {Invalid filter: malformed compound filter expression}
+
+test filter-19.3 {Compound filters: junk in expression} -body {
+ ldap::filter::encode {(&&(foo=bar)(baz=quux))}
+} -returnCodes error -result {Invalid filter: malformed compound filter expression}
+
+test filter-19.4 {Compound filters: junk in expression} -body {
+ ldap::filter::encode {((foo=bar)&(baz=quux))}
+} -returnCodes error -match glob -result {Invalid filter: malformed attribute *}
+
+test filter-20.0 {Missing elements in filter composition} -body {
+ ldap::filter::encode (!)
+} -returnCodes error -result {Invalid filter:\
+ filter expression must be surrounded by parentheses}
+
+test filter-20.1 {Missing elements in filter composition} -body {
+ ldap::filter::encode (&)
+} -returnCodes error -result {Invalid filter: malformed compound filter expression}
+
+test filter-20.2 {Missing elements in filter composition} -body {
+ ldap::filter::encode (|)
+} -returnCodes error -result {Invalid filter: malformed compound filter expression}
+
+test filter-21.0 {Torture test} -body {
+ ldap::filter::encode [regsub -all \\s+ {
+ (|
+ (&
+ (userName=Jane\20Random\00)
+ (userCategory;x-lang-ru~=human)
+ )
+ (!
+ (|
+ (!
+ (salary=*)
+ )
+ (&
+ (personAge>=80)
+ (yearsEmployed<=70)
+ (employeeName=Joe*a**nd**Hacker)
+ )
+ )
+ )
+ (|
+ (11.22.33.44;x-files:dn:=value)
+ (:567.34.56:=\28\2a\29)
+ )
+ (foo=bar)
+ )
+ } ""]
+} -result [asnChoiceConstr 1 [glue \
+ [asnChoiceConstr 0 [glue \
+ [asnChoiceConstr 3 [glue \
+ [asnOctetString [ldap::filter::LDAPString userName]] \
+ [asnOctetString [ldap::filter::LDAPString "Jane Random\0"]]]] \
+ [asnChoiceConstr 8 [glue \
+ [asnOctetString [ldap::filter::LDAPString userCategory\;x-lang-ru]] \
+ [asnOctetString [ldap::filter::LDAPString human]]]]]] \
+ [asnChoiceConstr 2 \
+ [asnChoiceConstr 1 [glue \
+ [asnChoiceConstr 2 \
+ [asnChoice 7 [ldap::filter::LDAPString salary]]] \
+ [asnChoiceConstr 0 [glue \
+ [asnChoiceConstr 5 [glue \
+ [asnOctetString [ldap::filter::LDAPString personAge]] \
+ [asnOctetString [ldap::filter::LDAPString 80]]]] \
+ [asnChoiceConstr 6 [glue \
+ [asnOctetString [ldap::filter::LDAPString yearsEmployed]] \
+ [asnOctetString [ldap::filter::LDAPString 70]]]] \
+ [asnChoiceConstr 4 [glue \
+ [asnOctetString [ldap::filter::LDAPString employeeName]] \
+ [asnSequence [glue \
+ [asnChoice 0 [ldap::filter::LDAPString Joe]] \
+ [asnChoice 1 [ldap::filter::LDAPString a]] \
+ [asnChoice 1 [ldap::filter::LDAPString nd]] \
+ [asnChoice 2 [ldap::filter::LDAPString Hacker]]]]]]]]]]] \
+ [asnChoiceConstr 1 [glue \
+ [asnChoiceConstr 9 [glue \
+ [asnChoice 2 [ldap::filter::LDAPString 11.22.33.44\;x-files]] \
+ [asnChoice 3 [ldap::filter::LDAPString value]] \
+ [asnChoice 4 [binary format cc 1 1]]]] \
+ [asnChoiceConstr 9 [glue \
+ [asnChoice 1 [ldap::filter::LDAPString 567.34.56]] \
+ [asnChoice 3 [ldap::filter::LDAPString (*)]]]]]] \
+ [asnChoiceConstr 3 [glue \
+ [asnOctetString [ldap::filter::LDAPString foo]] \
+ [asnOctetString [ldap::filter::LDAPString bar]]]] \
+ ]]
# -------------------------------------------------------------------------
testsuiteCleanup
@@ -267,3 +866,4 @@
# mode: tcl
# indent-tabs-mode: nil
# End:
+# vim:ts=8:sw=4:sts=4:noet:syntax=tcl