Skip to content

Commit

Permalink
checkpoint
Browse files Browse the repository at this point in the history
  • Loading branch information
martyall committed Sep 19, 2023
1 parent 15e3e6d commit fc71a51
Show file tree
Hide file tree
Showing 24 changed files with 214 additions and 271 deletions.
25 changes: 13 additions & 12 deletions src/Chanterelle.purs
Original file line number Diff line number Diff line change
Expand Up @@ -5,9 +5,10 @@ import Prelude
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.Logging (LogLevel(..), log, logCompileError, readLogLevel, setLogLevel)
import Chanterelle.Types.Deploy (DeployM)
import Chanterelle.Types.Compile (runCompileMExceptT)
import Chanterelle.Types.Project (ChanterelleProject)
import Chanterelle.Internal.Utils (eitherM_)
import Chanterelle.Project (loadProject)
import Control.Monad.Error.Class (try)
Expand All @@ -23,18 +24,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,7 +44,7 @@ data CommonOpts = CommonOpts
, rootPath :: DirPath
}

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

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

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

Expand All @@ -74,8 +75,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 @@ -106,4 +107,4 @@ runCommand project = case _ of
doCompile = eitherM_ terminateOnCompileError $ runCompileMExceptT Chanterelle.compile project
doCodegen = eitherM_ terminateOnCompileError $ runCompileMExceptT Chanterelle.generatePS project

terminateOnCompileError e = logCompileError e *> liftEffect (exit 1)
terminateOnCompileError e = logCompileError e *> liftEffect (exit 1)
7 changes: 2 additions & 5 deletions src/Chanterelle/Deploy.purs
Original file line number Diff line number Diff line change
@@ -1,15 +1,12 @@
module Chanterelle.Deploy
( deploy
, deployWithProvider
, module Exports
) where

import Prelude

