Skip to content

Commit

Permalink
Merge pull request #92 from objectionary/CLI-output-path
Browse files Browse the repository at this point in the history
CLI outPath support
  • Loading branch information
fizruk authored Feb 6, 2024
2 parents 9cda60b + c5a71b6 commit 65f4db2
Showing 1 changed file with 14 additions and 11 deletions.
25 changes: 14 additions & 11 deletions eo-phi-normalizer/app/Main.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,5 @@
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedRecordDot #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
Expand All @@ -16,6 +15,7 @@ import Language.EO.Phi (Object (Formation), Program (Program), defaultMain, pars
import Language.EO.Phi.Rules.Common (Context (..), applyRules, applyRulesChain)
import Language.EO.Phi.Rules.Yaml
import Options.Generic
import System.IO (IOMode (WriteMode), hClose, hPutStr, hPutStrLn, openFile, stdout)

data CLINamedParams = CLINamedParams
{ chain :: Bool
Expand All @@ -41,8 +41,11 @@ main = do
let (CLINamedParams{..}) = params
case rulesYaml of
Just path -> do
handle <- maybe (pure stdout) (`openFile` WriteMode) outPath
let logStr = hPutStr handle
let logStrLn = hPutStrLn handle
ruleSet <- parseRuleSetFromFile path
putStrLn ruleSet.title
logStrLn ruleSet.title
src <- maybe getContents readFile inPath
let progOrError = parseProgram src
case progOrError of
Expand All @@ -53,18 +56,18 @@ main = do
| otherwise = pure <$> applyRules (Context (convertRule <$> ruleSet.rules)) (Formation bindings)
uniqueResults = nub results
totalResults = length uniqueResults
-- TODO #48:15m use outPath to output to file if provided
putStrLn "Input:"
putStrLn (printTree input)
putStrLn "===================================================="
logStrLn "Input:"
logStrLn (printTree input)
logStrLn "===================================================="
forM_ (zip [1 ..] uniqueResults) $ \(i, steps) -> do
putStrLn $
logStrLn $
"Result " <> show i <> " out of " <> show totalResults <> ":"
let n = length steps
forM_ (zip [1 ..] steps) $ \(k, step) -> do
Control.Monad.when chain $ do
putStr ("[ " <> show k <> " / " <> show n <> " ]")
putStrLn (printTree step)
putStrLn "----------------------------------------------------"
Control.Monad.when chain $
logStr ("[ " <> show k <> " / " <> show n <> " ]")
logStrLn (printTree step)
logStrLn "----------------------------------------------------"
hClose handle
-- TODO #48:15m still need to consider `chain` (should rewrite/change defaultMain to mainWithOptions)
Nothing -> defaultMain

1 comment on commit 65f4db2

@0pdd
Copy link

@0pdd 0pdd commented on 65f4db2 Feb 6, 2024

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Puzzle 48-a228400d disappeared from eo-phi-normalizer/app/Main.hs), that's why I closed #84. Please, remember that the puzzle was not necessarily removed in this particular commit. Maybe it happened earlier, but we discovered this fact only now.

Please sign in to comment.