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:  I wrote a state monad example - help me      make it more
      Haskellic (David Place)
   2. Re:  I wrote a state monad example - help me make it more
      Haskellic (Rohit Garg)
   3.  For class Monoid; better names than mempty & mappend might
      have been: mid (mident) & mbinop (KC)
   4. Re:  I wrote a state monad example - help me make it more
      Haskellic (aditya siram)
   5. Re:  Data.Typeable (Stephen Tetley)
   6. Re:  a problem with maps (Ertugrul Soeylemez)
   7. Re:  a problem with maps (David Place)
   8. Re:  a problem with maps (Yitzchak Gale)
   9. Re:  a problem with maps (Ertugrul Soeylemez)


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

Message: 1
Date: Sat, 23 Jul 2011 12:20:07 -0400
From: David Place <d...@vidplace.com>
Subject: Re: [Haskell-beginners] I wrote a state monad example - help
        me      make it more Haskellic
To: Rohit Garg <rpg....@gmail.com>
Cc: beginners@haskell.org
Message-ID: <2b63e193-7e03-49a2-89cd-bbfd716a7...@vidplace.com>
Content-Type: text/plain; charset=us-ascii

On Jul 23, 2011, at 11:56 AM, Rohit Garg wrote:

> Also, I'd like to make the RegisterVal type Word32, but when I do that, then
> ================
> initial_rf = [0,0,0,0]
> ================
> this line fails to typecheck.

I changed the RegisterVal type to Word32.  It works for me using GHCi version 
7.0.2.    Your code looks great!


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

Message: 2
Date: Sat, 23 Jul 2011 22:06:14 +0530
From: Rohit Garg <rpg....@gmail.com>
Subject: Re: [Haskell-beginners] I wrote a state monad example - help
        me make it more Haskellic
To: David Place <d...@vidplace.com>
Cc: beginners@haskell.org
Message-ID:
        <CAC1T7giNJCdP+CBq44Rs==dw9b-cbh-gydw8rzr0cu9u7dj...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

On Sat, Jul 23, 2011 at 9:50 PM, David Place <d...@vidplace.com> wrote:
> On Jul 23, 2011, at 11:56 AM, Rohit Garg wrote:
>
>> Also, I'd like to make the RegisterVal type Word32, but when I do that, then
>> ================
>> initial_rf = [0,0,0,0]
>> ================
>> this line fails to typecheck.
>

> I changed the RegisterVal type to Word32. ?It works for me using GHCi version 
> 7.0.2. ? ?Your code looks great!

Ah!, I was changing the type of RegisterID as well and then it was
complaining. For RegisterVal only, it works fine, thanks.

-- 
Rohit Garg

http://rpg-314.blogspot.com/



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

Message: 3
Date: Sat, 23 Jul 2011 11:41:19 -0700
From: KC <kc1...@gmail.com>
Subject: [Haskell-beginners] For class Monoid; better names than
        mempty & mappend might have been: mid (mident) & mbinop
To: beginners@haskell.org, haskell-cafe <haskell-c...@haskell.org>
Message-ID:
        <camlkxykx-mzmps1qx74pew9useghydow+ejezizmutvsn2q...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

It would be easier for beginners to "grok".

-- 
--
Regards,
KC



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

Message: 4
Date: Sat, 23 Jul 2011 14:25:52 -0500
From: aditya siram <aditya.si...@gmail.com>
Subject: Re: [Haskell-beginners] I wrote a state monad example - help
        me make it more Haskellic
To: Rohit Garg <rpg....@gmail.com>
Cc: beginners@haskell.org
Message-ID:
        <cajrreyjns1dbw51ohucjx0ihrr9-nyjiahwmscgzqkcyn84...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Hi Rohit,
I've refactored your program a little bit. Hope you don't mind. The
main change I made was, since there can only be four registers, to
create explicit datatypes for each register and turn your RegisterFile
datatype into a 4-tuple. The corresponding setter and getter,
store_operand and get_operand have also been changed to reflect the
new datatypes. This way there can never be errors with list indices
etc.

I've also used two new State monad functions of which you might be unaware:
1. modify :: modifies state with the given function.
2. mapM_ :: is like a "map" but takes a monadic action and applied it
to the given ist.

The output is stil the same as your code, but I've added a little type safety.

I haven't covered every detail of the changes but if you're reading
through it and get stuck, please let me know.

-deech

import Control.Monad.State

type RegisterVal = Int
data RegisterID = R1 | R2 | R3 | R4 deriving Show
type RegisterFile = (RegisterVal, RegisterVal, RegisterVal, RegisterVal)

get_operand :: RegisterFile -> RegisterID -> RegisterVal
get_operand (r1,_,_,_) R1 = r1
get_operand (_,r2,_,_) R2 = r2
get_operand (_,_,r3,_) R3 = r3
get_operand (_,_,_,r4) R4 = r4

