module Ldap.Client.Internal
( Host(..)
, PortNumber
, Ldap(..)
, ClientMessage(..)
, Type.ResultCode(..)
, Async
, AttrList
, wait
, waitSTM
, Response
, ResponseError(..)
, Request
, raise
, sendRequest
, Dn(..)
, Attr(..)
, AttrValue
, unAttr
, unbindAsync
, unbindAsyncSTM
) where
import Control.Concurrent.STM (STM, atomically)
import Control.Concurrent.STM.TMVar (TMVar, newEmptyTMVar, readTMVar)
import Control.Concurrent.STM.TQueue (TQueue, writeTQueue)
import Control.Exception (Exception, throwIO)
import Control.Monad (void)
import Data.ByteString (ByteString)
import Data.List.NonEmpty (NonEmpty)
import Data.Text (Text)
import Data.Typeable (Typeable)
import Network (PortNumber)
import qualified Ldap.Asn1.Type as Type
data Host =
Plain String
| Insecure String
| Secure String
deriving (Show, Eq, Ord)
data Ldap = Ldap
{ client :: TQueue ClientMessage
} deriving (Eq)
data ClientMessage = New Request (TMVar (NonEmpty Type.ProtocolServerOp))
type Request = Type.ProtocolClientOp
type InMessage = Type.ProtocolServerOp
type Response = NonEmpty InMessage
data Async a = Async (STM (Either ResponseError a))
instance Functor Async where
fmap f (Async stm) = Async (fmap (fmap f) stm)
newtype Dn = Dn Text
deriving (Show, Eq)
data ResponseError =
ResponseInvalid Request Response
| ResponseErrorCode Request Type.ResultCode Dn Text
deriving (Show, Eq, Typeable)
instance Exception ResponseError
newtype Attr = Attr Text
deriving (Show, Eq)
type AttrValue = ByteString
type AttrList f = [(Attr, f AttrValue)]
unAttr :: Attr -> Text
unAttr (Attr a) = a
wait :: Async a -> IO (Either ResponseError a)
wait = atomically . waitSTM
waitSTM :: Async a -> STM (Either ResponseError a)
waitSTM (Async stm) = stm
sendRequest :: Ldap -> (Response -> Either ResponseError a) -> Request -> STM (Async a)
sendRequest l p msg =
do var <- newEmptyTMVar
writeRequest l var msg
return (Async (fmap p (readTMVar var)))
writeRequest :: Ldap -> TMVar Response -> Request -> STM ()
writeRequest Ldap { client } var msg = writeTQueue client (New msg var)
raise :: Exception e => Either e a -> IO a
raise = either throwIO return
unbindAsync :: Ldap -> IO ()
unbindAsync =
atomically . unbindAsyncSTM
unbindAsyncSTM :: Ldap -> STM ()
unbindAsyncSTM l =
void (sendRequest l die Type.UnbindRequest)
where
die = error "Ldap.Client: do not wait for the response to UnbindRequest"