Skip to content

Commit

Permalink
Experimental daml assistant support for metering report.
Browse files Browse the repository at this point in the history
changelog_begin
Enable experimental GRPC endpoint for metering report.
changelog_end

Remove unused import

Fix merge issue
  • Loading branch information
simonmaxen-da committed Jan 21, 2022
1 parent cbb4986 commit 32e12a2
Show file tree
Hide file tree
Showing 13 changed files with 238 additions and 23 deletions.
2 changes: 2 additions & 0 deletions daml-assistant/daml-helper/BUILD.bazel
Original file line number Diff line number Diff line change
Expand Up @@ -68,6 +68,8 @@ da_haskell_binary(
"process",
"safe-exceptions",
"typed-process",
"time",
"text",
],
main_function = "DA.Daml.Helper.Main.main",
visibility = ["//visibility:public"],
Expand Down
26 changes: 24 additions & 2 deletions daml-assistant/daml-helper/src/DA/Daml/Helper/Ledger.hs
Original file line number Diff line number Diff line change
Expand Up @@ -25,16 +25,17 @@ module DA.Daml.Helper.Ledger (
runLedgerGetDalfs,
runLedgerListPackages,
runLedgerListPackages0,
runLedgerMeteringReport,
-- exported for testing
downloadAllReachablePackages
downloadAllReachablePackages,
) where

import Control.Exception (SomeException(..), catch)
import Control.Applicative ((<|>))
import Control.Lens (toListOf)
import Control.Monad.Extra hiding (fromMaybeM)
import Control.Monad.IO.Class (liftIO)
import Data.Aeson ((.=))
import Data.Aeson ((.=), encode)
import qualified Data.Aeson as A
import Data.Aeson.Text
import qualified Data.ByteString as BS
Expand Down Expand Up @@ -74,6 +75,8 @@ import qualified DA.Ledger as L
import qualified DA.Service.Logger as Logger
import qualified DA.Service.Logger.Impl.IO as Logger
import qualified SdkVersion
import DA.Ledger.Types (Timestamp(..), ApplicationId(..), IsoTime(..))


data LedgerApi
= Grpc
Expand Down Expand Up @@ -651,3 +654,22 @@ sanitizeToken :: String -> String
sanitizeToken tok
| "Bearer " `isPrefixOf` tok = tok
| otherwise = "Bearer " <> tok

-- | Report on Ledger Use.
runLedgerMeteringReport :: LedgerFlags -> IsoTime -> Maybe IsoTime -> Maybe ApplicationId -> IO ()
runLedgerMeteringReport flags fromIso toIso application = do
args <- getDefaultArgs flags
report <- meteringReport args (L.isoTimeToTimestamp fromIso) (fmap L.isoTimeToTimestamp toIso) application
let encoded = encode report
let bsc = BSL.toStrict encoded
let output = BSC.unpack bsc
putStrLn output

meteringReport :: LedgerArgs -> Timestamp -> Maybe Timestamp -> Maybe ApplicationId -> IO L.MeteringReport
meteringReport args from to application =
case api args of
Grpc -> runWithLedgerArgs args $ do L.getMeteringReport from to application
HttpJson -> do
hPutStrLn stderr "Error: daml ledger metering can only be run via gRPC atm"
exitFailure

13 changes: 12 additions & 1 deletion daml-assistant/daml-helper/src/DA/Daml/Helper/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,6 @@ import System.IO.Extra
import System.Process (showCommandForUser)
import System.Process.Typed (unsafeProcessHandle)
import Text.Read (readMaybe)

import DA.Signals
import DA.Daml.Helper.Init
import DA.Daml.Helper.Ledger
Expand All @@ -26,6 +25,7 @@ import DA.Daml.Helper.Studio
import DA.Daml.Helper.Util
import DA.Daml.Helper.Codegen
import DA.PortFile
import DA.Ledger.Types (ApplicationId(..), IsoTime(..))

