Send Beginners mailing list submissions to
        [email protected]

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
        [email protected]

You can reach the person managing the list at
        [email protected]

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


Today's Topics:

   1. Re:  Making sense of currying in the context of the Hask
      Category (Lino Rosa)
   2.  two typos in my last. Was: Re: Making sense of currying in
      the context of the Hask Category (Jay Sulzberger)
   3. Re:  firering event in netwire (Nathan H?sken)
   4. Re:  firering event in netwire (Ertugrul S?ylemez)
   5. Re:  Using my first map instance (Chadda? Fouch?)


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

Message: 1
Date: Fri, 28 Sep 2012 20:53:11 -0400
From: Lino Rosa <[email protected]>
Subject: Re: [Haskell-beginners] Making sense of currying in the
        context of the Hask Category
To: [email protected]
Message-ID:
        <camrcgw1kehekhdeacuefsdt87kfwzg6kj7b_rc8f9n6k+ar...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Thanks for the responses :) I've read on cartesian closed categories,
but I guess I need more time for it to sink in - my knowlege on
category theory is *very* limited.

Still, continuing on the Int + Int example. Would this be the sequence
of transformations, then?

Int -> (Int -> Int) -> Int
     (+)      (z)      (?)

What do I label the arrow (?) ?
I understand the first transformation as "function (+) when applied to
an Int will result in (Int -> Int)". How would I describe function (?)
similarly ?
It's almost as it the arrow is z and (?) is the Int and I'm applying z
to (?), but that makes no sense!

If I understood correctly, 'z' would be a special type, one which when
applied (?) would return the final Int. This comes Hask being
cartesian closed. Still I'm clueless on the arrow (?)

On Fri, Sep 28, 2012 at 8:07 AM, Kim-Ee Yeoh <[email protected]> wrote:
> Hi Lino,
>
> Brent gave an excellent answer. Looking up "cartesian closed category"
> should yield even more insights.
>
> On Fri, Sep 28, 2012 at 9:07 AM, Lino Rosa <[email protected]>
> wrote:
>
>> That's the
>> function resulting from the previous partial application of (+), but
>> that fuction only exists at run time, after you apply the first one.
>
>
> When you speak of a function that "only exists at run time", I think you're
> alluding to partial evaluation. Haskell doesn't do that, although many have
> wished for it.
>
>
> -- Kim-Ee
>



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

Message: 2
Date: Fri, 28 Sep 2012 22:01:19 -0400 (EDT)
From: Jay Sulzberger <[email protected]>
Subject: [Haskell-beginners] two typos in my last. Was: Re: Making
        sense of currying in the context of the Hask Category
To: [email protected]
Message-ID: <[email protected]>
Content-Type: TEXT/PLAIN; charset=US-ASCII; format=flowed



On Fri, 28 Sep 2012, Jay Sulzberger wrote:

>
> On Thu, 27 Sep 2012, Lino Rosa <[email protected]> wrote:
>
>> Hi,
>> 
>> I'm a Haskell newbie and I couldn't quite make sense of how currying
>> maps to the the Hask Category.
>> How would I map, for instance (+) to a Hask 'arrow'?
>
> There are several categories that might be called "the Hask
> category".  At
>
>  http://www.haskell.org/haskellwiki/Hask
>
> there are pointers to papers on what a useful Hask might be.
>
> Let us consider the category SET whose objects are sets and whose
> morphisms are everywhere defined single valued maps.  So a
> morphism f: X -> B, where X and B are sets, would just be a
> function, usual modern sense, from X to B.  Now the set of all
> morphisms from X to B, let us call it SET(X;B), is itself a set,
> so SET(X;B) is an object of SET.
>
> Now suppose B is the set SET(Y;Z) of morphisms from the set X to
> the set Y.  In this case given an element x of X, we have that

Oi, typo:

Above lines should be:

Now suppose B is the set SET(Y;Z) of morphisms from the set Y to
the set Z.  In this case given an element x of X, we have that

> f(x) is a morphism of SET, and f(x) has source Y and target Z, that
> is, f(x): Y -> Z.  So given x, and now given y in Y, we have a new two
> place function, call it g: X x Y -> Z, defined by:
>
>  for all x in X and y in Y, g(x, y) = [f(x)](y)
>
> where the square brackets are just for grouping.
>
> Note that we have the "operation" of Cartesian product on objects
> of SET, which operation is shown above as the "x" in the
> expression "X x Y".  Note also that SET is an odd sort of
> category in that SET(X;B), for any two objects X, B, is itself an
> object of SET.
>
> Now in SET we may also, for any g: X x Y -> Z get an
> f: X -> SET(Y;Z), such that our condition holds.
>
> Category theorists apparatus to make explicit what we have just

and another, above line should be

Category theorists have apparatus to make explicit what we have just

oo--JS.


> claimed in vague and not quite precise terms.  This apparatus is
> the theory of Cartesian Closed Categories:
>
>  http://en.wikipedia.org/wiki/Cartesian_closed_category
>  [page was last modified on 28 September 2012 at 19:08]
>
> Let me give an example of our imprecision, which formal category
> theory clarifies:
>
>  We said that g is a two place function.  We also wrote
>  g: X x Y -> Z.  What does this mean?  In any category every
>  morphism goes from exactly one object to exactly one object.
>  So how can there be such a thing as a "function with two
>  inputs"?
>
> oo--JS.
>
>
>> 
>> If objects are types on Hask, then would a -> a -> a be the first
>> object on this chain?
>> 
>> In that case, for the first arrow, would I have as many arrows as
>> there are possible partial applications on this type? In other words,
>> would I have (+) 1, (+) 2, (+) 3 ... all those transitioning to the
>> second object ( a -> a )
>> Or, do I have ONE arrow only, like (+) a ?
>> 
>> In either case, what happens after 'm left with the object a -> a?
>> What function (arrow) mutates it to the final value 'a'? That's the
>> function resulting from the previous partial application of (+), but
>> that fuction only exists at run time, after you apply the first one. I
>> guess the question is, if you'd have to write a diagram for this, what
>> would you write beside each object and beside each arrow?
>> 
>> _______________________________________________
>> Beginners mailing list
>> [email protected]
>> http://www.haskell.org/mailman/listinfo/beginners
>> 
>> 
>
>



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

