-
Notifications
You must be signed in to change notification settings - Fork 14
/
Copy pathMain.hs
172 lines (162 loc) · 6.11 KB
/
Main.hs
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
module Main where
import qualified Data.ByteString as BS
import Data.List (intersperse)
import Data.List.NonEmpty (NonEmpty, toList)
import Data.Maybe
import Data.Semigroup
import Data.Text (Text, intercalate, pack, strip, unpack)
import qualified Data.Text as Text
import qualified Data.Text.IO as TIO
import Rainbow hiding ((<>))
import Safe
import System.Environment
import System.Exit
import System.IO
import Text.Megaparsec hiding (chunk)
import Text.Megaparsec.Error
import Text.RawString.QQ
import Compiler
import HaskellSyntax
import TypeChecker
showT :: Show a => a -> Text
showT = Text.pack . show
usage :: Text
usage =
strip
[r|
usage: forest command path
commands:
build - typechecks and compiles the given file to Wast
format - format and print the given file
check - typechecks the given file
|]
main :: IO ()
main = do
args <- getArgs
case args of
["build", filename] -> do
contents <- TIO.readFile filename
let (printText, exitCode) =
case compile contents of
Success compiledWast -> (TIO.putStrLn compiledWast, ExitSuccess)
ParseErr err ->
( TIO.hPutStrLn stderr $ reportParseError filename err
, ExitFailure 1)
CompileErr errors ->
let errorChunks :: [[Chunk Text]]
errorChunks = toList $ printError contents <$> errors
divider = [chunk "\n\n-----------\n\n"]
chunks =
intersperse divider errorChunks <>
[[chunk ("\n" :: Text)]]
in (printChunks $ concat chunks, ExitFailure 2)
printText >> exitWith exitCode
["format", filename] -> do
contents <- TIO.readFile filename
case format contents of
Right formattedCode ->
TIO.writeFile filename formattedCode >>
TIO.putStrLn "Formatted successfully."
Left err ->
(TIO.hPutStrLn stderr $ reportParseError filename err) >>
exitWith (ExitFailure 1)
["format-js", filename] -> do
contents <- TIO.readFile filename
case formatJS contents of
Right formattedCode ->
TIO.putStrLn formattedCode
Left err ->
(TIO.hPutStrLn stderr $ reportParseError filename err) >>
exitWith (ExitFailure 1)
["check", filename] -> do
contents <- TIO.readFile filename
let (printText, exitCode) =
case typeCheck contents of
Success _ -> (TIO.putStrLn "No errors found.", ExitSuccess)
ParseErr err ->
( TIO.hPutStrLn stderr $ reportParseError filename err
, ExitFailure 1)
CompileErr errors ->
let errorChunks :: [[Chunk Text]]
errorChunks = toList $ printError contents <$> errors
divider = [chunk "\n\n-----------\n\n"]
chunks =
intersperse divider errorChunks <>
[[chunk ("\n" :: Text)]]
in (printChunks $ concat chunks, ExitFailure 2)
printText >> exitWith exitCode
_ -> TIO.hPutStrLn stderr usage >> exitFailure
where
positionText p =
case p of
Just (start, end) ->
Text.pack (sourcePosPretty start <> "-" <> sourcePosPretty end)
Nothing -> ""
printError contents (CompileError error maybeSourceRange message) =
case error of
ExpressionError expression ->
case maybeSourceRange of
Just (start, end) ->
let contextRangeStart = unPos (sourceLine start) - 2
contextRangeEnd = unPos (sourceLine end) + 1
contentLines = Text.lines contents
colorLine line =
let (lineStart, remainder) =
Text.splitAt (unPos (sourceColumn start) + 3) line
(highlight, lineEnd) = Text.splitAt (unPos (sourceColumn end) - unPos (sourceColumn start)) remainder
in [ chunk lineStart
, chunk highlight & underline & fore brightRed
, chunk lineEnd
]
color lineNumber line =
if lineNumber >= unPos (sourceLine start) &&
lineNumber <= unPos (sourceLine end)
then colorLine line
else [chunk line]
contextLines =
concatMap
(\(lineNumber, line) ->
color
lineNumber
(showT lineNumber <> " | " <> line <> "\n"))
(filter
(\(i, _) ->
i >= contextRangeStart && i <= contextRangeEnd)
(zip [1 ..] contentLines))
in [chunk $ "Error: ", chunk $ message <> "\n"] <> contextLines
Nothing ->
[ chunk $
"Encountered a type error in an expression:\n" <> "\n" <>
indent2 (printExpression expression) <>
"\n\n" <>
message
]
DeclarationError declaration ->
[ chunk $
"Encountered a type error in a declaration:\n" <>
positionText maybeSourceRange <>
"\n" <>
indent2 (printDeclaration declaration) <>
"\n\n" <>
message
]
DataTypeError dataType ->
[ chunk $
"Encountered a type error in a datatype:\n" <>
positionText maybeSourceRange <>
"\n" <>
indent2 (printDataType dataType) <>
"\n\n" <>
message
]
printChunks :: [Chunk Text] -> IO ()
printChunks chunks = do
printer <- byteStringMakerFromEnvironment
mapM_ (BS.hPut stderr) . chunksToByteStrings printer $ chunks
reportParseError :: String -> ParseError' -> Text
reportParseError filename parseError =
"Syntax error in " <> pack filename <> "\n" <>
pack (errorBundlePretty parseError)