module Control.Eff.LogWriter.UnixSocket
( withUnixSocketLogWriter
, withUnixSocketLogging
)
where
import Control.Eff as Eff
import Control.Eff.Log
import Control.Eff.LogWriter.Rich
import Data.Text as T
import Data.Text.Encoding as T
import qualified Control.Exception.Safe as Safe
import Control.Monad ( void )
import qualified Control.Monad.Catch as Catch
import Control.Monad.Trans.Control ( MonadBaseControl
, liftBaseOp
)
import GHC.Stack
import Network.Socket hiding ( sendTo )
import Network.Socket.ByteString
withUnixSocketLogging
:: (HasCallStack, MonadBaseControl IO (Eff e), Lifted IO e)
=> LogMessageRenderer Text
-> FilePath
-> Text
-> Facility
-> LogPredicate
-> Eff (Logs : LogWriterReader : e) a
-> Eff e a
withUnixSocketLogging render socketPath a f p e = liftBaseOp
(withUnixSocketSocket render socketPath)
(\lw -> withRichLogging lw a f p e)
withUnixSocketLogWriter
:: (IoLogging e, MonadBaseControl IO (Eff e), HasCallStack)
=> LogMessageRenderer Text
-> FilePath
-> Eff e b
-> Eff e b
withUnixSocketLogWriter render socketPath e =
liftBaseOp (withUnixSocketSocket render socketPath) (`addLogWriter` e)
withUnixSocketSocket
:: HasCallStack
=> LogMessageRenderer Text
-> FilePath
-> (LogWriter -> IO a)
-> IO a
withUnixSocketSocket render socketPath ioE = Safe.bracket
(socket AF_UNIX Datagram defaultProtocol)
(Safe.try @IO @Catch.SomeException . close)
(\s ->
let addr = SockAddrUnix socketPath
in
ioE
(MkLogWriter
(\lmStr ->
void $ sendTo s (T.encodeUtf8 (render lmStr)) addr
)
)
)