File: stdlib_re_replace_func.txt

package info (click to toggle)
erlang 1%3A27.3.4.1%2Bdfsg-1
  • links: PTS, VCS
  • area: main
  • in suites: trixie
  • size: 225,000 kB
  • sloc: erlang: 1,658,966; ansic: 405,769; cpp: 177,850; xml: 82,435; makefile: 15,031; sh: 14,401; lisp: 9,812; java: 8,603; asm: 6,541; perl: 5,836; python: 5,484; sed: 72
file content (82 lines) | stat: -rw-r--r-- 3,350 bytes parent folder | download | duplicates (2)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82

  replace(Subject, RE, Replacement)

  There is no documentation for replace(Subject, RE, Replacement,
  [])

  replace(Subject, RE, Replacement, Options)

  Replaces the matched part of the Subject string with 
  Replacement.

  The permissible options are the same as for run/3, except that
  option capture is not allowed. Instead a {return, ReturnType}
  is present. The default return type is iodata, constructed in a
  way to minimize copying. The iodata result can be used directly
  in many I/O operations. If a flat list/0 is desired, specify 
  {return, list}. If a binary is desired, specify {return, binary}.

  As in function run/3, an mp/0 compiled with option unicode
  requires Subject to be a Unicode charlist(). If compilation is
  done implicitly and the unicode compilation option is specified
  to this function, both the regular expression and Subject are to
  specified as valid Unicode charlist()s.

  If the replacement is given as a string, it can contain the
  special character &, which inserts the whole matching expression
  in the result, and the special sequence `N (where N is an integer >
  0), \gN, or \g{N}, resulting in the subexpression number N,
  is inserted in the result. If no subexpression with that number is
  generated by the regular expression, nothing is inserted.

  To insert an & or a \ in the result, precede it with a \. Notice
  that Erlang already gives a special meaning to \ in literal
  strings, so a single \ must be written as "\\" and therefore a
  double \ as "\\\\".

  Example:

    1> re:replace("abcd","c","[&]",[{return,list}]).
    "ab[c]d"

  while

    2> re:replace("abcd","c","[\\&]",[{return,list}]).
    "ab[&]d"

  If the replacement is given as a fun, it will be called with the
  whole matching expression as the first argument and a list of
  subexpression matches in the order in which they appear in the
  regular expression. The returned value will be inserted in the
  result.

  Example:

    3> re:replace("abcd", ".(.)",
        fun(Whole, [<<C>>]) ->
             <<$#, Whole/binary, $-, (C - $a + $A), $#>>
        end,
        [{return, list}]).
    "#ab-B#cd"

  Note

    Non-matching optional subexpressions will not be included in
    the list of subexpression matches if they are the last
    subexpressions in the regular expression. Example: The
    regular expression "(a)(b)?(c)?" ("a", optionally followed
    by "b", optionally followed by "c") will create the following
    subexpression lists:

     • [<<"a">>, <<"b">>, <<"c">>] when applied to the string 
       "abc"

     • [<<"a">>, <<>>, <<"c">>] when applied to the string 
       "acx"

     • [<<"a">>, <<"b">>] when applied to the string "abx"

     • [<<"a">>] when applied to the string "axx"

  As with run/3, compilation errors raise the badarg exception. 
  compile/2 can be used to get more information about the error.