Skip to content

Commit

Permalink
0.12 Updates (#57)
Browse files Browse the repository at this point in the history
  • Loading branch information
safareli authored Dec 14, 2018
1 parent 2d81005 commit 294c307
Show file tree
Hide file tree
Showing 7 changed files with 86 additions and 90 deletions.
31 changes: 15 additions & 16 deletions bower.json
Original file line number Diff line number Diff line change
Expand Up @@ -18,23 +18,22 @@
"url": "git://github.com/f-o-a-m/purescript-web3-generator.git"
},
"dependencies": {
"purescript-argonaut": "^3.1.0",
"purescript-argonaut-core": "^3.1.0",
"purescript-argonaut-generic-codecs": "^6.0.4",
"purescript-prelude": "^3.1.0",
"purescript-errors": "^3.0.0",
"purescript-yargs": "^3.1.0",
"purescript-ansi": "^4.0.0",
"purescript-node-fs-aff": "^5.0.0",
"purescript-console": "^3.0.0",
"purescript-string-parsers": "^3.0.1",
"purescript-web3": "^0.25.0",
"purescript-mkdirp": "^0.3.0",
"purescript-fixed-points": "^4.0.0",
"purescript-record-extra": "^0.3.0"
"purescript-argonaut": "^4.0.0",
"purescript-ordered-collections": "^1.0.0",
"purescript-prelude": "^4.0.0",
"purescript-errors": "^4.0.0",
"purescript-yargs": "^4.0.0",
"purescript-ansi": "^5.0.0",
"purescript-node-fs-aff": "^6.0.0",
"purescript-console": "^4.0.0",
"purescript-string-parsers": "^4.0.0",
"purescript-web3": "^1.0.0",
"purescript-mkdirp": "joshuahhh/purescript-mkdirp#48ecb4039d5fe3be82d0e82c3a9f2338d1af82d2",
"purescript-fixed-points": "^5.0.0",
"purescript-record-extra": "^1.0.0"
},
"devDependencies": {
"purescript-spec": "^2.0.0",
"purescript-psci-support": "^3.0.0"
"purescript-spec": "^3.0.0",
"purescript-psci-support": "^4.0.0"
}
}
4 changes: 2 additions & 2 deletions package.json
Original file line number Diff line number Diff line change
Expand Up @@ -11,8 +11,8 @@
"rlp": "^2.0.0",
"secp256k1": "^3.0.1",
"psc-package": "^0.2.4-rc1",
"pulp": "^12.0.0",
"purescript": "^0.11.7",
"purescript": "^0.12.0",
"pulp": "^12.2.0",
"purescript-psa": "^0.6.0",
"yargs": "^8.0.2"
}
Expand Down
43 changes: 22 additions & 21 deletions src/Data/AbiParser.purs
Original file line number Diff line number Diff line change
Expand Up @@ -13,13 +13,14 @@ import Data.Bifunctor (lmap)
import Data.Either (Either(..))
import Data.Foldable (all, foldMap)
import Data.FunctorWithIndex (mapWithIndex)
import Data.Generic (class Generic, gEq, gShow)
import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Eq (genericEq)
import Data.Generic.Rep.Show (genericShow)
import Data.Int (fromString)
import Data.List.Types (List(..), NonEmptyList(..))
import Data.Maybe (Maybe(..))
import Data.NonEmpty ((:|))
import Data.Record.Extra (showRecord)
import Data.String (fromCharArray)
import Data.String.CodeUnits (fromCharArray)
import Data.TacitString as TacitString
import Text.Parsing.StringParser (Parser, fail, runParser, try)
import Text.Parsing.StringParser.Combinators (choice, lookAhead, manyTill, many1, optionMaybe)
Expand All @@ -45,13 +46,13 @@ data SolidityType =
| SolidityVector (NonEmptyList Int) SolidityType
| SolidityArray SolidityType

derive instance genericSolidityType :: Generic SolidityType
derive instance genericSolidityType :: Generic SolidityType _

instance showSolidityType :: Show SolidityType where
show = gShow
show x = genericShow x

instance eqSolidityType :: Eq SolidityType where
eq = gEq
eq x = genericEq x

instance formatSolidityType :: Format SolidityType where
format s = case s of
Expand Down Expand Up @@ -151,10 +152,10 @@ newtype FunctionInput =
, type :: SolidityType
}

derive instance genericFunctionInput :: Generic FunctionInput
derive instance genericFunctionInput :: Generic FunctionInput _

instance showFunctionInput :: Show FunctionInput where
show = gShow
show = genericShow

instance formatInput :: Format FunctionInput where
format (FunctionInput fi) = format fi.type
Expand All @@ -177,10 +178,10 @@ data SolidityFunction =
, isUnCurried :: Boolean
}