store_operand :: RegisterFile -> RegisterID -> RegisterVal -> RegisterFile
store_operand (r1,r2,r3,r4) r v = case r of
                                    R1 -> (v,r2,r3,r4)
                                    R2 -> (r1,v,r3,r4)
                                    R3 -> (r1,r2,v,r4)
                                    R4 -> (r1,r2,r3,v)

eval_inst :: Instruction -> RegisterFile -> RegisterFile
eval_inst inst rf = let store_op' = store_operand rf
                        get_op'   = get_operand rf
                    in
                      case inst of
                       Add dest rid1 rid2 -> store_op' dest (get_op'
rid1 + get_op' rid2)
                       Sub dest rid1 rid2 -> store_op' dest (get_op'
rid1 - get_op' rid2)
                       Mov dest rid       -> store_op' dest (get_op' rid)
                       Movc dest v        -> store_op' dest v

--destination comes first
data Instruction = Add RegisterID RegisterID RegisterID
                   | Sub RegisterID RegisterID RegisterID
                   | Mov RegisterID RegisterID
                   | Movc RegisterID RegisterVal
                   deriving (Show)

initial_rf :: RegisterFile
initial_rf = (0,0,0,0)

insts = [Movc R1 231, Movc R2 (-42), Add R3 R2 R1, Sub R4 R2 R1]

execute_program2 :: [Instruction] -> State RegisterFile ()
execute_program2 = mapM_ (modify . eval_inst)

main :: IO ()
main = putStrLn $ show $ execState (execute_program2 insts) initial_rf



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

Message: 5
Date: Sat, 23 Jul 2011 21:03:31 +0100
From: Stephen Tetley <stephen.tet...@gmail.com>
Subject: Re: [Haskell-beginners] Data.Typeable
Cc: haskellbeginners <beginners@haskell.org>
Message-ID:
        <cab2tprcgkhkz1l-6kz1v17f85hat3zszqsfomgusokaej6u...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

In a nutshell Data.Typeable is helper module for Data.Data.
Data.Typeable provides a "type representation" and Data.Data is a
"Generics" library.

A "type representation" is set of datatypes that models Haskell's
built-in algebraic datatypes.

There are simpler type representations than Data.Typeable - Stephanie
Weirich's paper describing RepLib might be the most approachable:

http://www.seas.upenn.edu/~sweirich/publications.html

For documentation on Data.Typeable / Data.Data:

http://research.microsoft.com/en-us/um/people/simonpj/papers/hmap/

Data.Data is covered in the first "Scrap Your Boilerplate" paper.
Data.Typeable is covered in the second STB paper.



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

Message: 6
Date: Sat, 23 Jul 2011 23:46:51 +0200
From: Ertugrul Soeylemez <e...@ertes.de>
Subject: Re: [Haskell-beginners] a problem with maps
To: beginners@haskell.org
Message-ID: <20110723234651.6719b...@angst.streitmacht.eu>
Content-Type: text/plain; charset=US-ASCII

David Place <d...@vidplace.com> wrote:

> >   fromAmbList :: Ord k => [(k, a)] -> Map k [a]
> >    fromAmbList = M.fromListWith (++) . map (second pure)
>
> If I am reading your code, I may look up second and find it in
> Control.Arrow.  I have to learn about Arrows to understand your code?
> And pure makes me need to study the Applicative class.  I imagine that
> it is likely that second is the only thing from Control.Arrow that you
> are using and pure is the only thing from Control.Applicative.  So,
> you need two lines of extra code to express what could be expressed
> much more perspicuously as:

Point taken, but to get serious with Haskell you will want to learn
applicative functors and at least the function arrow anyway.  This is
the solution I would have written, and which would be most readable to
me, and there is a practical reason for that:  I have trained myself to
write my code as composable as possible, hence such code is very easy to
read for me, and I don't really think about it when writing.

Similar comparison:  Why would you want to learn a sophisticated
language like Haskell with a steep learning curve together with the
hassle of setting up a compilation environment on both the development
and production systems and a specialized web server configuration, if
you could just use PHP, which is preinstalled almost everywhere anyway?

Why would you want to use a complicated mechanism like exceptions, if
you could just as well just return an error value?


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/





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

Message: 7
Date: Sat, 23 Jul 2011 18:34:37 -0400
From: David Place <d...@vidplace.com>
Subject: Re: [Haskell-beginners] a problem with maps
To: Ertugrul Soeylemez <e...@ertes.de>
Cc: beginners@haskell.org
Message-ID: <4abaaad7-2adc-40a8-9c97-359e98ebc...@vidplace.com>
Content-Type: text/plain; charset=windows-1252

On Jul 23, 2011, at 5:46 PM, Ertugrul Soeylemez wrote:

> Point taken, but to get serious with Haskell you will want to learn
> applicative functors and at least the function arrow anyway.  

Interesting thoughts,  Ertugrul.  I would argue that you can get very serious 
with Haskell without understanding applicative functors and the function arrow. 
 The very basic aspects of the language (the type system, higher-order 
functions, lazy evaluation, etc?) are already so powerful, that you really 
don't need to add complexity to simple programs by including some of the more 
obscure extensions.  I could see if it made the code substantially more 
compact.  In this case,  it makes the code more verbose as you need to import 
the two modules to do something which can be so trivially expressed as an 
abstraction.

