-
Notifications
You must be signed in to change notification settings - Fork 58
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
Add RPC call and dev command for listUnrevealedCommits
- Loading branch information
1 parent
4eb7509
commit 8637618
Showing
8 changed files
with
161 additions
and
1 deletion.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,21 @@ | ||
module Commands.Dev.Anoma.Indexer where | ||
|
||
import Anoma.Effect.Base | ||
import Anoma.Effect.Indexer.ListUnrevealedCommits | ||
import Commands.Base | ||
import Commands.Dev.Anoma.Indexer.ListUnrevealedCommits.Options | ||
import Commands.Dev.Anoma.Indexer.Options | ||
import Data.Text qualified as T | ||
import Juvix.Compiler.Nockma.Pretty hiding (Path) | ||
|
||
runCommand :: forall r. (Members (Anoma ': Error SimpleError ': AppEffects) r) => AnomaIndexerCommand -> Sem r () | ||
runCommand = \case | ||
AnomaIndexerListUnrevealedCommits opts -> do | ||
res <- listUnrevealedCommits | ||
case opts ^. indexerListUnrevealedCommitsOutputFile of | ||
Just out -> do | ||
f <- fromAppFile out | ||
let cs = T.unlines (ppPrint <$> res ^. listUnrevealedCommitsResultCommits) | ||
writeFileEnsureLn' f cs | ||
Nothing -> do | ||
forM_ (res ^. listUnrevealedCommitsResultCommits) (renderStdOutLn . ppOutDefault) |
14 changes: 14 additions & 0 deletions
14
app/Commands/Dev/Anoma/Indexer/ListUnrevealedCommits/Options.hs
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,14 @@ | ||
module Commands.Dev.Anoma.Indexer.ListUnrevealedCommits.Options where | ||
|
||
import CommonOptions | ||
|
||
newtype IndexerListUnrevealedCommitsOptions = IndexerListUnrevealedCommitsOptions | ||
{_indexerListUnrevealedCommitsOutputFile :: Maybe (AppPath File)} | ||
deriving stock (Data) | ||
|
||
parseUnrevealedCommitsOptions :: Parser IndexerListUnrevealedCommitsOptions | ||
parseUnrevealedCommitsOptions = do | ||
_indexerListUnrevealedCommitsOutputFile <- optional parseGenericOutputFile | ||
pure IndexerListUnrevealedCommitsOptions {..} | ||
|
||
makeLenses ''IndexerListUnrevealedCommitsOptions |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,21 @@ | ||
module Commands.Dev.Anoma.Indexer.Options where | ||
|
||
import Commands.Dev.Anoma.Indexer.ListUnrevealedCommits.Options | ||
import CommonOptions | ||
|
||
newtype AnomaIndexerCommand | ||
= AnomaIndexerListUnrevealedCommits IndexerListUnrevealedCommitsOptions | ||
deriving stock (Data) | ||
|
||
parseAnomaIndexerCommand :: Parser AnomaIndexerCommand | ||
parseAnomaIndexerCommand = | ||
hsubparser commandListUnrevealedCommits | ||
where | ||
commandListUnrevealedCommits :: Mod CommandFields AnomaIndexerCommand | ||
commandListUnrevealedCommits = command "list-unrevealed-commits" runInfo | ||
where | ||
runInfo :: ParserInfo AnomaIndexerCommand | ||
runInfo = | ||
info | ||
(AnomaIndexerListUnrevealedCommits <$> parseUnrevealedCommitsOptions) | ||
(progDesc "Call the Anoma.Protobuf.IndexerService.ListUnrevealedCommits endpoint") |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,39 @@ | ||
module Anoma.Effect.Indexer.ListUnrevealedCommits where | ||
|
||
import Anoma.Effect.Base | ||
import Anoma.Rpc.Indexer.ListUnrevealedCommits | ||
import Data.ByteString.Base64 qualified as Base64 | ||
import Juvix.Compiler.Nockma.Encoding | ||
import Juvix.Compiler.Nockma.Language qualified as Nockma | ||
import Juvix.Compiler.Nockma.Pretty | ||
import Juvix.Prelude | ||
import Juvix.Prelude.Aeson (Value) | ||
import Juvix.Prelude.Aeson qualified as Aeson | ||
|
||
newtype ListUnrevealedCommitsResult = ListUnrevealedCommitsResult | ||
{_listUnrevealedCommitsResultCommits :: [Nockma.Term Natural]} | ||
|
||
listUnrevealedCommits :: | ||
forall r. | ||
(Members '[Anoma, Error SimpleError, Logger] r) => | ||
Sem r ListUnrevealedCommitsResult | ||
listUnrevealedCommits = do | ||
nodeInfo <- getNodeInfo | ||
let msg = Request {_requestNodeInfo = nodeInfo} | ||
logMessageValue "Request payload" msg | ||
resVal :: Value <- anomaRpc listUnrevealedCommitsGrpcUrl (Aeson.toJSON msg) >>= fromJSONErr | ||
logMessageValue "Response Payload" resVal | ||
res :: Response <- fromJSONErr resVal | ||
commitBs :: [ByteString] <- mapM decodeCommit (res ^. responseCommits) | ||
commits :: [Atom Natural] <- | ||
mapError @NockNaturalNaturalError | ||
(SimpleError . mkAnsiText @Text . show) | ||
(mapM byteStringToAtom commitBs) | ||
return ListUnrevealedCommitsResult {_listUnrevealedCommitsResultCommits = TermAtom <$> commits} | ||
where | ||
decodeCommit :: Text -> Sem r ByteString | ||
decodeCommit t = case (Base64.decode (encodeUtf8 t)) of | ||
Left e -> throw (SimpleError (mkAnsiText ("Failed to decode commitment: " <> pack e))) | ||
Right bs -> return bs | ||
|
||
makeLenses ''ListUnrevealedCommitsResult |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,39 @@ | ||
module Anoma.Rpc.Indexer.ListUnrevealedCommits where | ||
|
||
import Anoma.Rpc.Base | ||
import Anoma.Rpc.Indexer.ListUnrevealedCommits.JsonOptions | ||
import Juvix.Prelude | ||
import Juvix.Prelude.Aeson as Aeson | ||
|
||
listUnrevealedCommitsGrpcUrl :: GrpcMethodUrl | ||
listUnrevealedCommitsGrpcUrl = | ||
mkGrpcMethodUrl $ | ||
"Anoma" :| ["Protobuf", "IndexerService", "ListUnrevealedCommits"] | ||
|
||
newtype Request = Request | ||
{_requestNodeInfo :: NodeInfo} | ||
|
||
$( deriveJSON | ||
defaultOptions | ||
{ fieldLabelModifier = \case | ||
"_requestNodeInfo" -> "node_info" | ||
_ -> impossibleError "All fields must be covered" | ||
} | ||
''Request | ||
) | ||
|
||
newtype Response = Response | ||
{_responseCommits :: [Text]} | ||
|
||
$(deriveToJSON responseOptions ''Response) | ||
|
||
instance FromJSON Response where | ||
parseJSON = | ||
$(mkParseJSON responseOptions ''Response) | ||
. addDefaultValues' defaultValues | ||
where | ||
defaultValues :: HashMap Key Value | ||
defaultValues = hashMap [("commits", Aeson.Array mempty)] | ||
|
||
makeLenses ''Request | ||
makeLenses ''Response |
14 changes: 14 additions & 0 deletions
14
src/Anoma/Rpc/Indexer/ListUnrevealedCommits/JsonOptions.hs
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,14 @@ | ||
-- | Options needed to derive JSON instances need to be put in a separate file due to | ||
-- Template Haskell stage restriction | ||
module Anoma.Rpc.Indexer.ListUnrevealedCommits.JsonOptions where | ||
|
||
import Juvix.Prelude | ||
import Juvix.Prelude.Aeson as Aeson | ||
|
||
responseOptions :: Aeson.Options | ||
responseOptions = | ||
defaultOptions | ||
{ fieldLabelModifier = \case | ||
"_responseCommits" -> "commits" | ||
_ -> impossibleError "All fields must be covered" | ||
} |