-- This file is part of the Wire Server implementation.
--
-- Copyright (C) 2022 Wire Swiss GmbH <opensource@wire.com>
--
-- This program is free software: you can redistribute it and/or modify it under
-- the terms of the GNU Affero General Public License as published by the Free
-- Software Foundation, either version 3 of the License, or (at your option) any
-- later version.
--
-- This program is distributed in the hope that it will be useful, but WITHOUT
-- ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
-- FOR A PARTICULAR PURPOSE. See the GNU Affero General Public License for more
-- details.
--
-- You should have received a copy of the GNU Affero General Public License along
-- with this program. If not, see <https://www.gnu.org/licenses/>.

-- NOTE: This is an obsolete module. Instead, please use the more general
-- Wire.Sem.Logger logging effect.
module Polysemy.TinyLog
  ( module Polysemy.TinyLog,
    Logger (..),
    trace,
    debug,
    info,
    warn,
    err,
    fatal,
  )
where

import Imports
import Polysemy
import Polysemy.Error (Error)
import qualified Polysemy.Error
import qualified System.Logger as Log
import Wire.Sem.Logger
import qualified Wire.Sem.Logger as Logger

type TinyLog = Logger (Log.Msg -> Log.Msg)

logErrors ::
  ( Member TinyLog r,
    Member (Error e) r
  ) =>
  (e -> Text) ->
  Text ->
  Sem r a ->
  Sem r a
logErrors :: forall (r :: EffectRow) e a.
(Member TinyLog r, Member (Error e) r) =>
(e -> Text) -> Text -> Sem r a -> Sem r a
logErrors e -> Text
showError Text
msg Sem r a
action = Sem r a -> (e -> Sem r a) -> Sem r a
forall e (r :: EffectRow) a.
Member (Error e) r =>
Sem r a -> (e -> Sem r a) -> Sem r a
Polysemy.Error.catch Sem r a
action ((e -> Sem r a) -> Sem r a) -> (e -> Sem r a) -> Sem r a
forall a b. (a -> b) -> a -> b
$ \e
e -> do
  (Msg -> Msg) -> Sem r ()
forall msg (r :: EffectRow).
Member (Logger msg) r =>
msg -> Sem r ()
Logger.err ((Msg -> Msg) -> Sem r ()) -> (Msg -> Msg) -> Sem r ()
forall a b. (a -> b) -> a -> b
$ Text -> Msg -> Msg
forall a. ToBytes a => a -> Msg -> Msg
Log.msg Text
msg (Msg -> Msg) -> (Msg -> Msg) -> Msg -> Msg
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text -> Msg -> Msg
forall a. ToBytes a => ByteString -> a -> Msg -> Msg
Log.field ByteString
"error" (e -> Text
showError e
e)
  e -> Sem r a
forall e (r :: EffectRow) a. Member (Error e) r => e -> Sem r a
Polysemy.Error.throw e
e

logAndIgnoreErrors ::
  forall e r.
  ( Member TinyLog r
  ) =>
  (e -> Text) ->
  Text ->
  Sem (Error e ': r) () ->
  Sem r ()
logAndIgnoreErrors :: forall e (r :: EffectRow).
Member TinyLog r =>
(e -> Text) -> Text -> Sem (Error e : r) () -> Sem r ()
logAndIgnoreErrors e -> Text
showError Text
msg = Sem r (Either e ()) -> Sem r ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Sem r (Either e ()) -> Sem r ())
-> (Sem (Error e : r) () -> Sem r (Either e ()))
-> Sem (Error e : r) ()
-> Sem r ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Sem (Error e : r) () -> Sem r (Either e ())
forall e (r :: EffectRow) a.
Sem (Error e : r) a -> Sem r (Either e a)
Polysemy.Error.runError (Sem (Error e : r) () -> Sem r (Either e ()))
-> (Sem (Error e : r) () -> Sem (Error e : r) ())
-> Sem (Error e : r) ()
-> Sem r (Either e ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (e -> Text) -> Text -> Sem (Error e : r) () -> Sem (Error e : r) ()
forall (r :: EffectRow) e a.
(Member TinyLog r, Member (Error e) r) =>
(e -> Text) -> Text -> Sem r a -> Sem r a
logErrors e -> Text
showError Text
msg