Skip to content
This repository has been archived by the owner on Aug 18, 2020. It is now read-only.

Commit

Permalink
[TSD-116] Changes required on the cardano-sl side.
Browse files Browse the repository at this point in the history
  • Loading branch information
ksaric committed Aug 14, 2018
1 parent 08339e4 commit b115ae3
Showing 1 changed file with 5 additions and 5 deletions.
10 changes: 5 additions & 5 deletions infra/Pos/Infra/Reporting/Http.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,3 @@
{-# LANGUAGE AllowAmbiguousTypes #-}

module Pos.Infra.Reporting.Http
( sendReport
, sendReportNodeImpl
Expand All @@ -13,11 +11,13 @@ import Control.Exception.Safe (catchAny, try)
import Data.Aeson (encode)
import qualified Data.List.NonEmpty as NE
import Data.Time.Clock (getCurrentTime)
import Data.Version (showVersion)
import Formatting (sformat, shown, string, (%))
import Network.HTTP.Client (httpLbs, newManager, parseUrlThrow)
import qualified Network.HTTP.Client.MultipartFormData as Form
import Network.HTTP.Client.TLS (tlsManagerSettings)
import Pos.ReportServer.Report (ReportInfo (..), ReportType (..))
import Pos.ReportServer.Report (BackendVersion (..), ReportInfo (..), ReportType (..),
Version (..))
import System.FilePath (takeFileName)
import System.Info (arch, os)

Expand All @@ -26,7 +26,7 @@ import Pos.Crypto (ProtocolMagic (..))
import Pos.Infra.Reporting.Exceptions (ReportingError (..))
import Pos.Infra.Reporting.MemState ()
import Pos.Util.CompileInfo (CompileTimeInfo)
import Pos.Util.Trace (Trace, Severity (..), traceWith)
import Pos.Util.Trace (Severity (..), Trace, traceWith)
import Pos.Util.Util ((<//>))


Expand Down Expand Up @@ -69,7 +69,7 @@ sendReport pm compileInfo mLogFile reportType appName reportServerUri = do
-- We are using version of 'cardano-sl-infra' here. We agreed
-- that the version of 'cardano-sl' and it subpackages should
-- be same.
, rVersion = version
, rVersion = BackendVersion . Version . fromString . showVersion $ version
, rBuild = pretty compileInfo
, rOS = toText (os <> "-" <> arch)
, rMagic = getProtocolMagic pm
Expand Down

0 comments on commit b115ae3

Please sign in to comment.