derive instance genericSolidityFunction :: Generic SolidityFunction
derive instance genericSolidityFunction :: Generic SolidityFunction _

instance showSolidityFunction :: Show SolidityFunction where
show = gShow
show = genericShow

instance decodeJsonSolidityFunction :: DecodeJson SolidityFunction where
decodeJson json = do
Expand Down Expand Up @@ -209,10 +210,10 @@ data SolidityConstructor =
, isUnCurried :: Boolean
}

derive instance genericSolidityConstructor :: Generic SolidityConstructor
derive instance genericSolidityConstructor :: Generic SolidityConstructor _

instance showSolidityConstructor :: Show SolidityConstructor where
show = gShow
show = genericShow

instance decodeJsonSolidityConstructor :: DecodeJson SolidityConstructor where
decodeJson json = do
Expand All @@ -233,10 +234,10 @@ data IndexedSolidityValue =
, indexed :: Boolean
}

derive instance genericSolidityIndexedValue :: Generic IndexedSolidityValue
derive instance genericSolidityIndexedValue :: Generic IndexedSolidityValue _

instance showSolidityIndexedValue :: Show IndexedSolidityValue where
show = gShow
show = genericShow

instance formatIndexedSolidityValue :: Format IndexedSolidityValue where
format (IndexedSolidityValue v) = format v.type
Expand All @@ -259,10 +260,10 @@ data SolidityEvent =
, inputs :: Array IndexedSolidityValue
}

derive instance genericSolidityEvent :: Generic SolidityEvent
derive instance genericSolidityEvent :: Generic SolidityEvent _

instance showSolidityEvent :: Show SolidityEvent where
show = gShow
show = genericShow

instance decodeJsonSolidityEvent :: DecodeJson SolidityEvent where
decodeJson json = do
Expand All @@ -277,10 +278,10 @@ instance decodeJsonSolidityEvent :: DecodeJson SolidityEvent where

data SolidityFallback = SolidityFallback

derive instance genericSolidityFallback :: Generic SolidityFallback
derive instance genericSolidityFallback :: Generic SolidityFallback _

instance showSolidityFallback :: Show SolidityFallback where
show = gShow
show = genericShow

instance decodeJsonSolidityFallback :: DecodeJson SolidityFallback where
decodeJson json = do
Expand All @@ -296,10 +297,10 @@ data AbiType =
| AbiEvent SolidityEvent
| AbiFallback SolidityFallback

derive instance genericAbiType :: Generic AbiType
derive instance genericAbiType :: Generic AbiType _

instance showAbiType :: Show AbiType where
show = gShow
show = genericShow

instance decodeJsonAbiType :: DecodeJson AbiType where
decodeJson json = do
Expand Down Expand Up @@ -336,4 +337,4 @@ instance showAbi ::
showFAbiType = map (show >>> TacitString.hush)

