Copyright | 2014 Kei Hibino |
---|---|
License | BSD3 |
Maintainer | ex8k.hibino@gmail.com |
Stability | experimental |
Portability | unknown |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- type Attribute = (AttrType, AttrValue)
- data AttrType
- attrOid :: ByteString -> [ByteString] -> AttrType
- newtype AttrValue = AttrValue ByteString
- data Component
- component :: Attribute -> [Attribute] -> Component
- type DN = List1 Component
- consDN :: Component -> [Component] -> DN
- unconsDN :: DN -> (Component, [Component])
- type List1 = NonEmpty
- data LdifAttrValue
- type DN' = [Component']
- toDN' :: DN -> DN'
- type Component' = [Attribute]
- type Bound a = (a, a)
- exact :: a -> Bound a
- boundsElems :: Enum a => [(a, a)] -> [a]
- inBounds :: (Enum a, Ord a) => a -> [(a, a)] -> Bool
- elem' :: Ord a => a -> [a] -> Bool
- notElem' :: Ord a => a -> [a] -> Bool
- inSBounds :: (Enum a, Ord a) => a -> [(a, a)] -> Bool
- ordW8 :: Char -> Word8
- quotation :: Word8
- specialChars :: [Word8]
- ldifSafeBounds :: [Bound Char]
- ldifSafeInitBounds :: [Bound Char]
DN AST
Type of dn attribute type
attrOid :: ByteString -> [ByteString] -> AttrType Source #
Construct OID attribute type
Type of dn attribute value
Type of dn component (rdn)
data LdifAttrValue Source #
Type of LDIF attribute value
Instances
Eq LdifAttrValue Source # | |
Defined in Text.LDAP.Data (==) :: LdifAttrValue -> LdifAttrValue -> Bool # (/=) :: LdifAttrValue -> LdifAttrValue -> Bool # | |
Ord LdifAttrValue Source # | |
Defined in Text.LDAP.Data compare :: LdifAttrValue -> LdifAttrValue -> Ordering # (<) :: LdifAttrValue -> LdifAttrValue -> Bool # (<=) :: LdifAttrValue -> LdifAttrValue -> Bool # (>) :: LdifAttrValue -> LdifAttrValue -> Bool # (>=) :: LdifAttrValue -> LdifAttrValue -> Bool # max :: LdifAttrValue -> LdifAttrValue -> LdifAttrValue # min :: LdifAttrValue -> LdifAttrValue -> LdifAttrValue # | |
Show LdifAttrValue Source # | |
Defined in Text.LDAP.Data showsPrec :: Int -> LdifAttrValue -> ShowS # show :: LdifAttrValue -> String # showList :: [LdifAttrValue] -> ShowS # |
Weaken constraint but popular list type
type DN' = [Component'] Source #
Type of dn, simple list type
type Component' = [Attribute] Source #
Type of dn component (rdn), simple list type
Low-level Charset check interfaces
boundsElems :: Enum a => [(a, a)] -> [a] Source #
Element list in value bounds
inSBounds :: (Enum a, Ord a) => a -> [(a, a)] -> Bool infix 4 Source #
Test element in value bounds using ordered set.
specialChars :: [Word8] Source #
Secial word8 codes of dn
ldifSafeBounds :: [Bound Char] Source #
Char bounds LDIF safe string
ldifSafeInitBounds :: [Bound Char] Source #
Char bounds LDIF safe string first char