-
Notifications
You must be signed in to change notification settings - Fork 0
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
feature: support parse single file and print its AST content (#5)
* move the parser.hs under AST to make the hierachy look better
- Loading branch information
1 parent
343a781
commit 9ee6917
Showing
19 changed files
with
308 additions
and
55 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
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) |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
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" |
Oops, something went wrong.