{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE NamedFieldPuns #-}
module Ldap.Client.Internal
  ( Host(..)
  , PortNumber
  , Ldap(..)
  , ClientMessage(..)
  , Type.ResultCode(..)
  , Async
  , AttrList
    
  , wait
  , waitSTM
    
  , Response
  , ResponseError(..)
  , Request
  , eitherToIO
  , sendRequest
  , Dn(..)
  , Attr(..)
  , AttrValue
  , unAttr
    
  , unbindAsync
  , unbindAsyncSTM
  ) where
import qualified Control.Concurrent.Async as Async (Async)
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)
#if __GLASGOW_HASKELL__ >= 84
import           Network.Socket (PortNumber)
#else
import           Network (PortNumber)
#endif
import           Network.Connection (TLSSettings, Connection)
import           Data.Void (Void)
import qualified Ldap.Asn1.Type as Type
data Host =
    Plain String           
  | Tls String TLSSettings 
    deriving (Int -> Host -> ShowS
[Host] -> ShowS
Host -> String
(Int -> Host -> ShowS)
-> (Host -> String) -> ([Host] -> ShowS) -> Show Host
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Host -> ShowS
showsPrec :: Int -> Host -> ShowS
$cshow :: Host -> String
show :: Host -> String
$cshowList :: [Host] -> ShowS
showList :: [Host] -> ShowS
Show)
data Ldap = Ldap
  { Ldap -> TQueue ClientMessage
reqQ    :: !(TQueue ClientMessage) 
  , Ldap -> Async Void
workers :: !(Async.Async Void) 
  , Ldap -> Connection
conn    :: !Connection 
  }
data ClientMessage = New !Request !(TMVar (NonEmpty Type.ProtocolServerOp))
type Request = Type.ProtocolClientOp
type InMessage = Type.ProtocolServerOp
type Response = NonEmpty InMessage
newtype Async a = Async (STM (Either ResponseError a))
instance Functor Async where
  fmap :: forall a b. (a -> b) -> Async a -> Async b
