Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data SourceLocation = SourceLocation Int Int
- data SourceRange = SourceRange SourceLocation SourceLocation
- data RChar = RChar (Maybe Char) Bool SourceLocation ByteString
- data Replacement = Replacement SourceRange String
- data ReplacementError
- type Chunk = [RChar]
- type ReplacementMap = Map String [Replacement]
- toRCharList :: ByteString -> [RChar]
- markRChars :: [RChar] -> SourceRange -> [RChar]
- markRChars_ :: [RChar] -> SourceRange -> SourceLocation -> [RChar]
- setReplacementStringSL :: [RChar] -> SourceLocation -> ByteString -> Bool -> [RChar]
- setReplacementStringSR :: [RChar] -> SourceRange -> ByteString -> Bool -> [RChar]
- evaluateRChars :: [RChar] -> ByteString
- evaluateRChar :: RChar -> ByteString
- nextChunk :: [RChar] -> (Chunk, [RChar])
- nextChunk_ :: [RChar] -> (Chunk, [RChar])
- allChunks :: [RChar] -> [Chunk]
- evaluateChunks :: [Chunk] -> ByteString
- evaluateChunks_ :: [Chunk] -> Int64 -> Maybe Char -> ByteString
- isMarkedForRemoval :: [RChar] -> Bool
- isInsertion :: Replacement -> Bool
- insertionSR :: SourceRange -> SourceRange
- setReplacement :: [RChar] -> Replacement -> [RChar]
- setReplacements :: [RChar] -> [Replacement] -> [RChar]
- adjustLineWrap :: [RChar] -> [RChar]
- adjustLineWrapAux :: RChar -> [RChar] -> [RChar] -> [RChar]
- deleteRC :: RChar -> RChar
- appendRC :: RChar -> Char -> RChar
- areDisjoint :: Replacement -> Replacement -> Bool
- isValidRange :: SourceRange -> [RChar] -> Bool
- isValidLocation :: SourceLocation -> [RChar] -> Bool
- checkRanges :: [RChar] -> [Replacement] -> [RChar]
- checkOverlapping :: [Replacement] -> [Replacement]
- applyReplacements :: ByteString -> [Replacement] -> ByteString
- applyReplacements_ :: [RChar] -> [Replacement] -> ByteString
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
Show SourceLocation Source # | |
Defined in Language.Fortran.Rewriter.Internal showsPrec :: Int -> SourceLocation -> ShowS # show :: SourceLocation -> String # showList :: [SourceLocation] -> ShowS # | |
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 # |
data SourceRange Source #
Represents range in source code.
Instances
Show SourceRange Source # | |
Defined in Language.Fortran.Rewriter.Internal showsPrec :: Int -> SourceRange -> ShowS # show :: SourceRange -> String # showList :: [SourceRange] -> ShowS # | |
Eq SourceRange Source # | |
Defined in Language.Fortran.Rewriter.Internal (==) :: SourceRange -> SourceRange -> Bool # (/=) :: SourceRange -> SourceRange -> Bool # |
Represents a character in the original source text along with any replacement operations applied to the character in place.
It expects a character (in case it's empty, Nothing should be used),
whether it should be removed, its SourceLocation
and a string that
should be put in place of it.
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
Show Replacement Source # | |
Defined in Language.Fortran.Rewriter.Internal showsPrec :: Int -> Replacement -> ShowS # show :: Replacement -> String # showList :: [Replacement] -> ShowS # | |
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 # |
data ReplacementError Source #
Exception raised when two Replacement
objects overlap
(OverlappingError
) or Replacement
points at invalid locations
(InvalidRangeError
).
Instances
Exception ReplacementError Source # | |
Show ReplacementError Source # | |
Defined in Language.Fortran.Rewriter.Internal showsPrec :: Int -> ReplacementError -> ShowS # show :: ReplacementError -> String # showList :: [ReplacementError] -> ShowS # | |
Eq ReplacementError Source # | |
Defined in Language.Fortran.Rewriter.Internal (==) :: ReplacementError -> ReplacementError -> Bool # (/=) :: ReplacementError -> ReplacementError -> Bool # |
type ReplacementMap = Map String [Replacement] Source #
Represents map of files and replacements that will be done.
toRCharList :: ByteString -> [RChar] Source #
Parses input string into a list of annotated characters.
markRChars :: [RChar] -> SourceRange -> [RChar] Source #
Marks RChars
in a given range to be removed later.
markRChars_ :: [RChar] -> SourceRange -> SourceLocation -> [RChar] Source #
setReplacementStringSL :: [RChar] -> SourceLocation -> ByteString -> Bool -> [RChar] Source #
Sets replacement string to be prepended to the given location.
setReplacementStringSR :: [RChar] -> SourceRange -> ByteString -> Bool -> [RChar] Source #
Sets replacement string to be prepended to the begining of the given range.
evaluateRChars :: [RChar] -> ByteString Source #
Applies all deletions and additions and transforms RChars
back
to a string.
evaluateRChar :: RChar -> ByteString Source #
If RChar
is marked as deleted, it'll be evaluated to its
replacement string, otherwise original character will be returned.
evaluateChunks :: [Chunk] -> ByteString Source #
Transform a list of Chunk
s into a single string, applying
continuation lines when neccessary.
evaluateChunks_ :: [Chunk] -> Int64 -> Maybe Char -> ByteString Source #
This expands the chunks from the left to right. If the length
of what has already been put into the current line exceeds the
limit of 72 characters (excluding inline comments starting with
!
and implicit comments starting at column 73) then it ends
the current line with a continuation, otherwise it simply adds
the line as-is. It also calculates if the chunk is inside or outside
of a string literal, using that to determine where explicit comments are
if any.
In either case, we make sure that we are padding implicit comments *from the original source* even if the tail of that line has been moved onto a continuation line.
isMarkedForRemoval :: [RChar] -> Bool Source #
isInsertion :: Replacement -> Bool Source #
Return TRUE iff the Replacement
constitutes a character
insertion.
insertionSR :: SourceRange -> SourceRange Source #
setReplacement :: [RChar] -> Replacement -> [RChar] Source #
Sets a single Replacement
given a list of RChar
s.
setReplacements :: [RChar] -> [Replacement] -> [RChar] Source #
Sets a list of Replacement
s given a list of RChar
s.
adjustLineWrap :: [RChar] -> [RChar] Source #
heuristic to wrap line after comma or right parenthesis if applicable
areDisjoint :: Replacement -> Replacement -> Bool Source #
Checks whether two Replacement
s are not overlapping.
isValidRange :: SourceRange -> [RChar] -> Bool Source #
Checks whether:
- the start is before the end of the range and
- both start and end locations are within the code.
isValidLocation :: SourceLocation -> [RChar] -> Bool Source #
checkRanges :: [RChar] -> [Replacement] -> [RChar] Source #
checkOverlapping :: [Replacement] -> [Replacement] Source #
applyReplacements :: ByteString -> [Replacement] -> ByteString Source #
Applies Replacement
s to a string and return it.
Firstly, it transforms the string into a list of RChar
s.
After that, it validates the SourceRange
of each Replacement
.
In the end, it splits up RChar
s in Chunk
s, set the
Replacement
s and evaluates the Chunk
s.
applyReplacements_ :: [RChar] -> [Replacement] -> ByteString Source #