Skip to content

Commit cc5f1fd

Browse files
handleLogTrace
1 parent 629023e commit cc5f1fd

File tree

2 files changed

+9
-2
lines changed

2 files changed

+9
-2
lines changed

bot-plutus-interface.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -103,6 +103,7 @@ library
103103
, data-default
104104
, data-default-class
105105
, directory
106+
, prettyprinter
106107
, either
107108
, filepath
108109
, freer-extras

src/BotPlutusInterface/Contract.hs

Lines changed: 8 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
{-# LANGUAGE AllowAmbiguousTypes #-}
22
{-# LANGUAGE RankNTypes #-}
3+
{-# OPTIONS_GHC -Wno-orphans #-}
34

45
module BotPlutusInterface.Contract (runContract, handleContract) where
56

@@ -34,7 +35,7 @@ import Control.Lens (preview, (^.))
3435
import Control.Monad (join, void, when)
3536
import Control.Monad.Freer (Eff, Member, interpret, reinterpret, runM, subsume, type (~>))
3637
import Control.Monad.Freer.Error (runError)
37-
import Control.Monad.Freer.Extras.Log (handleLogIgnore)
38+
import Control.Monad.Freer.Extras.Log (handleLogTrace)
3839
import Control.Monad.Freer.Extras.Modify (raiseEnd)
3940
import Control.Monad.Freer.Writer (Writer (Tell))
4041
import Control.Monad.Trans.Class (lift)
@@ -71,6 +72,8 @@ import Plutus.Contract.Types (Contract (..), ContractEffs)
7172
import PlutusTx.Builtins (fromBuiltin)
7273
import Wallet.Emulator.Error (WalletAPIError (..))
7374
import Prelude
75+
import Prettyprinter
76+
import Data.String (fromString)
7477

7578
runContract ::
7679
forall (w :: Type) (s :: Row Type) (e :: Type) (a :: Type).
@@ -92,10 +95,13 @@ handleContract contractEnv =
9295
. handleResumable contractEnv
9396
. handleCheckpointIgnore
9497
. handleWriter
95-
. handleLogIgnore @Value
98+
. handleLogTrace
9699
. runError
97100
. raiseEnd
98101

102+
instance Pretty Value where
103+
pretty = fromString . show
104+
99105
handleWriter ::
100106
forall (w :: Type) (effs :: [Type -> Type]).
101107
(ToJSON w, Monoid w) =>

0 commit comments

Comments
 (0)