main :: IO ()
main = do
Expand Down Expand Up @@ -71,6 +71,7 @@ data Command
| LedgerNavigator { flags :: LedgerFlags, remainingArguments :: [String] }
| Codegen { lang :: Lang, remainingArguments :: [String] }
| PackagesList {flags :: LedgerFlags}
| LedgerMeteringReport { flags :: LedgerFlags, from :: IsoTime, to :: Maybe IsoTime, application :: Maybe ApplicationId }
| CantonSandbox
{ cantonOptions :: CantonOptions
, portFileM :: Maybe FilePath
Expand Down Expand Up @@ -261,6 +262,9 @@ commandParser = subparser $ fold
, command "navigator" $ info
(ledgerNavigatorCmd <**> helper)
(forwardOptions <> progDesc "Launch Navigator on ledger")
, command "metering-report" $ info
(ledgerMeteringReportCmd <**> helper)
(forwardOptions <> progDesc "Report on Ledger Use")
]
, subparser $ internal <> fold -- hidden subcommands
[ command "allocate-party" $ info
Expand Down Expand Up @@ -335,6 +339,12 @@ commandParser = subparser $ fold
<$> ledgerFlags (ShowJsonApi False)
<*> many (argument str (metavar "ARG" <> help "Extra arguments to navigator."))

ledgerMeteringReportCmd = LedgerMeteringReport
<$> ledgerFlags (ShowJsonApi True)
<*> option auto (long "from" <> metavar "FROM" <> help "From date of report (inclusive).")
<*> optional (option auto (long "to" <> metavar "TO" <> help "To date of report (exclusive)."))
<*> optional (option auto (long "application" <> metavar "APP" <> help "Report application identifier."))

ledgerFlags showJsonApi = LedgerFlags
<$> httpJsonFlag showJsonApi
<*> sslConfig
Expand Down Expand Up @@ -470,6 +480,7 @@ runCommand = \case
LedgerExport {..} -> runLedgerExport flags remainingArguments
LedgerNavigator {..} -> runLedgerNavigator flags remainingArguments
Codegen {..} -> runCodegen lang remainingArguments
LedgerMeteringReport {..} -> runLedgerMeteringReport flags from to application
CantonSandbox {..} ->
withCantonPortFile cantonOptions $ \cantonOptions cantonPortFile ->
withCantonSandbox cantonOptions remainingArguments $ \ph -> do
Expand Down
10 changes: 9 additions & 1 deletion language-support/hs/bindings/src/DA/Ledger/Convert.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,9 @@ module DA.Ledger.Convert (
raiseGetTimeResponse,
raiseTimestamp,
raisePackageId,
RaiseFailureReason,
raiseApplicationId,
raiseParticipantId,
RaiseFailureReason(..),
) where

import Prelude hiding(Enum)
Expand Down Expand Up @@ -485,6 +487,12 @@ raiseChoice = fmap Choice . raiseText "Choice"
raiseParty :: Text -> Perhaps Party
raiseParty = fmap Party . raiseText "Party"

raiseApplicationId :: Text -> Perhaps ApplicationId
raiseApplicationId = fmap ApplicationId . raiseText "ApplicationId"

raiseParticipantId :: Text -> Perhaps ParticipantId
raiseParticipantId = fmap ParticipantId . raiseText "ParticipantId"

raisePackageId :: Text -> Perhaps PackageId
raisePackageId = fmap PackageId . raiseText "PackageId"

Expand Down
1 change: 1 addition & 0 deletions language-support/hs/bindings/src/DA/Ledger/Services.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,3 +14,4 @@ import DA.Ledger.Services.PartyManagementService as X
import DA.Ledger.Services.PackageService as X
import DA.Ledger.Services.TimeService as X
import DA.Ledger.Services.TransactionService as X
import DA.Ledger.Services.MeteringReportService as X
Original file line number Diff line number Diff line change
@@ -0,0 +1,116 @@
-- Copyright (c) 2022 Digital Asset (Switzerland) GmbH and/or its affiliates. All rights reserved.
-- SPDX-License-Identifier: Apache-2.0

{-# LANGUAGE DuplicateRecordFields #-}

module DA.Ledger.Services.MeteringReportService (
getMeteringReport,
MeteringReport(..),
isoTimeToTimestamp,
) where


import Data.Aeson ( KeyValue((.=)), ToJSON(..), object)
import DA.Ledger.Convert
import DA.Ledger.GrpcWrapUtils
import DA.Ledger.LedgerService
import DA.Ledger.Types
import qualified Data.Text.Lazy as TL
import Network.GRPC.HighLevel.Generated
import qualified Com.Daml.Ledger.Api.V1.Admin.MeteringReportService as LL
import Data.Maybe (maybeToList)
import qualified Data.Time.Clock.System as System
import qualified Data.Time.Format.ISO8601 as ISO8601
import GHC.Int (Int64)
import GHC.Word (Word32)

data MeteredApplication = MeteredApplication {
application :: ApplicationId
, events :: Int64
} deriving (Show)

instance ToJSON MeteredApplication where
toJSON (MeteredApplication application events) =
object
[ "application" .= unApplicationId application
, "events" .= events
]

data MeteringReport = MeteringReport {
participant :: ParticipantId
, from :: Timestamp
, toRequested :: Maybe Timestamp
, toActual :: Timestamp
, applications :: [MeteredApplication]
} deriving (Show)

instance ToJSON MeteringReport where
toJSON (MeteringReport participant from toRequested toActual applications) =
object (
[ "participant" .= unParticipantId participant
, "from" .= timestampToIso8601 from
, "to-actual" .= timestampToIso8601 toActual
, "applications" .= applications
]
++ maybeToList (fmap (("to-requested" .=) . timestampToIso8601) toRequested)
)

timestampToSystemTime :: Timestamp -> System.SystemTime
timestampToSystemTime ts = st
where
s = fromIntegral (seconds ts) :: Int64
n = fromIntegral (nanos ts) :: Word32
st = System.MkSystemTime s n

systemTimeToTimestamp :: System.SystemTime -> Timestamp
systemTimeToTimestamp st = ts
where
s = fromIntegral (System.systemSeconds st) :: Int
n = fromIntegral (System.systemNanoseconds st) :: Int
ts = Timestamp s n

timestampToIso8601 :: Timestamp -> String
timestampToIso8601 ts = ISO8601.iso8601Show ut
where
st = timestampToSystemTime ts
ut = System.systemToUTCTime st

isoTimeToTimestamp :: IsoTime -> Timestamp
isoTimeToTimestamp iso = systemTimeToTimestamp $ System.utcToSystemTime $ unIsoTime iso

raiseApplicationMeteringReport :: LL.ApplicationMeteringReport -> Perhaps MeteredApplication
raiseApplicationMeteringReport (LL.ApplicationMeteringReport llApp events) = do
application <- raiseApplicationId llApp
return MeteredApplication {..}

raiseParticipantMeteringReport :: LL.GetMeteringReportRequest -> LL.ParticipantMeteringReport -> Perhaps MeteringReport
raiseParticipantMeteringReport (LL.GetMeteringReportRequest (Just llFrom) llTo _) (LL.ParticipantMeteringReport llParticipantId (Just llToActual) llAppReports) = do
participant <- raiseParticipantId llParticipantId
from <- raiseTimestamp llFrom
toRequested <- traverse raiseTimestamp llTo
toActual <- raiseTimestamp llToActual
applications <- raiseList raiseApplicationMeteringReport llAppReports
return MeteringReport{..}

raiseParticipantMeteringReport _ response = Left $ Unexpected ("raiseParticipantMeteringReport unable to parse response: " <> show response)

raiseGetMeteringReportResponse :: LL.GetMeteringReportResponse -> Perhaps MeteringReport
raiseGetMeteringReportResponse (LL.GetMeteringReportResponse (Just request) (Just report) (Just _)) =
raiseParticipantMeteringReport request report

raiseGetMeteringReportResponse response = Left $ Unexpected ("raiseMeteredReport unable to parse response: " <> show response)

getMeteringReport :: Timestamp -> Maybe Timestamp -> Maybe ApplicationId -> LedgerService MeteringReport
getMeteringReport from to applicationId =
makeLedgerService $ \timeout config mdm ->
withGRPCClient config $ \client -> do
service <- LL.meteringReportServiceClient client
let
LL.MeteringReportService {meteringReportServiceGetMeteringReport=rpc} = service
gFrom = Just $ lowerTimestamp from
gTo = fmap lowerTimestamp to
gApp = maybe TL.empty unApplicationId applicationId
request = LL.GetMeteringReportRequest gFrom gTo gApp
rpc (ClientNormalRequest request timeout mdm)
>>= unwrap
>>= either (fail . show) return . raiseGetMeteringReportResponse
Original file line number Diff line number Diff line change
Expand Up @@ -20,8 +20,6 @@ import qualified Data.Aeson as A
import Data.Aeson ((.:))
import qualified Com.Daml.Ledger.Api.V1.Admin.PartyManagementService as LL

newtype ParticipantId = ParticipantId { unParticipantId :: Text} deriving (Eq,Ord,Show)

getParticipantId :: LedgerService ParticipantId
getParticipantId =
makeLedgerService $ \timeout config mdm -> do
Expand Down
21 changes: 19 additions & 2 deletions language-support/hs/bindings/src/DA/Ledger/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -55,18 +55,23 @@ module DA.Ledger.Types( -- High Level types for communication over Ledger API
SubmissionId(..),
LL.Duration(..),
LL.Status(..),
DeduplicationPeriod(..)
DeduplicationPeriod(..),
ParticipantId(..),
IsoTime(..),
) where

import qualified Data.Aeson as A
import Data.Fixed
import Data.Int (Int64)
import Data.Map (Map)
import Data.Text.Lazy (Text)
import Data.Text.Lazy (Text, pack)
import Prelude hiding(Enum)
import qualified Data.Text.Lazy as Text(unpack)
import qualified Google.Protobuf.Duration as LL
import qualified Google.Rpc.Status as LL
import qualified Data.Time.Format.ISO8601 as ISO8601
import qualified Data.Time.Clock as Clock
import qualified Text.ParserCombinators.ReadP as ReadP

-- commands.proto

Expand Down Expand Up @@ -272,6 +277,11 @@ newtype DaysSinceEpoch = DaysSinceEpoch { unDaysSinceEpoch :: Int}
newtype TemplateId = TemplateId Identifier deriving (Eq,Ord,Show)

newtype ApplicationId = ApplicationId { unApplicationId :: Text } deriving (Eq,Ord,Show)

instance Read ApplicationId where
readsPrec _ = \s -> [(ApplicationId (pack s),"")]

newtype ParticipantId = ParticipantId { unParticipantId :: Text} deriving (Eq,Ord,Show)
newtype CommandId = CommandId { unCommandId :: Text } deriving (Eq,Ord,Show)
newtype ConstructorId = ConstructorId { unConstructorId :: Text } deriving (Eq,Ord,Show)
newtype ContractId = ContractId { unContractId :: Text } deriving (Eq,Ord,Show)
Expand All @@ -294,3 +304,10 @@ instance A.FromJSON Party where
parseJSON v = Party <$> A.parseJSON v

newtype Verbosity = Verbosity { unVerbosity :: Bool } deriving (Eq,Ord,Show)

-- A wrapped UTCTime the can be read in ISO8601 format
newtype IsoTime = IsoTime { unIsoTime :: Clock.UTCTime } deriving Show

instance Read IsoTime where
readsPrec _ = ReadP.readP_to_S $ fmap IsoTime $ ISO8601.formatReadP ISO8601.iso8601Format

8 changes: 8 additions & 0 deletions language-support/hs/bindings/test/DA/Ledger/Tests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -77,6 +77,7 @@ sharedSandboxTests testDar = testGroupWithSandbox testDar Nothing "shared sandbo
, tUploadDarFileBad
, tUploadDarFileGood
, tAllocateParty
, tMeteringReport
]

authenticatingSandboxTests :: FilePath -> TestTree
Expand Down Expand Up @@ -543,6 +544,13 @@ tValueConversion withSandbox = testCase "tValueConversion" $ run withSandbox $ \
[RecordField{label="owner"},RecordField{label="bucket",fieldValue=bucketReturned}] <- return fields
liftIO $ assertEqual "bucket" bucket (detag bucketReturned)

tMeteringReport :: SandboxTest
tMeteringReport withSandbox = testCase "tMeteringReport" $ run withSandbox $ \_ _testId -> do
let expected = Just (Timestamp {seconds = 1, nanos = 2})
report <- getMeteringReport expected Nothing Nothing
let MeteringReport{from=actual} = report
liftIO $ assertEqual "report from date" expected actual

-- Strip the rid,vid,eid tags recusively from record, variant and enum values
detag :: Value -> Value
detag = \case
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -5,11 +5,15 @@ package com.daml.ledger.api.auth.services

import com.daml.ledger.api.auth.Authorizer
import com.daml.ledger.api.v1.admin.metering_report_service.MeteringReportServiceGrpc.MeteringReportService
<<<<<<< HEAD
import com.daml.ledger.api.v1.admin.metering_report_service.{
GetMeteringReportRequest,
GetMeteringReportResponse,
MeteringReportServiceGrpc,
}
=======
import com.daml.ledger.api.v1.admin.metering_report_service.{GetMeteringReportRequest, GetMeteringReportResponse, MeteringReportServiceGrpc}
>>>>>>> 13a2ee4491 (Experimental daml assistant support for metering report.)
import com.daml.platform.api.grpc.GrpcApiService
import com.daml.platform.server.api.ProxyCloseable
import io.grpc.ServerServiceDefinition
Expand All @@ -24,9 +28,13 @@ private[daml] final class MeteringReportServiceAuthorization(
with ProxyCloseable
with GrpcApiService {

<<<<<<< HEAD
override def getMeteringReport(
request: GetMeteringReportRequest
): Future[GetMeteringReportResponse] = {
=======
override def getMeteringReport(request: GetMeteringReportRequest): Future[GetMeteringReportResponse] = {
>>>>>>> 13a2ee4491 (Experimental daml assistant support for metering report.)
authorizer.requireAdminClaims(service.getMeteringReport)(request)
}

Expand Down
Loading

0 comments on commit 32e12a2

Please sign in to comment.