Skip to content

Commit

Permalink
refactor
Browse files Browse the repository at this point in the history
  • Loading branch information
janmasrovira committed Oct 28, 2024
1 parent 4e4876c commit 727605d
Show file tree
Hide file tree
Showing 8 changed files with 79 additions and 35 deletions.
11 changes: 7 additions & 4 deletions app/Commands/Dev/Anoma/Node.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,10 @@ import Commands.Base
import Commands.Dev.Anoma.Node.Options

runCommand :: forall r. (Members AppEffects r) => NodeOptions -> Sem r ()
runCommand opts = runConcurrent . runProcess $ do
anomaDir :: AnomaPath <- AnomaPath <$> fromAppPathDir (opts ^. nodeAnomaPath)
runAnoma anomaDir $ do
void noHalt
runCommand opts = runAppError @SimpleError
. runConcurrent
. runProcess
$ do
anomaDir :: AnomaPath <- AnomaPath <$> fromAppPathDir (opts ^. nodeAnomaPath)
runAnoma anomaDir $ do
void noHalt
4 changes: 2 additions & 2 deletions app/Commands/Dev/Nockma/Run.hs
Original file line number Diff line number Diff line change
Expand Up @@ -36,6 +36,6 @@ runCommand opts = do
inputFile = opts ^. nockmaRunFile

runInAnoma :: (Members AppEffects r) => AnomaPath -> Term Natural -> [Term Natural] -> Sem r ()
runInAnoma anoma t args = runAnoma anoma $ do
res <- runAppError @SimpleError (runNockma t args)
runInAnoma anoma t args = runAppError @SimpleError . runAnoma anoma $ do
res <- runNockma t args
putStrLn (ppPrint res)
40 changes: 17 additions & 23 deletions src/Anoma/Effect/Base.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,11 +5,13 @@ module Anoma.Effect.Base
AnomaPath (..),
anomaPath,
runAnoma,
module Juvix.Prelude.Aeson,
module Anoma.Rpc.Base,
module Juvix.Compiler.Nockma.Translation.FromTree,
)
where

import Anoma.Effect.Paths
import Anoma.Rpc.Base
import Data.ByteString qualified as B
import Juvix.Compiler.Nockma.Translation.FromTree (AnomaResult)
import Juvix.Data.CodeAnn
Expand All @@ -21,7 +23,7 @@ data Anoma :: Effect where
-- | Keep the node and client running
NoHalt :: Anoma m ExitCode
-- | Blocking rpc call
AnomaRpc :: Value -> Anoma m Value
AnomaRpc :: GrpcMethodUrl -> Value -> Anoma m Value

makeSem ''Anoma

