Skip to content

Commit

Permalink
chore: use my hackage lib instead of git submodule
Browse files Browse the repository at this point in the history
* try lens a bit(when we start to analyze the structures from SolFile
  data, it's very helpful)
* print contracts inside a function instead of the whole AST
  • Loading branch information
xieyuschen committed Aug 23, 2024
1 parent 9ee6917 commit 649fafd
Show file tree
Hide file tree
Showing 7 changed files with 24 additions and 42 deletions.
3 changes: 0 additions & 3 deletions .gitmodules

This file was deleted.

17 changes: 2 additions & 15 deletions slinter.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -7,19 +7,6 @@ author: xieyuschen
maintainer: xieyuschen@gmail.com
build-type: Simple
extra-doc-files: CHANGELOG.md

-- todo: remove this after I upload my forked version to hackage
-- https://github.com/xieyuschen/x-sum-type-boilerplate
library x-sum-type-boilerplate
exposed-modules:
SumTypes.TH
hs-source-dirs:
src/Lib/x-sum-type-boilerplate/library
ghc-options: -Wall
build-depends:
base >= 4.1 && < 4.20
, template-haskell
default-language: Haskell2010

common warnings
ghc-options: -Wall
Expand All @@ -35,9 +22,9 @@ common common-depends
bytestring,
hspec,
parsec ^>=3.1.16.1,
-- force to use my forked version
x-sum-type-boilerplate,
optparse-applicative
optparse-applicative,
lens

library internallib
import: common-depends
Expand Down
9 changes: 6 additions & 3 deletions src/Lib/AST/Model.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,9 +4,10 @@

module Lib.AST.Model where

import Control.Lens
import Data.Text (Text)
import Lib.AST.Parser (SemVer)
import SumTypes.TH
import SumTypesX.TH

keywordLogicalOr :: Text
keywordLogicalOr = "||"
Expand Down Expand Up @@ -81,8 +82,8 @@ data Mapping = Mapping
deriving (Show, Eq)

data UserDefinedValueTypeDefinition = UserDefinedValueTypeDefinition
{ userDefinedValueTypeName :: Text,
userDefinedValueElemType :: SType
{ _userDefinedValueTypeName :: Text,
_userDefinedValueElemType :: SType
}
deriving (Show, Eq)

Expand Down Expand Up @@ -629,6 +630,8 @@ data SolFile = SolFile
}
deriving (Show, Eq)

makeLenses ''UserDefinedValueTypeDefinition

constructSumType
"SolFileSum"
defaultSumTypeOptions
Expand Down
14 changes: 2 additions & 12 deletions src/Lib/AST/Type.hs
Original file line number Diff line number Diff line change
Expand Up @@ -139,12 +139,7 @@ pTypeDefinition =
pUserDefinedValueTypeDefinition :: Parser UserDefinedValueTypeDefinition
pUserDefinedValueTypeDefinition = do
liftA2
( \ident tp ->
UserDefinedValueTypeDefinition
{ userDefinedValueTypeName = ident,
userDefinedValueElemType = tp
}
)
UserDefinedValueTypeDefinition
( pManySpaces
*> pOneKeyword "type"
*> pMany1Spaces
Expand All @@ -157,12 +152,7 @@ pUserDefinedValueTypeDefinition = do
pTypeStruct :: Parser Structure
pTypeStruct =
liftA2
( \ident pairs ->
Structure
{ structName = ident,
structFields = pairs
}
)
Structure
( pManySpaces
*> pOneKeyword "struct"
*> pMany1Spaces
Expand Down
8 changes: 7 additions & 1 deletion src/Lib/Command.hs
Original file line number Diff line number Diff line change
@@ -1,9 +1,11 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}

module Lib.Command (executeFile, executeProject) where

import Data.Text (Text, pack, unpack)
import Lib.AST.File (pWholeSolFile)
import Lib.AST.Model (ContractDefinition (contractName), SolFile (SolFile, solContracts, solFunctions))
import Lib.AST.Parser (runSParser)
import System.Directory (canonicalizePath, doesDirectoryExist, doesFileExist)
import System.Directory.Internal.Prelude (exitFailure)
Expand All @@ -26,7 +28,7 @@ executeFile filepath = do
fileContent <- pack <$> readFile ensuredPath
let (re, _) = runSParser (pWholeSolFile ensuredPath) fileContent
case re of
Right file -> print file
Right file -> checkFile file
Left err -> print err >> exitFailure
return ()

Expand All @@ -35,3 +37,7 @@ executeProject folderPath = do
ei <- ensureExist folderPath Folder doesDirectoryExist
ensuredPath <- either (\err -> print err >> exitFailure) return ei
print "unsupported faeture for a project"

checkFile :: SolFile -> IO ()
checkFile SolFile {..} = do
foldMap (\c -> putStr "contract definition: " >> (print . contractName) c) solContracts
1 change: 0 additions & 1 deletion src/Lib/x-sum-type-boilerplate
Submodule x-sum-type-boilerplate deleted from 497154
14 changes: 7 additions & 7 deletions tests/Lib/AST/TypeSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,7 @@ import Lib.AST.Model
),
STypeEnum (STypeEnum, eelems, ename),
Structure (Structure, structFields, structName),
UserDefinedValueTypeDefinition (UserDefinedValueTypeDefinition, userDefinedValueElemType, userDefinedValueTypeName),
UserDefinedValueTypeDefinition (UserDefinedValueTypeDefinition, _userDefinedValueElemType, _userDefinedValueTypeName),
)
import Lib.AST.Type
( pType,
Expand Down Expand Up @@ -305,16 +305,16 @@ parseTypeAliasSpec = do
[ ( "type Alias1 is uint256;",
Right $
UserDefinedValueTypeDefinition
{ userDefinedValueTypeName = "Alias1",
userDefinedValueElemType = STypeUint 256
{ _userDefinedValueTypeName = "Alias1",
_userDefinedValueElemType = STypeUint 256
},
""
),
( "type _Ab is address;",
Right $
UserDefinedValueTypeDefinition
{ userDefinedValueTypeName = "_Ab",
userDefinedValueElemType = STypeAddress
{ _userDefinedValueTypeName = "_Ab",
_userDefinedValueElemType = STypeAddress
},
""
),
Expand Down Expand Up @@ -406,8 +406,8 @@ parseTypeDifinitionSpec = do
Right $
STypeAlias $
UserDefinedValueTypeDefinition
{ userDefinedValueTypeName = "Alias1",
userDefinedValueElemType = STypeUint 256
{ _userDefinedValueTypeName = "Alias1",
_userDefinedValueElemType = STypeUint 256
},
""
)
Expand Down

0 comments on commit 649fafd

Please sign in to comment.