module Ldap.Asn1.ToAsn1
( ToAsn1(toAsn1)
) where
import Data.ASN1.Types (ASN1, ASN1Class, ASN1Tag, ASN1ConstructionType)
import qualified Data.ASN1.Types as Asn1
import Data.ByteString (ByteString)
import Data.Foldable (fold, foldMap)
import Data.List.NonEmpty (NonEmpty)
import Data.Maybe (maybe)
import Data.Monoid (Endo(Endo), (<>), mempty)
import qualified Data.Text.Encoding as Text
import Prelude (Integer, (.), fromIntegral)
import Ldap.Asn1.Type
class ToAsn1 a where
toAsn1 :: a -> Endo [ASN1]
instance ToAsn1 op => ToAsn1 (LdapMessage op) where
toAsn1 (LdapMessage i op mc) =
sequence (toAsn1 i <> toAsn1 op <> maybe mempty (context 0 . toAsn1) mc)
instance ToAsn1 Id where
toAsn1 (Id i) = single (Asn1.IntVal (fromIntegral i))
instance ToAsn1 LdapString where
toAsn1 (LdapString s) = single (Asn1.OctetString (Text.encodeUtf8 s))
instance ToAsn1 LdapOid where
toAsn1 (LdapOid s) = single (Asn1.OctetString (Text.encodeUtf8 s))
instance ToAsn1 LdapDn where
toAsn1 (LdapDn s) = toAsn1 s
instance ToAsn1 RelativeLdapDn where
toAsn1 (RelativeLdapDn s) = toAsn1 s
instance ToAsn1 AttributeDescription where
toAsn1 (AttributeDescription s) = toAsn1 s
instance ToAsn1 AttributeValue where
toAsn1 (AttributeValue s) = single (Asn1.OctetString s)
instance ToAsn1 AttributeValueAssertion where
toAsn1 (AttributeValueAssertion d v) = toAsn1 d <> toAsn1 v
instance ToAsn1 AssertionValue where
toAsn1 (AssertionValue s) = single (Asn1.OctetString s)
instance ToAsn1 PartialAttribute where
toAsn1 (PartialAttribute d xs) = sequence (toAsn1 d <> set (toAsn1 xs))
instance ToAsn1 Attribute where
toAsn1 (Attribute d xs) = sequence (toAsn1 d <> set (toAsn1 xs))
instance ToAsn1 MatchingRuleId where
toAsn1 (MatchingRuleId s) = toAsn1 s
instance ToAsn1 Controls where
toAsn1 (Controls cs) = sequence (toAsn1 cs)
instance ToAsn1 Control where
toAsn1 (Control t c v) =
sequence (fold
[ toAsn1 t
, single (Asn1.Boolean c)
, maybe mempty (single . Asn1.OctetString) v
])
instance ToAsn1 ProtocolClientOp where
toAsn1 (BindRequest v n a) =
application 0 (single (Asn1.IntVal (fromIntegral v)) <> toAsn1 n <> toAsn1 a)
toAsn1 UnbindRequest =
other Asn1.Application 2 mempty
toAsn1 (SearchRequest bo s da sl tl to f a) =
application 3 (fold
[ toAsn1 bo
, enum s'
, enum da'
, single (Asn1.IntVal (fromIntegral sl))
, single (Asn1.IntVal (fromIntegral tl))
, single (Asn1.Boolean to)
, toAsn1 f
, toAsn1 a
])
where
s' = case s of
BaseObject -> 0
SingleLevel -> 1
WholeSubtree -> 2
da' = case da of
NeverDerefAliases -> 0
DerefInSearching -> 1
DerefFindingBaseObject -> 2
DerefAlways -> 3
toAsn1 (ModifyRequest dn xs) =
application 6 (fold
[ toAsn1 dn
, sequence (foldMap (\(op, pa) -> sequence (enum (case op of
Add -> 0
Delete -> 1
Replace -> 2) <> toAsn1 pa)) xs)
])
toAsn1 (AddRequest dn as) =
application 8 (toAsn1 dn <> toAsn1 as)
toAsn1 (DeleteRequest (LdapDn (LdapString dn))) =
other Asn1.Application 10 (Text.encodeUtf8 dn)
toAsn1 (ModifyDnRequest dn rdn del new) =
application 12 (fold
[ toAsn1 dn
, toAsn1 rdn
, single (Asn1.Boolean del)
, maybe mempty
(\(LdapDn (LdapString dn')) -> other Asn1.Context 0 (Text.encodeUtf8 dn'))
new
])
toAsn1 (CompareRequest dn av) =
application 14 (toAsn1 dn <> sequence (toAsn1 av))
toAsn1 (ExtendedRequest (LdapOid oid) mv) =
application 23 (fold
[ other Asn1.Context 0 (Text.encodeUtf8 oid)
, maybe mempty (other Asn1.Context 1) mv
])
instance ToAsn1 AuthenticationChoice where
toAsn1 (Simple s) = other Asn1.Context 0 s
instance ToAsn1 AttributeSelection where
toAsn1 (AttributeSelection as) = sequence (toAsn1 as)
instance ToAsn1 Filter where
toAsn1 f = case f of
And xs -> context 0 (toAsn1 xs)
Or xs -> context 1 (toAsn1 xs)
Not x -> context 2 (toAsn1 x)
EqualityMatch x -> context 3 (toAsn1 x)
Substrings x -> context 4 (toAsn1 x)
GreaterOrEqual x -> context 5 (toAsn1 x)
LessOrEqual x -> context 6 (toAsn1 x)
Present (AttributeDescription (LdapString x))
-> other Asn1.Context 7 (Text.encodeUtf8 x)
ApproxMatch x -> context 8 (toAsn1 x)
ExtensibleMatch x -> context 9 (toAsn1 x)
instance ToAsn1 SubstringFilter where
toAsn1 (SubstringFilter ad ss) =
toAsn1 ad <> sequence (foldMap (\s -> case s of
Initial (AssertionValue v) -> other Asn1.Context 0 v
Any (AssertionValue v) -> other Asn1.Context 1 v
Final (AssertionValue v) -> other Asn1.Context 2 v) ss)
instance ToAsn1 MatchingRuleAssertion where
toAsn1 (MatchingRuleAssertion mmr mad (AssertionValue av) _) = fold
[ maybe mempty f mmr
, maybe mempty g mad
, other Asn1.Context 3 av
]
where
f (MatchingRuleId (LdapString x)) = other Asn1.Context 1 (Text.encodeUtf8 x)
g (AttributeDescription (LdapString x)) = other Asn1.Context 2 (Text.encodeUtf8 x)
instance ToAsn1 AttributeList where
toAsn1 (AttributeList xs) = sequence (toAsn1 xs)
instance ToAsn1 a => ToAsn1 [a] where
toAsn1 = foldMap toAsn1
instance ToAsn1 a => ToAsn1 (NonEmpty a) where
toAsn1 = foldMap toAsn1
sequence :: Endo [ASN1] -> Endo [ASN1]
sequence = construction Asn1.Sequence
set :: Endo [ASN1] -> Endo [ASN1]
set = construction Asn1.Set
application :: ASN1Tag -> Endo [ASN1] -> Endo [ASN1]
application = construction . Asn1.Container Asn1.Application
context :: ASN1Tag -> Endo [ASN1] -> Endo [ASN1]
context = construction . Asn1.Container Asn1.Context
construction :: ASN1ConstructionType -> Endo [ASN1] -> Endo [ASN1]
construction t x = single (Asn1.Start t) <> x <> single (Asn1.End t)
other :: ASN1Class -> ASN1Tag -> ByteString -> Endo [ASN1]
other c t = single . Asn1.Other c t
enum :: Integer -> Endo [ASN1]
enum = single . Asn1.Enumerated
single :: a -> Endo [a]
single x = Endo (x :)