Skip to content

Commit

Permalink
CLI
Browse files Browse the repository at this point in the history
  • Loading branch information
lukaszcz committed Apr 24, 2024
1 parent eb981dc commit 3af8bb4
Show file tree
Hide file tree
Showing 7 changed files with 40 additions and 13 deletions.
19 changes: 17 additions & 2 deletions app/Commands/Isabelle.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,7 @@ module Commands.Isabelle where

import Commands.Base
import Commands.Isabelle.Options
import Data.Text.IO qualified as Text
import Juvix.Compiler.Backend.Isabelle.Data.Result
import Juvix.Compiler.Backend.Isabelle.Pretty

Expand All @@ -13,5 +14,19 @@ runCommand opts = do
let inputFile = opts ^. isabelleInputFile
res <- runPipelineNoOptions inputFile upToIsabelle
let thy = res ^. resultTheory
renderStdOut (ppOutDefault thy)
putStrLn ""
outputDir <- fromAppPathDir (opts ^. isabelleOutputDir)
if
| opts ^. isabelleStdout -> do
renderStdOut (ppOutDefault thy)
putStrLn ""
| otherwise -> do
ensureDir outputDir
let file :: Path Rel File
file =
relFile
( unpack (res ^. resultModuleId . moduleIdPath)
<.> isabelleFileExt
)
absPath :: Path Abs File
absPath = outputDir <//> file
liftIO $ Text.writeFile (toFilePath absPath) (ppPrint thy)
12 changes: 6 additions & 6 deletions app/Commands/Isabelle/Options.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,25 +5,25 @@ import CommonOptions
data IsabelleOptions = IsabelleOptions
{ _isabelleInputFile :: Maybe (AppPath File),
_isabelleOutputDir :: AppPath Dir,
_isabelleRecursive :: Bool
_isabelleStdout :: Bool
}
deriving stock (Data)

makeLenses ''IsabelleOptions

parseIsabelle :: Parser IsabelleOptions
parseIsabelle = do
_isabelleRecursive <-
switch
( long "recursive"
<> help "Process imported modules recursively"
)
_isabelleOutputDir <-
parseGenericOutputDir
( value "isabelle"
<> showDefault
<> help "Isabelle/HOL output directory"
<> action "directory"
)
_isabelleStdout <-
switch
( long "stdout"
<> help "Write the output to stdout instead of a file"
)
_isabelleInputFile <- optional (parseInputFile FileExtJuvix)
pure IsabelleOptions {..}
3 changes: 2 additions & 1 deletion src/Juvix/Compiler/Backend/Isabelle/Data/Result.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,8 @@ module Juvix.Compiler.Backend.Isabelle.Data.Result where
import Juvix.Compiler.Backend.Isabelle.Language

data Result = Result
{ _resultTheory :: Theory
{ _resultTheory :: Theory,
_resultModuleId :: ModuleId
}

makeLenses ''Result
3 changes: 1 addition & 2 deletions src/Juvix/Compiler/Backend/Isabelle/Pretty/Base.hs
Original file line number Diff line number Diff line change
Expand Up @@ -110,14 +110,13 @@ instance PrettyCode RecordField where
instance PrettyCode Theory where
ppCode Theory {..} = do
n <- ppCode _theoryName
imps <- mapM ppCode _theoryImports
stmts <- mapM ppCode _theoryStatements
return $
kwTheory
<+> n
<> line
<> kwImports
<+> hsep ("Main" : imps)
<+> "Main"
<> line
<> kwBegin
<> line
Expand Down
7 changes: 6 additions & 1 deletion src/Juvix/Compiler/Backend/Isabelle/Translation/FromTyped.hs
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,12 @@ fromInternal Internal.InternalTypedResult {..} = do
go table _resultModule
where
go :: Internal.InfoTable -> Internal.Module -> Sem r Result
go tab md = return $ Result $ goModule tab md
go tab md =
return $
Result
{ _resultTheory = goModule tab md,
_resultModuleId = md ^. Internal.moduleId
}

goModule :: Internal.InfoTable -> Internal.Module -> Theory
goModule infoTable Internal.Module {..} =
Expand Down
3 changes: 3 additions & 0 deletions src/Juvix/Data/FileExt.hs
Original file line number Diff line number Diff line change
Expand Up @@ -79,6 +79,9 @@ htmlFileExt = ".html"
markdownFileExt :: (IsString a) => a
markdownFileExt = ".md"

isabelleFileExt :: (IsString a) => a
isabelleFileExt = ".thy"

cFileExt :: (IsString a) => a
cFileExt = ".c"

Expand Down
6 changes: 5 additions & 1 deletion src/Juvix/Prelude/Prepath.hs
Original file line number Diff line number Diff line change
Expand Up @@ -19,15 +19,19 @@ import Juvix.Prelude.Pretty
import System.Directory (getHomeDirectory)
import System.Directory qualified as System
import System.Environment
import Prelude (show)

-- | A file/directory path that may contain environmental variables
newtype Prepath d = Prepath
{ _prepath :: String
}
deriving stock (Show, Eq, Data, Generic)
deriving stock (Eq, Data, Generic)

makeLenses ''Prepath

instance Show (Prepath d) where
show Prepath {..} = _prepath

type PrepathParts = NonEmpty PrepathPart

data PrepathPart
Expand Down

0 comments on commit 3af8bb4

Please sign in to comment.