instance showAbiDecodeError :: Show AbiDecodeError where
show (AbiDecodeError r) = "(AbiDecodeError " <> showRecord r <> ")"
show (AbiDecodeError r) = "(AbiDecodeError " <> show r <> ")"
65 changes: 32 additions & 33 deletions src/Data/CodeGen.purs
Original file line number Diff line number Diff line change
Expand Up @@ -5,11 +5,11 @@ import Prelude
import Ansi.Codes (Color(..))
import Ansi.Output (withGraphics, foreground)
import Control.Error.Util (note)
import Control.Monad.Aff (Aff, try)
import Control.Monad.Aff.Class (class MonadAff, liftAff)
import Control.Monad.Aff.Console (CONSOLE, log)
import Control.Monad.Eff.Class (liftEff)
import Control.Monad.Eff.Exception (error)
import Effect.Aff (Aff, try)
import Effect.Aff.Class (class MonadAff, liftAff)
import Effect.Console (log)
import Effect.Class (liftEffect)
import Effect.Exception (error)
import Control.Monad.Error.Class (throwError)
import Control.Monad.State (class MonadState, StateT, evalStateT, get, put)
import Control.Monad.Writer (class MonadTell, runWriter, runWriterT, tell)
Expand All @@ -23,18 +23,17 @@ import Data.Foldable (foldl, for_)
import Data.Generator (Imports, ModuleImport(..), ModuleImports, ModuleName, Imported, genCode, mkComment, newLine1)
import Data.Identity (Identity(..))
import Data.Lens ((^?))
import Data.Array as Array
import Data.Lens.Index (ix)
import Data.Map (Map, fromFoldableWith, insert, lookup, member, toAscUnfoldable)
import Data.Map (Map, fromFoldableWith, insert, lookup, member, toUnfoldable)
import Data.Maybe (Maybe(..), isNothing)
import Data.Monoid (mempty)
import Data.Newtype (un)
import Data.Record.Extra (showRecord)
import Data.StrMap as StrMap
import Data.Map as Map
import Data.String (Pattern(..), Replacement(..), joinWith, replaceAll, stripPrefix)
import Data.Traversable (for)
import Data.Tuple (Tuple(..))
import Node.Encoding (Encoding(UTF8))
import Node.FS.Aff (FS, readTextFile, writeTextFile, readdir, stat)
import Node.FS.Aff (readTextFile, writeTextFile, readdir, stat)
import Node.FS.Stats as Stats
import Node.FS.Sync.Mkdirp (mkdirp)
import Node.Path (FilePath, basenameWithoutExt, extname)
Expand Down Expand Up @@ -70,7 +69,7 @@ runImports = mergeImports >>> map runImport >>> newLine1 >>> ("import Prelude \n
runAcc <<< foldl f { types: mempty, imports: mempty }
where
runAcc :: ModuleImportsAcc -> Array String
runAcc acc = sort $ nub $ append acc.imports $ (toAscUnfoldable acc.types) >>= resolveCtrImports
runAcc acc = sort $ nub $ append acc.imports $ (toUnfoldable acc.types) >>= resolveCtrImports
resolveCtrImports :: Tuple String IsCtrInImports -> Array String
resolveCtrImports (Tuple typeName isCtrInImports) = case isCtrInImports of
CtrIsInImports -> []
Expand Down Expand Up @@ -98,29 +97,29 @@ runImports = mergeImports >>> map runImport >>> newLine1 >>> ("import Prelude \n
IOp a ->
acc {imports = acc.imports <> [ "(" <> a <> ")" ]}

-- NOTE this also sorts modules as we use toAscUnfoldable
-- NOTE this also sorts modules as we use toUnfoldable which returns ascending order result
mergeImports :: Imports -> Imports
mergeImports = fromFoldableWith append >>> toAscUnfoldable
mergeImports = fromFoldableWith append >>> toUnfoldable

generatePS :: forall e . GeneratorOptions -> Aff (fs :: FS, console :: CONSOLE | e) ABIErrors
generatePS :: GeneratorOptions -> Aff ABIErrors
generatePS os = do
let opts = os { pursDir = os.pursDir <> "/" <> replaceAll (Pattern ".") (Replacement "/") os.modulePrefix }
fs <- getAllJsonFiles opts.jsonDir
liftEff $ mkdirp opts.pursDir
liftEffect $ mkdirp opts.pursDir
case fs of
[] -> throwError <<< error $ "No abi json files found in directory: " <> opts.jsonDir
fs' -> do
errs <- join <$> for fs' \f -> do
let f' = genPSFileName opts f
Tuple _ errs <- runWriterT $ writeCodeFromAbi opts f f'
log if null errs
liftEffect $ log if null errs
then successCheck <> " contract module for " <> f <> " successfully written to " <> f'
else warningCheck <> " (" <> show (length errs) <> ") contract module for " <> f <> " written to " <> f'
pure errs
unless (null errs) do
log $ errorCheck <> " got " <> show (length errs) <> " error(s) during generation"
liftEffect $ log $ errorCheck <> " got " <> show (length errs) <> " error(s) during generation"
for_ errs \(ABIError err) ->
log $ errorCheck <> " while parsing abi type of object at index: " <> show err.idx <> " from: " <> err.abiPath <> " got error:\n " <> err.error
liftEffect $ log $ errorCheck <> " while parsing abi type of object at index: " <> show err.idx <> " from: " <> err.abiPath <> " got error:\n " <> err.error
pure errs
where
successCheck = withGraphics (foreground Green) $ ""
Expand All @@ -134,7 +133,7 @@ type ABIErrors = Array ABIError
newtype ABIError = ABIError { abiPath :: FilePath, idx :: Int, error :: String }

instance showABIError :: Show ABIError where
show (ABIError r) = "(ABIError " <> showRecord r <> ")"
show (ABIError r) = "(ABIError " <> show r <> ")"

generateCodeFromAbi :: GeneratorOptions -> Abi Identity -> FilePath -> String
generateCodeFromAbi opts (Abi abi) destFile =
Expand All @@ -143,8 +142,8 @@ generateCodeFromAbi opts (Abi abi) destFile =
# runImported opts destFile

-- | read in json abi and write the generated code to a destination file
writeCodeFromAbi :: forall e m
. MonadAff (fs :: FS, console :: CONSOLE | e) m
writeCodeFromAbi :: forall m
. MonadAff m
=> MonadTell ABIErrors m
=> GeneratorOptions
-> FilePath
Expand All @@ -166,8 +165,8 @@ maybeAnnotateArity :: Array AbiType -> Array AbiType
maybeAnnotateArity abi =
let
Tuple nonFuncAbi funcAbi = foldMap groupingFunc abi
nameToFunctions = StrMap.fromFoldableWith (<>) $ funcAbi <#> \fun@(SolidityFunction f) -> Tuple f.name [fun]
functionsWithArity = StrMap.values nameToFunctions >>= \fs -> if length fs > 1 then map go fs else fs
nameToFunctions = Map.fromFoldableWith (<>) $ funcAbi <#> \fun@(SolidityFunction f) -> Tuple f.name [fun]
functionsWithArity = Array.fromFoldable (Map.values nameToFunctions) >>= \fs -> if length fs > 1 then map go fs else fs
in
nonFuncAbi <> map AbiFunction functionsWithArity
where
Expand Down Expand Up @@ -199,8 +198,8 @@ genPSModuleStatement opts fp = comment <> "\n"

-- get all the "valid" directories rooted in a filepath
getAllDirectories
:: forall eff m.
MonadAff (fs :: FS | eff) m
:: forall m.
MonadAff m
=> MonadState FilePath m
=> m (Array FilePath)
getAllDirectories = do
Expand All @@ -211,8 +210,8 @@ getAllDirectories = do

-- determine whether or not a directory is valid (basically it's not dotted)
validateRootedDir
:: forall eff m.
MonadAff (fs :: FS | eff) m
:: forall m.
MonadAff m
=> FilePath -- prefix
-> FilePath -- dirname
-> m (Maybe FilePath)
Expand All @@ -229,8 +228,8 @@ validateRootedDir prefix dir = liftAff $ do

-- | get all files in a directory with a ".json" extension
getJsonFilesInDirectory
:: forall eff m.
MonadAff (fs :: FS | eff) m
:: forall m.
MonadAff m
=> MonadState FilePath m
=> m (Array FilePath)
getJsonFilesInDirectory = do
Expand All @@ -241,8 +240,8 @@ getJsonFilesInDirectory = do

-- | determine whether the file is a .json artifact
validateFile
:: forall eff m.
MonadAff (fs :: FS | eff) m
:: forall m.
MonadAff m
=> FilePath -- dir
-> FilePath -- filepath
-> m (Maybe FilePath)
Expand All @@ -258,8 +257,8 @@ validateFile dir f = liftAff $ do
else Nothing

getAllJsonFiles
:: forall eff m.
MonadAff (fs :: FS | eff) m
:: forall m.
MonadAff m
=> FilePath
-> m (Array FilePath)
getAllJsonFiles root = evalStateT getAllJsonFiles' root
Expand Down
11 changes: 6 additions & 5 deletions src/Data/Generator.purs
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,8 @@ import Data.List.Types (NonEmptyList(..)) as List
import Data.Maybe (Maybe(..))
import Data.Newtype (un)
import Data.NonEmpty ((:|))
import Data.String (drop, fromCharArray, joinWith, singleton, take, toCharArray, toLower, toUpper)
import Data.String.CodeUnits (fromCharArray, toCharArray, singleton)
import Data.String (drop, joinWith, take, toLower, toUpper)
import Data.Traversable (for)
import Data.Tuple (Tuple(..), uncurry)
import Network.Ethereum.Core.HexString (fromByteString)
Expand Down Expand Up @@ -221,7 +222,7 @@ funToHelperFunction isWhereClause fun@(SolidityFunction f) opts = do
let
var = if isWhereClause then "y" else "x"
constraints = []
quantifiedVars = ["e"]
quantifiedVars = []
stockVars =
if f.isConstructor
then [var <> "0", if isWhereClause then "bc'" else "bc"]
Expand Down Expand Up @@ -275,7 +276,7 @@ funToHelperFunction' fun@(SolidityFunction f) opts = do
pure ["TransactionOptions NoPay"]
let
constraints = []
quantifiedVars = ["e"]
quantifiedVars = []
stockVars = if f.isConstructor
then ["x0", "bc"]
else if f.constant
Expand Down Expand Up @@ -360,7 +361,7 @@ toReturnType constant outputs' = do
if not constant
then do
import' "Network.Ethereum.Web3.Types" [IType "HexString"]
pure "Web3 e HexString"
pure "Web3 HexString"
else do
import' "Network.Ethereum.Web3.Types" [IType "CallError"]
import' "Data.Either" [IType "Either"]
Expand All @@ -372,7 +373,7 @@ toReturnType constant outputs' = do
let tupleType = "Tuple" <> show (length outputs)
import' "Network.Ethereum.Web3.Solidity" [IType tupleType]
pure $ paren $ tupleType <> " " <> joinWith " " outputs
pure $ "Web3 e " <> paren ("Either CallError " <> out)
pure $ "Web3 " <> paren ("Either CallError " <> out)

instance codeHelperFunction :: Code HelperFunction where
genCode (CurriedHelperFunction h) opts =
Expand Down
Loading

0 comments on commit 294c307

Please sign in to comment.