Skip to content

Commit

Permalink
Cleanup on aisle chanterelle (#139)
Browse files Browse the repository at this point in the history
* checkpoint

* get rid of most of utils.errors
  • Loading branch information
martyall authored Sep 20, 2023
1 parent 15e3e6d commit 0cc1dd4
Show file tree
Hide file tree
Showing 31 changed files with 595 additions and 764 deletions.
2 changes: 1 addition & 1 deletion packages.dhall
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@ let upstream =
https://raw.githubusercontent.com/f-o-a-m/package-sets/b3ecf8e8e4e1a35ba97fcb7e9f2858d14ee6a912/purs-0.15.7-web3.dhall
sha256:ce57fd949b7cd331d7c61ff45283e35983dd5797b3f17616dd69f8bc06f54784
with eth-core.version = "v10.0.0"
with web3.version = "v6.0.0"
with web3.version = "v6.1.0"

let overrides = {=}

Expand Down
3 changes: 3 additions & 0 deletions spago.dhall
Original file line number Diff line number Diff line change
Expand Up @@ -17,13 +17,15 @@ You can edit this file as you like.
, "datetime"
, "effect"
, "either"
, "errors"
, "eth-core"
, "exceptions"
, "foldable-traversable"
, "foreign-object"
, "functors"
, "identity"
, "integers"
, "js-date"
, "logging"
, "maybe"
, "mkdirp"
Expand All @@ -33,6 +35,7 @@ You can edit this file as you like.
, "node-fs-aff"
, "node-path"
, "node-process"
, "now"
, "optparse"
, "ordered-collections"
, "parallel"
Expand Down
44 changes: 24 additions & 20 deletions src/Chanterelle.purs
Original file line number Diff line number Diff line change
Expand Up @@ -2,16 +2,16 @@ module Chanterelle where

import Prelude

import Chanterelle.Compile (compile) as Chanterelle
import Chanterelle.Deploy (deploy)
import Chanterelle.Internal.Codegen (generatePS) as Chanterelle
import Chanterelle.Internal.Compile (compile) as Chanterelle
import Chanterelle.Internal.Logging (LogLevel(..), log, logCompileError, readLogLevel, setLogLevel)
import Chanterelle.Internal.Types (DeployM, runCompileMExceptT)
import Chanterelle.Internal.Types.Project (ChanterelleProject)
import Chanterelle.Internal.Utils (eitherM_)
import Chanterelle.Logging (LogLevel(..), log, logCompileError, readLogLevel, setLogLevel)
import Chanterelle.Project (loadProject)
import Chanterelle.Types.Compile (runCompileM)
import Chanterelle.Types.Deploy (DeployM)
import Chanterelle.Types.Project (ChanterelleProject)
import Control.Monad.Error.Class (try)
import Data.Either (Either(..))
import Data.Either (Either(..), either)
import Data.Generic.Rep (class Generic)
import Data.Show.Generic (genericShow)
import Effect.Aff (Aff)
Expand All @@ -23,18 +23,18 @@ data SelectCLI (a :: Type) (b :: Type) = SelectCLI a

data SelectPS (a :: Type) (b :: Type) = SelectPS b

instance showSelectDeployM :: Show (SelectPS a (DeployM Unit)) where
instance Show (SelectPS a (DeployM Unit)) where
show (SelectPS _) = "<DeployM Unit>"

instance showSelectDeployPath :: Show a => Show (SelectCLI a b) where
instance Show a => Show (SelectCLI a b) where
show (SelectCLI a) = show a

type ArgsCLI = Args' SelectCLI
type Args = Args' SelectPS
data Args' s = Args' CommonOpts (Command s)

derive instance genericArgs :: Generic (Args' s) _
instance showArgs :: Show (DeployOptions s) => Show (Args' s) where
derive instance Generic (Args' s) _
instance Show (DeployOptions s) => Show (Args' s) where
show = genericShow

type DirPath = String
Expand All @@ -43,8 +43,8 @@ data CommonOpts = CommonOpts
, rootPath :: DirPath
}

derive instance genericCommonOpts :: Generic CommonOpts _
instance showCommonOpts :: Show CommonOpts where
derive instance Generic CommonOpts _
instance Show CommonOpts where
show = genericShow

data Command s
Expand All @@ -54,8 +54,8 @@ data Command s
| Deploy (DeployOptions s)
| GlobalDeploy (DeployOptions s)

derive instance genericCommand :: Generic (Command s) _
instance showCommand :: Show (DeployOptions s) => Show (Command s) where
derive instance Generic (Command s) _
instance Show (DeployOptions s) => Show (Command s) where
show = genericShow

traverseDeployOptions :: forall a b f. Applicative f => (DeployOptions a -> f (DeployOptions b)) -> Args' a -> f (Args' b)
Expand All @@ -74,8 +74,8 @@ data DeployOptions s = DeployOptions
, script :: s String (DeployM Unit)
}

derive instance genericDeployOptions :: Generic (DeployOptions s) _
instance showDeployOptions :: Show (DeployOptions SelectPS) where
derive instance Generic (DeployOptions s) _
instance Show (DeployOptions SelectPS) where
show = genericShow

chanterelle :: Args -> Aff Unit
Expand Down Expand Up @@ -103,7 +103,11 @@ runCommand project = case _ of
log Error $ "deploy is unavailable as Chanterelle is running from a global installation"
log Error $ "Please ensure your project's Chanterelle instance has compiled"
-- doClassicBuild = doCompile *> doCodegen
doCompile = eitherM_ terminateOnCompileError $ runCompileMExceptT Chanterelle.compile project
doCodegen = eitherM_ terminateOnCompileError $ runCompileMExceptT Chanterelle.generatePS project

terminateOnCompileError e = logCompileError e *> liftEffect (exit 1)
doCompile = do
eRes <- runCompileM Chanterelle.compile project
either terminateOnCompileError mempty eRes
doCodegen = do
eRes <- runCompileM Chanterelle.generatePS project
either terminateOnCompileError mempty eRes

terminateOnCompileError e = logCompileError e *> liftEffect (exit 1)
Original file line number Diff line number Diff line change
@@ -1,22 +1,20 @@
module Chanterelle.Internal.Artifact
( module ArtifactExports
, readArtifact
module Chanterelle.Artifact
( readArtifact
, updateArtifact
, writeArtifact
) where

import Prelude

import Chanterelle.Internal.Types.Artifact (Artifact(..))
import Chanterelle.Internal.Types.Artifact (Artifact(..), ArtifactBytecode(..), _Deployed, _NetworkBytecode, _abi, _address, _blockHash, _blockNumber, _bytecode, _code, _deployedBytecode, _lastModified, _network, _networks, _transactionHash, emptyArtifactBytecode, fromSolidityContractLevelOutput) as ArtifactExports
import Chanterelle.Internal.Utils.FS (readTextFile, withTextFile, writeTextFile)
import Chanterelle.Internal.Utils.Json (jsonStringifyWithSpaces, parseDecodeM)
import Chanterelle.Internal.Utils.Time (now, toEpoch)
import Chanterelle.Types.Artifact (Artifact(..))
import Chanterelle.Utils (jsonStringifyWithSpaces, parseDecodeM, readTextFile, withTextFile, writeTextFile)
import Control.Monad.Error.Class (class MonadThrow)
import Data.Argonaut (encodeJson)
import Data.DateTime.Instant (unInstant)
import Data.Time.Duration (Milliseconds(..))
import Effect.Aff.Class (class MonadAff)
import Effect.Class (class MonadEffect, liftEffect)
import Effect.Now (now)
import Node.Path (FilePath)

setModTimeAndStringify
Expand All @@ -25,7 +23,7 @@ setModTimeAndStringify
=> Artifact
-> m String
setModTimeAndStringify (Artifact a) = do
Milliseconds newLastModified <- toEpoch <$> liftEffect now
Milliseconds newLastModified <- unInstant <$> liftEffect now
let newArtifact = Artifact (a { lastModified = newLastModified })
pure $ jsonStringifyWithSpaces 4 $ encodeJson newArtifact

Expand Down Expand Up @@ -55,4 +53,4 @@ writeArtifact
-> Artifact
-> m Unit
writeArtifact filepath a =
liftEffect (setModTimeAndStringify a) >>= writeTextFile filepath
liftEffect (setModTimeAndStringify a) >>= writeTextFile filepath
Original file line number Diff line number Diff line change
Expand Up @@ -4,10 +4,10 @@ module Chanterelle.Internal.Codegen

import Prelude

import Chanterelle.Internal.Logging (LogLevel(..), log)
import Chanterelle.Internal.Types.Compile (CompileError(..))
import Chanterelle.Internal.Types.Project (ChanterelleProject(..), ChanterelleProjectSpec(..), ChanterelleModule(..))
import Chanterelle.Internal.Utils.FS (assertDirectory')
import Chanterelle.Logging (LogLevel(..), log)
import Chanterelle.Types.Compile (CompileError(..))
import Chanterelle.Types.Project (ChanterelleProject(..), ChanterelleProjectSpec(..), ChanterelleModule(..))
import Chanterelle.Utils (assertDirectory')
import Control.Monad.Error.Class (class MonadThrow, throwError)
import Control.Monad.Reader (class MonadAsk, ask)
import Data.AbiParser (Abi(Abi), AbiDecodeError(..), AbiWithErrors) as PSWeb3Gen
Expand Down
Original file line number Diff line number Diff line change
@@ -1,30 +1,34 @@
module Chanterelle.Internal.Compile
module Chanterelle.Compile
( compile
, makeSolcInput
, compileModuleWithoutWriting
, decodeModuleOutput
, resolveModuleContract
, module CompileReexports
) where

import Prelude

import Chanterelle.Internal.Artifact (writeArtifact)
import Chanterelle.Internal.Logging (LogLevel(..), log, logSolcError)
import Chanterelle.Internal.Types.Compile (CompileError(..)) as CompileReexports
import Chanterelle.Internal.Types.Compile (CompileError(..), resolveSolidityContractLevelOutput)
import Chanterelle.Internal.Types.Project (ChanterelleModule(..), ChanterelleProject(..), ChanterelleProjectSpec(..), Dependency(..), getSolc, partitionSelectionSpecs)
import Chanterelle.Internal.Utils.Error (withExceptM', withExceptT')
import Chanterelle.Internal.Utils.FS (assertDirectory', fileIsDirty)
import Chanterelle.Artifact (writeArtifact)
import Chanterelle.Logging (LogLevel(..), log, logSolcError)
import Chanterelle.Types.Artifact (Artifact(..))
import Chanterelle.Types.Bytecode (Bytecode(..), flattenLinkReferences)
import Chanterelle.Types.Compile (CompileError(..))
import Chanterelle.Types.Project (ChanterelleModule(..), ChanterelleProject(..), ChanterelleProjectSpec(..), Dependency(..), getSolc, partitionSelectionSpecs)
import Chanterelle.Utils (assertDirectory', fileIsDirty)
import Chanterelle.Utils.Error (withExceptT')
import Control.Error.Util (note)
import Control.Monad.Error.Class (class MonadThrow, throwError)
import Control.Monad.Reader (class MonadAsk, ask)
import Data.Argonaut (decodeJson, printJsonDecodeError)
import Data.Argonaut as A
import Data.Argonaut.Parser as AP
import Data.Array (catMaybes, partition)
import Data.Either (Either(..), hush)
import Data.Bifunctor (lmap)
import Data.Either (Either(..), either, hush)
import Data.Lens ((^?))
import Data.Lens.Index (ix)
import Data.Maybe (Maybe(..), fromMaybe)
import Data.Maybe (Maybe(..), fromMaybe, maybe)
import Data.Newtype (un)
import Data.String (Pattern(..), stripPrefix)
import Data.Time.Duration (Milliseconds(..))
import Data.Traversable (for, for_)
Expand All @@ -34,6 +38,7 @@ import Effect.Aff (attempt)
import Effect.Aff.Class (class MonadAff, liftAff)
import Effect.Class (class MonadEffect)
import Effect.Exception (catchException)
import Foreign.Object as FO
import Foreign.Object as M
import Language.Solidity.Compiler (compile) as Solc
import Language.Solidity.Compiler.Types as ST
Expand Down Expand Up @@ -108,7 +113,9 @@ compileModuleWithoutWriting
-> m ST.CompilerOutput
compileModuleWithoutWriting m@(ChanterelleModule mod) solcInput = do
(ChanterelleProject project) <- ask
solc <- withExceptM' CompilerUnavailable $ getSolc project.solc
solc <- do
eRes <- getSolc project.solc
either (throwError <<< CompilerUnavailable) pure eRes
log Info ("compiling " <> show mod.moduleType <> " " <> mod.moduleName)
output <- Solc.compile solc solcInput (loadSolcCallback m project.root project.spec) --liftEffect $ runFn2 _compile (A.stringify $ encodeJson solcInput) (loadSolcCallback m project.root project.spec)
case output of
Expand Down Expand Up @@ -232,3 +239,31 @@ writeBuildArtifact srcName filepath output solContractName = do
outputArtifact <- resolveSolidityContractLevelOutput co'
assertDirectory' (Path.dirname filepath)
withExceptT' FSError $ writeArtifact filepath outputArtifact

resolveSolidityContractLevelOutput
:: forall m
. MonadThrow CompileError m
=> ST.ContractLevelOutput
-> m Artifact
resolveSolidityContractLevelOutput a =
either (throwError <<< UnexpectedSolcOutput) pure $ fromSolidityContractLevelOutput a
where

fromSolidityBytecodeOutput :: ST.BytecodeOutput -> Either String Bytecode
fromSolidityBytecodeOutput (ST.BytecodeOutput o) = do
rawBytecode <- note "Solidity bytecode output lacked an \"object\" field" o.object
let linkReferences = maybe FO.empty (flattenLinkReferences <<< un ST.LinkReferences) o.linkReferences
pure $ case rawBytecode of
ST.BytecodeHexString bytecode -> BCLinked { bytecode, linkReferences }
_ -> BCUnlinked { rawBytecode, linkReferences, remainingLinkReferences: linkReferences }

fromSolidityContractLevelOutput :: ST.ContractLevelOutput -> Either String Artifact
fromSolidityContractLevelOutput (ST.ContractLevelOutput clo) = do
abi <- lmap printJsonDecodeError <<< decodeJson =<< note "Solidity contract output did not have an \"abi\" field" clo.abi
(ST.EvmOutput evm) <- note "Solidity contract output did not have an \"evm\" field" clo.evm
bytecode' <- note "Solidity contract output did not have an \"evm.bytecode\" field" evm.bytecode
bytecode <- fromSolidityBytecodeOutput bytecode'
deployedBytecode' <- note "Solidity contract output did not have an \"evm.deployedBytecode\" field" evm.deployedBytecode
deployedBytecode <- fromSolidityBytecodeOutput deployedBytecode'
let lastModified = top
pure $ Artifact { abi, code: { bytecode, deployedBytecode }, lastModified, networks: FO.empty }
Loading

0 comments on commit 0cc1dd4

Please sign in to comment.