import Chanterelle.Internal.Deploy (deployContract, deployLibrary, linkLibrary, readDeployAddress) as Exports
import Chanterelle.Internal.Logging (logDeployError)
import Chanterelle.Internal.Types (runDeployM) as Exports
import Chanterelle.Internal.Types.Deploy (DeployM, runDeployM)
import Chanterelle.Logging (logDeployError)
import Chanterelle.Types.Deploy (DeployM, runDeployM)
import Chanterelle.Internal.Utils (makeDeployConfigWithProvider, makeProvider)
import Control.Monad.Except (runExceptT)
import Data.Either (Either(..))
Expand Down
13 changes: 6 additions & 7 deletions src/Chanterelle/Internal/Artifact.purs
Original file line number Diff line number Diff line change
@@ -1,22 +1,21 @@
module Chanterelle.Internal.Artifact
( module ArtifactExports
, readArtifact
( 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.Types.Artifact (Artifact(..))
import Chanterelle.Internal.Utils.FS (readTextFile, withTextFile, writeTextFile)
import Chanterelle.Internal.Utils.Json (jsonStringifyWithSpaces, parseDecodeM)
import Chanterelle.Internal.Utils.Time (now, toEpoch)
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 +24,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 +54,4 @@ writeArtifact
-> Artifact
-> m Unit
writeArtifact filepath a =
liftEffect (setModTimeAndStringify a) >>= writeTextFile filepath
liftEffect (setModTimeAndStringify a) >>= writeTextFile filepath
6 changes: 3 additions & 3 deletions src/Chanterelle/Internal/Codegen.purs
Original file line number Diff line number Diff line change
Expand Up @@ -4,9 +4,9 @@ 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.Logging (LogLevel(..), log)
import Chanterelle.Types.Compile (CompileError(..))
import Chanterelle.Types.Project (ChanterelleProject(..), ChanterelleProjectSpec(..), ChanterelleModule(..))
import Chanterelle.Internal.Utils.FS (assertDirectory')
import Control.Monad.Error.Class (class MonadThrow, throwError)
import Control.Monad.Reader (class MonadAsk, ask)
Expand Down
46 changes: 39 additions & 7 deletions src/Chanterelle/Internal/Compile.purs
Original file line number Diff line number Diff line change
Expand Up @@ -4,27 +4,31 @@ module Chanterelle.Internal.Compile
, 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.Error (withExcept', withExceptM', withExceptT')
import Chanterelle.Internal.Utils.FS (assertDirectory', fileIsDirty)
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 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.Bifunctor (lmap)
import Data.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 @@ -232,3 +237,30 @@ 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 = withExcept' UnexpectedSolcOutput <<< fromSolidityContractLevelOutput
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 }
20 changes: 11 additions & 9 deletions src/Chanterelle/Internal/Deploy.purs
Original file line number Diff line number Diff line change
Expand Up @@ -3,21 +3,21 @@ module Chanterelle.Internal.Deploy
, deployLibrary
, linkLibrary
, readDeployAddress
, DeployReceipt
) where

import Prelude

import Chanterelle.Internal.Artifact (readArtifact, writeArtifact) as Artifact
import Chanterelle.Internal.Logging (LogLevel(..), log)
import Chanterelle.Internal.Types.Artifact (Artifact(..), ArtifactBytecode(..), NetworkInfo(..), _Deployed, _NetworkBytecode, _address, _code, _network)
import Chanterelle.Internal.Types.Bytecode (Bytecode(..))
import Chanterelle.Internal.Types.Bytecode as CBC
import Chanterelle.Internal.Types.Deploy (ContractConfig, DeployConfig(..), DeployError(..), LibraryConfig, NetworkID)
import Chanterelle.Internal.Utils (attemptWithTimeout, catchingAff', except', pollTransactionReceipt, validateDeployArgs, withExceptM', withExceptT', (??))
import Chanterelle.Internal.Utils (attemptWithTimeout, except', pollTransactionReceipt, validateDeployArgs, withExceptM', withExceptT', (??))
import Chanterelle.Logging (LogLevel(..), log)
import Chanterelle.Types.Artifact (Artifact(..), ArtifactBytecode(..), NetworkInfo(..), _Deployed, _NetworkBytecode, _address, _code, _network)
import Chanterelle.Types.Bytecode (Bytecode(..))
import Chanterelle.Types.Bytecode as CBC
import Chanterelle.Types.Deploy (ContractConfig, DeployConfig(..), DeployError(..), LibraryConfig, NetworkID)
import Control.Monad.Error.Class (class MonadThrow, throwError)
import Control.Monad.Reader.Class (class MonadAsk, ask)
import Data.Bifunctor (lmap)
import Data.Either (either)
import Data.Lens (_Just, (%~), (?~), (^.), (^?))
import Data.Map as Map
import Data.Maybe (fromMaybe, isNothing, maybe)
Expand Down Expand Up @@ -92,7 +92,9 @@ getPublishedContractDeployInfo txHash name (ArtifactBytecode { bytecode, deploye
(DeployConfig { timeout, provider }) <- ask
log Info $ "Polling for " <> name <> " transaction receipt: " <> show txHash
let txReceiptError err = OnDeploymentError { name, message: "Failed to get transaction receipt: " <> show err }
TransactionReceipt txReceipt <- catchingAff' txReceiptError $ attemptWithTimeout timeout (pollTransactionReceipt txHash provider)
TransactionReceipt txReceipt <- do
eRes <- liftAff $ attemptWithTimeout timeout (pollTransactionReceipt txHash provider)
either (throwError <<< txReceiptError) pure eRes
if txReceipt.status == Failed || isNothing (txReceipt.contractAddress) then
let
message = "Deployment failed to create contract, no address found or status 0x0 in receipt: " <> name
Expand Down Expand Up @@ -279,4 +281,4 @@ updateArtifact'
=> LibraryConfig a
-> (Artifact -> m Artifact)
-> m Unit
updateArtifact' lc action = readArtifact' lc >>= action >>= writeArtifact' lc
updateArtifact' lc action = readArtifact' lc >>= action >>= writeArtifact' lc
13 changes: 0 additions & 13 deletions src/Chanterelle/Internal/Types.purs

This file was deleted.

23 changes: 12 additions & 11 deletions src/Chanterelle/Internal/Utils.purs
Original file line number Diff line number Diff line change
Expand Up @@ -12,23 +12,22 @@ module Chanterelle.Internal.Utils

import Prelude

import Chanterelle.Internal.Types (ContractConfig, DeployConfig(..), DeployError(..))
import Chanterelle.Internal.Utils.Error (catchingAff')
import Chanterelle.Internal.Utils.Error (catchingAff, catchingAff', eitherM, eitherM_, except', exceptM', exceptNoteA', exceptNoteM', withExceptM', withExceptT', (!?), (??)) as Utils.Error
import Chanterelle.Internal.Utils.Error (catchingAff, eitherM, eitherM_, except', exceptM', exceptNoteA', exceptNoteM', withExceptM', withExceptT', (!?), (??)) as Utils.Error
import Chanterelle.Internal.Utils.FS (assertDirectory, fileIsDirty, fileModTime, readTextFile, unparsePath, withTextFile, writeTextFile) as Utils.FS
import Chanterelle.Internal.Utils.Json (jsonStringifyWithSpaces) as Json
import Chanterelle.Internal.Utils.Web3 (getCodeForContract, getPrimaryAccount, getNetworkID, logAndThrow, logAndThrow', makeProvider, pollTransactionReceipt, providerForNetwork, resolveCodeForContract, resolveProvider, web3WithTimeout) as Web3
import Chanterelle.Types.Deploy (ContractConfig, DeployConfig(..), DeployError(..))
import Control.Monad.Error.Class (class MonadThrow, throwError)
import Control.Parallel (parOneOf)
import Data.Either (Either)
import Data.Either (Either, either)
import Data.Int (toNumber)
import Data.Map as Map
import Data.Validation.Semigroup (validation)
import Effect.Aff (Aff, Milliseconds(..), attempt, delay)
import Effect.Aff.Class (class MonadAff)
import Effect.Ref as Ref
import Effect.Aff.Class (class MonadAff, liftAff)
import Effect.Class (liftEffect)
import Effect.Exception (Error, error)
import Effect.Ref as Ref
import Network.Ethereum.Web3 (Provider, runWeb3)

makeDeployConfig
Expand All @@ -54,11 +53,13 @@ makeDeployConfigWithProvider provider tout =
timeout = Milliseconds (toNumber tout)
toError = ConfigurationError <<< append "Couldn't create DeployConfig: " <<< show
in
catchingAff' toError $ runWeb3 provider do
primaryAccount <- Web3.getPrimaryAccount
networkID <- Web3.getNetworkID
artifactCache <- liftEffect $ Ref.new Map.empty
pure $ DeployConfig { provider, primaryAccount, networkID, timeout, ignoreNetworksInArtifact: false, writeArtifacts: true, artifactCache }
do
eRes <- liftAff $ runWeb3 provider do
primaryAccount <- Web3.getPrimaryAccount
networkID <- Web3.getNetworkID
artifactCache <- liftEffect $ Ref.new Map.empty
pure $ DeployConfig { provider, primaryAccount, networkID, timeout, ignoreNetworksInArtifact: false, writeArtifacts: true, artifactCache }
either (throwError <<< toError) pure eRes

-- | try an aff action for the specified amount of time before giving up.
withTimeout
Expand Down
11 changes: 1 addition & 10 deletions src/Chanterelle/Internal/Utils/Error.purs
Original file line number Diff line number Diff line change
Expand Up @@ -18,15 +18,6 @@ catchingAff
-> m a
catchingAff = withExceptM' show <<< liftAff <<< try

catchingAff'
:: forall m e e' a
. MonadAff m
=> MonadThrow e' m
=> (e -> e')
-> Aff (Either e a)
-> m a
catchingAff' f = withExceptM' f <<< liftAff

except'
:: forall m e a
. MonadThrow e m
Expand Down Expand Up @@ -99,4 +90,4 @@ eitherM_
=> (e -> m b)
-> ExceptT e m a
-> m Unit
eitherM_ f m = eitherM (void <<< f) (void m)
eitherM_ f m = eitherM (void <<< f) (void m)
6 changes: 3 additions & 3 deletions src/Chanterelle/Internal/Utils/FS.purs
Original file line number Diff line number Diff line change
Expand Up @@ -2,8 +2,8 @@ module Chanterelle.Internal.Utils.FS where

import Prelude

import Chanterelle.Internal.Logging (LogLevel(..), log)
import Chanterelle.Internal.Types.Compile (CompileError(..))
import Chanterelle.Logging (LogLevel(..), log)
import Chanterelle.Types.Compile (CompileError(..))
import Chanterelle.Internal.Utils.Error (catchingAff, withExceptT')
import Control.Monad.Error.Class (class MonadThrow, throwError)
import Data.DateTime.Instant (fromDateTime, unInstant)
Expand Down Expand Up @@ -128,4 +128,4 @@ withTextFile'
withTextFile' filename action = do
oldContents <- readTextFile filename
{ contents, result } <- action oldContents
writeTextFile filename contents *> pure result
writeTextFile filename contents *> pure result
22 changes: 0 additions & 22 deletions src/Chanterelle/Internal/Utils/Lazy.purs

This file was deleted.

Loading

0 comments on commit fc71a51

Please sign in to comment.