From: Emre Sevinc
Subject: Replacing all occurences of a string (maybe a candidate for cookbook)
Date: 
Message-ID: <87oe8h3v8z.fsf@ileriseviye.org>
I was trying to find a function which replaced all
occurences of a substring with another. Lisp Cookbook at

 http://cl-cookbook.sourceforge.net/strings.html#substrings

didn't seem to contain what I exactly wanted.

So I tried a first shoot:

(defun replace-all (old new string)
  (let ((index2 (search old string)))
	       (replace string new :start1 index2)
	       (loop for index = (search old string :start2 (1+ index2))
		     while index
		     do 
		     (replace string new :start1 index) 
		     (setf index2 index))))

However this one has the obvious bug that when your new
substring is longer than the older one there is overlapping,
overwriting, etc.:

CL-USER> (setf *pascal* "one two three four quic quick quic quick")
"one two three four quic quick quic quick"

CL-USER> (replace-all "quic" "quick" *pascal*)
NIL

CL-USER> *pascal*
"one two three four quickquick quickquick"

What I need is a result like that:

"one two three four quick quick quick quick"

which means that whole string must be modified to be longer.

Any suggestions for such a function which basically does
something like the search/replace functionality in editors
(to replace all the occurences)?

I think such a function would be a very good candidate for
the related part of the Lisp Cookbook.


Happy hacking,

-- 
Emre Sevinc

eMBA Software Developer         Actively engaged in:
http:www.bilgi.edu.tr           http://ileriseviye.org
http://www.bilgi.edu.tr         http://fazlamesai.net
Cognitive Science Student       http://cazci.com
http://www.cogsci.boun.edu.tr

From: Peter Seibel
Subject: Re: Replacing all occurences of a string (maybe a candidate for cookbook)
Date: 
Message-ID: <m2slxt3t57.fsf@gigamonkeys.com>
Emre Sevinc <·····@bilgi.edu.tr> writes:

> I was trying to find a function which replaced all
> occurences of a substring with another. Lisp Cookbook at
>
>  http://cl-cookbook.sourceforge.net/strings.html#substrings

Hmmm, maybe the maintainer of the cl-cookbook can point you to a good
Perl compatible regexp library in Common Lisp.

-Peter

-- 
Peter Seibel           * ·····@gigamonkeys.com
Gigamonkeys Consulting * http://www.gigamonkeys.com/
Practical Common Lisp  * http://www.gigamonkeys.com/book/
From: André Thieme
Subject: Re: Replacing all occurences of a string (maybe a candidate for cookbook)
Date: 
Message-ID: <dcmpro$3ht$1@ulric.tng.de>
Peter Seibel schrieb:
> Emre Sevinc <·····@bilgi.edu.tr> writes:
> 
> 
>>I was trying to find a function which replaced all
>>occurences of a substring with another. Lisp Cookbook at
>>
>> http://cl-cookbook.sourceforge.net/strings.html#substrings
> 
> 
> Hmmm, maybe the maintainer of the cl-cookbook can point you to a good
> Perl compatible regexp library in Common Lisp.

Or Emre simply tries http://weitz.de/cl-ppcre/

;-)


Andr�
-- 
From: Emre Sevinc
Subject: Re: Replacing all occurences of a string (maybe a candidate for cookbook)
Date: 
Message-ID: <87zms0kabi.fsf@ileriseviye.org>
Andr� Thieme <······························@justmail.de> writes:

> Peter Seibel schrieb:
>> Emre Sevinc <·····@bilgi.edu.tr> writes:
>>
>>>I was trying to find a function which replaced all
>>>occurences of a substring with another. Lisp Cookbook at
>>>
>>> http://cl-cookbook.sourceforge.net/strings.html#substrings
>> Hmmm, maybe the maintainer of the cl-cookbook can point you to a good
>> Perl compatible regexp library in Common Lisp.
>
> Or Emre simply tries http://weitz.de/cl-ppcre/

