
A few simple questions: What standard library function can be used to replace substring in a string (or sub-list in a list) ? I wrote my own version, please criticize: -- replace all occurances of "123" with "58" in a string: test = replStr "abc123def123gh123ikl" "123" "58" {-- In a string replace all occurances of an 'old' substring with a 'new' substring --} replStr str old new = foldr ((\newSub before after -> before ++ newSub ++ after) new) [] chunks where chunks = splitStr str old {-- Split string into a list of chunks. Chunks are substrings located in a string between 'sub' substrings --} splitStr str sub = mkChunkLst str sub [] where -- mkChunkLst 'src string' 'substr-to-extract' 'list of chunks' -- makes list of chunks located between 'substr-to-extract' pieces in src string mkChunkLst [] _ chunkLst = chunkLst mkChunkLst str sub chunkLst = mkChunkLst after sub (chunkLst ++ [chunk]) where (chunk, _, after) = takeOut str sub [] [] {-- Take out substring from a string. String is divided into: "before substr" ++ "match" ++ "after substr" where 'match' is substring to split out --} takeOut after [] before match = (before, match, after) takeOut [] _ before match = (before, match, []) takeOut (x:xs) (y:ys) before match | x == y = takeOut xs ys before (match ++ [x]) | otherwise = takeOut xs (y:ys) (before ++ match ++ [x]) [] -- Dmitri O. Kondratiev dokondr@gmail.com http://www.geocities.com/dkondr

Dmitri O.Kondratiev wrote:
I wrote my own version, please criticize:
-- replace all occurances of "123" with "58" in a string: test = replStr "abc123def123gh123ikl" "123" "58"
This is a tricky problem: first of all, you fail your own test! ;-) *Main> test "abc58def58gh58ikl58" (Note the extra 58 at the end.) Other common pitfalls: *Main> replStr "abc1123def" "123" "58" "abc1158def58" (extra 1 ?) *Main> replStr "abc12123def" "123" "58" "abc121258def58" (extra 12 ?) A useful function from Data.List: stripPrefix (Of course, there are more efficient string match algorithms) Regards, Zun.

Roberto thanks!
Shame on me, to post code without enough testing :(
Yet, thanks to your comments *I think* I have found the bugs you wrote about
and now my code works, please see corrected version below.
Extra substring at the end was a result of using foldr with initial element
of []. I fixed this with foldl and first chunk as its initial element.
Incomplete substitution in case of duplicate elements in the pattern was a
bug in my 'takeOut' function that I have also fixed.
Stiil the problem that I have not yet designed solution for is when a
substring to replace extends from the end of a string to the next string. In
other words - first part of substring ends the first string and second part
of substring starts the second string. My algorithm currently does not
account for such a case.
On the side: The more I use Haskell - the more I like it ! It helps me think
about the problem I solve much more clearly then when I use imperative
language.
Corrected code:
-- replace all occurances of "123" with "58" in a string:
test = replStr "abc123def123gh123ikl" "123" "58"
{--
In a string replace all occurances of an 'old' substring with a 'new'
substring
--}
replStr str old new = foldl ((\newSub before after -> before ++ newSub ++
after) new) firstChunk otherChunks
where chunks = splitStr str old
firstChunk = head chunks
otherChunks = tail chunks
{--
Split string into a list of chunks.
Chunks are substrings located in a string between 'sub' substrings
--}
splitStr str sub = mkChunkLst str sub []
where
-- mkChunkLst 'src string' 'substr-to-extract' 'list of chunks'
-- makes list of chunks located between 'substr-to-extract' pieces in
src string
mkChunkLst [] _ chunkLst = chunkLst
mkChunkLst str sub chunkLst = mkChunkLst after sub (chunkLst ++
[chunk])
where
(chunk, _, after) = takeOut str sub [] []
{--
Take out substring from a string.
String is divided into:
"before substr" ++ "match" ++ "after substr"
where 'match' is substring to split out
--}
takeOut after [] before match = (before, match, after)
takeOut [] _ before match = (before, match, [])
takeOut (x:xs) (y:ys) before match
| x == y = takeOut xs ys before (match ++ [x])
| otherwise = takeOut xs (y:ys) (before ++ [x]) []
On Tue, Jul 22, 2008 at 7:39 PM, Roberto Zunino
Dmitri O.Kondratiev wrote:
I wrote my own version, please criticize:
-- replace all occurances of "123" with "58" in a string: test = replStr "abc123def123gh123ikl" "123" "58"
This is a tricky problem: first of all, you fail your own test! ;-)
*Main> test "abc58def58gh58ikl58"
(Note the extra 58 at the end.)
Other common pitfalls:
*Main> replStr "abc1123def" "123" "58" "abc1158def58"
(extra 1 ?)
*Main> replStr "abc12123def" "123" "58" "abc121258def58"
(extra 12 ?)
A useful function from Data.List: stripPrefix
(Of course, there are more efficient string match algorithms)
Regards, Zun.
-- Dmitri O. Kondratiev dokondr@gmail.com http://www.geocities.com/dkondr

