Skip to content

Commit

Permalink
Support aeson 2.x
Browse files Browse the repository at this point in the history
Since the 2.x series contains a number of breaking changes, don't force
people to upgrade by CPP'ing the incompatibility. May revisit after a
few releases of aeson.
  • Loading branch information
kim committed Nov 8, 2021
1 parent 99ea847 commit b91620a
Show file tree
Hide file tree
Showing 2 changed files with 21 additions and 3 deletions.
12 changes: 10 additions & 2 deletions opentracing/OpenTracing/Log.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@ Module: OpenTracing.Log
Logs are structured data that occur over the lifetime of a span.
-}

{-# LANGUAGE CPP #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
Expand Down Expand Up @@ -31,6 +32,9 @@ import Control.Exception
import Control.Lens hiding ((.=))
import Data.Aeson
import qualified Data.Aeson.Encoding as Encoding
#if MIN_VERSION_aeson(2, 0, 0)
import qualified Data.Aeson.Key as Key
#endif
import Data.ByteString.Builder (Builder)
import Data.Foldable
import Data.List.NonEmpty (NonEmpty)
Expand Down Expand Up @@ -84,8 +88,12 @@ type LogFieldsFormatter = forall t. Foldable t => t LogField -> Builder
jsonAssoc :: LogFieldsFormatter
jsonAssoc = Encoding.fromEncoding . Encoding.list go . toList
where
go lf = Encoding.pairs $
Encoding.pair (logFieldLabel lf) (logFieldEncoding lf)
go lf = Encoding.pairs $ Encoding.pair (key lf) (logFieldEncoding lf)
#if MIN_VERSION_aeson(2, 0, 0)
key lf = Key.fromText $ logFieldLabel lf
#else
key lf = logFieldLabel lf
#endif

-- | A log formatter that encodes each `LogField` as an entry in a shared JSON object
--
Expand Down
12 changes: 11 additions & 1 deletion opentracing/OpenTracing/Reporting/Stdio.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,7 @@ Module: OpenTracing.Reporting.Stdio
Logging reporters that emit spans to stdout, stderr and System.IO `Handles`.
-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}

module OpenTracing.Reporting.Stdio
Expand All @@ -16,6 +17,9 @@ import Control.Lens (view)
import Control.Monad.IO.Class
import Data.Aeson (toEncoding)
import Data.Aeson.Encoding
#if MIN_VERSION_aeson(2, 0, 0)
import qualified Data.Aeson.Key as Key
#endif
import Data.ByteString.Lazy.Char8 (hPutStrLn)
import Data.Foldable (toList)
import GHC.Stack (prettyCallStack)
Expand Down Expand Up @@ -59,10 +63,16 @@ logRecE r = pairs $
<> pair "fields" (list logFieldE . toList $ view logFields r)

logFieldE :: LogField -> Encoding
logFieldE f = pairs . pair (logFieldLabel f) $ case f of
logFieldE f = pairs . pair key $ case f of
Event x -> text x
Message x -> text x
Stack x -> string . prettyCallStack $ x
ErrKind x -> text x
ErrObj x -> string . show $ x
LogField _ x -> string . show $ x
where
#if MIN_VERSION_aeson(2, 0, 0)
key = Key.fromText $ logFieldLabel f
#else
key = logFieldLabel f
#endif

0 comments on commit b91620a

Please sign in to comment.