Same suggestion was made in #lisp, however since I'm
talking about constant substrings (yes, every constatn
piece of string is also a valid regular expression, but that's not my
point) I think avoiding cl-ppcre would be better.

Do we really need regex functionality where a simple
"look for the occurences of that static string and
replace each with that..." would do?


-- 
Emre Sevinc

eMBA Software Developer         Actively engaged in:
http:www.bilgi.edu.tr           http://ileriseviye.org
http://www.bilgi.edu.tr         http://fazlamesai.net
Cognitive Science Student       http://cazci.com
http://www.cogsci.boun.edu.tr
From: Edi Weitz
Subject: Re: Replacing all occurences of a string (maybe a candidate for cookbook)
Date: 
Message-ID: <ur7dc67s6.fsf@agharta.de>
On Tue, 02 Aug 2005 11:33:05 +0300, Emre Sevinc <·····@bilgi.edu.tr> wrote:

> Same suggestion was made in #lisp, however since I'm talking about
> constant substrings (yes, every constatn piece of string is also a
> valid regular expression, but that's not my point) I think avoiding
> cl-ppcre would be better.
>
> Do we really need regex functionality where a simple "look for the
> occurences of that static string and replace each with that..."
> would do?

No, certainly not.  Untested:

  (defun replace-all (string part replacement &key (test #'char=))
    (with-output-to-string (out)
      (loop with part-length = (length part)
            for old-pos = 0 then (+ pos part-length)
            for pos = (search part string
                              :start2 old-pos
                              :test test)
            do (write-string string out
                             :start old-pos
                             :end (or pos (length string)))
            when pos do (write-string replacement out)
            while pos)))

However, depending on your implementation I'd nevertheless benchmark
against CL-PPCRE if you're concerned about speed.  Maybe it's
faster... :)

Cheers,
Edi.

-- 

Lisp is not dead, it just smells funny.

Real email: (replace (subseq ·········@agharta.de" 5) "edi")
From: Edi Weitz
Subject: Re: Replacing all occurences of a string (maybe a candidate for cookbook)
Date: 
Message-ID: <umzo065kc.fsf@agharta.de>
On Tue, 02 Aug 2005 10:51:37 +0200, Edi Weitz <········@agharta.de> wrote:

> However, depending on your implementation I'd nevertheless benchmark
> against CL-PPCRE if you're concerned about speed.  Maybe it's
> faster... :)

Below is a contrived example where CL-PPCRE easily wins:

···@vmware:/tmp$ cat foo.lisp
(in-package :cl-user)

(eval-when (:compile-toplevel :load-toplevel :execute)
  (asdf:oos 'asdf:load-op :cl-ppcre))

(defun replace-all (string part replacement &key (test #'char=))
  (declare #.ppcre::*standard-optimize-settings*)
  (declare (simple-string string part replacement))
  (with-output-to-string (out)
    (loop with part-length = (length part)
          for old-pos = 0 then (+ pos part-length)
          for pos = (search part string
                            :start2 old-pos
                            :test test)
          do (write-string string out
                           :start old-pos
                           :end (or pos (length string)))
          when pos do (write-string replacement out)
          while pos)))

(defun random-string (length)
  (with-output-to-string (out)
    (dotimes (i length)
      (write-char (code-char (+ #.(char-code #\a)
                                (random 26)))
                  out))))

(defun test (&optional (n 10000))
  (let* ((target (random-string (random (floor n 10))))
         (string (with-output-to-string (out)
                   (dotimes (i n)
                     (write-string (random-string (random 5)) out)
                     (write-string target out)))))
    (ext:gc :full t)
    (time (replace-all string target "frob"))
    (ext:gc :full t)
    (time (ppcre:regex-replace-all target string "frob"))
    (values)))

···@vmware:/tmp$ cmucl
; Loading #P"/home/edi/.cmucl-init".
CMU Common Lisp CVS 19b 19b-release-20050628-3 + minimal debian patches (19B), running on vmware
With core: /usr/lib/cmucl/lisp.core
Dumped on: Thu, 2005-07-28 12:52:09+02:00 on vmware
For support see http://www.cons.org/cmucl/support.html Send bug reports to the debian BTS.
or to ········@debian.org
type (help) for help, (quit) to exit, and (demo) to see the demos

Loaded subsystems:
    Python 1.1, target Intel x86
    CLOS based on Gerd's PCL 2004/04/14 03:32:47
* (load (compile-file "foo.lisp"))

; Python version 1.1, VM version Intel x86 on 02 AUG 05 11:34:43 am.
; Compiling: /tmp/foo.lisp 02 AUG 05 11:34:28 am


; loading system definition from /usr/local/lisp/Registry/cl-ppcre.asd into
; #<The ASDF0 package>
; registering #<SYSTEM #:CL-PPCRE {580DCB7D}> as CL-PPCRE
; Converted REPLACE-ALL.
; Compiling DEFUN REPLACE-ALL: 

; 
; 
; File: /tmp/foo.lisp

; In: DEFUN REPLACE-ALL

;   (LOOP WITH PART-LENGTH = #...)
; --> BLOCK LET LET LET ANSI-LOOP::LOOP-BODY TAGBODY 
; --> ANSI-LOOP::LOOP-REALLY-DESETQ 
; ==>
;   (SETQ OLD-POS (+ POS PART-LENGTH))
; Note: Doing signed word to integer coercion (cost 20) to OLD-POS.
; 
; Converted RANDOM-STRING.
; Compiling DEFUN RANDOM-STRING: 
; Converted TEST.
; Compiling DEFUN TEST: 
; Byte Compiling Top-Level Form: 

; Compilation unit finished.
;   1 note


; foo.x86f written.
; Compilation finished in 0:00:01.
T
* (test)

; Evaluation took:
;   0.2 seconds of real time
;   0.03 seconds of user run time
;   0.18 seconds of system run time
;   407,522,827 CPU cycles
;   1 page fault and
;   11,191,904 bytes consed.
; 

; Evaluation took:
;   0.04 seconds of real time
;   0.01 seconds of user run time
;   0.04 seconds of system run time
;   94,513,072 CPU cycles
;   27 page faults and
;   2,967,104 bytes consed.
; 
* (test)

; Evaluation took:
;   1.36 seconds of real time
;   0.34 seconds of user run time
;   1.03 seconds of system run time
;   2,736,817,142 CPU cycles
;   [Run times include 0.05 seconds GC run time]
;   0 page faults and
;   71,992,600 bytes consed.
; 

; Evaluation took:
;   0.09 seconds of real time
;   0.01 seconds of user run time
;   0.07 seconds of system run time
;   176,763,882 CPU cycles
;   0 page faults and
;   2,357,040 bytes consed.
; 
* (test)

; Evaluation took:
;   1.31 seconds of real time
;   0.2 seconds of user run time
;   1.11 seconds of system run time
;   2,609,271,422 CPU cycles
;   [Run times include 0.06 seconds GC run time]
;   0 page faults and
;   69,672,976 bytes consed.
; 

; Evaluation took:
;   0.09 seconds of real time
;   0.01 seconds of user run time
;   0.07 seconds of system run time
;   163,950,628 CPU cycles
;   0 page faults and
;   2,356,776 bytes consed.
; 
* (test)

; Evaluation took:
;   0.84 seconds of real time
;   0.13 seconds of user run time
;   0.71 seconds of system run time
;   1,679,279,328 CPU cycles
;   [Run times include 0.04 seconds GC run time]
;   0 page faults and
;   44,393,520 bytes consed.
; 

; Evaluation took:
;   0.06 seconds of real time
;   0.01 seconds of user run time
;   0.05 seconds of system run time
;   123,734,358 CPU cycles
;   0 page faults and
;   2,339,432 bytes consed.
; 
* (test)

; Evaluation took:
;   0.2 seconds of real time
;   0.01 seconds of user run time
;   0.2 seconds of system run time
;   411,365,678 CPU cycles
;   0 page faults and
;   11,429,936 bytes consed.
; 

; Evaluation took:
;   0.03 seconds of real time
;   0.0 seconds of user run time
;   0.03 seconds of system run time
;   63,108,753 CPU cycles
;   0 page faults and
;   2,314,536 bytes consed.
;

-- 

Lisp is not dead, it just smells funny.

Real email: (replace (subseq ·········@agharta.de" 5) "edi")
From: Christophe Rhodes
Subject: Re: Replacing all occurences of a string (maybe a candidate for cookbook)
Date: 
Message-ID: <sq7jf4lker.fsf@cam.ac.uk>
Edi Weitz <········@agharta.de> writes:

> Below is a contrived example where CL-PPCRE easily wins:

> (defun replace-all (string part replacement &key (test #'char=))
>   (declare #.ppcre::*standard-optimize-settings*)
>   (declare (simple-string string part replacement))
>   (with-output-to-string (out)
>     (loop with part-length = (length part)
>           for old-pos = 0 then (+ pos part-length)
>           for pos = (search part string
>                             :start2 old-pos
>                             :test test)
>           do (write-string string out
>                            :start old-pos
>                            :end (or pos (length string)))
>           when pos do (write-string replacement out)
>           while pos)))

> ;   (LOOP WITH PART-LENGTH = #...)
> ; --> BLOCK LET LET LET ANSI-LOOP::LOOP-BODY TAGBODY 
> ; --> ANSI-LOOP::LOOP-REALLY-DESETQ 
> ; ==>
> ;   (SETQ OLD-POS (+ POS PART-LENGTH))
> ; Note: Doing signed word to integer coercion (cost 20) to OLD-POS.

What happens if old-pos is declared to be of type fixnum?

Christophe
From: Edi Weitz
Subject: Re: Replacing all occurences of a string (maybe a candidate for cookbook)
Date: 
Message-ID: <uoe8g4oqy.fsf@agharta.de>
On Tue, 02 Aug 2005 11:09:48 +0100, Christophe Rhodes <·····@cam.ac.uk> wrote:

> What happens if old-pos is declared to be of type fixnum?

The compiler note goes away, the timings remain the same.

Cheers,
Edi.

-- 

Lisp is not dead, it just smells funny.

Real email: (replace (subseq ·········@agharta.de" 5) "edi")
From: Emre Sevinc
Subject: Re: Replacing all occurences of a string (maybe a candidate for cookbook)
Date: 
Message-ID: <87ll3kvbus.fsf@ileriseviye.org>
Edi Weitz <········@agharta.de> writes:

> On Tue, 02 Aug 2005 11:09:48 +0100, Christophe Rhodes <·····@cam.ac.uk> wrote:
>
>> What happens if old-pos is declared to be of type fixnum?
>
> The compiler note goes away, the timings remain the same.

I'm very impressed by the timings! I knew that CL-PPCRE has
beaten Perl's RegExp engine in some aspects but I didn't expect
it to beat a search-replace function in Lisp itself this much.

I must admit that, it was even contrary to my intuition at
the beginning, since we're talking about static pieces of
string. I think about using regex only when the job is 
about patterns, variable strings, etc. And I always prefer
"normal" string functions for the kinds of situation 
I presented (no matter which language I use be it JScript,
VBScript, C#, Perl, etc.).

As far as I can see from the messages, using fixnum
in order to optimize did not do any help, this made
me wonder if there's no hope left for optimizing it.

BTW, I still think a similar example must be put
in Lisp Cookbook to avoid frustration when people
examine Lisp for frequently-encountered string operations.

-- 
Emre Sevinc

eMBA Software Developer         Actively engaged in:
http:www.bilgi.edu.tr           http://ileriseviye.org
http://www.bilgi.edu.tr         http://fazlamesai.net
Cognitive Science Student       http://cazci.com
http://www.cogsci.boun.edu.tr
From: Edi Weitz
Subject: Re: Replacing all occurences of a string (maybe a candidate for cookbook)
Date: 
Message-ID: <ud5ow4m2y.fsf@agharta.de>
On Tue, 02 Aug 2005 14:04:27 +0300, Emre Sevinc <·····@bilgi.edu.tr> wrote:

> As far as I can see from the messages, using fixnum in order to
> optimize did not do any help, this made me wonder if there's no hope
> left for optimizing it.

As I said, CL-PPCRE uses BMH matchers which'll potentially buy you a
lot for long strings but they cons and are actually a disadvantage for
short strings.  Thus, there's really no reason for the "ordinary"
SEARCH operation to use this optimization and it can be disabled in
CL-PPCRE as well:

  <http://weitz.de/cl-ppcre/#use-bmh-matchers>

> BTW, I still think a similar example must be put in Lisp Cookbook to
> avoid frustration when people examine Lisp for
> frequently-encountered string operations.

You're very welcome to add stuff to the cookbook.  Send me your SF
account (create one if you don't have one) and I'll give you commit
access.

Cheers,
Edi.

-- 

Lisp is not dead, it just smells funny.

Real email: (replace (subseq ·········@agharta.de" 5) "edi")
From: Hakon Alstadheim
Subject: Re: Replacing all occurences of a string (maybe a candidate for cookbook)
Date: 
Message-ID: <CjHHe.3577$qE.901566@juliett.dax.net>
Emre Sevinc wrote:
> I was trying to find a function which replaced all
> occurences of a substring with another. Lisp Cookbook at
[snip]
> 
> However this one has the obvious bug that when your new
> substring is longer than the older one there is overlapping,
> overwriting, etc.:
[snip]

Edi Weitz gave you a good solution, but I think it is good to emphazize 
that Emre needs to take home a basic understanding: If you want to make 
a string longer by inserting stuff, this means you MUST cons up a new 
copy. This is a basic understanding that holds for all computer 
languages. Pointing Emre in the in the direction of 
http://weitz.de/cl-ppcre/ without mentioning this is doing h(im/er) a 
disservice. (note the name in that link btw.). Perl and VB and the like 
will paper over this fact, but it still holds for those languages aswell.
From: Edi Weitz
Subject: Re: Replacing all occurences of a string (maybe a candidate for cookbook)
Date: 
Message-ID: <u8xzk4kyi.fsf@agharta.de>
On Tue, 02 Aug 2005 09:48:18 GMT, Hakon Alstadheim <·····@alstadheim.priv.no> wrote:

> I think it is good to emphazize that Emre needs to take home a basic
> understanding: If you want to make a string longer by inserting
> stuff, this means you MUST cons up a new copy. This is a basic
> understanding that holds for all computer languages. [...] Perl and
> VB and the like will paper over this fact, but it still holds for
> those languages aswell.

Good point.  In Perl, e.g., you can write stuff like this

  #!/usr/bin/perl -l

  $a = "abcdefghi";
  $b = "abcdefghi";
  $c = "abcdefghi";
  (substr $a, 3, 3) = "XXX";
  (substr $b, 2, 4) = "XXX";
  (substr $c, 4, 2) = "XXX";
  print $a;
  print $b;
  print $c;

and expect a result that looks like so:

  ···@vmware:~$ perl /tmp/foo.pl
  abcXXXghi
  abXXXghi
  abcdXXXghi

However, I don't think it's specified somewhere whether the results
are actually EQ (in the sense of Lisp) to the strings you started
with.  (Not to mention that this concept of EQ doesn't really exist in
Perl.)

FWIW, for my cookbook (the not-yet-existing book, not the website) I
once wrote for fun a little macro that tries to mimic the behaviour
above.  The kick was to keep object identity if possible.

[Only lightly tested, the usual disclaimers apply.]

-------------------------- start of foo.lisp --------------------------

  (in-package :cl-user)

  #-:lispworks
  (eval-when (:compile-toplevel :load-toplevel :execute)
    (defmacro with-unique-names ((&rest bindings) &body body)
    ;; see <http://www.cliki.net/WITH-UNIQUE-NAMES>
      `(let ,(mapcar #'(lambda (binding)
                         (destructuring-bind (var prefix)
                             (if (consp binding)
                               binding
                               (list binding binding))
                           `(,var (gensym ,(string prefix)))))
                     bindings)
         ,@body)))

  (defun subseq* (sequence start &optional (end (length sequence)))
    (subseq sequence start end))

  (define-setf-expander subseq* (sequence start &optional (end (length sequence))
                                                &environment env)
    (multiple-value-bind (temps vals stores setter getter)
        (get-setf-expansion sequence env)
      (with-unique-names (%sequence %start %end new-length diff store rest)
        (let ((temp (first stores)))
          (values (append (list %sequence %start %end) temps)
                  (append (list getter start end) vals)
                  (list store)
                  `(let* ((,new-length (length ,store))
                          (,diff (- ,new-length (- ,%end ,%start)))
                          ,temp)
                    (cond ((zerop ,diff)
                            (setq ,temp (replace ,%sequence ,store :start1 ,%start
                                                                   :end1 ,%end)))
                          ((listp ,%sequence)
                            (setq ,temp (cons nil ,%sequence))
                            (let ((,rest (nthcdr ,%start ,temp)))
                              (setf (cdr ,rest)
                                      (nconc (make-list ,new-length)
                                             (nthcdr (- ,%end ,%start)
                                                     (cdr ,rest)))
                                    ,temp (cdr ,temp))
                              (replace ,temp ,store :start1 ,%start
                                                    :end1 (+ ,%end ,diff))))
                          ((and (minusp ,diff)
                                (array-has-fill-pointer-p ,%sequence))
                            (setq ,temp (replace ,%sequence ,store :start1 ,%start
                                                                   :end1 ,%end))
                            (replace ,temp ,temp :start1 (+ ,%start ,new-length)
                                                 :start2 ,%end)
                            (setf (fill-pointer ,temp) (+ (length ,%sequence) ,diff)))
                          ((and (plusp ,diff)
                                (adjustable-array-p ,%sequence))
                            (setq ,temp (adjust-array ,%sequence
                                                      (+ (length ,%sequence) ,diff)))
                            (when (array-has-fill-pointer-p ,temp)
                              (setf (fill-pointer ,temp)
                                    (+ (length ,%sequence) ,diff)))
                            (replace ,temp ,temp :start1 (+ ,%start ,new-length)
                                                 :start2 ,%end)
                            (replace ,temp ,store :start1 ,%start :end1 (+ ,%start ,new-length)))
                          (t
                            (setq ,temp (make-array (+ (length ,%sequence) ,diff)
                                                    :element-type (array-element-type
                                                                   ,%sequence)
                                                    :fill-pointer (array-has-fill-pointer-p
                                                                   ,%sequence)))
                            (replace ,temp ,%sequence :end1 ,%start
                                                      :end2 ,%start)
                            (replace ,temp ,%sequence :start1 (+ ,%end ,diff)
                                                      :start2 ,%end)
                            (replace ,temp ,store :start1 ,%start
                                                  :end1 (+ ,%end ,diff))))
                    ,setter
                    ,store)
                  `(subseq ,%sequence ,%start ,%end))))))

  (defun string-test (string x y)
    (let ((copy string))
      (setf (subseq* string x y) "XXX")
      (print (list string (eq string copy)))))

  (defun list-test (x y)
    (let* ((list (list 1 2 3 4 5 6 7 8 9))
           (copy list))
      (setf (subseq* list x y) (list 'x 'y 'z))
      (print (list list (eq list copy)))))

  (defun create-test-string (init fill-pointer adjustable)
    (make-array (length init)
                :element-type (array-element-type init)
                :fill-pointer fill-pointer
                :adjustable adjustable
                :initial-contents init))

  (defun test ()
    (let ((abc "abcdefghi"))
      (string-test (create-test-string abc nil nil) 3 6)
      (string-test (create-test-string abc nil nil) 4 6)
      (string-test (create-test-string abc nil nil) 2 6)
      (terpri)
      (string-test (create-test-string abc t nil) 3 6)
      (string-test (create-test-string abc t nil) 4 6)
      (string-test (create-test-string abc t nil) 2 6)
      (terpri)
      (string-test (create-test-string abc nil t) 3 6)
      (string-test (create-test-string abc nil t) 4 6)
      (string-test (create-test-string abc nil t) 2 6)
      (terpri)
      (string-test (create-test-string abc t t) 3 6)
      (string-test (create-test-string abc t t) 4 6)
      (string-test (create-test-string abc t t) 2 6))
    (terpri)
    (list-test 3 6)
    (list-test 4 6)
    (list-test 2 6)
    (terpri)
    (list-test 0 0)
    (list-test 0 2)
    (list-test 8 9)
    (list-test 9 9)
    (values))

-------------------------- end of foo.lisp --------------------------

In LispWorks, this'll behave like so:

  CL-USER 63 > (test)

  ("abcXXXghi" T) 
  ("abcdXXXghi" NIL) 
  ("abXXXghi" NIL) 

  ("abcXXXghi" T) 
  ("abcdXXXghi" NIL) ;;; <-- see below
  ("abXXXghi" T) 

  ("abcXXXghi" T) 
  ("abcdXXXghi" T) 
  ("abXXXghi" NIL) 

  ("abcXXXghi" T) 
  ("abcdXXXghi" T) 
  ("abXXXghi" T) 

  ((1 2 3 X Y Z 7 8 9) T) 
  ((1 2 3 4 X Y Z 7 8 9) T) 
  ((1 2 X Y Z 7 8 9) T) 

  ((X Y Z 1 2 3 4 5 6 7 8 9) NIL) 
  ((X Y Z 3 4 5 6 7 8 9) NIL) 
  ((1 2 3 4 5 6 7 8 X Y Z) T) 
  ((1 2 3 4 5 6 7 8 9 X Y Z) T) 

Note that the second element of the fifth list is T and not NIL in
CMUCL and SBCL.  This is obviously due to the fact that arrays with a
fill pointer are "actually adjustable" even if they're not "expressly
adjustable."  (See CLHS glossary.)

At least it's good to know that in Common Lisp all of this is actually
specified... :)

Cheers,
Edi.

-- 

Lisp is not dead, it just smells funny.

Real email: (replace (subseq ·········@agharta.de" 5) "edi")
From: Emre Sevinc
Subject: Re: Replacing all occurences of a string (maybe a candidate for cookbook)
Date: 
Message-ID: <87hde8vbna.fsf@ileriseviye.org>
Hakon Alstadheim <·····@alstadheim.priv.no> writes:

> Emre Sevinc wrote:
>> I was trying to find a function which replaced all
>> occurences of a substring with another. Lisp Cookbook at
> [snip]
>> However this one has the obvious bug that when your new
>> substring is longer than the older one there is overlapping,
>> overwriting, etc.:
> [snip]
>
> Edi Weitz gave you a good solution, but I think it is good to
> emphazize that Emre needs to take home a basic understanding: If you
> want to make a string longer by inserting stuff, this means you MUST
> cons up a new copy. 

I knew I needed somethig like that, however I couldn't come up
with with-output-to-string macro. I always have hard time remembering
that the language has this kind of facility (I guess this is due to my
previous programming experience!)

> This is a basic understanding that holds for all
> computer languages. Pointing Emre in the in the direction of
> http://weitz.de/cl-ppcre/ without mentioning this is doing h(im/er) a
> disservice. (note the name in that link btw.). Perl and VB and the
> like will paper over this fact, but it still holds for those languages
> aswell.

I still appreciate the suggestions and explanations given. I hope
some of the people understood why I was looking for an alternative
other than using cl-ppcre.

Happy hacking,

-- 
Emre Sevinc

eMBA Software Developer         Actively engaged in:
http:www.bilgi.edu.tr           http://ileriseviye.org
http://www.bilgi.edu.tr         http://fazlamesai.net
Cognitive Science Student       http://cazci.com
http://www.cogsci.boun.edu.tr