Message: 3
Date: Sat, 29 Sep 2012 04:07:42 +0200
From: Nathan H?sken <[email protected]>
Subject: Re: [Haskell-beginners] firering event in netwire
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset=ISO-8859-1

I believe I can now at least partly answer my own question:
Assuming my input is a list of Key events:

data KeyEvent = KeyDown Int | KeyUp Int

than the event wire:

keyDown code = when (`elem` KeyDown code) :: Event () (->) [KeyEvent]

would produce when the key with the given code is pressed down.

On 09/28/2012 08:19 PM, Nathan H?sken wrote:
> Hey,
> 
> I have a few question about the usage of netwire:
> 
> How do I fire events?
> For example my main wire should take keyboard events as input and output
> some state (which is than somehow outputed).
> I see that there is an event type, which has the some type as the
> identiy wire. I am just not sure how to use it?
> 
> Or asked differently, how is the "keyDown" event defined, that was
> talked of in an earlier mail?
> 
> Thanks!
> Nathan
> 
> _______________________________________________
> Beginners mailing list
> [email protected]
> http://www.haskell.org/mailman/listinfo/beginners
> 




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

Message: 4
Date: Sat, 29 Sep 2012 08:56:55 +0200
From: Ertugrul S?ylemez <[email protected]>
Subject: Re: [Haskell-beginners] firering event in netwire
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset="utf-8"

Nathan H?sken <[email protected]> wrote:

> How do I fire events?
> For example my main wire should take keyboard events as input and
> output some state (which is than somehow outputed).

The idea is that you either provide the decision of whether to fire an
event through the input (direct style) or you use an underlying monad
(indirect style).  The direct style would have this type:

    keyDown :: (Monoid e, Reactive cat) =>
               KeySym -> Event e cat SDL.Event

The indirect style is nicer to use, but requires an underlying monad:

    keyDown :: (Monoid e) => KeySym -> Event e (Kleisli MyMonad) a


> I see that there is an event type, which has the some type as the
> identiy wire. I am just not sure how to use it?

The idea is that event wires should act like the identity wire, if an
event has happened and inhibit otherwise.  That way you can easily put
it into a wire composition:

    time . periodically 1


> Or asked differently, how is the "keyDown" event defined, that was
> talked of in an earlier mail?

In the direct case you can define it as a simple composition:

    isSym :: KeySym -> SDL.Event -> Bool
    isSym s (KeyDown s') = s == s'
    isSym _ _ = False

    keyDown = require . isSym

In the indirect case you can use 'mkFixM' to construct your own wire:

    keyDown sym =
        mkFixM $ \_ x -> do
            ev <- asks currentEvent
            return $
                case ev of
                  KeyDown sym' | sym == sym' -> Right x
                  _                          -> Left mempty

I hope this helps.


Greets,
Ertugrul

-- 
Not to be or to be and (not to be or to be and (not to be or to be and
(not to be or to be and ... that is the list monad.
-------------- next part --------------
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 836 bytes
Desc: not available
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120929/8af0952c/attachment-0001.pgp>

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

Message: 5
Date: Sat, 29 Sep 2012 11:36:52 +0200
From: Chadda? Fouch? <[email protected]>
Subject: Re: [Haskell-beginners] Using my first map instance
To: Darren Grant <[email protected]>
Cc: [email protected]
Message-ID:
        <CANfjZRa=HUQqKRNywPJTM+R=t3f80xubmdkk-ry2ifnxwoh...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

On Sat, Sep 29, 2012 at 2:44 AM, Darren Grant <[email protected]> wrote:
> On Fri, Sep 28, 2012 at 4:57 PM, Sean Perry <[email protected]> wrote:
>>
>>
>> Have you looked at 
>> http://www.haskell.org/haskellwiki/Euler_problems/11_to_20#Problem_14?
>>
>> The page is full of interesting and fast solutions once you have worked out 
>> your own versions.
>>
>
> Hah I didn't know the Haskell Wiki had a Project Euler page. I'll
> definitely be reviewing with that resource.
>
> I notice the use of Array instead of Map, and the careful use of
> unboxed types. :)
>

This comment is misleading, there are no unboxed type in this solution
(maybe the author meant that this compiled down to unboxed types with
optimisations but the Haskell code definitely use boxed types : Int
and Word32) though there's a little bit of parallelism involved (could
be improved).
The use of a functional (immutable) Array here makes perfect sense
since the keys are effectively an interval of Int... Note that my old
Array version rely on the laziness of the Array to make it work, this
is basically dynamic programming where the order of computation
appears natural but only because laziness means it will be determined
by the computation itself. This is perfectly functional, no need to
resort to any imperative style here (or most everywhere in project
Euler).

-- 
Jeda?



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

_______________________________________________
Beginners mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 51, Issue 44
*****************************************

Reply via email to