Skip to content

Commit

Permalink
feature: support parse single file and print its AST content (#5)
Browse files Browse the repository at this point in the history
* move the parser.hs under AST to make the hierachy look better
  • Loading branch information
xieyuschen authored Aug 20, 2024
1 parent 343a781 commit 9ee6917
Show file tree
Hide file tree
Showing 19 changed files with 308 additions and 55 deletions.
8 changes: 5 additions & 3 deletions slinter.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -36,7 +36,8 @@ common common-depends
hspec,
parsec ^>=3.1.16.1,
-- force to use my forked version
x-sum-type-boilerplate
x-sum-type-boilerplate,
optparse-applicative

library internallib
import: common-depends
Expand All @@ -51,7 +52,8 @@ library internallib
Lib.AST.Util,
Lib.AST.Oper,
Lib.AST.Definition,
Lib.Parser
Lib.AST.Parser,
Lib.Command
hs-source-dirs: src

executable slinter
Expand Down Expand Up @@ -86,6 +88,6 @@ test-suite tests
Lib.AST.UtilSpec,
Lib.AST.DefinitionSpec,
Lib.TestCommon,
Lib.ParserSpec
Lib.AST.ParserSpec
build-tool-depends: hspec-discover:hspec-discover == 2.*
ghc-options: -fforce-recomp -Wall -Werror
62 changes: 60 additions & 2 deletions src/App/Main.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,65 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}

module Main where
import Data.Maybe (fromJust, isJust, isNothing)
import Data.Text (Text)
import Lib.Command (executeFile, executeProject)
import Options.Applicative
import System.Exit (exitFailure)

data Flags = Flags
{ filePath :: Maybe Text,
projectPath :: Maybe Text
}

type ErrMsg = Text

validateFlags :: Flags -> Maybe ErrMsg
validateFlags Flags {..}
| isNothing filePath && isNothing projectPath =
Just "Error: Either --file or --project must be specified."
| isJust filePath && isJust projectPath =
Just "Error: Either --file or --project must be specified."
| otherwise = Nothing

flagsParser :: Parser Flags
flagsParser =
Flags
<$> optional
( strOption
( long "file"
<> short 'f'
<> metavar "TARGET"
<> help "the relative/absolute path of the file to lint"
)
)
<*> optional
( strOption
( long "project"
<> short 'p'
<> metavar "TARGET"
<> help "the relative/absolute path of the folder to lint all files with sol extension"
)
)

opts :: ParserInfo Flags
opts =
info
(flagsParser <**> helper)
( fullDesc
<> progDesc "please specify the TARGET via flag for slinter to lint"
<> header "slinter: a solidity linter to ensure a better quality"
)

main :: IO ()
main = do
putStrLn "hello hlinter"
flags <- execParser opts
let eFlags = validateFlags flags
_ <- maybe (return ()) (\err -> print err >> exitFailure) eFlags
execute flags

execute :: Flags -> IO ()
execute Flags {..}
| isJust filePath = executeFile (fromJust filePath)
| isJust projectPath = executeProject (fromJust projectPath)
| otherwise = print ("unreachable" :: Text)
2 changes: 1 addition & 1 deletion src/Lib/AST/Definition.hs
Original file line number Diff line number Diff line change
Expand Up @@ -44,11 +44,11 @@ import Lib.AST.Model
rightParenthesis,
semicolon,
)
import Lib.AST.Parser (Parser, pIdentifier, pMany1Spaces, pManySpaces, pNumber, pOneKeyword)
import Lib.AST.Pragma (pComment, pUsingDirective)
import Lib.AST.Stat (pState, pStateVariable)
import Lib.AST.Type (pInt, pType, pTypeEnum, pTypeStruct, pUserDefinedValueTypeDefinition)
import Lib.AST.Util
import Lib.Parser (Parser, pIdentifier, pMany1Spaces, pManySpaces, pNumber, pOneKeyword)
import Text.Parsec (between, char, many, optionMaybe, sepBy, sepEndBy, try, (<|>))

