1
1
mirror of https://github.com/anoma/juvix.git synced 2024-12-15 01:52:11 +03:00
juvix/app/Main.hs

139 lines
3.5 KiB
Haskell
Raw Normal View History

2022-01-18 14:25:42 +03:00
{-# LANGUAGE ApplicativeDo #-}
2022-01-21 11:50:37 +03:00
2022-01-18 14:25:42 +03:00
module Main (main) where
2022-01-21 11:50:37 +03:00
import Control.Monad.Extra
2022-01-20 14:50:01 +03:00
import qualified MiniJuvix.Syntax.Concrete.Language as M
2022-01-21 11:50:37 +03:00
import qualified MiniJuvix.Syntax.Concrete.Parser as M
import qualified MiniJuvix.Syntax.Concrete.Scoped.Pretty.Ansi as M
2022-01-21 11:50:37 +03:00
import MiniJuvix.Syntax.Concrete.Scoped.Pretty.Base (Options (_optShowNameId))
import qualified MiniJuvix.Syntax.Concrete.Scoped.Pretty.Base as M
2022-01-21 11:50:37 +03:00
import qualified MiniJuvix.Syntax.Concrete.Scoped.Scoper as M
import MiniJuvix.Utils.Prelude
2022-01-18 14:25:42 +03:00
import Options.Applicative
import Options.Applicative.Help.Pretty
2022-01-21 11:50:37 +03:00
import System.IO.Error
2022-01-20 14:50:01 +03:00
import Text.Show.Pretty
2022-01-18 14:25:42 +03:00
2022-01-21 11:50:37 +03:00
data Command
= Scope ScopeOptions
2022-01-18 14:25:42 +03:00
| Parse ParseOptions
2022-01-21 11:50:37 +03:00
data ScopeOptions = ScopeOptions
{ _scopeRootDir :: FilePath,
_scopeInputFile :: FilePath,
_scopeShowIds :: Bool
2022-01-18 14:25:42 +03:00
}
2022-01-21 11:50:37 +03:00
data ParseOptions = ParseOptions
{ _parseInputFile :: FilePath,
_parseNoPrettyShow :: Bool
2022-01-20 14:50:01 +03:00
}
parseParse :: Parser ParseOptions
parseParse = do
2022-01-21 11:50:37 +03:00
_parseInputFile <-
argument
str
( metavar "MINIJUVIX_FILE"
<> help "Path to a .mjuvix file"
)
_parseNoPrettyShow <-
switch
( long "no-pretty-show"
<> help "Disable formatting of the Haskell AST"
)
2022-01-20 14:50:01 +03:00
pure ParseOptions {..}
2022-01-18 14:25:42 +03:00
parseScope :: Parser ScopeOptions
parseScope = do
2022-01-21 11:50:37 +03:00
_scopeRootDir <-
strOption
( long "rootDir"
<> short 'd'
<> metavar "DIR"
<> value "."
<> showDefault
<> help "Root directory"
)
_scopeInputFile <-
argument
str
( metavar "MINIJUVIX_FILE"
<> help "Path to a .mjuvix file"
)
_scopeShowIds <-
switch
( long "show-name-ids"
<> help "Show the unique number of each identifier"
)
2022-01-18 14:25:42 +03:00
pure ScopeOptions {..}
descr :: ParserInfo Command
2022-01-21 11:50:37 +03:00
descr =
info
(parseCommand <**> helper)
( fullDesc
2022-01-18 14:25:42 +03:00
<> progDesc "The MiniJuvix compiler."
2022-01-20 14:50:01 +03:00
<> headerDoc (Just headDoc)
2022-01-18 14:25:42 +03:00
<> footerDoc (Just foot)
2022-01-21 11:50:37 +03:00
)
2022-01-18 14:25:42 +03:00
where
2022-01-21 11:50:37 +03:00
headDoc :: Doc
headDoc = dullblue $ bold $ underline "MiniJuvix help"
foot :: Doc
foot = bold "maintainers: " <> "jan@heliax.dev; jonathan@heliax.dev"
2022-01-18 14:25:42 +03:00
parseCommand :: Parser Command
2022-01-21 11:50:37 +03:00
parseCommand =
hsubparser $
mconcat
[ commandParse,
commandScope
]
2022-01-20 14:50:01 +03:00
where
2022-01-21 11:50:37 +03:00
commandParse :: Mod CommandFields Command
commandParse = command "parse" minfo
where
minfo :: ParserInfo Command
minfo =
info
(Parse <$> parseParse)
(progDesc "Parse a .mjuvix file")
commandScope :: Mod CommandFields Command
commandScope = command "scope" minfo
where
minfo :: ParserInfo Command
minfo =
info
(Scope <$> parseScope)
(progDesc "Parse and scope a .mjuvix file")
2022-01-18 14:25:42 +03:00
mkPrettyOptions :: ScopeOptions -> M.Options
2022-01-21 11:50:37 +03:00
mkPrettyOptions ScopeOptions {..} =
M.defaultOptions
{ _optShowNameId = _scopeShowIds
}
2022-01-20 14:50:01 +03:00
parseModuleIO :: FilePath -> IO (M.Module 'M.Parsed 'M.ModuleTop)
parseModuleIO = fromRightIO id . M.runModuleParserIO
fromRightIO :: (e -> Text) -> IO (Either e r) -> IO r
fromRightIO pp = eitherM (ioError . userError . unpack . pp) return
2022-01-18 14:25:42 +03:00
go :: Command -> IO ()
go c = case c of
Scope opts@ScopeOptions {..} -> do
2022-02-03 02:01:40 +03:00
root <- getCurrentDirectory
2022-01-20 14:50:01 +03:00
m <- parseModuleIO _scopeInputFile
2022-02-03 02:01:40 +03:00
s <- fromRightIO show $ M.scopeCheck1 root m
2022-01-20 14:50:01 +03:00
M.printTopModule (mkPrettyOptions opts) s
Parse ParseOptions {..} -> do
m <- parseModuleIO _parseInputFile
if _parseNoPrettyShow then print m else pPrint m
2022-01-18 14:25:42 +03:00
main :: IO ()
main = execParser descr >>= go