mirror of
https://github.com/anoma/juvix.git
synced 2024-12-02 01:04:57 +03:00
Add dev nockma encode
command (#3135)
- New command `juvix dev nockma encode --help` ``` Usage: juvix dev nockma encode --to ENCODING --from ENCODING Encode and decode nockma terms Available options: --to ENCODING Choose the source encoding. • base64: Jam and Base 64 encoding • bytes: Jam encoding • debug: Nockma code with annotations • text: Nockma code without annotations --from ENCODING Choose the target encoding. • base64: Jam and Base 64 encoding • bytes: Jam encoding • debug: Nockma code with annotations • text: Nockma code without annotations ```
This commit is contained in:
parent
0961d874d3
commit
bf09ee2888
@ -1,6 +1,7 @@
|
||||
module Commands.Dev.Nockma where
|
||||
|
||||
import Commands.Base
|
||||
import Commands.Dev.Nockma.Encode as Encode
|
||||
import Commands.Dev.Nockma.Eval as Eval
|
||||
import Commands.Dev.Nockma.Format as Format
|
||||
import Commands.Dev.Nockma.Options
|
||||
@ -13,3 +14,4 @@ runCommand = \case
|
||||
NockmaEval opts -> Eval.runCommand opts
|
||||
NockmaFormat opts -> Format.runCommand opts
|
||||
NockmaRun opts -> Run.runCommand opts
|
||||
NockmaEncode opts -> Encode.runCommand opts
|
||||
|
32
app/Commands/Dev/Nockma/Encode.hs
Normal file
32
app/Commands/Dev/Nockma/Encode.hs
Normal file
@ -0,0 +1,32 @@
|
||||
module Commands.Dev.Nockma.Encode where
|
||||
|
||||
import Commands.Base
|
||||
import Commands.Dev.Nockma.Encode.Options
|
||||
import Data.ByteString qualified as B
|
||||
import Juvix.Compiler.Nockma.Encoding
|
||||
import Juvix.Compiler.Nockma.Language (Term)
|
||||
import Juvix.Compiler.Nockma.Pretty qualified as Nockma
|
||||
import Juvix.Compiler.Nockma.Translation.FromSource.Base
|
||||
|
||||
runCommand :: forall r. (Members AppEffects r) => NockmaEncodeOptions -> Sem r ()
|
||||
runCommand opts = runSimpleErrorIO $ do
|
||||
from :: Term Natural <- case opts ^. nockmaEncodeFrom of
|
||||
EncodeBytes -> do
|
||||
bs <- liftIO B.getContents
|
||||
decodeCue bs
|
||||
EncodeBase64 -> do
|
||||
bs <- getContents
|
||||
decodeCue64 bs
|
||||
EncodeText -> fromTextEncoding
|
||||
EncodeDebug -> fromTextEncoding
|
||||
case opts ^. nockmaEncodeTo of
|
||||
EncodeBytes -> do
|
||||
renderStdOutRaw (jamToByteString from)
|
||||
EncodeBase64 -> renderStdOut (encodeJam64 from)
|
||||
EncodeText -> renderStdOut (Nockma.ppSerialize from)
|
||||
EncodeDebug -> renderStdOut (Nockma.ppPrint from)
|
||||
where
|
||||
fromTextEncoding :: (Members '[App, EmbedIO] r') => Sem r' (Term Natural)
|
||||
fromTextEncoding = do
|
||||
bs <- getContents
|
||||
getRight (parseText bs)
|
72
app/Commands/Dev/Nockma/Encode/Options.hs
Normal file
72
app/Commands/Dev/Nockma/Encode/Options.hs
Normal file
@ -0,0 +1,72 @@
|
||||
module Commands.Dev.Nockma.Encode.Options where
|
||||
|
||||
import CommonOptions
|
||||
import Prelude (show)
|
||||
|
||||
data EncodeType
|
||||
= EncodeBase64
|
||||
| EncodeBytes
|
||||
| EncodeDebug
|
||||
| EncodeText
|
||||
deriving stock (Eq, Enum, Bounded, Ord, Data)
|
||||
|
||||
instance Show EncodeType where
|
||||
show = \case
|
||||
EncodeBase64 -> "base64"
|
||||
EncodeBytes -> "bytes"
|
||||
EncodeDebug -> "debug"
|
||||
EncodeText -> "text"
|
||||
|
||||
instance Pretty EncodeType where
|
||||
pretty = pretty . Prelude.show
|
||||
|
||||
data NockmaEncodeOptions = NockmaEncodeOptions
|
||||
{ _nockmaEncodeFrom :: EncodeType,
|
||||
_nockmaEncodeTo :: EncodeType
|
||||
}
|
||||
deriving stock (Data)
|
||||
|
||||
makeLenses ''NockmaEncodeOptions
|
||||
|
||||
base64Help :: AnsiDoc
|
||||
base64Help = "Jam and Base 64 encoding"
|
||||
|
||||
bytesHelp :: AnsiDoc
|
||||
bytesHelp = "Jam encoding"
|
||||
|
||||
encodingHelp :: Doc AnsiStyle
|
||||
encodingHelp =
|
||||
enumHelp
|
||||
( \case
|
||||
EncodeBase64 -> base64Help
|
||||
EncodeBytes -> bytesHelp
|
||||
EncodeDebug -> "Nockma code with annotations"
|
||||
EncodeText -> "Nockma code without annotations"
|
||||
)
|
||||
|
||||
parseNockmaEncodeOptions :: Parser NockmaEncodeOptions
|
||||
parseNockmaEncodeOptions = do
|
||||
_nockmaEncodeFrom <-
|
||||
option
|
||||
(enumReader Proxy)
|
||||
( long "to"
|
||||
<> metavar "ENCODING"
|
||||
<> completer (enumCompleter @EncodeType Proxy)
|
||||
<> helpDoc
|
||||
( "Choose the source encoding.\n"
|
||||
<> encodingHelp
|
||||
)
|
||||
)
|
||||
|
||||
_nockmaEncodeTo <-
|
||||
option
|
||||
(enumReader Proxy)
|
||||
( long "from"
|
||||
<> metavar "ENCODING"
|
||||
<> completer (enumCompleter @EncodeType Proxy)
|
||||
<> helpDoc
|
||||
( "Choose the target encoding.\n"
|
||||
<> encodingHelp
|
||||
)
|
||||
)
|
||||
pure NockmaEncodeOptions {..}
|
@ -1,5 +1,6 @@
|
||||
module Commands.Dev.Nockma.Options where
|
||||
|
||||
import Commands.Dev.Nockma.Encode.Options
|
||||
import Commands.Dev.Nockma.Eval.Options
|
||||
import Commands.Dev.Nockma.Format.Options
|
||||
import Commands.Dev.Nockma.Repl.Options
|
||||
@ -11,6 +12,7 @@ data NockmaCommand
|
||||
| NockmaEval NockmaEvalOptions
|
||||
| NockmaFormat NockmaFormatOptions
|
||||
| NockmaRun NockmaRunOptions
|
||||
| NockmaEncode NockmaEncodeOptions
|
||||
deriving stock (Data)
|
||||
|
||||
parseNockmaCommand :: Parser NockmaCommand
|
||||
@ -20,9 +22,19 @@ parseNockmaCommand =
|
||||
[ commandRepl,
|
||||
commandFromAsm,
|
||||
commandFormat,
|
||||
commandEncode,
|
||||
commandRun
|
||||
]
|
||||
where
|
||||
commandEncode :: Mod CommandFields NockmaCommand
|
||||
commandEncode = command "encode" runInfo
|
||||
where
|
||||
runInfo :: ParserInfo NockmaCommand
|
||||
runInfo =
|
||||
info
|
||||
(NockmaEncode <$> parseNockmaEncodeOptions)
|
||||
(progDesc "Encode and decode nockma terms")
|
||||
|
||||
commandRun :: Mod CommandFields NockmaCommand
|
||||
commandRun = command "run" runInfo
|
||||
where
|
||||
|
@ -6,16 +6,12 @@ where
|
||||
|
||||
import Anoma.Effect.Base
|
||||
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.Encoding
|
||||
import Juvix.Compiler.Nockma.Language qualified as Nockma
|
||||
import Juvix.Data.CodeAnn (simpleErrorCodeAnn)
|
||||
import Juvix.Data.CodeAnn
|
||||
import Juvix.Prelude
|
||||
import Juvix.Prelude.Aeson (Value)
|
||||
import Juvix.Prelude.Aeson qualified as Aeson
|
||||
import Juvix.Prelude.Pretty
|
||||
|
||||
data RunNockmaInput = RunNockmaInput
|
||||
{ _runNockmaProgram :: AnomaResult,
|
||||
@ -24,19 +20,6 @@ data RunNockmaInput = RunNockmaInput
|
||||
|
||||
makeLenses ''RunNockmaInput
|
||||
|
||||
decodeJam64 :: (Members '[Error SimpleError] r) => Text -> Sem r (Nockma.Term Natural)
|
||||
decodeJam64 encoded =
|
||||
case Base64.decode (encodeUtf8 encoded) of
|
||||
Left err -> throw (SimpleError (mkAnsiText err))
|
||||
Right bs' ->
|
||||
case cueFromByteString'' bs' of
|
||||
Left (err :: NockNaturalNaturalError) -> throw (simpleErrorCodeAnn err)
|
||||
Right (Left (err :: DecodingError)) -> throw (simpleErrorCodeAnn err)
|
||||
Right (Right r) -> return r
|
||||
|
||||
encodeJam64 :: Nockma.Term Natural -> Text
|
||||
encodeJam64 = decodeUtf8 . Base64.encode . jamToByteString
|
||||
|
||||
fromJSON :: (Members '[Error SimpleError, Logger] r) => (Aeson.FromJSON a) => Value -> Sem r a
|
||||
fromJSON v = case Aeson.fromJSON v of
|
||||
Aeson.Success r -> return r
|
||||
@ -60,5 +43,5 @@ runNockma prog inputs = do
|
||||
res :: Response <- anomaRpc runNockGrpcUrl (Aeson.toJSON msg) >>= fromJSON
|
||||
logVerbose (mkAnsiText ("Response Payload:\n" <> Aeson.jsonEncodeToPrettyText res))
|
||||
case res of
|
||||
ResponseProof x -> decodeJam64 x
|
||||
ResponseProof x -> decodeCue64 x
|
||||
ResponseError err -> throw (SimpleError (mkAnsiText err))
|
||||
|
@ -1,11 +1,13 @@
|
||||
module Juvix.Compiler.Nockma.Encoding.Cue where
|
||||
|
||||
import Data.Bit as Bit
|
||||
import Data.ByteString.Base64 qualified as Base64
|
||||
import Juvix.Compiler.Nockma.Encoding.Base
|
||||
import Juvix.Compiler.Nockma.Encoding.ByteString
|
||||
import Juvix.Compiler.Nockma.Encoding.Effect.BitReader
|
||||
import Juvix.Compiler.Nockma.Language
|
||||
import Juvix.Compiler.Nockma.Pretty.Base
|
||||
import Juvix.Data.Error.GenericError
|
||||
import Juvix.Prelude.Base
|
||||
import VectorBuilder.Builder as Builder
|
||||
import VectorBuilder.Vector
|
||||
@ -344,3 +346,16 @@ fromNatural' = mapError (ErrNockNatural' @a) . fromNatural
|
||||
|
||||
nockNatural' :: forall a r. (NockNatural a, Member (Error (ErrNockNatural' a)) r) => Atom a -> Sem r Natural
|
||||
nockNatural' = mapError (ErrNockNatural' @a) . nockNatural
|
||||
|
||||
decodeCue :: (Members '[Error SimpleError] r) => ByteString -> Sem r (Term Natural)
|
||||
decodeCue encoded =
|
||||
case cueFromByteString'' encoded of
|
||||
Left (err :: NockNaturalNaturalError) -> throw (simpleErrorCodeAnn err)
|
||||
Right (Left (err :: DecodingError)) -> throw (simpleErrorCodeAnn err)
|
||||
Right (Right r) -> return r
|
||||
|
||||
decodeCue64 :: (Members '[Error SimpleError] r) => Text -> Sem r (Term Natural)
|
||||
decodeCue64 encoded =
|
||||
case Base64.decode (encodeUtf8 encoded) of
|
||||
Left err -> throw (SimpleError (mkAnsiText err))
|
||||
Right bs' -> decodeCue bs'
|
||||
|
@ -8,6 +8,7 @@ module Juvix.Compiler.Nockma.Encoding.Jam where
|
||||
|
||||
import Data.Bit as Bit
|
||||
import Data.Bits
|
||||
import Data.ByteString.Base64 qualified as Base64
|
||||
import Juvix.Compiler.Nockma.Encoding.Base
|
||||
import Juvix.Compiler.Nockma.Encoding.ByteString
|
||||
import Juvix.Compiler.Nockma.Encoding.Effect.BitWriter
|
||||
@ -109,3 +110,6 @@ jam t = do
|
||||
let i = fromInteger . vectorBitsToInteger . jamToBits $ t
|
||||
ai <- fromNatural i
|
||||
return (Atom ai emptyAtomInfo)
|
||||
|
||||
encodeJam64 :: Term Natural -> Text
|
||||
encodeJam64 = decodeUtf8 . Base64.encode . jamToByteString
|
||||
|
@ -182,7 +182,7 @@ import Data.Text qualified as Text
|
||||
import Data.Text.Encoding
|
||||
import Data.Text.IO hiding (appendFile, getContents, getLine, hGetContents, hGetLine, hPutStr, hPutStrLn, interact, putStr, putStrLn, readFile, writeFile)
|
||||
import Data.Text.IO qualified as Text
|
||||
import Data.Text.IO.Utf8 hiding (getLine, hGetLine, hPutStr, hPutStrLn, putStr, putStrLn, readFile, writeFile)
|
||||
import Data.Text.IO.Utf8 hiding (getContents, getLine, hGetLine, hPutStr, hPutStrLn, putStr, putStrLn, readFile, writeFile)
|
||||
import Data.Text.IO.Utf8 qualified as Utf8
|
||||
import Data.Text.Lazy.Builder qualified as LazyText
|
||||
import Data.Traversable
|
||||
@ -568,6 +568,9 @@ indexFrom i = zipWith Indexed [i ..]
|
||||
|
||||
makeLenses ''Indexed
|
||||
|
||||
getContents :: (MonadIO m) => m Text
|
||||
getContents = liftIO Utf8.getContents
|
||||
|
||||
hClose :: (MonadIO m) => Handle -> m ()
|
||||
hClose = liftIO . IO.hClose
|
||||
|
||||
|
Loading…
Reference in New Issue
Block a user