Hello all! I’m trying to use fold
and putChar
to implement putStr
but I somehow get stuck.
Here are what I’ve done so far :
First I declare the type of putString
function :
putString :: String -> IO ()
Notice that since foldr
has the following type :
foldr :: Foldable t => (a -> b -> b) -> b -> t a -> b
Comparing to our putString
’s type, we can infer that in our case foldr
has to be :
foldr :: Foldable [] => (Char -> IO () -> IO ()) -> IO () -> String -> IO ()
I defined the function body as follows :
putString xs = foldr (\x acc -> putChar x) (return ()) xs
However, this isn’t the function I want.
I think the problem here might be putChar
is an I/O action and I/O action will keep the “last value” which is the “head” of the string in my case! So it can only return the “head” of the string. The correct way might be to use foldl
and make every call of putChar
function returns, instead of only return once.
I was wondering if I analyse how the putString
function behaves correctly? I also want some hints to modify this cute little function to make it works like putStr
.
Any advice is of great help!
You’re pretty close! Notice that the lambda \x acc -> putChar x
needs to have type Char -> IO () -> IO ()
, so the acc
value has type IO ()
, and so does putChar x
. An IO ()
represents a promise to take some action involving the real world; you haven’t actually taken that action until a final IO ()
containing all of the actions you want to do is ultimately provided as the result of main
. So the acc
value here is the key; it represents the promise of printing ‘the rest of the string’, and what you want to return is a promise of printing ‘the character in x
, followed by the rest of the string’. To do that, you should combine the two actions sequentially. You can do that in any Monad
with the >>
operator.
3 Likes
Oh! This works just like magic!
This is how I modified the code :
putString xs = foldr (\x acc -> putChar x >> acc) (return ()) xs
I think I need to take a careful look at how this works, because I don’t know how acc
changes in the folding process.
Thank you very much!
Do have a think about it for yourself, but as we’ve observed before, it’s usually more clarifying to think of foldr
not as something that changes an accumulator, but as something that replaces the (:)
and []
constructors of a list.
Printing the string "hello"
, which is the same as the list 'h' : 'e' : 'l' : 'l' : 'o' : []
, is just a matter of sequentially putChar
ing each character—what you will get with the foldr
you found is equivalent to putChar 'h' >> putChar 'e' >> putChar 'l' >> putChar 'l' >> putChar 'o' >> return ()
. And, after wrapping each element with putChar
, that’s just a constructor replacement with (>>)
where the (:)
was and return ()
where the []
was! The lambda \x acc -> putChar x >> acc
does both the wrapping and the (>>)
replacement in a single step. It might be clearer if you separate out the two steps:
putString xs = foldr (>>) (return ()) $ map putChar xs
The foldr (>>) (return ())
pattern, by the way, is common enough to have its own name: sequence_
. And the composition of sequence_
with a map
(or, generalizing from lists to any Functor
+Foldable
, an fmap
) is mapM_
. So taking full advantage of the base library (without using putStr
itself, of course), one might write:
putString = mapM_ putChar
(One last note: nothing done in this thread actually requires the full power of a Monad
; conceptually, all that is needed is an Applicative
, but every Monad
is also Applicative
. For historical reasons, the operators and functions (>>)
, return
, sequence_
, and mapM_
are all specialized to the more restrictive Monad
; their more general Applicative
equivalents are (*>)
, pure
, sequenceA_
, and traverse_
. Some Haskellers prefer using the Monad
set when they can, and I stuck to that convention in this thread based on your use of return
. Other Haskellers—myself usually included—prefer using the Applicative
set everywhere, because there is never a case when the Applicative
version won’t work but the Monad
version will. This is a taste thing on which you’ll have to develop your own opinion.)
6 Likes