Skip to content

Commit 2894d81

Browse files
committed
Format .hs all non-IR files
1 parent 63ce020 commit 2894d81

File tree

16 files changed

+1421
-1089
lines changed

16 files changed

+1421
-1089
lines changed

app/Main.hs

Lines changed: 38 additions & 40 deletions
Original file line numberDiff line numberDiff line change
@@ -8,57 +8,55 @@ exiting with status code, etc.
88
module Main where
99

1010
import qualified Codegen
11-
import Common.Compiler ( passIO )
12-
import Common.Default ( Default(..) )
11+
import Common.Compiler (passIO)
12+
import Common.Default (Default (..))
1313
import qualified Front
1414
import qualified IR
1515

16-
import Control.Monad ( unless
17-
, when
18-
)
19-
import System.Console.GetOpt ( ArgDescr(..)
20-
, ArgOrder(..)
21-
, OptDescr(..)
22-
, getOpt
23-
, getOpt'
24-
, usageInfo
25-
)
26-
import System.Environment ( getArgs
27-
, getProgName
28-
)
29-
import System.Exit ( exitFailure
30-
, exitSuccess
31-
)
32-
import System.IO ( hPutStr
33-
, hPutStrLn
34-
, stderr
35-
)
16+
import System.Console.GetOpt (
17+
ArgDescr (..),
18+
ArgOrder (..),
19+
OptDescr (..),
20+
getOpt,
21+
getOpt',
22+
usageInfo,
23+
)
24+
import System.Environment (getArgs, getProgName)
25+
import System.Exit (exitFailure, exitSuccess)
26+
import System.IO (hPutStr, hPutStrLn, stderr)
27+
28+
import Control.Monad (unless, when)
29+
3630

3731
-- | Print the usage message, collating options from each compiler stage.
3832
usageMessage :: IO ()
3933
usageMessage = do
4034
prg <- getProgName
4135
let header = "Usage: " ++ prg ++ " [options] <filename>"
42-
hPutStr stderr $ unlines
43-
[ header
44-
, ""
45-
, "When `-' is specified as the filename, input is read from stdin."
46-
, usageInfo "" options
47-
, usageInfo "" Front.options
48-
, usageInfo "" IR.options
49-
, usageInfo "" Codegen.options
50-
]
36+
hPutStr stderr $
37+
unlines
38+
[ header
39+
, ""
40+
, "When `-' is specified as the filename, input is read from stdin."
41+
, usageInfo "" options
42+
, usageInfo "" Front.options
43+
, usageInfo "" IR.options
44+
, usageInfo "" Codegen.options
45+
]
46+
5147

5248
-- | CLI options.
5349
options :: [OptDescr (IO ())]
5450
options =
5551
[Option "h" ["help"] (NoArg $ usageMessage >> exitSuccess) "Print help"]
5652

53+
5754
-- | Read input from file or stdin.
5855
readInput :: String -> IO String
59-
readInput "-" = getContents
56+
readInput "-" = getContents
6057
readInput filename = readFile filename
6158

59+
6260
-- | Compiler executable entry point.
6361
main :: IO ()
6462
main = do
@@ -72,9 +70,9 @@ main = do
7270
getOpt' RequireOrder IR.options $ iArgs' ++ iArgs
7371
(cOpts, filenames, cErr) =
7472
getOpt RequireOrder Codegen.options $ cArgs' ++ cArgs
75-
errors = cliErrors ++ fErr ++ iErr ++ cErr
76-
frontOpts = foldr ($) def fOpts
77-
irOpts = foldr ($) def iOpts
73+
errors = cliErrors ++ fErr ++ iErr ++ cErr
74+
frontOpts = foldr ($) def fOpts
75+
irOpts = foldr ($) def iOpts
7876
codegenOpts = foldr ($) def cOpts
7977

8078
mapM_ return cliActions
@@ -94,12 +92,12 @@ main = do
9492
usageMessage
9593
exitFailure
9694

97-
input <- readInput $ head filenames
95+
input <- readInput $ head filenames
9896
(cStr, warnings) <-
99-
passIO
100-
$ Front.run frontOpts input
101-
>>= IR.run irOpts
102-
>>= Codegen.run codegenOpts
97+
passIO $
98+
Front.run frontOpts input
99+
>>= IR.run irOpts
100+
>>= Codegen.run codegenOpts
103101
unless (null warnings) $ do
104102
hPutStr stderr "Encountered warnings:"
105103
hPutStr stderr $ show warnings

src/Codegen.hs

Lines changed: 21 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -5,41 +5,46 @@ how it is represented.
55
-}
66
module Codegen where
77

8-
import qualified Common.Compiler as Compiler
9-
import Common.Default ( Default(..) )
8+
import qualified Common.Compiler as Compiler
9+
import Common.Default (Default (..))
1010

11-
import qualified IR.IR as I
11+
import qualified IR.IR as I
1212

13-
import qualified Text.PrettyPrint.Mainland as C
14-
import qualified Text.PrettyPrint.Mainland.Class
15-
as C
13+
import qualified Text.PrettyPrint.Mainland as C
14+
import qualified Text.PrettyPrint.Mainland.Class as C
15+
16+
import Codegen.Codegen (genProgram)
17+
import System.Console.GetOpt (
18+
ArgDescr (..),
19+
OptDescr (..),
20+
)
1621

17-
import Codegen.Codegen ( genProgram )
18-
import System.Console.GetOpt ( ArgDescr(..)
19-
, OptDescr(..)
20-
)
2122

2223
-- | Operation modes for the codegen compiler stage.
2324
data Mode = Continue
2425
deriving (Eq, Show)
2526

27+
2628
-- | Compiler options for the codegen compiler stage.
2729
data Options = Options
28-
{ mode :: Mode
30+
{ mode :: Mode
2931
, textWidth :: Int
3032
}
3133
deriving (Eq, Show)
3234

35+
3336
instance Default Options where
34-
def = Options { mode = Continue, textWidth = 120 }
37+
def = Options{mode = Continue, textWidth = 120}
38+
3539

3640
-- | CLI options for the codegen compiler stage.
3741
options :: [OptDescr (Options -> Options)]
3842
options =
39-
[ Option ""
40-
["codegen-textwidth"]
41-
(ReqArg (\tw o -> o { textWidth = read tw }) "<textwidth>")
42-
"Line width for pretty-printing the generated C code."
43+
[ Option
44+
""
45+
["codegen-textwidth"]
46+
(ReqArg (\tw o -> o{textWidth = read tw}) "<textwidth>")
47+
"Line width for pretty-printing the generated C code."
4348
]
4449

4550

0 commit comments

Comments
 (0)