
On Friday 02 July 2010 08:58:56, prad wrote:
On Thu, 1 Jul 2010 22:31:28 -0700
prad
wrote: so back to the drawing board!
here's what emerged:
====== #!/usr/bin/env runghc
module Main where
import Useful as U
main = do
let str = "This is original string" let ss = ["orig","ing"] let rs = ["very orig","ucture"]
putStrLn $ head (multRepl str ss rs)
--multRepl :: String -> [String] -> [String] -> [String] multRepl [] _ _ = [] multRepl str (s:ss) (r:rs) = do let newStr = U.replace str s r if (length ss) == 0
don't do that. If you want to know whether a list is empty, use null. if null ss then ... calculating the length of a list can be very costly.
then return newStr else multRepl newStr ss rs =======
What you probably want is multRepl [] _ _ = [] multRepl str (s:ss) (r:rs) = let newStr = U.replace str s r in multRepl newStr ss rs multRepl str _ _ = str
this does produce the correct output: This is very original structure
and here are my questions:
1. the type *Main Useful> :t multRepl multRepl :: (Eq t) => [t] -> [[t]] -> [[t]] -> [[t]]
but i have it returning newStr which equals U.replace str s r and the type of U.replace is String as shown below *Main Useful> :t Useful.replace Useful.replace :: (Eq a) => [a] -> [a] -> [a] -> [a]
so why is it returning [String] when newStr isn't a list of strings?
Because return in Haskell is entirely different from the return you may know from C/Java/... In Haskell, return is an ordinary function with the type return :: Monad m => a -> m a The first equation of multRepl, multRepl [] _ _ = [] says multRepl's result is some list type ([a], with an as yet unkown a) later, you have if something then return newStr else ... newStr is a list of something (by the type of Useful.replace, newStr has the same type as multRepl's first argument), so, by the type of return, multRepl's result must be have the type m ([b]) for some Monad m and some type b (the type of elements of str). Together with what we know from the first equation, it follows m = [] (indeed, [] is a Monad), so the result type is [[b]]
2. is the way i've done it proper haskellian? it took me quite some time to think this out trying to find my way through the fog of imperative programming.
Bad argument order. If you had replace pattern replacement string you could make multRepl pats reps = foldr (.) id (zipWith replace pats reps) Using a higher order combinator like foldr is more haskellish than explicit recursion :)
(my apologies for replying to my own posts - as well as my appreciation for your assistance)