Expand All @@ -41,7 +43,7 @@ relativeToAnomaDir p = do
return (anoma <//> p)

withSpawnAnomaClient ::
(Members '[Process, Logger, EmbedIO, Reader AnomaPath, Reader GrpcPort] r) =>
(Members '[Process, Logger, EmbedIO, Reader AnomaPath, Reader GrpcPort, Error SimpleError] r) =>
(ProcessHandle -> Sem r a) ->
Sem r a
withSpawnAnomaClient body = do
Expand All @@ -54,7 +56,7 @@ withSpawnAnomaClient body = do
logInfo "Anoma client successfully started"
logInfo (mkAnsiText ("Listening on port " <> annotate AnnImportant (pretty listenPort)))
body procHandle
_ -> error "Something went wrong when starting the anoma client"
_ -> throw (SimpleError (mkAnsiText @Text "Something went wrong when starting the anoma client"))
where
mkProcess :: (Members '[Reader AnomaPath, Reader GrpcPort] r') => Sem r' CreateProcess
mkProcess = do
Expand All @@ -74,9 +76,7 @@ withSpawnAnomaClient body = do
{ std_out = CreatePipe
}

-- Relative to the anoma repository
clientRelFile :: Path Rel File
clientRelFile = $(mkRelFile "apps/anoma_client/anoma_client")
-- Relative to the anoma repository

withSapwnAnomaNode ::
(Members '[EmbedIO, Logger, Process, Reader AnomaPath] r) =>
Expand All @@ -100,22 +100,22 @@ withSapwnAnomaNode body = withSystemTempFile "start.exs" $ \fp tmpHandle -> do
{ std_out = CreatePipe
}

anomaRpc' :: (Members '[Reader AnomaPath, Process, EmbedIO] r) => Value -> Sem r Value
anomaRpc' msg = do
cproc <- grpcCliProcess
anomaRpc' :: (Members '[Reader AnomaPath, Process, EmbedIO, Error SimpleError] r) => GrpcMethodUrl -> Value -> Sem r Value
anomaRpc' method payload = do
cproc <- grpcCliProcess method
withCreateProcess cproc $ \mstdin mstdout _stderr _procHandle -> do
let stdinH = fromJust mstdin
stdoutH = fromJust mstdout
inputbs = B.toStrict (encode msg)
inputbs = B.toStrict (encode payload)
liftIO (B.hPutStr stdinH inputbs)
hClose stdinH
res <- eitherDecodeStrict <$> liftIO (B.hGetContents stdoutH)
case res of
Right r -> return r
Left err -> error (pack err)
Left err -> throw (SimpleError (mkAnsiText err))

grpcCliProcess :: (Members '[Reader AnomaPath] r) => Sem r CreateProcess
grpcCliProcess = do
grpcCliProcess :: (Members '[Reader AnomaPath] r) => GrpcMethodUrl -> Sem r CreateProcess
grpcCliProcess method = do
paths <- relativeToAnomaDir relProtoDir
return
( proc
Expand All @@ -128,24 +128,18 @@ grpcCliProcess = do
"--protofiles",
toFilePath relProtoFile,
"localhost:" <> show listenPort,
"Anoma.Protobuf.Intents.Prove"
show method
]
)
{ std_in = CreatePipe,
std_out = CreatePipe
}
where
relProtoDir :: Path Rel Dir
relProtoDir = $(mkRelDir "apps/anoma_protobuf/priv/protobuf")

relProtoFile :: Path Rel File
relProtoFile = $(mkRelFile "anoma.proto")

runAnoma :: forall r a. (Members '[Logger, EmbedIO] r) => AnomaPath -> Sem (Anoma ': r) a -> Sem r a
runAnoma :: forall r a. (Members '[Logger, EmbedIO, Error SimpleError] r) => AnomaPath -> Sem (Anoma ': r) a -> Sem r a
runAnoma anomapath body = runReader anomapath . runConcurrent . runProcess $
withSapwnAnomaNode $ \grpcport _nodeOut nodeH ->
runReader (GrpcPort grpcport) $
withSpawnAnomaClient $ \_clientH -> do
(`interpret` inject body) $ \case
NoHalt -> waitForProcess nodeH
AnomaRpc i -> anomaRpc' i
AnomaRpc method i -> anomaRpc' method i
12 changes: 12 additions & 0 deletions src/Anoma/Effect/Paths.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,12 @@
module Anoma.Effect.Paths where

import Juvix.Prelude

clientRelFile :: Path Rel File
clientRelFile = $(mkRelFile "apps/anoma_client/anoma_client")

relProtoDir :: Path Rel Dir
relProtoDir = $(mkRelDir "apps/anoma_protobuf/priv/protobuf")

relProtoFile :: Path Rel File
relProtoFile = $(mkRelFile "anoma.proto")
12 changes: 6 additions & 6 deletions src/Anoma/Effect/RunNockma.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,15 +5,15 @@ module Anoma.Effect.RunNockma
where

import Anoma.Effect.Base
import Anoma.Rpc.RunNock (RunNock (_runNockJammedProgram))
import Anoma.Rpc.RunNock qualified as Rpc
import Anoma.Rpc.RunNock
import Data.ByteString.Base64 qualified as Base64
import Juvix.Compiler.Nockma.Encoding.Cue (DecodingError, cueFromByteString'')
import Juvix.Compiler.Nockma.Encoding.Jam (jamToByteString)
import Juvix.Compiler.Nockma.Language (NockNaturalNaturalError)
import Juvix.Compiler.Nockma.Language qualified as Nockma
import Juvix.Data.CodeAnn (simpleErrorCodeAnn)
import Juvix.Prelude
import Juvix.Prelude.Aeson (Value)
import Juvix.Prelude.Aeson qualified as Aeson
import Juvix.Prelude.Pretty

Expand Down Expand Up @@ -49,13 +49,13 @@ runNockma ::
Sem r (Nockma.Term Natural)
runNockma prog inputs = do
let prog' = encodeJam64 prog
args = map (Rpc.NockInputJammed . encodeJam64) inputs
args = map (NockInputJammed . encodeJam64) inputs
msg =
Rpc.RunNock
RunNock
{ _runNockJammedProgram = prog',
_runNockPrivateInputs = args,
_runNockPublicInputs = []
}
let json = Aeson.toJSON msg
res :: Rpc.Response <- anomaRpc json >>= fromJSON
decodeJam64 (res ^. Rpc.proof)
res :: Response <- anomaRpc runNockGrpcUrl json >>= fromJSON
decodeJam64 (res ^. proof)
6 changes: 6 additions & 0 deletions src/Anoma/Rpc/Base.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
module Anoma.Rpc.Base
( module Anoma.Rpc.GrpcMethodUrl,
)
where

import Anoma.Rpc.GrpcMethodUrl
23 changes: 23 additions & 0 deletions src/Anoma/Rpc/GrpcMethodUrl.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,23 @@
module Anoma.Rpc.GrpcMethodUrl
( GrpcMethodUrl,
mkGrpcMethodUrl,
grpcMethodUrlToText,
)
where

import Data.Text qualified as Text
import Juvix.Prelude
import Prelude (show)

newtype GrpcMethodUrl = GrpcMethodUrl
{ _grpcMethodUrl :: NonEmpty Text
}

mkGrpcMethodUrl :: NonEmpty Text -> GrpcMethodUrl
mkGrpcMethodUrl = GrpcMethodUrl

grpcMethodUrlToText :: GrpcMethodUrl -> Text
grpcMethodUrlToText (GrpcMethodUrl u) = Text.intercalate "." (toList u)

instance Show GrpcMethodUrl where
show = unpack . grpcMethodUrlToText
6 changes: 6 additions & 0 deletions src/Anoma/Rpc/RunNock.hs
Original file line number Diff line number Diff line change
@@ -1,8 +1,14 @@
module Anoma.Rpc.RunNock where

import Anoma.Rpc.Base
import Juvix.Prelude
import Juvix.Prelude.Aeson

runNockGrpcUrl :: GrpcMethodUrl
runNockGrpcUrl =
mkGrpcMethodUrl $
"Anoma" :| ["Protobuf", "Intents", "Prove"]

data NockInput
= NockInputText Text
| NockInputJammed Text
Expand Down

0 comments on commit 727605d

Please sign in to comment.