Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This module provides an interface for rewriting textual, unparsed Fortran using a diff-like algorithm.
Original code from Bloomberg, used with permission.
Original authors: * Daniel Beer * Anthony Burzillo * Raoul Hidalgo Charman * Aiden Jeffrey * Jason Xu * Beleth Apophis * Lukasz Kolodziejczyk
Synopsis
- data SourceLocation = SourceLocation Int Int
- data SourceRange = SourceRange SourceLocation SourceLocation
- data Replacement = Replacement SourceRange String
- data ReplacementError
- type ReplacementMap = Map String [Replacement]
- partitionOverlapping :: [Replacement] -> ([Replacement], [Replacement])
- processReplacements :: ReplacementMap -> IO ()
- spanToSourceRange :: SrcSpan -> SourceRange
- spanToSourceRange2 :: SrcSpan -> SrcSpan -> SourceRange
- sourceRangeBetweenTwoSpans :: SrcSpan -> SrcSpan -> SourceRange
Documentation
data SourceLocation Source #
Represents location in source code.
Note that, SourceLocation
indicates space between characters,
i.e the following example:
SourceLocation 0 1
indicates position between first and second characters in a file.
Instances
Eq SourceLocation Source # | |
Defined in Language.Fortran.Rewriter.Internal (==) :: SourceLocation -> SourceLocation -> Bool # (/=) :: SourceLocation -> SourceLocation -> Bool # | |
Ord SourceLocation Source # | |
Defined in Language.Fortran.Rewriter.Internal compare :: SourceLocation -> SourceLocation -> Ordering # (<) :: SourceLocation -> SourceLocation -> Bool # (<=) :: SourceLocation -> SourceLocation -> Bool # (>) :: SourceLocation -> SourceLocation -> Bool # (>=) :: SourceLocation -> SourceLocation -> Bool # max :: SourceLocation -> SourceLocation -> SourceLocation # min :: SourceLocation -> SourceLocation -> SourceLocation # | |
Show SourceLocation Source # | |
Defined in Language.Fortran.Rewriter.Internal showsPrec :: Int -> SourceLocation -> ShowS # show :: SourceLocation -> String # showList :: [SourceLocation] -> ShowS # |
data SourceRange Source #
Represents range in source code.
Instances
Eq SourceRange Source # | |
Defined in Language.Fortran.Rewriter.Internal (==) :: SourceRange -> SourceRange -> Bool # (/=) :: SourceRange -> SourceRange -> Bool # | |
Show SourceRange Source # | |
Defined in Language.Fortran.Rewriter.Internal showsPrec :: Int -> SourceRange -> ShowS # show :: SourceRange -> String # showList :: [SourceRange] -> ShowS # |
data Replacement Source #
Represents the intent to replace content in the file.
The content in Replacement
will be used in place of what is in
the range described. Note that the replacement text can be shorter
or larger than the original span, and it can also be multi-line.
Instances
Eq Replacement Source # | |
Defined in Language.Fortran.Rewriter.Internal (==) :: Replacement -> Replacement -> Bool # (/=) :: Replacement -> Replacement -> Bool # | |
Ord Replacement Source # | |
Defined in Language.Fortran.Rewriter.Internal compare :: Replacement -> Replacement -> Ordering # (<) :: Replacement -> Replacement -> Bool # (<=) :: Replacement -> Replacement -> Bool # (>) :: Replacement -> Replacement -> Bool # (>=) :: Replacement -> Replacement -> Bool # max :: Replacement -> Replacement -> Replacement # min :: Replacement -> Replacement -> Replacement # | |
Show Replacement Source # | |
Defined in Language.Fortran.Rewriter.Internal showsPrec :: Int -> Replacement -> ShowS # show :: Replacement -> String # showList :: [Replacement] -> ShowS # |
data ReplacementError Source #
Exception raised when two Replacement
objects overlap
(OverlappingError
) or Replacement
points at invalid locations
(InvalidRangeError
).
Instances
Eq ReplacementError Source # | |
Defined in Language.Fortran.Rewriter.Internal (==) :: ReplacementError -> ReplacementError -> Bool # (/=) :: ReplacementError -> ReplacementError -> Bool # | |
Show ReplacementError Source # | |
Defined in Language.Fortran.Rewriter.Internal showsPrec :: Int -> ReplacementError -> ShowS # show :: ReplacementError -> String # showList :: [ReplacementError] -> ShowS # | |
Exception ReplacementError Source # | |
type ReplacementMap = Map String [Replacement] Source #
Represents map of files and replacements that will be done.
partitionOverlapping :: [Replacement] -> ([Replacement], [Replacement]) Source #
Remove overlapping items from a list of replacements and return a pair of lists containing disjoint items and overlapping items, respectively.
Important notes:
Replacements that come first in the list will be given precedence over later items.
processReplacements :: ReplacementMap -> IO () Source #
Apply a list of Replacement
s to the orginal source file.
Important notes:
Source locations specified in replacements are 0-indexed.
Rewriting applies continuation lines when lines are longer than 72 characters.
Example replacements:
Delete the first character in a file
Replacement (SourceRange (SourceLocation 0 0) (SourceLocation 0 1)) ""
Prepend "a" to 1 line, 2 column character
Replacement (SourceRange (SourceLocation 0 1) (SourceLocation 0 1)) "a"
Replace a character located in 2 line, 4 column with "a"
Replacement (SourceRange (SourceLocation 1 3) (SourceLocation 1 4)) "a"
Replace string starting in 2 line, 4 column and ending in 2 line, 6 column (inclusive) with "a"
Replacement (SourceRange (SourceLocation 1 3) (SourceLocation 1 6)) "a"
Since: 0.1.0.0
spanToSourceRange :: SrcSpan -> SourceRange Source #
Utility function to convert SrcSpan
to SourceRange
Since: 0.1.13.7
spanToSourceRange2 :: SrcSpan -> SrcSpan -> SourceRange Source #
Given two Span
s, returns a SourceRange
that starts at the starting
location of the first span, and ends at the starting location of the second
span
Since: 0.1.17.2
sourceRangeBetweenTwoSpans :: SrcSpan -> SrcSpan -> SourceRange Source #
Given two Span
s, returns a SourceRange
that starts at the ending
location of the first span, and ends at the starting location of the second
span
Since: 0.1.17.2