Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1. Re:  Is there an "unscan" function? (Christian Maeder)
   2. Re:  LYAH Control.Monad.Writer tell (TJ Takei)


----------------------------------------------------------------------

Message: 1
Date: Mon, 16 Jan 2012 09:14:50 +0100
From: Christian Maeder <christian.mae...@dfki.de>
Subject: Re: [Haskell-beginners] Is there an "unscan" function?
To: Stephen Tetley <stephen.tet...@gmail.com>
Cc: beginners@haskell.org
Message-ID: <4f13dc7a.30...@dfki.de>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Am 13.01.2012 19:19, schrieb Stephen Tetley:
> Hi Jeffrey
>
> My version actually contains an error, it should be:
>
> unscan :: (a ->  a ->  b) ->  [a] ->  [b]
> unscan f (a:b:bs) = f a b : unscan f (b:bs)
> unscan _ _        = []
>
> A slightly less concise, but optimized version avoids putting the
> second element back in a list:
>
> unscan f (a:b:bs) = f a b : go b bs
>    where
>      go _ [] = []
>      go x (z:zs) = f x z : go z zs
> unscan _ _        = []

This version contains duplicate code: The first line could be:

   unscan f (a : bs) = go a bs

"putting the second element back" can be avoided by @-Patterns!

   unscan f (a : bs@(b : _)) = f a b : unscan bs

Cheers Christian



------------------------------

Message: 2
Date: Mon, 16 Jan 2012 00:32:51 -0800
From: TJ Takei <tj.ta...@gmail.com>
Subject: Re: [Haskell-beginners] LYAH Control.Monad.Writer tell
To: dmcbr...@neondsl.com
Cc: Beginners@haskell.org
Message-ID:
        <cagyeonwgotsdqlbcbskfguadkkerqvlzq5fhphmnsdq-zx9...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Thanks, David.
I'm quite relieved to know there is a better way to make a correct/full use
of the standard library.
"newtype" seems powerful, but in this case I learned through my hardship
that
[1] it deviates from good use of the library, and even worse
[2] I had to instantiate the "tell" myself. - despite of DRY pricipal.
The author may have a different intent to teach me "newtype" example,
but... oh well.
Thanks again for your kind elaboration.
TJ


On Sun, Jan 15, 2012 at 11:52 PM, David McBride <toa...@gmail.com> wrote:

> Reading that chapter, he seemed to have veered off course at some
> point.  He started having you implement your own simple writer type,
> but he stopped short of actually making it usable, then he started
> showing you how you would use the real writer class.  Unless I'm
> mistaken, he also didn't tell you how to reimplement logNumber with
> the real library, so of course the code didn't work.
>
> So the tell class is part of the MonadWriter class, which he didn't
> explain the point of (along with listen).  Tell just takes a list of
> things and adds them to the list of things you have.  The reason why
> his Writer class has a tuple, is that in addition to concatenating log
> messages, when you do a return from runWriter, you will get a first
> argument in a tuple.  That argument ends up being the last item that
> was returned or the last value returned from any monad passed as an
> argument into listen.
>
> Why would it do that?  Well I don't think it is used very often (or
> possibly at all), but originally the idea was that the writer monad
> can encompass both the ability to track what has happened in a program
> and also its final return value.  I'm having trouble thinking of a use
> for it, perhaps returning a failure code from a compilation, as well
> as the log of messages?  Generally if you wanted to keep state you
> would use the state monad for something like that, which allows you to
> query it as well as set it.
>
> The actual running code that you would have at that point in the book
> would be:
>
> import Data.Monoid
> import Control.Monad.Writer
>
> logNumber :: Int -> Writer [String] Int
> logNumber x = do
>  tell ["Got number: " ++ show x]
>  return x
>
> multWithLog :: Writer [String] Int
> multWithLog = do
>    a <- logNumber 3
>    b <- logNumber 5
>    tell ["Gonna multiply these two"]
>    return (a*b)
>
> main = putStrLn . show $ runWriter multWithLog
>
> which returns
> (15,["Got number: 3","Got number: 5","Gonna multiply these two"])
>
> On Sun, Jan 15, 2012 at 8:07 PM, TJ Takei <tj.ta...@gmail.com> wrote:
> > Hi
> >
> > I have a trouble to run an example of "Learn Your A Haskell.." Chap 13
> > below:
> >
> > ========
> > import Data.Monoid
> > --Don't import Control.Monad.Writer
> >
> > newtype Writer w a = Writer { runWriter :: (a, w) }
> >
> > instance (Monoid w) => Monad (Writer w) where
> >     return x = Writer (x, mempty)
> >     (Writer (x,v)) >>= f = let (Writer (y, v')) = f x in Writer (y, v
> > `mappend` v')
> >
> > --Define tell
> > tell :: [String] -> Writer [String] Int
> > tell w = Writer (0, w)  -- what'sa hell "0" for ???!!!
> >
> > logNumber :: Int -> Writer [String] Int
> > logNumber x = Writer (x, ["Got number: " ++ show x])
> >
> > multWithLog :: Writer [String] Int
> > multWithLog = do
> >     a <- logNumber 3
> >     b <- logNumber 5
> >     tell ["Gonna multiply these two"]
> >     return (a*b)
> >
> > main = putStrLn . show $ runWriter multWithLog
> > ========
> >
> > I changed two places to run it without error:
> > [1] Ambiguity error of Writer, uneless I comment out "import
> > Control.Monad.Writer", and
> > [2] Define tell function
> >
> > My questions are:
> > Why does LYAH sample fail as is?
> > Do the changes above look reasonable?
> > I'm not certain about my "tell". Where is the correct instantiation of
> > "tell" included?
> >
> > Thanks,
> > TJ
> >
> >
> > _______________________________________________
> > Beginners mailing list
> > Beginners@haskell.org
> > http://www.haskell.org/mailman/listinfo/beginners
> >
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120116/122b581a/attachment-0001.htm>

------------------------------

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 43, Issue 21
*****************************************

Reply via email to