Skip to content

Commit

Permalink
WIP
Browse files Browse the repository at this point in the history
  • Loading branch information
j-mueller committed Aug 7, 2020
1 parent b436cb5 commit 3820356
Show file tree
Hide file tree
Showing 4 changed files with 44 additions and 38 deletions.
11 changes: 8 additions & 3 deletions cabal.project
Expand Up @@ -155,7 +155,11 @@ package shelley-spec-ledger-test

package iohk-monitoring
-- disable all warnings
ghc-options: -w
ghc-options: -w

package contra-tracer
-- disable all warnings
ghc-options: -w

source-repository-package
type: git
Expand Down Expand Up @@ -190,12 +194,13 @@ source-repository-package

source-repository-package
type: git
location: https://github.com/raduom/iohk-monitoring-framework
tag: b5c035ad4e226d634242ad5979fa677921181435
location: https://github.com/j-mueller/iohk-monitoring-framework
tag: d8e6df66e2cf2442a6ec9bc0ced69ecd1d518947
subdir:
iohk-monitoring
tracer-transformers
contra-tracer
plugins/backend-ekg

source-repository-package
type: git
Expand Down
3 changes: 3 additions & 0 deletions nix/stack.materialized/plutus-scb.nix

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

3 changes: 2 additions & 1 deletion plutus-scb/plutus-scb.cabal
Expand Up @@ -174,7 +174,8 @@ library
mwc-random -any,
primitive -any,
hedgehog -any,
iohk-monitoring -any
iohk-monitoring -any,
lobemo-backend-ekg -any

executable plutus-scb
main-is: Main.hs
Expand Down
65 changes: 31 additions & 34 deletions plutus-scb/src/Plutus/SCB/Monitoring.hs
Expand Up @@ -8,86 +8,83 @@
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
module Plutus.SCB.Monitoring(
defaultConfig
, runWithMonitoring
, handleLogMsgTrace
-- * Effect handlers
handleLogMsgTrace
, handleObserveTrace
-- * Conveniences for configuration
, defaultConfig
, loadConfig
-- * Misc
, test
) where


import qualified Cardano.BM.Configuration.Model as CM
import qualified Cardano.BM.Backend.EKGView
import Cardano.BM.Configuration (setup)
import qualified Cardano.BM.Configuration.Model as CM
import Cardano.BM.Counters (readCounters)
import Cardano.BM.Data.Aggregated (Measurable (..))
import Cardano.BM.Data.AggregatedKind
import Cardano.BM.Data.BackendKind
import Cardano.BM.Data.Counter
import Cardano.BM.Data.LogItem
import Cardano.BM.Data.MonitoringEval
import Cardano.BM.Data.Observable (ObservableInstance (..))
import Cardano.BM.Data.Output
import Cardano.BM.Data.Rotation
import Cardano.BM.Data.Severity
import Cardano.BM.Data.SubTrace
import Cardano.BM.Data.Trace
import Cardano.BM.Data.Tracer
import Cardano.BM.Observer.Monadic
import Cardano.BM.Plugin
import Cardano.BM.Plugin (loadPlugin)
import Cardano.BM.Setup
import Cardano.BM.Trace
import Control.Monad (void)
import Control.Monad.Freer
import Control.Monad.Freer.Log (LogMsg (..), LogObserve (..), Observation (..))
import qualified Control.Monad.Freer.Log as L
import Control.Monad.IO.Class (MonadIO)
import Data.Aeson (FromJSON, ToJSON)
import Control.Monad.IO.Class (MonadIO (..))
import Data.Maybe (fromMaybe)
import Data.Text (Text)

-- TODO: Load configuration from file

-- | A default 'CM.Configuration' that logs on 'Info' and above
-- to stdout
defaultConfig :: IO CM.Configuration
defaultConfig = do
c <- CM.empty
CM.setMinSeverity c Info
CM.setSetupBackends c [ KatipBK
, AggregationBK
, MonitoringBK
, EKGViewBK
]
CM.setDefaultBackends c [KatipBK, AggregationBK]
CM.setDefaultBackends c [KatipBK, AggregationBK, EKGViewBK]
CM.setSetupScribes c [ ScribeDefinition {
scName = "stdout"
, scKind = StdoutSK
, scFormat = ScText
, scPrivacy = ScPublic
, scRotation = Nothing
}]
let observables = (Just $ ObservableTraceSelf [MonotonicClock, MemoryStats])
CM.setSubTrace c "processAllContractOutboxes" observables
CM.setDefaultScribes c ["StdoutSK::stdout"]
CM.setEKGport c 12790
pure c

runWithMonitoring ::
(ToJSON a
, FromJSON a
, ToObject a)
=> CM.Configuration
-> (Trace IO a -> IO ())
-> IO ()
runWithMonitoring config k = setupTrace_ config "pab" >>= k . fst
-- | Load a 'CM.Configuration' from a YAML file.
loadConfig :: FilePath -> IO CM.Configuration
loadConfig = setup

test :: IO ()
test = do
conf <- defaultConfig
runWithMonitoring @Text conf $ \trace -> do
runM
$ handleObserveTrace conf trace
$ handleLogMsgTrace @Text trace
$ do
L.logInfo @Text "hello"
L.logInfo @Text "world"
L.surroundInfo @Text "this place" $ do
L.logInfo @Text "hello"
L.logInfo @Text "world"
(trace, sb) <- setupTrace_ conf "pab"
Cardano.BM.Backend.EKGView.plugin conf trace sb >>= loadPlugin sb
runM
$ handleObserveTrace conf trace
$ handleLogMsgTrace @Text trace
$ do
L.logInfo @Text "hello"
L.logInfo @Text "world"
L.surroundInfo @Text "processAllContractOutboxes" $ do
L.logInfo @Text "doing some work"
liftIO readLn

-- | Handle the 'LogMsg' effect by logging messages to a 'Trace'
handleLogMsgTrace :: forall a m effs.
Expand Down

0 comments on commit 3820356

Please sign in to comment.