Skip to content

Commit

Permalink
hlint fixes
Browse files Browse the repository at this point in the history
  • Loading branch information
jutaro committed Nov 22, 2023
1 parent b45e1ef commit 8862441
Show file tree
Hide file tree
Showing 4 changed files with 4 additions and 7 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,6 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE PackageImports #-}

module Cardano.Node.Tracing.Tracers.StartLeadershipCheck
( TraceStartLeadershipCheckPlus (..)
Expand Down
2 changes: 1 addition & 1 deletion cardano-tracer/src/Cardano/Tracer/MetaTrace.hs
Original file line number Diff line number Diff line change
Expand Up @@ -155,7 +155,7 @@ instance MetaTrace TracerTrace where
]

stderrShowTracer :: Trace IO TracerTrace
stderrShowTracer = Trace $ T.arrow $ T.emit $
stderrShowTracer = Trace $ T.arrow $ T.emit
(either (const $ pure ()) (Sys.hPrint Sys.stderr) . snd)

stderrTracer :: Trace IO FormattedMessage
Expand Down
2 changes: 1 addition & 1 deletion trace-dispatcher/src/Cardano/Logging/Formatter.hs
Original file line number Diff line number Diff line change
Expand Up @@ -36,7 +36,7 @@ import Network.HostName


encodingToText :: AE.Encoding -> Text
{-# INLINE encodingToText#-}
{-# INLINE encodingToText #-}
encodingToText = toStrict . decodeUtf8 . AE.encodingToLazyByteString

-- | Format this trace as metrics
Expand Down
6 changes: 2 additions & 4 deletions trace-dispatcher/src/Cardano/Logging/Trace.hs
Original file line number Diff line number Diff line change
Expand Up @@ -37,7 +37,7 @@ module Cardano.Logging.Trace (
, withInnerNames
) where

import Control.Monad (join)
import Control.Monad (forM_, join)
import Control.Monad.IO.Unlift
import qualified Control.Tracer as T
import Data.Maybe (isJust)
Expand Down Expand Up @@ -307,9 +307,7 @@ contramapMCond (Trace tr) mFunc =
where
rFunc arg = do
condMes <- mFunc arg
case condMes of
Nothing -> pure ()
Just mes -> T.traceWith tr mes
forM_ condMes (T.traceWith tr)

{-# INLINE contramapM' #-}
contramapM' :: Monad m
Expand Down

0 comments on commit 8862441

Please sign in to comment.