Safe Haskell | None |
---|---|
Language | Haskell2010 |
- sed :: IsRegex re ByteString => Edits IO re ByteString -> FilePath -> FilePath -> IO ()
- sed' :: (IsRegex re a, Monad m, Functor m) => Edits m re a -> a -> m a
- grep :: IsRegex re ByteString => Verbosity -> re -> FilePath -> IO ()
- data Verbosity
- data Line s = Line {
- getLineNumber :: LineNo
- getLineMatches :: Matches s
- grepLines :: IsRegex re ByteString => re -> FilePath -> IO [Line ByteString]
- grepFilter :: IsRegex re s => re -> s -> [Line s]
- type GrepScript re s t = [(re, LineNo -> Matches s -> Maybe t)]
- grepWithScript :: IsRegex re s => GrepScript re s t -> [s] -> [t]
- report :: Verbosity -> [Line ByteString] -> String
- linesMatched :: Verbosity -> [Line s] -> [Line s]
- alex :: IsRegex re s => [(re, Match s -> Maybe t)] -> t -> s -> [t]
- alex' :: Replace s => (re -> s -> Match s) -> [(re, Match s -> Maybe t)] -> t -> s -> [t]
- data FindMethods s = FindMethods {
- doesDirectoryExistDM :: s -> IO Bool
- listDirectoryDM :: s -> IO [s]
- combineDM :: s -> s -> s
- findMatches_ :: IsRegex re s => FindMethods s -> re -> s -> IO [s]
- findMatches_' :: IsRegex re s => FindMethods s -> ([s] -> [s]) -> (Match s -> Bool) -> re -> s -> IO [s]
- class Replace s => IsRegex re s where
- data SearchReplace re s = SearchReplace {
- getSearch :: !re
- getTemplate :: !s
- searchReplaceAll :: IsRegex re s => SearchReplace re s -> s -> s
- searchReplaceFirst :: IsRegex re s => SearchReplace re s -> s -> s
- data Edits m re s
- data Edit m re s
- data LineEdit s
- = NoEdit
- | ReplaceWith !s
- | Delete
- applyEdits :: (IsRegex re s, Monad m, Functor m) => LineNo -> Edits m re s -> s -> m s
- applyEdit :: (IsRegex re s, Monad m, Functor m) => (s -> s) -> LineNo -> Edit m re s -> s -> m (Maybe s)
- applyLineEdit :: Monoid s => (s -> s) -> LineEdit s -> Maybe s
- newtype LineNo = ZeroBasedLineNo {}
- firstLine :: LineNo
- getLineNo :: LineNo -> Int
- lineNo :: Int -> LineNo
- module Text.RE.Replace
The Tools Tutorial
This API module provides some familiar RE tools on top of the core package functions and types.
See the Regex Tools tutorial at http://re-tutorial-tools.regex.uk
Sed
sed :: IsRegex re ByteString => Edits IO re ByteString -> FilePath -> FilePath -> IO () Source #
read a file, apply an Edits
script to each line it and
write the file out again; "-" is used to indicate standard input
standard output as appropriate
sed' :: (IsRegex re a, Monad m, Functor m) => Edits m re a -> a -> m a Source #
apply an Edits
script to each line of the argument text
Grep
grep :: IsRegex re ByteString => Verbosity -> re -> FilePath -> IO () Source #
operates a bit like classic grep
printing out the lines matched
specifies whether to return the linss matched or missed
Line | |
|
grepLines :: IsRegex re ByteString => re -> FilePath -> IO [Line ByteString] Source #
returns a Line
for each line in the file, enumerating all of the
matches for that line
grepFilter :: IsRegex re s => re -> s -> [Line s] Source #
returns a Line
for each line in the argument text, enumerating
all of the matches for that line
type GrepScript re s t = [(re, LineNo -> Matches s -> Maybe t)] Source #
a GrepScript lists RE-action associations, with the first RE to match a line selecting the action to be executed on each line in the file
grepWithScript :: IsRegex re s => GrepScript re s t -> [s] -> [t] Source #
given a list of lines, apply the GrepScript
to each line of the file
report :: Verbosity -> [Line ByteString] -> String Source #
generate a grep report from a list of Line
linesMatched :: Verbosity -> [Line s] -> [Line s] Source #
given a velocity
flag filter out either the lines matched or not
matched
Lex
alex :: IsRegex re s => [(re, Match s -> Maybe t)] -> t -> s -> [t] Source #
a simple regex-based scanner interpretter for prototyping scanners
alex' :: Replace s => (re -> s -> Match s) -> [(re, Match s -> Maybe t)] -> t -> s -> [t] Source #
a higher order version of alex
parameterised over the matchOnce
function
Find
data FindMethods s Source #
as we don't want the directory
and FilePath dependencies
we will abstract the three calls we need into this record type
FindMethods | |
|
findMatches_ :: IsRegex re s => FindMethods s -> re -> s -> IO [s] Source #
recursively list all files whose filename matches given RE,
sorting the list into ascending order; if the argument path has a
trailing /
then it will be removed
:: IsRegex re s | |
=> FindMethods s | the directory and filepath methods |
-> ([s] -> [s]) | result post-processing function |
-> (Match s -> Bool) | filtering function |
-> re | re to be matched against the leaf filename |
-> s | root directory of the search |
-> IO [s] |
recursively list all files whose filename matches given RE, using the given function to determine which matches to accept
IsRegex
class Replace s => IsRegex re s where Source #
the IsRegex
class allows polymorhic tools to be written that
will work with a variety of regex back ends and text types
matchOnce :: re -> s -> Match s Source #
finding the first match
matchMany :: re -> s -> Matches s Source #
finding all matches
makeRegex :: (Functor m, Monad m) => s -> m re Source #
compiling an RE, failing if the RE is not well formed
makeRegexWith :: (Functor m, Monad m) => SimpleREOptions -> s -> m re Source #
comiling an RE, specifying the SimpleREOptions
makeSearchReplace :: (Functor m, Monad m, IsRegex re s) => s -> s -> m (SearchReplace re s) Source #
compiling a SearchReplace
template from the RE text and the template Text, failing if they are not well formed
makeSearchReplaceWith :: (Functor m, Monad m, IsRegex re s) => SimpleREOptions -> s -> s -> m (SearchReplace re s) Source #
compiling a SearchReplace
template specifing the SimpleREOptions
for the RE
makeEscaped :: (Functor m, Monad m) => (s -> s) -> s -> m re Source #
incorporate an escaped string into a compiled RE with the default options
makeEscapedWith :: (Functor m, Monad m) => SimpleREOptions -> (s -> s) -> s -> m re Source #
incorporate an escaped string into a compiled RE with the specified SimpleREOptions
regexSource :: re -> s Source #
extract the text of the RE from the RE
data SearchReplace re s Source #
contains a compiled RE and replacement template
SearchReplace | |
|
Functor (SearchReplace re) Source # | |
(Show s, Show re) => Show (SearchReplace re s) Source # | |
searchReplaceAll :: IsRegex re s => SearchReplace re s -> s -> s Source #
search and replace all matches in the argument text; e.g., this function will convert every YYYY-MM-DD format date in its argument text into a DD/MM/YYYY date:
searchReplaceAll [ed|${y}([0-9]{4})-0*${m}([0-9]{2})-0*${d}([0-9]{2})///${d}/${m}/${y}|]
searchReplaceFirst :: IsRegex re s => SearchReplace re s -> s -> s Source #
search and replace the first occurrence only (if any) in the input text
e.g., to prefix the first string of four hex digits in the imput text,
if any, with 0x
:
searchReplaceFirst [ed|[0-9A-Fa-f]{4}///0x$0|]
Edit
an Edits
script will, for each line in the file, either perform
the action selected by the first RE in the list, or perform all of the
actions on line, arranged as a pipeline
each Edit action specifies how the match should be processed
Template !(SearchReplace re s) | replace the match with this template text, substituting ${capture} as apropriate |
Function !re REContext !(LineNo -> Match s -> RELocation -> Capture s -> m (Maybe s)) | use this function to replace the |
LineEdit !re !(LineNo -> Matches s -> m (LineEdit s)) | use this function to edit each line matched |
a LineEdit is the most general action thar can be performed on a line and is the only means of deleting a line
NoEdit | do not edit this line but leave as is |
ReplaceWith !s | replace the line with this text (terminating newline should not be included) |
Delete | delete the this line altogether |
applyEdits :: (IsRegex re s, Monad m, Functor m) => LineNo -> Edits m re s -> s -> m s Source #
apply an Edit
script to a single line
applyEdit :: (IsRegex re s, Monad m, Functor m) => (s -> s) -> LineNo -> Edit m re s -> s -> m (Maybe s) Source #
apply a single edit action to a line, the function in the first argument
being used to add a new line onto the end of the line where appropriate;
the function returns Nothing
if no edit is to be performed on the line,
Just mempty
to delete the line
applyLineEdit :: Monoid s => (s -> s) -> LineEdit s -> Maybe s Source #
apply a LineEdit
to a line, using the function in the first
argument to append a new line to the result; Nothing should be
returned if no edit is to be performed, Just mempty
to
delete the line
LineNo
our line numbers are of the proper zero-based kind
Replace
module Text.RE.Replace