2008/7/22 Dmitri O.Kondratiev
On the side: The more I use Haskell - the more I like it ! It helps me think about the problem I solve much more clearly then when I use imperative language.
If I want to replace a substring in a string, then I would search my string left to right, looking for any occurrence of the substring. If I find such an occurrence, I would replace it and continue searching from immediately after the replacement. This algorithm can be directly expressed in Haskell. More efficient algorithms do exist. replaceStr :: String -> String -> String -> String replaceStr [] old new = [] replaceStr str old new = loop str where loop [] = [] loop str = let (prefix, rest) = splitAt n str in if old == prefix -- found an occurrence? then new ++ loop rest -- yes: replace it else head str : loop (tail str) -- no: keep looking n = length old

2008/7/22 Ronald Guida
2008/7/22 Dmitri O.Kondratiev
: On the side: The more I use Haskell - the more I like it ! It helps me think about the problem I solve much more clearly then when I use imperative language.
If I want to replace a substring in a string, then I would search my string left to right, looking for any occurrence of the substring. If I find such an occurrence, I would replace it and continue searching from immediately after the replacement. This algorithm can be directly expressed in Haskell. More efficient algorithms do exist.
Your idea but expressed in a more elegant fashion (maybe...) : replace :: (Eq a) => [a] -> [a] -> [a] -> [a] replace _ _ [] = [] replace old new xs@(y:ys) = case stripPrefix old xs of Nothing -> y : replace old new ys Just ys' -> new ++ replace old new ys' -- Jedaï

Ronald,
Your algoritm is more simple and so it is better, I agree.
My algorithm is different and consists of two steps:
1) Split source string into a list of chunks not containing substring to be
replaced.
2) Concatenate chunks inserting new substring in between chuncks.
With this approach I get a 'bonus' function of spliting string into chunks
:)
*
Tue Jul 22 16:38:53 EDT 2008 **Ronald Guida* oddron at
gmail.com
Roberto thanks! Shame on me, to post code without enough testing :( Yet, thanks to your comments *I think* I have found the bugs you wrote about and now my code works, please see corrected version below. Extra substring at the end was a result of using foldr with initial element of []. I fixed this with foldl and first chunk as its initial element. Incomplete substitution in case of duplicate elements in the pattern was a bug in my 'takeOut' function that I have also fixed. Stiil the problem that I have not yet designed solution for is when a substring to replace extends from the end of a string to the next string. In other words - first part of substring ends the first string and second part of substring starts the second string. My algorithm currently does not account for such a case.
On the side: The more I use Haskell - the more I like it ! It helps me think about the problem I solve much more clearly then when I use imperative language.
Corrected code:
-- replace all occurances of "123" with "58" in a string: test = replStr "abc123def123gh123ikl" "123" "58"
{-- In a string replace all occurances of an 'old' substring with a 'new' substring --} replStr str old new = foldl ((\newSub before after -> before ++ newSub ++ after) new) firstChunk otherChunks where chunks = splitStr str old firstChunk = head chunks otherChunks = tail chunks {-- Split string into a list of chunks. Chunks are substrings located in a string between 'sub' substrings --} splitStr str sub = mkChunkLst str sub [] where -- mkChunkLst 'src string' 'substr-to-extract' 'list of chunks' -- makes list of chunks located between 'substr-to-extract' pieces in src string mkChunkLst [] _ chunkLst = chunkLst mkChunkLst str sub chunkLst = mkChunkLst after sub (chunkLst ++ [chunk]) where (chunk, _, after) = takeOut str sub [] []
{-- Take out substring from a string. String is divided into: "before substr" ++ "match" ++ "after substr" where 'match' is substring to split out --}
takeOut after [] before match = (before, match, after) takeOut [] _ before match = (before, match, []) takeOut (x:xs) (y:ys) before match | x == y = takeOut xs ys before (match ++ [x]) | otherwise = takeOut xs (y:ys) (before ++ [x]) []
On Tue, Jul 22, 2008 at 7:39 PM, Roberto Zunino
wrote: Dmitri O.Kondratiev wrote:
I wrote my own version, please criticize:
-- replace all occurances of "123" with "58" in a string: test = replStr "abc123def123gh123ikl" "123" "58"
This is a tricky problem: first of all, you fail your own test! ;-)
*Main> test "abc58def58gh58ikl58"
(Note the extra 58 at the end.)
Other common pitfalls:
*Main> replStr "abc1123def" "123" "58" "abc1158def58"
(extra 1 ?)
*Main> replStr "abc12123def" "123" "58" "abc121258def58"
(extra 12 ?)
A useful function from Data.List: stripPrefix
(Of course, there are more efficient string match algorithms)
Regards, Zun.
-- Dmitri O. Kondratiev dokondr@gmail.com http://www.geocities.com/dkondr
-- Dmitri O. Kondratiev dokondr@gmail.com http://www.geocities.com/dkondr
participants (4)
-
Chaddaï Fouché
-
Dmitri O.Kondratiev
-
Roberto Zunino
-
Ronald Guida