When you write a program, do you think of it as a document only for the 
compiler to understand, or might some other people need to understand it 
someday?

____________________
David Place   
Owner, Panpipes Ho! LLC
http://panpipesho.com
d...@vidplace.com






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

Message: 8
Date: Sun, 24 Jul 2011 01:46:43 +0300
From: Yitzchak Gale <g...@sefer.org>
Subject: Re: [Haskell-beginners] a problem with maps
To: David Place <d...@vidplace.com>
Cc: beginners@haskell.org, Ertugrul Soeylemez <e...@ertes.de>
Message-ID:
        <CAOrUaLao-F834W8=jzeqsqihdkwodj5mqyyowmmewkl7erm...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Ertugrul Soeylemez wrote:
>> ? fromAmbList :: Ord k => [(k, a)] -> Map k [a]
>> ? ?fromAmbList = M.fromListWith (++) . map (second pure)

David Place wrote:
> If I am reading your code, I may look up second
> and find it in Control.Arrow. I have to learn about
> Arrows to understand your code? ?And pure makes
> me need to study the Applicative class.

For this, there is no need to get into the issue
of when is the right time to learn about Arrows and
Applicative.

The functions "first" and "second" from Control.Arrow
are quite common in Haskell. They are simple and
convenient, they don't require knowing
anything about Arrows when used with plain old
functions and tuples, and using them doesn't create
any library dependencies. Whether or not you use them
in your own style is your own choice (I have gone through
different periods either way, currently I don't use them
much), but it's a good idea to be familiar with them.

Here are their type signatures, translated into the usual
non-Arrows style:

first :: (a -> a') -> (a, b) -> (a', b)
second :: (b -> b') -> (a, b) -> (a, b')

As for "pure", my opinion is that it's not very good style
to use it in this context. We're not using the Applicative
structure of lists in any significant way here, we're just
creating singleton lists. So I would just use (: []).

That said, "pure" is also very simple. For lists, we
have:

pure = return = (: []) -- for lists only

Another simple but useful Haskell fact.

-Yitz



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

Message: 9
Date: Sun, 24 Jul 2011 01:39:49 +0200
From: Ertugrul Soeylemez <e...@ertes.de>
Subject: Re: [Haskell-beginners] a problem with maps
To: beginners@haskell.org
Message-ID: <20110724013949.65223...@angst.streitmacht.eu>
Content-Type: text/plain; charset=UTF-8

David Place <d...@vidplace.com> wrote:

> > Point taken, but to get serious with Haskell you will want to learn
> > applicative functors and at least the function arrow anyway.
>
> Interesting thoughts, Ertugrul.  I would argue that you can get very
> serious with Haskell without understanding applicative functors and
> the function arrow.  The very basic aspects of the language (the type
> system, higher-order functions, lazy evaluation, etc?) are already so
> powerful, that you really don't need to add complexity to simple
> programs by including some of the more obscure extensions.  I could
> see if it made the code substantially more compact.  In this case, it
> makes the code more verbose as you need to import the two modules to
> do something which can be so trivially expressed as an abstraction.

Haskell application development is more than just the language.  The
language itself is very powerful, yes, but serious applications I write
usually have quite a few dependencies.  If you want to reinvent the
wheel for everything, then yes, I'm exaggerating.  Personally I don't
want to, because there are great libraries and design patterns out
there, for which you simply need to understand more than just the
language.

It's as simple as this:  To get serious with Haskell, you need to
understand Haskell monads.  Understanding them implies understanding
applicative functors (not necessarily the applicative style).  For many
of the useful libraries you will want to go further and understand monad
transformers and more.

I'm not talking about any ideals here.  I'm talking about real world
application development, which is what I am doing.


> When you write a program, do you think of it as a document only for
> the compiler to understand, or might some other people need to
> understand it someday?

"It"?  For me type signatures are specification for the compiler and
documentation for humans, along with Haddock-style comments.  My code is
usually very well documented.  In most cases Haddock shows me a coverage
of 100% for all of my source files, and every top-level and
'where'-definition has a type signature.  I'm very rigorous here.

All of the power I get from Haskell itself, the base library and the
many libraries I use I view as tools to get stuff done quickly, safely
and elegantly.  As said, there is always a simpler way to write stuff,
but I have a certain style, which I follow consistently, and in that
style I write 'second pure'.  That's it.

Why not '(:[])'?  Simply because I hate it and find it confusing.  Why
not 'return'?  Because I write my code reasonably general.  Not that
using 'return' would change the type signature in question, but it is
just my style.  In a do-block I use 'return'.  Everywhere else I use
'pure'.  Consistently.  Why 'second'?  Because it's convenient.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/





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

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


End of Beginners Digest, Vol 37, Issue 52
*****************************************

Reply via email to