regex-1.1.0.0: Toolkit for regex-base

Safe HaskellNone
LanguageHaskell2010

Text.RE.Tools.Sed

Contents

Synopsis

Sed

The Sed toolkit applyies Edits scripts to each line of a text, running the actions and adjusting each line accordingly.

See the Regex Tools tutorial at http://re-tutorial-tools.regex.uk

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

Edit

data Edits m re s Source #

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

Constructors

Select ![Edit m re s]

for each line select the first Edit to match each line and edit the line with it

Pipe ![Edit m re s]

for each line apply every edit that matches in turn to the line

data Edit m re s Source #

each Edit action specifies how the match should be processed

Constructors

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 REContext specified captures in each line matched

LineEdit !re !(LineNo -> Matches s -> m (LineEdit s))

use this function to edit each line matched

data LineEdit s Source #

a LineEdit is the most general action thar can be performed on a line and is the only means of deleting a line

Constructors

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

Instances
Functor LineEdit Source # 
Instance details

Defined in Text.RE.Tools.Edit

Methods

fmap :: (a -> b) -> LineEdit a -> LineEdit b #

(<$) :: a -> LineEdit b -> LineEdit a #

Show s => Show (LineEdit s) Source # 
Instance details

Defined in Text.RE.Tools.Edit

Methods

showsPrec :: Int -> LineEdit s -> ShowS #

show :: LineEdit s -> String #

showList :: [LineEdit s] -> ShowS #

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 Edit 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

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

Methods

matchOnce :: re -> s -> Match s Source #

finding the first match

matchMany :: re -> s -> Matches s Source #

finding all matches

makeRegex :: (Functor m, Monad m, MonadFail m) => s -> m re Source #

compiling an RE, failing if the RE is not well formed

makeRegexWith :: (Functor m, Monad m, MonadFail m) => SimpleREOptions -> s -> m re Source #

comiling an RE, specifying the SimpleREOptions

makeSearchReplace :: (Functor m, Monad m, MonadFail 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, MonadFail 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, MonadFail m) => (s -> s) -> s -> m re Source #

incorporate an escaped string into a compiled RE with the default options

makeEscapedWith :: (Functor m, Monad m, MonadFail 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

Instances
IsRegex RE String Source # 
Instance details

Defined in Text.RE.TDFA.String

IsRegex RE ByteString Source # 
Instance details

Defined in Text.RE.TDFA.ByteString.Lazy

IsRegex RE ByteString Source # 
Instance details

Defined in Text.RE.TDFA.ByteString

IsRegex RE Text Source # 
Instance details

Defined in Text.RE.TDFA.Text.Lazy

IsRegex RE Text Source # 
Instance details

Defined in Text.RE.TDFA.Text

IsRegex RE (Seq Char) Source # 
Instance details

Defined in Text.RE.TDFA.Sequence

data SearchReplace re s Source #

contains a compiled RE and replacement template

Constructors

SearchReplace 

Fields

  • getSearch :: !re

    the RE to match a string to replace

  • getTemplate :: !s

    the replacement template with ${cap} used to identify a capture (by number or name if one was given) and $$ being used to escape a single $

Instances
Functor (SearchReplace re) Source # 
Instance details

Defined in Text.RE.ZeInternals.Types.SearchReplace

Methods

fmap :: (a -> b) -> SearchReplace re a -> SearchReplace re b #

(<$) :: a -> SearchReplace re b -> SearchReplace re a #

(Show re, Show s) => Show (SearchReplace re s) Source # 
Instance details

Defined in Text.RE.ZeInternals.Types.SearchReplace

Methods

showsPrec :: Int -> SearchReplace re s -> ShowS #

show :: SearchReplace re s -> String #

showList :: [SearchReplace re s] -> ShowS #

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|]

LineNo

newtype LineNo Source #

our line numbers are of the proper zero-based kind

Constructors

ZeroBasedLineNo 

firstLine :: LineNo Source #

the first line in a file

getLineNo :: LineNo -> Int Source #

extract a conventional 1-based line number

lineNo :: Int -> LineNo Source #

inject a conventional 1-based line number

Replace