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
|
2022-01-19 14:41:16 +03:00
|
|
|
import qualified MiniJuvix.Syntax.Concrete.Scoped.Pretty.Ansi as M
|
2022-02-03 12:24:43 +03:00
|
|
|
import MiniJuvix.Syntax.Concrete.Scoped.Pretty.Base (Options (..))
|
2022-01-19 14:49:07 +03:00
|
|
|
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
|
2022-02-18 19:47:41 +03:00
|
|
|
import MiniJuvix.Prelude hiding (Doc)
|
2022-01-18 14:25:42 +03:00
|
|
|
import Options.Applicative
|
|
|
|
import Options.Applicative.Help.Pretty
|
2022-02-05 01:14:06 +03:00
|
|
|
import Text.Show.Pretty hiding (Html)
|
|
|
|
import MiniJuvix.Syntax.Concrete.Scoped.Pretty.Html
|
|
|
|
import MiniJuvix.Syntax.Concrete.Scoped.Pretty.Base (defaultOptions)
|
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-02-05 01:14:06 +03:00
|
|
|
| Html HtmlOptions
|
2022-01-18 14:25:42 +03:00
|
|
|
|
2022-01-21 11:50:37 +03:00
|
|
|
data ScopeOptions = ScopeOptions
|
|
|
|
{ _scopeRootDir :: FilePath,
|
2022-02-17 21:28:19 +03:00
|
|
|
_scopeInputFiles :: [FilePath],
|
2022-02-03 12:24:43 +03:00
|
|
|
_scopeShowIds :: Bool,
|
|
|
|
_scopeInlineImports :: 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
|
|
|
}
|
|
|
|
|
2022-02-05 01:14:06 +03:00
|
|
|
data HtmlOptions = HtmlOptions
|
2022-02-05 21:08:03 +03:00
|
|
|
{ _htmlInputFile :: FilePath,
|
2022-02-06 01:15:42 +03:00
|
|
|
_htmlRecursive :: Bool,
|
|
|
|
_htmlTheme :: Theme
|
2022-02-05 01:14:06 +03:00
|
|
|
}
|
|
|
|
|
|
|
|
parseHtml :: Parser HtmlOptions
|
|
|
|
parseHtml = do
|
|
|
|
_htmlInputFile <-
|
|
|
|
argument
|
|
|
|
str
|
|
|
|
( metavar "MINIJUVIX_FILE"
|
|
|
|
<> help "Path to a .mjuvix file"
|
|
|
|
)
|
2022-02-05 21:08:03 +03:00
|
|
|
_htmlRecursive <-
|
|
|
|
switch
|
|
|
|
( long "recursive"
|
|
|
|
<> help "export imported modules recursively"
|
|
|
|
)
|
2022-02-06 01:15:42 +03:00
|
|
|
_htmlTheme <- option (eitherReader parseTheme)
|
|
|
|
( long "theme"
|
|
|
|
<> metavar "THEME"
|
|
|
|
<> value Nord
|
|
|
|
<> showDefault
|
|
|
|
<> help "selects a theme: ayu (light); nord (dark)"
|
|
|
|
)
|
2022-02-05 01:14:06 +03:00
|
|
|
pure HtmlOptions {..}
|
2022-02-06 01:15:42 +03:00
|
|
|
where
|
|
|
|
parseTheme :: String -> Either String Theme
|
|
|
|
parseTheme s = case s of
|
|
|
|
"nord" -> Right Nord
|
|
|
|
"ayu" -> Right Ayu
|
|
|
|
_ -> Left $ "unrecognised theme: " <> s
|
2022-02-05 01:14:06 +03:00
|
|
|
|
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"
|
|
|
|
)
|
2022-02-17 21:28:19 +03:00
|
|
|
_scopeInputFiles <-
|
|
|
|
some $ argument
|
2022-01-21 11:50:37 +03:00
|
|
|
str
|
2022-02-17 21:28:19 +03:00
|
|
|
( metavar "MINIJUVIX_FILE(s)"
|
|
|
|
<> help "Path to one ore more .mjuvix files"
|
2022-01-21 11:50:37 +03:00
|
|
|
)
|
|
|
|
_scopeShowIds <-
|
|
|
|
switch
|
|
|
|
( long "show-name-ids"
|
|
|
|
<> help "Show the unique number of each identifier"
|
|
|
|
)
|
2022-02-03 12:24:43 +03:00
|
|
|
_scopeInlineImports <-
|
|
|
|
switch
|
|
|
|
( long "inline-imports"
|
|
|
|
<> help "Show the code of imported modules next to the import statement"
|
|
|
|
)
|
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,
|
2022-02-05 01:14:06 +03:00
|
|
|
commandScope,
|
|
|
|
commandHtml
|
2022-01-21 11:50:37 +03:00
|
|
|
]
|
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")
|
|
|
|
|
2022-02-05 01:14:06 +03:00
|
|
|
commandHtml :: Mod CommandFields Command
|
|
|
|
commandHtml = command "html" minfo
|
|
|
|
where
|
|
|
|
minfo :: ParserInfo Command
|
|
|
|
minfo =
|
|
|
|
info
|
|
|
|
(Html <$> parseHtml)
|
|
|
|
(progDesc "Generate html for a .mjuvix file")
|
2022-01-21 11:50:37 +03:00
|
|
|
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
|
|
|
|
2022-01-19 14:49:07 +03:00
|
|
|
mkPrettyOptions :: ScopeOptions -> M.Options
|
2022-01-21 11:50:37 +03:00
|
|
|
mkPrettyOptions ScopeOptions {..} =
|
|
|
|
M.defaultOptions
|
2022-02-03 12:24:43 +03:00
|
|
|
{ _optShowNameId = _scopeShowIds,
|
|
|
|
_optInlineImports = _scopeInlineImports
|
2022-01-21 11:50:37 +03:00
|
|
|
}
|
2022-01-19 14:49:07 +03:00
|
|
|
|
2022-01-20 14:50:01 +03:00
|
|
|
parseModuleIO :: FilePath -> IO (M.Module 'M.Parsed 'M.ModuleTop)
|
|
|
|
parseModuleIO = fromRightIO id . M.runModuleParserIO
|
|
|
|
|
2022-02-11 21:12:48 +03:00
|
|
|
fromRightIO' :: (e -> IO ()) -> IO (Either e r) -> IO r
|
|
|
|
fromRightIO' pp = do
|
|
|
|
eitherM ifLeft return
|
|
|
|
where
|
|
|
|
ifLeft e = pp e >> exitFailure
|
|
|
|
|
2022-01-20 14:50:01 +03:00
|
|
|
fromRightIO :: (e -> Text) -> IO (Either e r) -> IO r
|
2022-02-11 21:12:48 +03:00
|
|
|
fromRightIO pp = fromRightIO' (putStrLn . pp)
|
2022-01-20 14:50:01 +03:00
|
|
|
|
2022-01-18 14:25:42 +03:00
|
|
|
go :: Command -> IO ()
|
|
|
|
go c = case c of
|
2022-01-19 14:49:07 +03:00
|
|
|
Scope opts@ScopeOptions {..} -> do
|
2022-02-03 02:01:40 +03:00
|
|
|
root <- getCurrentDirectory
|
2022-02-17 21:28:19 +03:00
|
|
|
forM_ _scopeInputFiles $ \scopeInputFile -> do
|
|
|
|
m <- parseModuleIO scopeInputFile
|
2022-02-18 19:47:41 +03:00
|
|
|
s <- fromRightIO' printErrorAnsi $ M.scopeCheck1IO root m
|
2022-02-17 21:28:19 +03:00
|
|
|
M.printPrettyCode (mkPrettyOptions opts) s
|
2022-01-20 14:50:01 +03:00
|
|
|
Parse ParseOptions {..} -> do
|
|
|
|
m <- parseModuleIO _parseInputFile
|
|
|
|
if _parseNoPrettyShow then print m else pPrint m
|
2022-02-05 01:14:06 +03:00
|
|
|
Html HtmlOptions {..} -> do
|
|
|
|
root <- getCurrentDirectory
|
|
|
|
m <- parseModuleIO _htmlInputFile
|
2022-02-18 19:47:41 +03:00
|
|
|
s <- fromRightIO' printErrorAnsi $ M.scopeCheck1IO root m
|
2022-02-06 01:15:42 +03:00
|
|
|
genHtml defaultOptions _htmlRecursive _htmlTheme s
|
2022-01-20 14:50:01 +03:00
|
|
|
|
2022-01-18 14:25:42 +03:00
|
|
|
main :: IO ()
|
|
|
|
main = execParser descr >>= go
|