fmap a -> b
f (Async STM (Either ResponseError a)
stm) = STM (Either ResponseError b) -> Async b
forall a. STM (Either ResponseError a) -> Async a
Async ((Either ResponseError a -> Either ResponseError b)
-> STM (Either ResponseError a) -> STM (Either ResponseError b)
forall a b. (a -> b) -> STM a -> STM b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b) -> Either ResponseError a -> Either ResponseError b
forall a b.
(a -> b) -> Either ResponseError a -> Either ResponseError b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f) STM (Either ResponseError a)
stm)
newtype Dn = Dn Text
    deriving (Int -> Dn -> ShowS
[Dn] -> ShowS
Dn -> String
(Int -> Dn -> ShowS)
-> (Dn -> String) -> ([Dn] -> ShowS) -> Show Dn
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Dn -> ShowS
showsPrec :: Int -> Dn -> ShowS
$cshow :: Dn -> String
show :: Dn -> String
$cshowList :: [Dn] -> ShowS
showList :: [Dn] -> ShowS
Show, Dn -> Dn -> Bool
(Dn -> Dn -> Bool) -> (Dn -> Dn -> Bool) -> Eq Dn
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Dn -> Dn -> Bool
== :: Dn -> Dn -> Bool
$c/= :: Dn -> Dn -> Bool
/= :: Dn -> Dn -> Bool
Eq)
data ResponseError =
    ResponseInvalid !Request !Response 
  | ResponseErrorCode !Request !Type.ResultCode !Dn !Text 
    deriving (Int -> ResponseError -> ShowS
[ResponseError] -> ShowS
ResponseError -> String
(Int -> ResponseError -> ShowS)
-> (ResponseError -> String)
-> ([ResponseError] -> ShowS)
-> Show ResponseError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ResponseError -> ShowS
showsPrec :: Int -> ResponseError -> ShowS
$cshow :: ResponseError -> String
show :: ResponseError -> String
$cshowList :: [ResponseError] -> ShowS
showList :: [ResponseError] -> ShowS
Show, ResponseError -> ResponseError -> Bool
(ResponseError -> ResponseError -> Bool)
-> (ResponseError -> ResponseError -> Bool) -> Eq ResponseError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ResponseError -> ResponseError -> Bool
== :: ResponseError -> ResponseError -> Bool
$c/= :: ResponseError -> ResponseError -> Bool
/= :: ResponseError -> ResponseError -> Bool
Eq, Typeable)
instance Exception ResponseError
newtype Attr = Attr Text
    deriving (Int -> Attr -> ShowS
[Attr] -> ShowS
Attr -> String
(Int -> Attr -> ShowS)
-> (Attr -> String) -> ([Attr] -> ShowS) -> Show Attr
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Attr -> ShowS
showsPrec :: Int -> Attr -> ShowS
$cshow :: Attr -> String
show :: Attr -> String
$cshowList :: [Attr] -> ShowS
showList :: [Attr] -> ShowS
Show, Attr -> Attr -> Bool
(Attr -> Attr -> Bool) -> (Attr -> Attr -> Bool) -> Eq Attr
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Attr -> Attr -> Bool
== :: Attr -> Attr -> Bool
$c/= :: Attr -> Attr -> Bool
/= :: Attr -> Attr -> Bool
Eq)
type AttrValue = ByteString
type AttrList f = [(Attr, f AttrValue)]
unAttr :: Attr -> Text
unAttr :: Attr -> Text
unAttr (Attr Text
a) = Text
a
wait :: Async a -> IO (Either ResponseError a)
wait :: forall a. Async a -> IO (Either ResponseError a)
wait = STM (Either ResponseError a) -> IO (Either ResponseError a)
forall a. STM a -> IO a
atomically (STM (Either ResponseError a) -> IO (Either ResponseError a))
-> (Async a -> STM (Either ResponseError a))
-> Async a
-> IO (Either ResponseError a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Async a -> STM (Either ResponseError a)
forall a. Async a -> STM (Either ResponseError a)
waitSTM
waitSTM :: Async a -> STM (Either ResponseError a)
waitSTM :: forall a. Async a -> STM (Either ResponseError a)
waitSTM (Async STM (Either ResponseError a)
stm) = STM (Either ResponseError a)
stm
sendRequest :: Ldap -> (Response -> Either ResponseError a) -> Request -> STM (Async a)
sendRequest :: forall a.
Ldap
-> (Response -> Either ResponseError a) -> Request -> STM (Async a)
sendRequest Ldap
l Response -> Either ResponseError a
p Request
msg =
  do TMVar Response
var <- STM (TMVar Response)
forall a. STM (TMVar a)
newEmptyTMVar
     Ldap -> TMVar Response -> Request -> STM ()
writeRequest Ldap
l TMVar Response
var Request
msg
     Async a -> STM (Async a)
forall a. a -> STM a
forall (m :: * -> *) a. Monad m => a -> m a
return (STM (Either ResponseError a) -> Async a
forall a. STM (Either ResponseError a) -> Async a
Async ((Response -> Either ResponseError a)
-> STM Response -> STM (Either ResponseError a)
forall a b. (a -> b) -> STM a -> STM b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Response -> Either ResponseError a
p (TMVar Response -> STM Response
forall a. TMVar a -> STM a
readTMVar TMVar Response
var)))
writeRequest :: Ldap -> TMVar Response -> Request -> STM ()
writeRequest :: Ldap -> TMVar Response -> Request -> STM ()
writeRequest Ldap { TQueue ClientMessage
reqQ :: Ldap -> TQueue ClientMessage
reqQ :: TQueue ClientMessage
reqQ } TMVar Response
var Request
msg = TQueue ClientMessage -> ClientMessage -> STM ()
forall a. TQueue a -> a -> STM ()
writeTQueue TQueue ClientMessage
reqQ (Request -> TMVar Response -> ClientMessage
New Request
msg TMVar Response
var)
eitherToIO :: Exception e => Either e a -> IO a
eitherToIO :: forall e a. Exception e => Either e a -> IO a
eitherToIO = (e -> IO a) -> (a -> IO a) -> Either e a -> IO a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either e -> IO a
forall e a. Exception e => e -> IO a
throwIO a -> IO a
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
unbindAsync :: Ldap -> IO ()
unbindAsync :: Ldap -> IO ()
unbindAsync =
  STM () -> IO ()
forall a. STM a -> IO a
atomically (STM () -> IO ()) -> (Ldap -> STM ()) -> Ldap -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ldap -> STM ()
unbindAsyncSTM
unbindAsyncSTM :: Ldap -> STM ()
unbindAsyncSTM :: Ldap -> STM ()
unbindAsyncSTM Ldap
l =
  STM (Async Any) -> STM ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Ldap
-> (Response -> Either ResponseError Any)
-> Request
-> STM (Async Any)
forall a.
Ldap
-> (Response -> Either ResponseError a) -> Request -> STM (Async a)
sendRequest Ldap
l Response -> Either ResponseError Any
forall {a}. a
die Request
Type.UnbindRequest)
 where
  die :: a
die = String -> a
forall a. HasCallStack => String -> a
error String
"Ldap.Client: do not wait for the response to UnbindRequest"