Copyright | Copyright 2017 Dominic Orchard Andrew Rice Mistral Contrastin Matthew Danish |
---|---|
License | Apache-2.0 |
Maintainer | dom.orchard@gmail.com |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- class Default t where
- defaultValue :: t
- type ProgramFile = ProgramFile A
- type AnalysisProgram e w m a b = a -> AnalysisT e w m b
- type AnalysisRunner e w m a b r = AnalysisProgram e w m a b -> LogOutput m -> LogLevel -> Bool -> ModFiles -> [(ProgramFile, SourceText)] -> m r
- type AnalysisRunnerP e w m a b r = AnalysisProgram e w m a b -> LogOutput m -> LogLevel -> Bool -> ModFiles -> Pipe (ProgramFile, SourceText) r m ()
- type AnalysisRunnerConsumer e w m a b r = AnalysisProgram e w m a b -> LogOutput m -> LogLevel -> Bool -> ModFiles -> Consumer (ProgramFile, SourceText) m ()
- runPerFileAnalysisP :: (MonadIO m, Describe e, Describe w, NFData e, NFData w, NFData b) => AnalysisRunnerP e w m ProgramFile b (AnalysisReport e w b)
- runMultiFileAnalysis :: (Monad m, Describe e, Describe w) => AnalysisRunner e w m [ProgramFile] b (AnalysisReport e w b)
- describePerFileAnalysisP :: (MonadIO m, Describe r, ExitCodeOfReport r, Describe w, Describe e, NFData e, NFData w, NFData r) => Text -> AnalysisRunnerP e w m ProgramFile r (AnalysisReport e w r)
- doRefactor :: (Describe e, Describe e', Describe w, Describe r, ExitCodeOfReport r) => Text -> FileOrDir -> FilePath -> AnalysisRunner e w IO [ProgramFile] (r, [Either e' ProgramFile]) Int
- doRefactorAndCreate :: (Describe e, Describe w) => Text -> FileOrDir -> FilePath -> AnalysisRunner e w IO [ProgramFile] ([ProgramFile], [ProgramFile]) Int
- perFileRefactoring :: Monad m => AnalysisProgram e w m ProgramFile ProgramFile -> AnalysisProgram e w m [ProgramFile] ((), [Either e ProgramFile])
- readParseSrcDir :: Maybe FortranVersion -> ModFiles -> FileOrDir -> [Filename] -> IO [(ProgramFile A, SourceText)]
- loadModAndProgramFiles :: MonadIO m => Maybe FortranVersion -> MFCompiler r m -> r -> FileOrDir -> FileOrDir -> [Filename] -> m (ModFiles, [(ProgramFile, SourceText)])
- runThen :: Monad m => AnalysisRunner e w m a b r -> (r -> m r') -> AnalysisRunner e w m a b r'
Classes
Datatypes and Aliases
type ProgramFile = ProgramFile A Source #
For refactorings which create additional files.
type AnalysisProgram e w m a b = a -> AnalysisT e w m b Source #
An analysis program which accepts inputs of type a
and produces results
of type b
.
Has error messages of type e
and warnings of type w
. Runs in the base
monad m
.
type AnalysisRunner e w m a b r = AnalysisProgram e w m a b -> LogOutput m -> LogLevel -> Bool -> ModFiles -> [(ProgramFile, SourceText)] -> m r Source #
An AnalysisRunner
is a function to run an AnalysisProgram
in a
particular way. Produces a final result of type r
.
type AnalysisRunnerP e w m a b r = AnalysisProgram e w m a b -> LogOutput m -> LogLevel -> Bool -> ModFiles -> Pipe (ProgramFile, SourceText) r m () Source #
type AnalysisRunnerConsumer e w m a b r = AnalysisProgram e w m a b -> LogOutput m -> LogLevel -> Bool -> ModFiles -> Consumer (ProgramFile, SourceText) m () Source #
Builders for analysers and refactorings
runPerFileAnalysisP :: (MonadIO m, Describe e, Describe w, NFData e, NFData w, NFData b) => AnalysisRunnerP e w m ProgramFile b (AnalysisReport e w b) Source #
Given an analysis program for a single file, run it over every input file and collect the reports. Doesn't produce any output.
runMultiFileAnalysis :: (Monad m, Describe e, Describe w) => AnalysisRunner e w m [ProgramFile] b (AnalysisReport e w b) Source #
Run an analysis program over every input file and get the report. Doesn't produce any output.
describePerFileAnalysisP :: (MonadIO m, Describe r, ExitCodeOfReport r, Describe w, Describe e, NFData e, NFData w, NFData r) => Text -> AnalysisRunnerP e w m ProgramFile r (AnalysisReport e w r) Source #
Given an analysis program for a single file, run it over every input file and collect the reports, then print those reports to standard output.
doRefactor :: (Describe e, Describe e', Describe w, Describe r, ExitCodeOfReport r) => Text -> FileOrDir -> FilePath -> AnalysisRunner e w IO [ProgramFile] (r, [Either e' ProgramFile]) Int Source #
Accepts an analysis program for multiple input files which produces a result value along with refactored files. Performs the refactoring, and prints the result value with the report.
doRefactorAndCreate :: (Describe e, Describe w) => Text -> FileOrDir -> FilePath -> AnalysisRunner e w IO [ProgramFile] ([ProgramFile], [ProgramFile]) Int Source #
Accepts an analysis program for multiple input files which produces refactored files and creates new files. Performs the refactoring.
perFileRefactoring :: Monad m => AnalysisProgram e w m ProgramFile ProgramFile -> AnalysisProgram e w m [ProgramFile] ((), [Either e ProgramFile]) Source #
Accepts an analysis program to refactor a single file and returns an analysis program to refactor each input file with that refactoring.
Source directory and file handling
readParseSrcDir :: Maybe FortranVersion -> ModFiles -> FileOrDir -> [Filename] -> IO [(ProgramFile A, SourceText)] Source #
loadModAndProgramFiles Source #
:: MonadIO m | |
=> Maybe FortranVersion | |
-> MFCompiler r m | |
-> r | |
-> FileOrDir | Input source file or directory |
-> FileOrDir | Include path |
-> [Filename] | Excluded files |
-> m (ModFiles, [(ProgramFile, SourceText)]) |
Combinators
runThen :: Monad m => AnalysisRunner e w m a b r -> (r -> m r') -> AnalysisRunner e w m a b r' Source #
Monadic bind for analysis runners.