summaryrefslogtreecommitdiff
path: root/src/Main.hs
diff options
context:
space:
mode:
authorJosh Rahm <joshuarahm@gmail.com>2024-10-03 18:23:50 -0600
committerJosh Rahm <joshuarahm@gmail.com>2024-10-03 18:23:50 -0600
commit407e41489cc22fbf0518fd370530f8857b8c3ed0 (patch)
tree8c5f3fceb7c9e083033e06c818556eba1dcf9a06 /src/Main.hs
parent72eeba5fd6178409b4aab5eb8dbfaf4460f6841c (diff)
downloadfiddle-407e41489cc22fbf0518fd370530f8857b8c3ed0.tar.gz
fiddle-407e41489cc22fbf0518fd370530f8857b8c3ed0.tar.bz2
fiddle-407e41489cc22fbf0518fd370530f8857b8c3ed0.zip
Clean up warnings and remove unused files.
Diffstat (limited to 'src/Main.hs')
-rw-r--r--src/Main.hs40
1 files changed, 22 insertions, 18 deletions
diff --git a/src/Main.hs b/src/Main.hs
index fb2a1f2..4da2295 100644
--- a/src/Main.hs
+++ b/src/Main.hs
@@ -2,7 +2,7 @@ module Main where
import Control.Monad (forM_)
import Control.Monad.Identity (Identity)
-import Data.Aeson (Value (Null, String), encode)
+import Data.Aeson (Value (..), encode)
import qualified Data.ByteString.Lazy.Char8 as BL
import qualified Data.Text as Text
import qualified Data.Text.IO as TextIO
@@ -16,19 +16,28 @@ import Language.Fiddle.Compiler.ImportResolution
import Language.Fiddle.Compiler.Qualification
import Language.Fiddle.Compiler.Stage0
import Language.Fiddle.GenericTree
- ( GenericSyntaxTree (..),
- ToGenericSyntaxTree (toGenericSyntaxTree),
- alterGenericSyntaxTree,
- )
-import qualified Language.Fiddle.Parser
-import qualified Language.Fiddle.Tokenizer
-import Language.Fiddle.Types (Commented (unCommented))
+import Language.Fiddle.Types (Commented (unCommented), SourceSpan)
import Options.Applicative
import qualified System.Environment as System
import System.Exit (exitWith)
-import System.IO
--- compilationPipeline :: _ -> _ -> CompilationPhase Parsed Checked
+compilationPipeline ::
+ ( FilePath ->
+ IO
+ ( [Diagnostic],
+ Maybe
+ ( FiddleUnit Parsed Identity (Commented SourceSpan)
+ )
+ )
+ ) ->
+ ( FiddleUnit Parsed Identity (Commented SourceSpan) ->
+ IO
+ ( [Diagnostic],
+ Maybe
+ (FiddleUnit Checked Identity (Commented SourceSpan))
+ )
+ ) ->
+ CompilationPhase Parsed Checked
compilationPipeline parse compile =
importResolutionPhase parse compile
>>> expansionPhase
@@ -56,12 +65,12 @@ runCompilationPipeline ::
IO ([Diagnostic], Maybe (TreeType FiddleUnit Checked))
runCompilationPipeline argv tree =
case fromArgs argv of
- Failure failure ->
+ Success (_, pipelineAction) -> pipelineAction tree
+ _ ->
return
( [Diagnostic Error "Internal parsing failure (this is a bug)." (unCommented $ annot tree)],
Nothing
)
- Success (_, pipelineAction) -> pipelineAction tree
-- | Parse command-line arguments into global flags and a compilation action.
fromArgs ::
@@ -111,12 +120,7 @@ parseCommandLineArgs ::
TreeType FiddleUnit Parsed ->
IO ([Diagnostic], Maybe (TreeType FiddleUnit Checked))
)
-parseCommandLineArgs argv =
- case fromArgs argv of
- Failure failure -> do
- hPutStrLn stderr (fst $ renderFailure failure "")
- exitWith (ExitFailure 1)
- Success v -> return v
+parseCommandLineArgs argv = handleParseResult (fromArgs argv)
-- | Parse the input file into the initial AST.
parseInputFile :: String -> IO ([Diagnostic], Maybe (TreeType FiddleUnit Parsed))