pConstructorMutability :: Parser ConstructorMutability
Expand Down
2 changes: 1 addition & 1 deletion src/Lib/AST/Expr.hs
Original file line number Diff line number Diff line change
Expand Up @@ -58,7 +58,7 @@ import Lib.AST.Oper
pOpRankLast,
pOperator,
)
import Lib.Parser
import Lib.AST.Parser
( Parser,
pBool,
pIdentifier,
Expand Down
37 changes: 19 additions & 18 deletions src/Lib/AST/File.hs
Original file line number Diff line number Diff line change
@@ -1,16 +1,17 @@
module Lib.AST.File where

import Data.Text (Text)
import Lib.AST.Definition
import Lib.AST.Function
import Lib.AST.Model (SolFile (..), SolFileSum (..))
import Lib.AST.Model (SolFile (..), SolFileSum (..), StateVariable (svConstrains), StateVariableConstrain (SVarConstant))
import Lib.AST.Parser
import Lib.AST.Pragma
import Lib.AST.Stat (pStateVariable)
import Lib.AST.Type (pTypeEnum, pTypeStruct, pUserDefinedValueTypeDefinition)
import Lib.Parser
import Text.Parsec (sepEndBy, try, (<|>))

pWholeSolFile :: Parser SolFile
pWholeSolFile = do
pWholeSolFile :: FilePath -> Parser SolFile
pWholeSolFile filename = do
spdx <- pManySpaces *> pSPDXComment
pragma <- pManySpaces *> pPragma

Expand All @@ -33,21 +34,21 @@ pWholeSolFile = do
pManySpaces

return $
-- todo: finish me with the real data
SolFile
{ solUsingDirectives = [],
solUserDefineValueType = [],
solStructs = [],
{ solUsingDirectives = [v | SolFileSumUsingDirective v <- all],
solUserDefineValueType = [v | SolFileSumUserDefinedValueTypeDefinition v <- all],
solStructs = [v | SolFileSumStructure v <- all],
solSpdxLicense = spdx,
solPragma = pragma,
solLibraries = [],
solInterfaces = [],
solImprotDirectives = [],
solFunctions = [],
solFileName = [],
solEvents = [],
solErrors = [],
solEnums = [],
solContracts = [],
solConstantVars = []
solLibraries = [v | SolFileSumLibraryDefinition v <- all],
solInterfaces = [v | SolFileSumInterfaceDefinition v <- all],
solImprotDirectives = [v | SolFileSumImportDirective v <- all],
solFunctions = [v | SolFileSumFunctionDefinition v <- all],
solFileName = filename,
solEvents = [v | SolFileSumEventDefinition v <- all],
solErrors = [v | SolFileSumErrorDefinition v <- all],
solEnums = [v | SolFileSumSTypeEnum v <- all],
solContracts = [v | SolFileSumContractDefinition v <- all],
solStateVars = [v | SolFileSumStateVariable v <- all],
solConstantVars = [v | SolFileSumStateVariable v <- all, SVarConstant `elem` svConstrains v]
}
2 changes: 1 addition & 1 deletion src/Lib/AST/Function.hs
Original file line number Diff line number Diff line change
Expand Up @@ -52,11 +52,11 @@ import Lib.AST.Model
rightParenthesis,
semicolon,
)
import Lib.AST.Parser
import Lib.AST.Pragma (pComment)
import Lib.AST.Stat (pState)
import Lib.AST.Type (pType)
import Lib.AST.Util
import Lib.Parser
import Text.Parsec

pFunctionDefinition :: Parser FunctionDefinition
Expand Down
5 changes: 3 additions & 2 deletions src/Lib/AST/Model.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@
module Lib.AST.Model where

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

keywordLogicalOr :: Text
Expand Down Expand Up @@ -610,7 +610,7 @@ deriving instance Eq CBFSSum
-- SolFile stands all definitions and the filename of a sol file,
-- which typically ends with file extension `.sol`
data SolFile = SolFile
{ solFileName :: String,
{ solFileName :: FilePath,
solPragma :: Pragma,
solSpdxLicense :: SPDXComment,
solImprotDirectives :: [ImportDirective],
Expand All @@ -620,6 +620,7 @@ data SolFile = SolFile
solLibraries :: [LibraryDefinition],
solFunctions :: [FunctionDefinition],
solConstantVars :: [StateVariable],
solStateVars :: [StateVariable],
solStructs :: [Structure],
solEnums :: [STypeEnum],
solUserDefineValueType :: [UserDefinedValueTypeDefinition],
Expand Down
2 changes: 1 addition & 1 deletion src/Lib/AST/Oper.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ import Control.Monad.State (guard)
import Data.Text (Text)
import qualified Data.Text as T
import Lib.AST.Model (Operator (..))
import Lib.Parser (Parser, pManySpaces)
import Lib.AST.Parser (Parser, pManySpaces)
import Text.Parsec (getInput, setInput, try, (<|>))

pOperator3Char :: Parser Operator
Expand Down
2 changes: 1 addition & 1 deletion src/Lib/Parser.hs → src/Lib/AST/Parser.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@
{-# LANGUAGE DoAndIfThenElse #-}
{-# LANGUAGE OverloadedStrings #-}

module Lib.Parser where
module Lib.AST.Parser where

import Control.Monad (guard)
import Data.Char (chr)
Expand Down
6 changes: 3 additions & 3 deletions src/Lib/AST/Pragma.hs
Original file line number Diff line number Diff line change
Expand Up @@ -55,9 +55,7 @@ import Lib.AST.Model
semicolon,
)
import Lib.AST.Oper (pOperator)
import Lib.AST.Type (pType)
import Lib.AST.Util
import Lib.Parser
import Lib.AST.Parser
( Parser,
pIdentifier,
pMany1Spaces,
Expand All @@ -67,6 +65,8 @@ import Lib.Parser
pSemVer,
pString,
)
import Lib.AST.Type (pType)
import Lib.AST.Util
import Text.Parsec

-- // SPDX-License-Identifier: MIT
Expand Down
14 changes: 7 additions & 7 deletions src/Lib/AST/Stat.hs
Original file line number Diff line number Diff line change
Expand Up @@ -49,20 +49,20 @@ import Lib.AST.Model
rightParenthesis,
semicolon,
)
import Lib.AST.Parser
( Parser,
pIdentifier,
pMany1Spaces,
pManySpaces,
pOneKeyword,
)
import Lib.AST.Pragma (pComment)
import Lib.AST.Type (pType)
import Lib.AST.Util
( pFunctionArgs,
pLocationModifier,
pStateVariableConstrain,
)
import Lib.Parser
( Parser,
pIdentifier,
pMany1Spaces,
pManySpaces,
pOneKeyword,
)
import Text.Parsec
( between,
getInput,
Expand Down
2 changes: 1 addition & 1 deletion src/Lib/AST/Type.hs
Original file line number Diff line number Diff line change
Expand Up @@ -55,7 +55,7 @@ import Lib.AST.Model
rightSquareBracket,
semicolon,
)
import Lib.Parser
import Lib.AST.Parser
( Parser,
isUnderscore,
pIdentifier,
Expand Down
2 changes: 1 addition & 1 deletion src/Lib/AST/Util.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,8 +22,8 @@ import Data.Text (Text)
import qualified Data.Text as T
import Debug.Trace
import Lib.AST.Model
import Lib.AST.Parser
import Lib.AST.Type
import Lib.Parser
import Text.Parsec

pLocationModifier :: Parser DataLocation
Expand Down
37 changes: 37 additions & 0 deletions src/Lib/Command.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,37 @@
{-# LANGUAGE OverloadedStrings #-}

module Lib.Command (executeFile, executeProject) where

import Data.Text (Text, pack, unpack)
import Lib.AST.File (pWholeSolFile)
import Lib.AST.Parser (runSParser)
import System.Directory (canonicalizePath, doesDirectoryExist, doesFileExist)
import System.Directory.Internal.Prelude (exitFailure)
import Text.Printf (printf)

data ProvidedPath = File | Folder deriving (Show)

ensureExist :: Text -> ProvidedPath -> (FilePath -> IO Bool) -> IO (Either Text FilePath)
ensureExist path p exist = do
abs <- canonicalizePath $ unpack path
fileExists <- exist abs
if fileExists
then return $ Right abs
else return $ Left (pack $ printf "%s %s doesn't exist" (show p) abs)

executeFile :: Text -> IO ()
executeFile filepath = do
ei <- ensureExist filepath File doesFileExist
ensuredPath <- either (\err -> print err >> exitFailure) return ei
fileContent <- pack <$> readFile ensuredPath
let (re, _) = runSParser (pWholeSolFile ensuredPath) fileContent
case re of
Right file -> print file
Left err -> print err >> exitFailure
return ()

executeProject :: Text -> IO ()
executeProject folderPath = do
ei <- ensureExist folderPath Folder doesDirectoryExist
ensuredPath <- either (\err -> print err >> exitFailure) return ei
print "unsupported faeture for a project"
Loading

0 comments on commit 9ee6917

Please sign in to comment.