Re: [Haskell-cafe] Hackage Update Brigade

2013-05-28 Thread wren ng thornton
On 5/27/13 5:29 PM, Alexander Solla wrote:
> As per recent discussions, I'm making a list of volunteers who are willing
> to pick up some slack in Hackage package maintenance, so that we can submit
> an amendment to the Haskell Prime Committee's ticket 113 (
> http://hackage.haskell.org/trac/haskell-prime/ticket/113)

I'd much prefer sticking with the names (<*>), (<*), (*>), and deprecating
`ap` and (>>). There's no good name for (<*) since we already have (<<) =
flip (>>) which means something different entirely. Plus "`ap`" is longer
than "<*>" and loses the suggestive relationship between the operator
names. Not to mention the fact that these name changes would cause immense
breakage for all users of Applicative, rather than relatively minor
breakage for those who define Monad instances.

-- 
Live well,
~wren


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Hackage Update Brigade

2013-05-28 Thread David Virebayre
2013/5/28 Conrad Parker :

> For that proposal, there is also an informal github group for updating
> unmaintained packages,
> which anyone willing is welcome to join:

Say I would be willing to spend a few hours a month to fix some
problems, but I'm not very experienced;
I only use haskell for a few small programs at work, I'm not used to
working collaboratively (but willing to learn)
Would I still be able to be useful ?

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Hackage Update Brigade

2013-05-28 Thread Alfredo Di Napoli
Can I join too? Always happy to spend my free time merging and reviewing
some Haskell code :)

A.


On 29 May 2013 04:56, Lyndon Maydwell  wrote:

> Done :)
>
>
> On Wed, May 29, 2013 at 12:22 PM, Conrad Parker wrote:
>
>> On 29 May 2013 08:54, Lyndon Maydwell  wrote:
>> > How can I join the group?
>>
>> by asking any of the current members :) I've added you.
>>
>> > P.S. I've attached a simple image for the Gravatar if it looks okay.
>>
>> great, can you add it?
>>
>> Conrad.
>>
>> >
>> >
>> > On Tue, May 28, 2013 at 12:40 PM, Conrad Parker 
>> > wrote:
>> >>
>> >> On 28 May 2013 05:29, Alexander Solla  wrote:
>> >> > As per recent discussions, I'm making a list of volunteers who are
>> >> > willing
>> >> > to pick up some slack in Hackage package maintenance, so that we can
>> >> > submit
>> >> > an amendment to the Haskell Prime Committee's ticket 113
>> >> > (http://hackage.haskell.org/trac/haskell-prime/ticket/113)
>> >> >
>> >> > I think that showing that people are willing to pick up missing
>> package
>> >> > maintainer's slack will alleviate the concern of breaking lots of
>> code
>> >> > by
>> >> > refactoring the monad/applicative/functor hierarchy.  Code will be
>> >> > broken,
>> >> > but publicly available packages can be fixed by the community during
>> a
>> >> > "staging" period.  To that end, I have made a Google Form to collect
>> >> > some
>> >> > volunteer information.  If you are interested in helping, please
>> visit:
>> >> >
>> >> >
>> >> >
>> https://docs.google.com/forms/d/1o4B8CEE_42u9f-sgmu2t5iSEvm0cq6-um6g_fHJt6GE/viewform
>> >> >
>> >> >
>> >>
>> >> For that proposal, there is also an informal github group for updating
>> >> unmaintained packages,
>> >> which anyone willing is welcome to join:
>> >>
>> >> https://github.com/haskell-pkg-janitors
>> >>
>> >> cheers,
>> >>
>> >> Conrad.
>> >>
>> >> ___
>> >> Haskell-Cafe mailing list
>> >> Haskell-Cafe@haskell.org
>> >> http://www.haskell.org/mailman/listinfo/haskell-cafe
>> >
>> >
>> >
>> > ___
>> > Haskell-Cafe mailing list
>> > Haskell-Cafe@haskell.org
>> > http://www.haskell.org/mailman/listinfo/haskell-cafe
>> >
>>
>
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Design of extremely usable programming language libraries

2013-05-28 Thread Roman Cheplyaka
Unfortunately you can only do traversals, not unfolds, with GADTs.

That's because in an unfold, the return type is determined by the value
itself and can vary among the produced results, whereas in a traversal
it is determined by the input type.

This means also that you cannot simply derive Data, because the derived
instance will contain a gunfold function, which then will fail to
typecheck.

You can copy-paste the generated instance (-ddump-deriv) and simply
remove the code for gunfold (or write your own deriver). The following
compiles for me:
https://gist.github.com/feuerbach/5668198

Roman

* Andrey Chudnov  [2013-05-28 17:29:10-0400]
> Thanks for a prompt reply, Roman.
> 
> On 05/28/2013 04:52 PM, Roman Cheplyaka wrote:
> > Any syb-style library works with GADTs, by the virtue of dealing with
> > value representations instead of type representations. 
> I tried to use syb, but the following code fails to typecheck for me.
> What am I doing wrong?
> > {-# LANGUAGE GADTs, EmptyDataDecls, MultiParamTypeClasses,
> TypeFamilies #-}
> > {-# LANGUAGE DeriveDataTypeable, StandaloneDeriving #-}
> 
> > data HasHoles
> > data Complete
> > deriving instance Typeable HasHoles
> > deriving instance Data HasHoles
> > deriving instance Typeable Complete
> > deriving instance Data Complete
> > type family Holes a b :: *
> > canHaveHolesT :: a -> b -> Holes a b
> > canHaveHolesT _ _ = undefined
> > type instance Holes HasHoles Complete = HasHoles
> > type instance Holes Complete HasHoles = HasHoles
> > type instance Holes HasHoles HasHoles = HasHoles
> > type instance Holes Complete Complete = HasHoles
> 
> > data Expression k a where
> >   EQuote  :: a -> String -> Expression HasHoles a
> >   IntLit  :: a -> Int -> Expression Complete a
> >   EArith  :: a -> ArithOp -> Expression k1 a -> Expression k2 a ->
> >  Expression (Holes k1 k2) a
> > deriving instance Typeable2 (Expression)
> > deriving instance Data (Expression k a)
> > data ArithOp = OpAdd
> >   | OpSub
> >   | OpMul
> >   | OpDiv
> >deriving (Data, Typeable)
> 
> Fails with:
> > Couldn't match type `Complete' with `HasHoles'
> > Expected type: a -> String -> Expression k a
> >   Actual type: a -> String -> Expression HasHoles a
> > In the first argument of `z', namely `EQuote'
> > In the first argument of `k', namely `z EQuote'
> > When typechecking the code for  `Data.Data.gunfold'
> >   in a standalone derived instance for `Data (Expression k a)':
> >   To see the code I am typechecking, use -ddump-deriv
> 
> 
> > Not sure what you mean here — attoparsec does support unlimited
> > lookahead, in the sense that a parser may fail arbitrarily late in the
> > input stream, and backtrack to any previous state. Although attoparsec
> > is a poor choice for programming language parsing, primarily because
> > of the error messages. 
> I guess I have an outdated notion of attoparsec. But yes, error messages
> seem to be the weak point of attoparsec. Also, the fact that it only
> accepts bytestrings makes it harder (but no impossible, since we can
> convert Strings to ByteStrings) to reuse the parser as a QuasiQuoter.
> So, I'll rephrase my question. What's the best choice for a library for
> parsing programming languages nowadays?
> 
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Hackage Update Brigade

2013-05-28 Thread Lyndon Maydwell
Done :)


On Wed, May 29, 2013 at 12:22 PM, Conrad Parker wrote:

> On 29 May 2013 08:54, Lyndon Maydwell  wrote:
> > How can I join the group?
>
> by asking any of the current members :) I've added you.
>
> > P.S. I've attached a simple image for the Gravatar if it looks okay.
>
> great, can you add it?
>
> Conrad.
>
> >
> >
> > On Tue, May 28, 2013 at 12:40 PM, Conrad Parker 
> > wrote:
> >>
> >> On 28 May 2013 05:29, Alexander Solla  wrote:
> >> > As per recent discussions, I'm making a list of volunteers who are
> >> > willing
> >> > to pick up some slack in Hackage package maintenance, so that we can
> >> > submit
> >> > an amendment to the Haskell Prime Committee's ticket 113
> >> > (http://hackage.haskell.org/trac/haskell-prime/ticket/113)
> >> >
> >> > I think that showing that people are willing to pick up missing
> package
> >> > maintainer's slack will alleviate the concern of breaking lots of code
> >> > by
> >> > refactoring the monad/applicative/functor hierarchy.  Code will be
> >> > broken,
> >> > but publicly available packages can be fixed by the community during a
> >> > "staging" period.  To that end, I have made a Google Form to collect
> >> > some
> >> > volunteer information.  If you are interested in helping, please
> visit:
> >> >
> >> >
> >> >
> https://docs.google.com/forms/d/1o4B8CEE_42u9f-sgmu2t5iSEvm0cq6-um6g_fHJt6GE/viewform
> >> >
> >> >
> >>
> >> For that proposal, there is also an informal github group for updating
> >> unmaintained packages,
> >> which anyone willing is welcome to join:
> >>
> >> https://github.com/haskell-pkg-janitors
> >>
> >> cheers,
> >>
> >> Conrad.
> >>
> >> ___
> >> Haskell-Cafe mailing list
> >> Haskell-Cafe@haskell.org
> >> http://www.haskell.org/mailman/listinfo/haskell-cafe
> >
> >
> >
> > ___
> > Haskell-Cafe mailing list
> > Haskell-Cafe@haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
> >
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Hackage Update Brigade

2013-05-28 Thread Conrad Parker
On 29 May 2013 08:54, Lyndon Maydwell  wrote:
> How can I join the group?

by asking any of the current members :) I've added you.

> P.S. I've attached a simple image for the Gravatar if it looks okay.

great, can you add it?

Conrad.

>
>
> On Tue, May 28, 2013 at 12:40 PM, Conrad Parker 
> wrote:
>>
>> On 28 May 2013 05:29, Alexander Solla  wrote:
>> > As per recent discussions, I'm making a list of volunteers who are
>> > willing
>> > to pick up some slack in Hackage package maintenance, so that we can
>> > submit
>> > an amendment to the Haskell Prime Committee's ticket 113
>> > (http://hackage.haskell.org/trac/haskell-prime/ticket/113)
>> >
>> > I think that showing that people are willing to pick up missing package
>> > maintainer's slack will alleviate the concern of breaking lots of code
>> > by
>> > refactoring the monad/applicative/functor hierarchy.  Code will be
>> > broken,
>> > but publicly available packages can be fixed by the community during a
>> > "staging" period.  To that end, I have made a Google Form to collect
>> > some
>> > volunteer information.  If you are interested in helping, please visit:
>> >
>> >
>> > https://docs.google.com/forms/d/1o4B8CEE_42u9f-sgmu2t5iSEvm0cq6-um6g_fHJt6GE/viewform
>> >
>> >
>>
>> For that proposal, there is also an informal github group for updating
>> unmaintained packages,
>> which anyone willing is welcome to join:
>>
>> https://github.com/haskell-pkg-janitors
>>
>> cheers,
>>
>> Conrad.
>>
>> ___
>> Haskell-Cafe mailing list
>> Haskell-Cafe@haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [haskell.org Google Summer of Code 2013] Approved Projects

2013-05-28 Thread Edward Kmett
The majority of the rejections are of precisely that form, or just were
slightly out-competed by another similar proposal in their space.

These items either are stated or should be stated in the student
application guidelines, but a successful summer of code submission probably
has most of the following attributes:

* *A good timeline* -- It is easy to miss this one! At one extreme, we've
had proposals that just never submitted any details beyond a paragraph
saying something would be nice to have. Other red flags are projects that
promise the moon, but come from someone nobody knows (there is nothing
wrong with promising the moon if everyone knows you can deliver it!) or
which look like they close out an easy issue that someone could bang out in
a weekend. We've passed on otherwise decent proposals that just completely
lacked any details about how they were going to get there, as there is
really no good way for a mentor to judge progress. Speaking of whom, it is
useful to have...

* *Some idea of who the mentor could be* -- We came very close to not
finding mentors for a couple of projects, despite community interest. As a
corollary, if you are interested in having something happen in the
community, stepping up to mentor it along is a good first step to making it
a reality! We generally can find mentors for projects, but having already
reached out to someone beforehand helps show that you have...

* *A student who has already started to get involved in the community* --
Haskell generally has a long ramp up, its rather hard to learn it on the
fly if you've never really used it, and still accomplish some other goal.
Students with a long history of good commits to a project are generally
taken before ones of whom we're less sure. Without knowledge of haskell you
are unlikely to have...

* *Demonstrable impact on the community as a whole* -- Proposals that work
on a specific aspect of something we all use generally see good responses.
We definitely tend to favor projects that benefit the community as a whole
over ones that improve niches. Work on Cabal, GHC, Hackage is a much easier
to sell, than say me getting someone to hack on my kan-extensions library,
which doesn't have many users, but at least it is...

* *Not a greenfield project* -- In general we're a bit gunshy about
students designing libraries from scratch. Your MMORPG example fits that
mold. It'd likely be a completely new project, which brings with it a lot
of design decisions, and it comes with no pre-existing users impacted by
the project, so it is easy to flounder and have nobody care. For instance,
we have routinely received submissions to build a library for type level
programming, but we already have several that have failed to gain much
traction. What discriminates the new design from the old? Now, if the
library already exists and has begun to pick up traction and has users? You
might be able to make a case for a summer of code project to improve it. I
just can't think of such a proposal that we've had in recent years.

-Edward



On Tue, May 28, 2013 at 8:24 PM, Ben Lippmeier  wrote:

>
> On 29/05/2013, at 1:11 AM, Edward Kmett wrote:
>
> This unfortunately means, that we can't really show the unaccepted
> proposals with information about how to avoid getting your proposal
> rejected.
>
>
> You can if you rewrite the key points of proposal to retain the overall
> message, but remove identifying information. I think it would be helpful to
> write up some of the general reasons for projects being rejected.
>
> I tried to do this for Haskell experience reports, on the Haskell
> Symposium experience report advice page.
>  http://www.haskell.org/haskellwiki/HaskellSymposium/ExperienceReports
>
>
> I'd imagine you could write up some common proposal / rejection / advice
> tuples like:
>
> Proposal: I want to write a MMORPG in Haskell, because this would be a
> good demonstration for Haskell in a large real world project. We can use
> this as a platform to develop the networking library infrastructure.
>
> Rejection: This project is much too big, and the production of a MMORPG
> wouldn't benefit the community as a whole.
>
> Advice: If you know of specific problems in the networking library
> infrastructure, then focus on those, using specific examples of where
> people have tried to do something and failed.
>
>
> Ben.
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Hackage Update Brigade

2013-05-28 Thread Lyndon Maydwell
How can I join the group?

P.S. I've attached a simple image for the Gravatar if it looks okay.


On Tue, May 28, 2013 at 12:40 PM, Conrad Parker wrote:

> On 28 May 2013 05:29, Alexander Solla  wrote:
> > As per recent discussions, I'm making a list of volunteers who are
> willing
> > to pick up some slack in Hackage package maintenance, so that we can
> submit
> > an amendment to the Haskell Prime Committee's ticket 113
> > (http://hackage.haskell.org/trac/haskell-prime/ticket/113)
> >
> > I think that showing that people are willing to pick up missing package
> > maintainer's slack will alleviate the concern of breaking lots of code by
> > refactoring the monad/applicative/functor hierarchy.  Code will be
> broken,
> > but publicly available packages can be fixed by the community during a
> > "staging" period.  To that end, I have made a Google Form to collect some
> > volunteer information.  If you are interested in helping, please visit:
> >
> >
> https://docs.google.com/forms/d/1o4B8CEE_42u9f-sgmu2t5iSEvm0cq6-um6g_fHJt6GE/viewform
> >
> >
>
> For that proposal, there is also an informal github group for updating
> unmaintained packages,
> which anyone willing is welcome to join:
>
> https://github.com/haskell-pkg-janitors
>
> cheers,
>
> Conrad.
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
<>___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [haskell.org Google Summer of Code 2013] Approved Projects

2013-05-28 Thread Ben Lippmeier

On 29/05/2013, at 1:11 AM, Edward Kmett wrote:

> This unfortunately means, that we can't really show the unaccepted proposals 
> with information about how to avoid getting your proposal rejected.

You can if you rewrite the key points of proposal to retain the overall 
message, but remove identifying information. I think it would be helpful to 
write up some of the general reasons for projects being rejected.

I tried to do this for Haskell experience reports, on the Haskell Symposium 
experience report advice page.
 http://www.haskell.org/haskellwiki/HaskellSymposium/ExperienceReports


I'd imagine you could write up some common proposal / rejection / advice tuples 
like:

Proposal: I want to write a MMORPG in Haskell, because this would be a good 
demonstration for Haskell in a large real world project. We can use this as a 
platform to develop the networking library infrastructure.

Rejection: This project is much too big, and the production of a MMORPG 
wouldn't benefit the community as a whole.

Advice: If you know of specific problems in the networking library 
infrastructure, then focus on those, using specific examples of where people 
have tried to do something and failed.


Ben.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Design of extremely usable programming language libraries

2013-05-28 Thread John Lato
> > Not sure what you mean here — attoparsec does support unlimited
> > lookahead, in the sense that a parser may fail arbitrarily late in the
> > input stream, and backtrack to any previous state. Although attoparsec
> > is a poor choice for programming language parsing, primarily because
> > of the error messages.
> I guess I have an outdated notion of attoparsec. But yes, error messages
> seem to be the weak point of attoparsec. Also, the fact that it only
> accepts bytestrings makes it harder (but no impossible, since we can
> convert Strings to ByteStrings) to reuse the parser as a QuasiQuoter.
> So, I'll rephrase my question. What's the best choice for a library for
> parsing programming languages nowadays?


Parsec is still widely popular since it's part of the HP, but I use
uu-parsinglib as my first-choice parser.  It comes with a lot of examples,
good documentation, and many features I like (good error messages and auto
error correction).  I don't know how performance compares with parsec or
attoparsec, but it's always been good enough for me.

John L.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type classes

2013-05-28 Thread Tom Ellis
On Tue, May 28, 2013 at 11:22:22PM +0200, Johannes Gerer wrote:
> I have to ask, why was plausability and looking at the actual definition
> (not just the types) not important for the other examples.

It would also be important to check the definitions in the other examples
too, but it's hard enough to get the types to match!

> But I think my problem lies somewhere else. Maybe all would become
> evident, if I knew the rigorous definition of "A is more general than
> B" in this context. Especially when A is a class of type, that takes
> two arguments (i.e. Unit and Arrow) and B for ones, that takes only
> one (like Monad, Pure,..)

I'm not sure what the right definition is.  You are right that it is far
from obvious (at least to you and me!).

For a definition of equivalence, I feel it should go something like this:

To every instance a of A I can assign an instance b of B, and to every
instance b of B I can assign an instance a' of A.  Moreover there should be
a function polymorphic in all parameters between a and a', which has a
polymorphic inverse.  (And likewise for A and B swapped).  These functions
might need to be required to commute with all member functions of A.

Perhaps this is perfectly obvious and well known, but I haven't managed to
work it out on my own.

Tom

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Design of extremely usable programming language libraries

2013-05-28 Thread Andrey Chudnov
Thanks for a prompt reply, Roman.

On 05/28/2013 04:52 PM, Roman Cheplyaka wrote:
> Any syb-style library works with GADTs, by the virtue of dealing with
> value representations instead of type representations. 
I tried to use syb, but the following code fails to typecheck for me.
What am I doing wrong?
> {-# LANGUAGE GADTs, EmptyDataDecls, MultiParamTypeClasses,
TypeFamilies #-}
> {-# LANGUAGE DeriveDataTypeable, StandaloneDeriving #-}

> data HasHoles
> data Complete
> deriving instance Typeable HasHoles
> deriving instance Data HasHoles
> deriving instance Typeable Complete
> deriving instance Data Complete
> type family Holes a b :: *
> canHaveHolesT :: a -> b -> Holes a b
> canHaveHolesT _ _ = undefined
> type instance Holes HasHoles Complete = HasHoles
> type instance Holes Complete HasHoles = HasHoles
> type instance Holes HasHoles HasHoles = HasHoles
> type instance Holes Complete Complete = HasHoles

> data Expression k a where
>   EQuote  :: a -> String -> Expression HasHoles a
>   IntLit  :: a -> Int -> Expression Complete a
>   EArith  :: a -> ArithOp -> Expression k1 a -> Expression k2 a ->
>  Expression (Holes k1 k2) a
> deriving instance Typeable2 (Expression)
> deriving instance Data (Expression k a)
> data ArithOp = OpAdd
>   | OpSub
>   | OpMul
>   | OpDiv
>deriving (Data, Typeable)

Fails with:
> Couldn't match type `Complete' with `HasHoles'
> Expected type: a -> String -> Expression k a
>   Actual type: a -> String -> Expression HasHoles a
> In the first argument of `z', namely `EQuote'
> In the first argument of `k', namely `z EQuote'
> When typechecking the code for  `Data.Data.gunfold'
>   in a standalone derived instance for `Data (Expression k a)':
>   To see the code I am typechecking, use -ddump-deriv


> Not sure what you mean here — attoparsec does support unlimited
> lookahead, in the sense that a parser may fail arbitrarily late in the
> input stream, and backtrack to any previous state. Although attoparsec
> is a poor choice for programming language parsing, primarily because
> of the error messages. 
I guess I have an outdated notion of attoparsec. But yes, error messages
seem to be the weak point of attoparsec. Also, the fact that it only
accepts bytestrings makes it harder (but no impossible, since we can
convert Strings to ByteStrings) to reuse the parser as a QuasiQuoter.
So, I'll rephrase my question. What's the best choice for a library for
parsing programming languages nowadays?

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type classes

2013-05-28 Thread Johannes Gerer
Dear Tom,

I really appreciate your help, but If I could ask the perfect question
I probably would already know the answer... My example should not
prove anything, instead they collectively show, that I am missing
something. And it is not the fact, that "pure f does not depend on f."
If, however, this makes all the difference, I have to ask, why was
plausability and looking at the actual definition (not just the types)
not important for the other examples.
But I think my problem lies somewhere else. Maybe all would become
evident, if I knew the rigorous definition of "A is more general than
B" in this context. Especially when A is a class of type, that takes
two arguments (i.e. Unit and Arrow) and B for ones, that takes only
one (like Monad, Pure,..)
Thanks again!
Johannes

On Tue, May 28, 2013 at 11:11 PM, Tom Ellis
 wrote:
> On Tue, May 28, 2013 at 09:09:48PM +0200, Johannes Gerer wrote:
>> What about these two very simple type classes. Are they equivalent?
> [...]
>> class Pointed f where
>>   pure  :: a -> f a
>>
>> class Unit f where
>>   unit :: f a a
>>
>> newtype UnitPointed f a = UnitPointed f a a
>> instance Unit f => Pointed (UnitPointed f) where
>>   pure f = UnitPointed unit
>>
>> newtype Kleisli f a b = Kleisli (a -> f b)
>> instance Pointed f => Unit (Kleisli f) where
>>   unit = Kleisli pure
>
> This is implausible, since "pure f" does not depend on "f".
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type classes

2013-05-28 Thread Tom Ellis
On Tue, May 28, 2013 at 09:09:48PM +0200, Johannes Gerer wrote:
> What about these two very simple type classes. Are they equivalent?
[...]
> class Pointed f where
>   pure  :: a -> f a
> 
> class Unit f where
>   unit :: f a a
> 
> newtype UnitPointed f a = UnitPointed f a a
> instance Unit f => Pointed (UnitPointed f) where
>   pure f = UnitPointed unit
> 
> newtype Kleisli f a b = Kleisli (a -> f b)
> instance Pointed f => Unit (Kleisli f) where
>   unit = Kleisli pure

This is implausible, since "pure f" does not depend on "f".

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Design of extremely usable programming language libraries

2013-05-28 Thread Roman Cheplyaka
* Andrey Chudnov  [2013-05-28 16:36:14-0400]
> * Does any generic traversal/transformation (uniplate-style) library
>   support GADTs?

Any syb-style library works with GADTs, by the virtue of dealing with
value representations instead of type representations.

> * What is the best choice, performance- and memory-wise, for a parser
>   combinator  library with support for arbitrary look-ahead? Parsec is
>   considered slow by some [1], but is it only in comparison with
>   attoparsec (which, unfortunately, doesn't support arbitrary
>   look-ahead)? Is there any parser library that performs better than
>   Parsec while still supporting arbitrary look-ahead.

Not sure what you mean here — attoparsec does support unlimited
lookahead, in the sense that a parser may fail arbitrarily late in the
input stream, and backtrack to any previous state.
Although attoparsec is a poor choice for programming language parsing,
primarily because of the error messages.

Roman

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Design of extremely usable programming language libraries

2013-05-28 Thread Andrey Chudnov
Dear Cafe,
I'm exploring the design space of programming language
libraries with enhanced usability and I'd your help and comments.
I'll start with a few short questions, but offer a detailed discussion
of the motivations
and the problems I'm facing below. So, if you have interest in
the subject or feel you can offer some insight, please, do read on.

* Does any generic traversal/transformation (uniplate-style) library
  support GADTs?
* What is the best choice, performance- and memory-wise, for a parser
  combinator  library with support for arbitrary look-ahead? Parsec is
  considered slow by some [1], but is it only in comparison with
  attoparsec (which, unfortunately, doesn't support arbitrary
  look-ahead)? Is there any parser library that performs better than
  Parsec while still supporting arbitrary look-ahead.
* Any multi-mode pretty printer libraries? By multi-mode I mean
  writing code once and being able to generate, say, both "pretty" and
  "minified" text representations of a program by changing just one
  parameter. Also, what's the most efficient pretty-printing library
  nowadays? Blaze?

I've been using Haskell for quite a while now, primarily, for
programming-language applications: program analysis, transformation
and compilation. I'm sure many would agree that PL work is where
Haskell shines. In the recent years new language features and
libraries --namely, GADTs, Template Haskell, quasi-quotation and
generic programming--- have appeared that could make working with
languages even easier than before. That's why it's sad to see that
none of the PL libraries seem to make good use of these features
(however, I might be starting to understand why). So, I'm currently
exploring
the design space for a library that uses these advanced Haskell features for
delivering better usability, and I'm having problems with implementing some
of them. I welcome comments on both the motivations, overall design and
the more technical aspects. I've omitted a few details because it's a long
e-mail as is. If something is not clear or doesn't make sense, please,
let me know.

I'll start by listing the features that an "ideal" PL library should
have, and that I've come to cherish as both a heavy user and a
developer of such. The basic features (pretty much every library has
them) include a parser (text->AST (abstract syntax tree)) and a
pretty-printer (AST->text), as well as a Haskell representation of the
AST that is somewhat easy to use. Pretty much every library has that
--- although some might debate the ease of use of the AST
representations.


However, there are other features that, in my opinion, are essential
to a PL library. The features are motivated by three requirements:
static safety (as few run-time errors as possible), minimal code
duplication (DRY) and ease of use and inspection of the code.

1) the pretty-printer should be multi-mode. One should be able to write
code once and be able to generate different textual representations of
the AST:
 - the "pretty" which is nice to the eye with white spaces,
   indentations etc.
 - minified, with minimum white space (while still being valid)
 - debuggable which inserts comments based on AST annotations
 - source-map generation
 - being able to generate colored LaTeX/HTML code would be
   nice, but non-essential

2) ASTs should be statically safe: you should only be able construct
values that represent valid programs, or get a typechecker/compiler
error otherwise. Languages that have syntactic productions that can
appear in one context but not in another need GADTs with type witnesses to
achieve that. In fact, such languages are often used to motivate GADTs
in the first place [2]. And while the problem in [2] could have been
solved by splitting the Expr datatype into two (IntExpr and BoolExpr),
in some languages this can't be done (or produces awkward syntax
trees).

3) a quasi-quoter with support for anti-quotation and quoted
patterns. This also saves a lot of typing *and* makes your code less
error-prone and easier to read. What is better (to both write and read)?
>  [js|#x# = (function (a, b) {return {t1: a + b, t2: a*b};})(#x#, #y#);|]
or
> ExprStmt def $ AssignExpr def x (CallExpr def (FuncExpr def Nothing
> [Id def "a", Id def "b"] $ ReturnStmt def $ ObjectLit [(PropId def $
> Id def "t1", InfixExpr def OpAdd (VarRef def $ Id def "a") (VarRef def $
> Id def "b")), PropId def $
> Id def "t2", InfixExpr def OpMul (VarRef def $ Id def "a") (VarRef def $
> Id def "b")])) [x, y]

The caveat here is that, to help ensure correctness,
the quasi-quoter and the parser should share code as much code as
possible. Ideally, there should be just one parser that has a switch
for recognizing normal and quasi-quoted programs. However, that would
require adding additional constructors representing anti-quotations to
our AST. And with that the user might be able to generate invalid
AST's and cause a run-time error. 

Re: [Haskell-cafe] Stream instance for Parsec + conduits

2013-05-28 Thread Roman Cheplyaka
Hi Phil,

Sorry for the late answer — somehow I missed your email when it was
originally posted.

Parsec wasn't designed for incremental input, and adding it without
modifying the internals would be tricky.

The problem with your code is this: at the branching point, Parsec
remembers the current state of the stream — i.e. "".

Then it runs the first branch, and, after that has
failed, the second branch — both with the same state of the stream, "".

The first branch, when being run, grabs the "g" from conduit.
The second branch, since it was passed "", also asks conduit for the
input. Alas, conduit has already given away its only chunk of data. It
has no idea that this is a different branch which is unaware of the
previous events.

One way around this is to have a wrapper around the conduit monad — a
simple StateT should suffice. It must cache the whole input. The stream
itself (i.e. your StreamSource) can be simply an Int which denotes the
position in the stream. Your monad then can supply the data requested by
its position, without losing data when switching branches.

A drawback of this is that you don't know how long to hold that data,
and thus have a memory leak. Attoparsec has it, too, by the way, but
it is not related to being incremental. It is possible to alter Parsec
so that you have both incremental input support and the ability to
release parts of the input that are no longer needed.

Roman

* Phil Scott  [2013-05-09 18:57:51+0100]
> Hi all.
> 
> I would like to have a Parsec Stream instance for Data.Text streams in 
> yesod's ConduitM. So far, I have this:
> 
> hpaste.org/87599
> 
> The idea is that because Yesod's conduits will be chunking values in 
> Data.Text, I should have a wrapper StreamSource to cache chunked values.
> 
> For some reason, the test parser fails, saying:
> 
> [Left "Blah" (line 1, column 1):
> unexpected "g"
> expecting "h" or "g"]
> 
> Any ideas?
> 
> Cheers!
> 
> Phil



> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type classes

2013-05-28 Thread Johannes Gerer
What about these two very simple type classes. Are they equivalent?
(As Monad and ArrowApply)

(This actually compiles in GHC)

class Pointed f where
  pure  :: a -> f a

class Unit f where
  unit :: f a a

newtype UnitPointed f a = UnitPointed f a a
instance Unit f => Pointed (UnitPointed f) where
  pure f = UnitPointed unit

newtype Kleisli f a b = Kleisli (a -> f b)
instance Pointed f => Unit (Kleisli f) where
  unit = Kleisli pure

On Tue, May 28, 2013 at 6:05 PM, Johannes Gerer  wrote:
> Ok, now I see a difference, why Kleisli can be used to relate
> typeclasses (like Monad and ArrowApply) and Cokleisli can not:
>
> "Kleisli m () _"  =  "() -> m _" is isomorphic to "m _"
>
> whereas
>
> "Cokleisli m () _" = "m _ -> ()" is not.
>
> Can somebody point out the relevant category theoretical concepts,
> that are at work here?
>
>
>
> On Tue, May 28, 2013 at 5:43 PM, Tom Ellis
>  wrote:
>> On Tue, May 28, 2013 at 05:21:58PM +0200, Johannes Gerer wrote:
>>> That makes sense. But why does
>>>
>>> instance Monad m => ArrowApply (Kleisli m)
>>>
>>> show that a Monad can do anything an ArrowApply can (and the two are
>>> thus equivalent)?
>>
>> I've tried to chase around the equivalence between these two before, and
>> I didn't find the algebra simple.  I'll give an outline.
>>
>> In non-Haskell notation
>>
>> 1) instance Monad m => ArrowApply (Kleisli m)
>>
>> means that if "m" is a Monad then "_ -> m _" is an ArrowApply.
>>
>> 2) instance ArrowApply a => Monad (a anyType)
>>
>> means that if "_ ~> _" is an ArrowApply then "a ~> _" is a Monad.
>>
>> One direction seems easy: for a Monad m, 1) gives that "_ -> m _" is an
>> ArrowApply.  By 2), "() -> m _" is a Monad.  It is equivalent
>> to the Monad m we started with.
>>
>> Given an ArrowApply "_ ~> _", 2) shows that "() ~> _" is a Monad.  Thus by
>> 1) "_ -> (() ~> _)" is an ArrowApply.  I believe this should be the same
>> type as "_ ~> _" but I don't see how to demonstrate the isomorphsim here.
>>
>> Tom
>>
>> ___
>> Haskell-Cafe mailing list
>> Haskell-Cafe@haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Interfacing Java/Haskell

2013-05-28 Thread Kristopher Micinski
Awesome!

I was hoping that someone would do this, and I'd be really happy to see
what could be done here.

This is the big crutch of using Haskell on Android is obviously that the
API sort of sucks for Haskell...

Kris


On Tue, May 28, 2013 at 2:01 PM, CJ van den Berg  wrote:

> No, you can go both ways. You can call Haskell from Java and Java from
> Haskell.
>
> Write Android Apps in Haskell will of course be just the same as writing
> Android Apps in Java. That’s just the price you pay for having full API
> access. There is of course nothing preventing someone from creating more
> idiomatic Haskell GUI libraries for Android on top of the API bindings.
>
> On 2013-05-28 15:37, Kristopher Micinski wrote:
> > I guess you can't really go from native -> framework code like this, so
> > this would really make sense only for native methods that are self
> > contained.  Is this right?  It seems like this would imply that you can
> > only write parts of an app's computation in Haskell, not the whole
> > thing.  But maybe I'm wrong.  I have seen people that write apps in
> > native / managed code integrating in a reasonable way, but it's very
> > ugly afaik.
> >
> > Kris
> >
> >
> > On Tue, May 28, 2013 at 9:35 AM, Kristopher Micinski
> > mailto:krismicin...@gmail.com>> wrote:
> >
> > I'm also interested in seeing this.
> >
> > Have you ported the Haskell runtime to Android?  It seems like this
> > should be able to be done, and through the JNI it seems like you
> > should be able to get the system API (albeit, ugly).
> >
> > However, I'd be really happy to see this setup if you were willing
> > to put it up somewhere so I could hack on it too.
> >
> > Kris
> >
> >
> > On Mon, May 27, 2013 at 8:07 PM, Manuel M T Chakravarty
> > mailto:c...@cse.unsw.edu.au>> wrote:
> >
> > CJ van den Berg mailto:c...@vdbonline.com>>:
> > > I have successfully written Java/Haskell programs using the
> Java
> > > Native Interface. You can find my JNI to Haskell binding
> > library at
> > > https://github.com/neurocyte/foreign-jni. I am primarily using
> > it to
> > > write Android Apps with Haskell,
> >
> > Just out of curiosity, have you got any complete apps that you
> > built that way? Are they in the Google Store?
> >
> > Manuel
> >
> >
> > ___
> > Haskell-Cafe mailing list
> > Haskell-Cafe@haskell.org 
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
> >
> >
> >
>
>
> --
> CJ van den Berg
>
> mailto:c...@vdbonline.com
> xmpp:neuroc...@gmail.com
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Interfacing Java/Haskell

2013-05-28 Thread CJ van den Berg
No, you can go both ways. You can call Haskell from Java and Java from
Haskell.

Write Android Apps in Haskell will of course be just the same as writing
Android Apps in Java. That’s just the price you pay for having full API
access. There is of course nothing preventing someone from creating more
idiomatic Haskell GUI libraries for Android on top of the API bindings.

On 2013-05-28 15:37, Kristopher Micinski wrote:
> I guess you can't really go from native -> framework code like this, so
> this would really make sense only for native methods that are self
> contained.  Is this right?  It seems like this would imply that you can
> only write parts of an app's computation in Haskell, not the whole
> thing.  But maybe I'm wrong.  I have seen people that write apps in
> native / managed code integrating in a reasonable way, but it's very
> ugly afaik.
> 
> Kris
> 
> 
> On Tue, May 28, 2013 at 9:35 AM, Kristopher Micinski
> mailto:krismicin...@gmail.com>> wrote:
> 
> I'm also interested in seeing this.
> 
> Have you ported the Haskell runtime to Android?  It seems like this
> should be able to be done, and through the JNI it seems like you
> should be able to get the system API (albeit, ugly).
> 
> However, I'd be really happy to see this setup if you were willing
> to put it up somewhere so I could hack on it too.
> 
> Kris
> 
> 
> On Mon, May 27, 2013 at 8:07 PM, Manuel M T Chakravarty
> mailto:c...@cse.unsw.edu.au>> wrote:
> 
> CJ van den Berg mailto:c...@vdbonline.com>>:
> > I have successfully written Java/Haskell programs using the Java
> > Native Interface. You can find my JNI to Haskell binding
> library at
> > https://github.com/neurocyte/foreign-jni. I am primarily using
> it to
> > write Android Apps with Haskell,
> 
> Just out of curiosity, have you got any complete apps that you
> built that way? Are they in the Google Store?
> 
> Manuel
> 
> 
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org 
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 
> 
> 


-- 
CJ van den Berg

mailto:c...@vdbonline.com
xmpp:neuroc...@gmail.com

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Interfacing Java/Haskell

2013-05-28 Thread CJ van den Berg
The RTS was ported to Android, yes. But not by me. I just wrote
ghc-android, which is just a build script to help people with setting up
the somewhat complex cross-compiler build.

IIRC Nathan Hüsken did most of the porting work.

Everything you need should be on github. ghc-android and foreign-jni is
pretty much it right now.

Using the JNI is a bit ugly, yes. But I see it really as just a tool for
writing more appealing API bindings, which is what I am working on now.

On 2013-05-28 15:35, Kristopher Micinski wrote:
> I'm also interested in seeing this.
> 
> Have you ported the Haskell runtime to Android?  It seems like this
> should be able to be done, and through the JNI it seems like you should
> be able to get the system API (albeit, ugly).
> 
> However, I'd be really happy to see this setup if you were willing to
> put it up somewhere so I could hack on it too.
> 
> Kris
> 
> 
> On Mon, May 27, 2013 at 8:07 PM, Manuel M T Chakravarty
> mailto:c...@cse.unsw.edu.au>> wrote:
> 
> CJ van den Berg mailto:c...@vdbonline.com>>:
> > I have successfully written Java/Haskell programs using the Java
> > Native Interface. You can find my JNI to Haskell binding library at
> > https://github.com/neurocyte/foreign-jni. I am primarily using it to
> > write Android Apps with Haskell,
> 
> Just out of curiosity, have you got any complete apps that you built
> that way? Are they in the Google Store?
> 
> Manuel
> 
> 
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org 
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 
> 


-- 
CJ van den Berg

mailto:c...@vdbonline.com
xmpp:neuroc...@gmail.com

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Interfacing Java/Haskell

2013-05-28 Thread CJ van den Berg


On 2013-05-28 02:07, Manuel M T Chakravarty wrote:
> CJ van den Berg :
>> I have successfully written Java/Haskell programs using the Java
>> Native Interface. You can find my JNI to Haskell binding library at
>> https://github.com/neurocyte/foreign-jni. I am primarily using it to
>> write Android Apps with Haskell,
> 
> Just out of curiosity, have you got any complete apps that you built
> that way? Are they in the Google Store?

No. Nothing more than the demo app at this point and it is not in the
Play Store. I hope to port some more interesting Haskell application
once I have the full API bindings working. I am fairly short on extra
time though at the moment.

-- 
CJ van den Berg

mailto:c...@vdbonline.com
xmpp:neuroc...@gmail.com
b

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Module import and use in GHC plugin?

2013-05-28 Thread Conal Elliott
In writing GHC plugins, how can I (a) add a module import (preferably
qualified) and (b) make vars/ids for names imported from the newly imported
module (to insert in the transformed Core code)?

Thanks,

  - Conal
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type classes

2013-05-28 Thread Johannes Gerer
Ok, now I see a difference, why Kleisli can be used to relate
typeclasses (like Monad and ArrowApply) and Cokleisli can not:

"Kleisli m () _"  =  "() -> m _" is isomorphic to "m _"

whereas

"Cokleisli m () _" = "m _ -> ()" is not.

Can somebody point out the relevant category theoretical concepts,
that are at work here?



On Tue, May 28, 2013 at 5:43 PM, Tom Ellis
 wrote:
> On Tue, May 28, 2013 at 05:21:58PM +0200, Johannes Gerer wrote:
>> That makes sense. But why does
>>
>> instance Monad m => ArrowApply (Kleisli m)
>>
>> show that a Monad can do anything an ArrowApply can (and the two are
>> thus equivalent)?
>
> I've tried to chase around the equivalence between these two before, and
> I didn't find the algebra simple.  I'll give an outline.
>
> In non-Haskell notation
>
> 1) instance Monad m => ArrowApply (Kleisli m)
>
> means that if "m" is a Monad then "_ -> m _" is an ArrowApply.
>
> 2) instance ArrowApply a => Monad (a anyType)
>
> means that if "_ ~> _" is an ArrowApply then "a ~> _" is a Monad.
>
> One direction seems easy: for a Monad m, 1) gives that "_ -> m _" is an
> ArrowApply.  By 2), "() -> m _" is a Monad.  It is equivalent
> to the Monad m we started with.
>
> Given an ArrowApply "_ ~> _", 2) shows that "() ~> _" is a Monad.  Thus by
> 1) "_ -> (() ~> _)" is an ArrowApply.  I believe this should be the same
> type as "_ ~> _" but I don't see how to demonstrate the isomorphsim here.
>
> Tom
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type classes

2013-05-28 Thread Tom Ellis
On Tue, May 28, 2013 at 05:21:58PM +0200, Johannes Gerer wrote:
> That makes sense. But why does
> 
> instance Monad m => ArrowApply (Kleisli m)
> 
> show that a Monad can do anything an ArrowApply can (and the two are
> thus equivalent)?

I've tried to chase around the equivalence between these two before, and
I didn't find the algebra simple.  I'll give an outline.

In non-Haskell notation

1) instance Monad m => ArrowApply (Kleisli m)

means that if "m" is a Monad then "_ -> m _" is an ArrowApply.

2) instance ArrowApply a => Monad (a anyType)

means that if "_ ~> _" is an ArrowApply then "a ~> _" is a Monad.

One direction seems easy: for a Monad m, 1) gives that "_ -> m _" is an
ArrowApply.  By 2), "() -> m _" is a Monad.  It is equivalent
to the Monad m we started with.

Given an ArrowApply "_ ~> _", 2) shows that "() ~> _" is a Monad.  Thus by
1) "_ -> (() ~> _)" is an ArrowApply.  I believe this should be the same
type as "_ ~> _" but I don't see how to demonstrate the isomorphsim here.

Tom

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type classes

2013-05-28 Thread Johannes Gerer
That makes sense. But why does

instance Monad m => ArrowApply (Kleisli m)

show that a Monad can do anything an ArrowApply can (and the two are
thus equivalent)?

On Tue, May 28, 2013 at 5:17 PM, Tom Ellis
 wrote:
> On Tue, May 28, 2013 at 04:42:35PM +0200, Johannes Gerer wrote:
>> By the same argument, could'nt I say, that any type class (call it
>> AnyClass) can do everything a Monad can:
>>
>> instance AnyClass m => Monad (Cokleilsi m ())
>
> That doesn't say that AnyClass can do anything a Monad can.  "AnyClass m =>
> Monad m" would say that, but that's not what you've got.
>
> What you've got is that "Cokleisli m ()" i.e. "(->) m ()" is a Monad for any
> "m".  This is not surprising.  The implementation is the same as the Reader
> monad.
>
> Check out the instance implementations for "Monad (Reader r)" and "Monad
> (CoKleisli w a)".  You will find they are the same.
>
> 
> http://hackage.haskell.org/packages/archive/mtl/1.1.0.2/doc/html/src/Control-Monad-Reader.html#Reader
> 
> http://hackage.haskell.org/packages/archive/comonad/3.0.0.2/doc/html/src/Control-Comonad.html#Cokleisli
>
> Tom
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type classes

2013-05-28 Thread Tom Ellis
On Tue, May 28, 2013 at 04:42:35PM +0200, Johannes Gerer wrote:
> By the same argument, could'nt I say, that any type class (call it
> AnyClass) can do everything a Monad can:
> 
> instance AnyClass m => Monad (Cokleilsi m ())

That doesn't say that AnyClass can do anything a Monad can.  "AnyClass m =>
Monad m" would say that, but that's not what you've got.

What you've got is that "Cokleisli m ()" i.e. "(->) m ()" is a Monad for any
"m".  This is not surprising.  The implementation is the same as the Reader
monad.

Check out the instance implementations for "Monad (Reader r)" and "Monad
(CoKleisli w a)".  You will find they are the same.


http://hackage.haskell.org/packages/archive/mtl/1.1.0.2/doc/html/src/Control-Monad-Reader.html#Reader

http://hackage.haskell.org/packages/archive/comonad/3.0.0.2/doc/html/src/Control-Comonad.html#Cokleisli

Tom

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [haskell.org Google Summer of Code 2013] Approved Projects

2013-05-28 Thread Edward Kmett
Hi Dominic,

The proposal is admittedly rather unfortunately opaque.

The parts I can shed light on:

Students come up with proposals with the help of the community and then
submit them to google-melange.com.

A bunch of folks from the haskell community sign up as potential mentors,
vote on and discuss the proposals. (We had ~25 candidate mentors and ~20
proposals this year).

The student application template contains a number of desirable criteria
for a successful summer of code application, which is shown on the
google-melange website under our organization -- an old version is
available 
http://hackage.haskell.org/trac/summer-of-code/wiki/StudApply2012contains

Once we have the proposals in hand, and some initial ranking, we ask google
for slots. Allocation is based on past performance, arcane community
parameters that only they know, mentor ratio, etc. This should be our
largest year in the program, despite the fact that in general organizations
have been getting fewer slots as more organizations join, so we're
apparently doing rather well.

In general we do try to select projects that maximize the public good. Most
of the time this can almost be done by just straight cut off based on the
average score. There is some special casing for duplicate applications
between different students and where students have submitted multiple
applications we can have some flexibility in how to apply them.

This year we also received an extra couple of special-purpose darcs slots
from Google in exchange for continuing to act as an umbrella organization
over darcs at the request of the administrator of the program at Google. In
previous years I had requested an extra slot for them, this year the
request came in the other direction.

We do inevitably get more good proposals than we get slots. This year we
could have easily used another 3-4 slots to good effect.

The main part I can't shed light on:

Google requests that the final vote tallies remain private. This is done so
that students who put in proposals to a high volume orgs and don't get
accepted, or who are new to the process and don't quite catch all the
rules, don't wind up with any sort of publicly visible black mark. This
unfortunately means, that we can't really show the unaccepted proposals
with information about how to avoid getting your proposal rejected.

I hope that helps. If you have any more questions or if my answer didn't
suffice please feel free to follow up!

-Edward Kmett



On Tue, May 28, 2013 at 6:52 AM, Dominic Steinitz wrote:

> Hi Edward,
>
> Although the project I am interested in (as a user) has been accepted :-),
> I can't help feeling the selection process is a bit opaque. Is it
> documented somewhere and I just missed it? Apologies if I did.
>
> BTW I appreciate all the hard work that goes into the selection process.
>
> Dominic Steinitz
> domi...@steinitz.org
> http://idontgetoutmuch.wordpress.com
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Generalizing unionWithKey, unionWith, ...

2013-05-28 Thread Petr Pudlák

Dne 28.5.2013 12:32, Johannes Waldmann napsal(a):

Jose A. Lopes  ist.utl.pt> writes:


 unionWith :: Ord k => (a -> b -> c) -> Map k a -> Map
 k b -> Map k c

what should be the result of

unionWith undefined (M.singleton False 42) (M.singleton True "bar")  ?

Perhaps the generalized signature should be instead:

```haskell
unionWith :: Ord k => (Maybe a -> Maybe b -> c) -> Map k a -> Map k b -> 
Map k c

```
(The function would always get at least one `Just`.)
But this functionality can be achieved using `map`s and the current 
`unionWith`.


P.P.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type classes

2013-05-28 Thread Johannes Gerer
Thank you for the comments on the first part. While one can argue
about
the different meanings of powerful and flexible here, that's not the
question. The question is, about showing "A => B" using wrappers like
Kleisli or Cokleisli:

I can use Kleisli to show that a Monad can do everything an
ArrowApply
can do:

Instance Monad m => ArrowApply (Kleisli m)

By the same argument, could'nt I say, that any type class (call it
AnyClass) can do everything a Monad can:

instance AnyClass m => Monad (Cokleilsi m ())




Another way to look at the question:

An Applicative lets you build static trees using the available
combinators. Arrows let you combine effectful computations into
networks
or graphs and monad even more complex things. But again Cokleilsi
crashes the party, as it gives you the Monad's combinators for any
type
and consequently you can build almost anything. I do not understand,
what this tells me!

Johannes

On Tue, May 28, 2013 at 3:04 PM, Anton Kholomiov
 wrote:
> I don't understand the final part of the question but here are some comments
> for the first part.
>
> I don't like the phrase:
>
>
>> the more powerfull a class is, the more fleixblility you have for
>> combining them to complex programs
>
> powerfull, more flexibility, complex programs -- are not so precise terms.
>
> A => B
>
> means that B can do everything that A can do and more (methods that are
> specific to B). So if type is in B we can use all A's methods with it. Does
> it make B more powerful or more flexible? Is Applicative less powerful than
> a Monad? It depends on the program. If we don't ever need the B's specific
> operations they will confuse us all the time. We are going to end up with
> more complex program but not a better one. there are cases when Applicative
> code is much better than a monadic one.
>
> Anton
>
>
>
> 2013/5/28 Johannes Gerer 
>>
>> Dear Haskellers,
>>
>> While trying to understand the interconnection and hierarchy behind
>> the important typeclasses, I stumbled upon the following question that
>> I am not able to answer:
>>
>> There seems to be a hierachy of the type classes, in the sense, that
>> the more powerfull a class is, the more fleixblility you have for
>> combining them to complex programs. (Functor -> Applicative ->
>> Arrow[Choice,Plus,Apply,..] -> Monad). It was nice to read in the
>> Typeclassopedia, that ArrowApply and Monad are equivalent, which is
>> shown by deriving two instances from each other:
>>
>> instance Monad m => ArrowApply (Kleisli m)
>> instance ArrowApply a => Monad (a anyType)
>>
>> The logic seems to be, that if I can derive from every instance of
>> class A an instance of class B, then A is more powerfull than B and
>> (in general) it is easier to be of class B than of class A (e.g. more
>> types can be made Applicatives, than Monads)
>>
>> So far, I think I can follow. But what really hit me was the Cokleisli
>> type. Using it and the logic from above, I can show that ANY type
>> class is more (or equally) powerfull than the Monad:
>>
>> instance AnyClass m => Monad (Cokleilsi m anyType)
>>
>> I know this makes no sense, but where is the fallacy? Why even bother
>> with the above derivation, if any type class can be made into a monad?
>>
>> I can see, that the Monad instance from above does not really
>> transform the type "a", but instead simply fix its first argument. But
>> then on the other hand, the ArrowApply Instance does transform the "m"
>> type (in a way similar to Cokleisli). If attention needs to be paid to
>> the details, then what are they and why did they not matter above?
>>
>> Thanks,
>>
>> Johannes
>>
>> ___
>> Haskell-Cafe mailing list
>> Haskell-Cafe@haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] mapFst and mapSnd

2013-05-28 Thread Emil Axelsson

`mapPair` also exists as `tup2` in patch-combinators:

  http://hackage.haskell.org/package/patch-combinators

/ Emil

2013-05-28 16:01, Andreas Abel skrev:

See Agda.Utils.Tuple :-)

-- | Bifunctoriality for pairs.
(-*-) :: (a -> c) -> (b -> d) -> (a,b) -> (c,d)
(f -*- g) ~(x,y) = (f x, g y)

-- | @mapFst f = f -*- id@
mapFst :: (a -> c) -> (a,b) -> (c,b)
mapFst f ~(x,y) = (f x, y)

-- | @mapSnd g = id -*- g@
mapSnd :: (b -> d) -> (a,b) -> (a,d)
mapSnd g ~(x,y) = (x, g y)

I think mapPair, mapFst, and mapSnd are canonical names that could be
added to Data.Tuple.  But if you suggest this on librar...@haskell.org,
you get probably turned down, see e.g.

   http://comments.gmane.org/gmane.comp.lang.haskell.libraries/17411

Cheers,
Andreas

On 28.05.2013 15:34, Petr Pudlák wrote:

Dne 28.5.2013 10:54, Dominique Devriese napsal(a):

Hi all,

I often find myself needing the following definitions:

   mapPair :: (a -> b) -> (c -> d) -> (a,c) -> (b,d)
   mapPair f g (x,y) = (f x, g y)

   mapFst :: (a -> b) -> (a,c) -> (b,c)
   mapFst f = mapPair f id

   mapSnd :: (b -> c) -> (a,b) -> (a,c)
   mapSnd = mapPair id

But they seem missing from the prelude and Hoogle or Hayoo only turn
up versions of them in packages like scion or fgl.  Has anyone else
felt the need for these functions?  Am I missing some generalisation
of them perhaps?

Apart from Arrows, there is also package "bifunctors" that defines this
functionality for (,), Either and a few others:
http://hackage.haskell.org/packages/archive/bifunctors/3.2.0.1/doc/html/Data-Bifunctor.html



Petr Pudlak


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe






___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] mapFst and mapSnd

2013-05-28 Thread Andreas Abel

See Agda.Utils.Tuple :-)

-- | Bifunctoriality for pairs.
(-*-) :: (a -> c) -> (b -> d) -> (a,b) -> (c,d)
(f -*- g) ~(x,y) = (f x, g y)

-- | @mapFst f = f -*- id@
mapFst :: (a -> c) -> (a,b) -> (c,b)
mapFst f ~(x,y) = (f x, y)

-- | @mapSnd g = id -*- g@
mapSnd :: (b -> d) -> (a,b) -> (a,d)
mapSnd g ~(x,y) = (x, g y)

I think mapPair, mapFst, and mapSnd are canonical names that could be 
added to Data.Tuple.  But if you suggest this on librar...@haskell.org, 
you get probably turned down, see e.g.


  http://comments.gmane.org/gmane.comp.lang.haskell.libraries/17411

Cheers,
Andreas

On 28.05.2013 15:34, Petr Pudlák wrote:

Dne 28.5.2013 10:54, Dominique Devriese napsal(a):

Hi all,

I often find myself needing the following definitions:

   mapPair :: (a -> b) -> (c -> d) -> (a,c) -> (b,d)
   mapPair f g (x,y) = (f x, g y)

   mapFst :: (a -> b) -> (a,c) -> (b,c)
   mapFst f = mapPair f id

   mapSnd :: (b -> c) -> (a,b) -> (a,c)
   mapSnd = mapPair id

But they seem missing from the prelude and Hoogle or Hayoo only turn
up versions of them in packages like scion or fgl.  Has anyone else
felt the need for these functions?  Am I missing some generalisation
of them perhaps?

Apart from Arrows, there is also package "bifunctors" that defines this
functionality for (,), Either and a few others:
http://hackage.haskell.org/packages/archive/bifunctors/3.2.0.1/doc/html/Data-Bifunctor.html


Petr Pudlak


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe




--
Andreas Abel  <><  Du bist der geliebte Mensch.

Theoretical Computer Science, University of Munich
Oettingenstr. 67, D-80538 Munich, GERMANY

andreas.a...@ifi.lmu.de
http://www2.tcs.ifi.lmu.de/~abel/

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: Haskell Platform 2013.2.0.0

2013-05-28 Thread harry
Good to see it released! Was there a deliberate decision not to build a
Windows x64 platform, or is it just that there wasn't anyone to do it?


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Interfacing Java/Haskell

2013-05-28 Thread Kristopher Micinski
I guess you can't really go from native -> framework code like this, so
this would really make sense only for native methods that are self
contained.  Is this right?  It seems like this would imply that you can
only write parts of an app's computation in Haskell, not the whole thing.
 But maybe I'm wrong.  I have seen people that write apps in native /
managed code integrating in a reasonable way, but it's very ugly afaik.

Kris


On Tue, May 28, 2013 at 9:35 AM, Kristopher Micinski  wrote:

> I'm also interested in seeing this.
>
> Have you ported the Haskell runtime to Android?  It seems like this should
> be able to be done, and through the JNI it seems like you should be able to
> get the system API (albeit, ugly).
>
> However, I'd be really happy to see this setup if you were willing to put
> it up somewhere so I could hack on it too.
>
> Kris
>
>
> On Mon, May 27, 2013 at 8:07 PM, Manuel M T Chakravarty <
> c...@cse.unsw.edu.au> wrote:
>
>> CJ van den Berg :
>> > I have successfully written Java/Haskell programs using the Java
>> > Native Interface. You can find my JNI to Haskell binding library at
>> > https://github.com/neurocyte/foreign-jni. I am primarily using it to
>> > write Android Apps with Haskell,
>>
>> Just out of curiosity, have you got any complete apps that you built that
>> way? Are they in the Google Store?
>>
>> Manuel
>>
>>
>> ___
>> Haskell-Cafe mailing list
>> Haskell-Cafe@haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] mapFst and mapSnd

2013-05-28 Thread Petr Pudlák

Dne 28.5.2013 10:54, Dominique Devriese napsal(a):

Hi all,

I often find myself needing the following definitions:

   mapPair :: (a -> b) -> (c -> d) -> (a,c) -> (b,d)
   mapPair f g (x,y) = (f x, g y)

   mapFst :: (a -> b) -> (a,c) -> (b,c)
   mapFst f = mapPair f id

   mapSnd :: (b -> c) -> (a,b) -> (a,c)
   mapSnd = mapPair id

But they seem missing from the prelude and Hoogle or Hayoo only turn
up versions of them in packages like scion or fgl.  Has anyone else
felt the need for these functions?  Am I missing some generalisation
of them perhaps?
Apart from Arrows, there is also package "bifunctors" that defines this 
functionality for (,), Either and a few others:

http://hackage.haskell.org/packages/archive/bifunctors/3.2.0.1/doc/html/Data-Bifunctor.html

Petr Pudlak


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Interfacing Java/Haskell

2013-05-28 Thread Kristopher Micinski
I'm also interested in seeing this.

Have you ported the Haskell runtime to Android?  It seems like this should
be able to be done, and through the JNI it seems like you should be able to
get the system API (albeit, ugly).

However, I'd be really happy to see this setup if you were willing to put
it up somewhere so I could hack on it too.

Kris


On Mon, May 27, 2013 at 8:07 PM, Manuel M T Chakravarty <
c...@cse.unsw.edu.au> wrote:

> CJ van den Berg :
> > I have successfully written Java/Haskell programs using the Java
> > Native Interface. You can find my JNI to Haskell binding library at
> > https://github.com/neurocyte/foreign-jni. I am primarily using it to
> > write Android Apps with Haskell,
>
> Just out of curiosity, have you got any complete apps that you built that
> way? Are they in the Google Store?
>
> Manuel
>
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type classes

2013-05-28 Thread Anton Kholomiov
I don't understand the final part of the question but here are some
comments for the first part.

I don't like the phrase:

> the more powerfull a class is, the more fleixblility you have for
> combining them to complex programs

powerfull, more flexibility, complex programs -- are not so precise terms.

A => B

means that B can do everything that A can do and more (methods that are
specific to B). So if type is in B we can use all A's methods with it. Does
it make B more powerful or more flexible? Is Applicative less powerful than
a Monad? It depends on the program. If we don't ever need the B's specific
operations they will confuse us all the time. We are going to end up with
more complex program but not a better one. there are cases when Applicative
code is much better than a monadic one.

Anton



2013/5/28 Johannes Gerer 

> Dear Haskellers,
>
> While trying to understand the interconnection and hierarchy behind
> the important typeclasses, I stumbled upon the following question that
> I am not able to answer:
>
> There seems to be a hierachy of the type classes, in the sense, that
> the more powerfull a class is, the more fleixblility you have for
> combining them to complex programs. (Functor -> Applicative ->
> Arrow[Choice,Plus,Apply,..] -> Monad). It was nice to read in the
> Typeclassopedia, that ArrowApply and Monad are equivalent, which is
> shown by deriving two instances from each other:
>
> instance Monad m => ArrowApply (Kleisli m)
> instance ArrowApply a => Monad (a anyType)
>
> The logic seems to be, that if I can derive from every instance of
> class A an instance of class B, then A is more powerfull than B and
> (in general) it is easier to be of class B than of class A (e.g. more
> types can be made Applicatives, than Monads)
>
> So far, I think I can follow. But what really hit me was the Cokleisli
> type. Using it and the logic from above, I can show that ANY type
> class is more (or equally) powerfull than the Monad:
>
> instance AnyClass m => Monad (Cokleilsi m anyType)
>
> I know this makes no sense, but where is the fallacy? Why even bother
> with the above derivation, if any type class can be made into a monad?
>
> I can see, that the Monad instance from above does not really
> transform the type "a", but instead simply fix its first argument. But
> then on the other hand, the ArrowApply Instance does transform the "m"
> type (in a way similar to Cokleisli). If attention needs to be paid to
> the details, then what are they and why did they not matter above?
>
> Thanks,
>
> Johannes
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Type classes

2013-05-28 Thread Johannes Gerer
Dear Haskellers,

While trying to understand the interconnection and hierarchy behind
the important typeclasses, I stumbled upon the following question that
I am not able to answer:

There seems to be a hierachy of the type classes, in the sense, that
the more powerfull a class is, the more fleixblility you have for
combining them to complex programs. (Functor -> Applicative ->
Arrow[Choice,Plus,Apply,..] -> Monad). It was nice to read in the
Typeclassopedia, that ArrowApply and Monad are equivalent, which is
shown by deriving two instances from each other:

instance Monad m => ArrowApply (Kleisli m)
instance ArrowApply a => Monad (a anyType)

The logic seems to be, that if I can derive from every instance of
class A an instance of class B, then A is more powerfull than B and
(in general) it is easier to be of class B than of class A (e.g. more
types can be made Applicatives, than Monads)

So far, I think I can follow. But what really hit me was the Cokleisli
type. Using it and the logic from above, I can show that ANY type
class is more (or equally) powerfull than the Monad:

instance AnyClass m => Monad (Cokleilsi m anyType)

I know this makes no sense, but where is the fallacy? Why even bother
with the above derivation, if any type class can be made into a monad?

I can see, that the Monad instance from above does not really
transform the type "a", but instead simply fix its first argument. But
then on the other hand, the ArrowApply Instance does transform the "m"
type (in a way similar to Cokleisli). If attention needs to be paid to
the details, then what are they and why did they not matter above?

Thanks,

Johannes

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Generalizing unionWithKey, unionWith, ...

2013-05-28 Thread Johannes Waldmann
Jose A. Lopes  ist.utl.pt> writes:

> What makes it an interesting example ?

it shows that your proposed type for unionWith is not reasonable.

> why would you want to use undefined in that particular case?

the two argument maps have disjoint key sets,
so the combining function will never be called,
and writing "undefined" just states this.

of course, all of this refers to the implicit specification 
for unionWith, which should contain something like

M.keysSet (M.unionWith f m1 m2) = S.union (M.keysSet m1) (M.keysSet m2)

(hence the name, union) and this is an implication of

M.lookup k (M.unionWith f m1 m1) = 
case (M.lookup k m1, M.lookup k m2) of
(Nothing,Nothing) -> Nothing
(Just v1, Nothing) -> Just v1
(Nothing,Just v2) -> Just v2
(Just v1, Just v2) -> Just (f v1 v2)

I would very much welcome that such specs be added to the 
library documentation - in some suitable way, e.g., haddock
can generate "source" links already, and it would be nice if it 
also could show "spec" links, pointing to small/quick-check properties, 
which I guess are in the source code somewhere already,
cf. 
https://github.com/haskell/containers/blob/master/tests/map-properties.hs#L408 

- J.W.



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [haskell.org Google Summer of Code 2013] Approved Projects

2013-05-28 Thread Dominic Steinitz
Hi Edward,

Although the project I am interested in (as a user) has been accepted :-), I 
can't help feeling the selection process is a bit opaque. Is it documented 
somewhere and I just missed it? Apologies if I did.

BTW I appreciate all the hard work that goes into the selection process.

Dominic Steinitz
domi...@steinitz.org
http://idontgetoutmuch.wordpress.com


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Generalizing unionWithKey, unionWith, ...

2013-05-28 Thread Jose A. Lopes

Yes! intersectionWith is just what I needed.

In any case, coming back to your example, why would
you want to use undefined in that particular case?

What makes it an interesting example ?

Best,
Jose

On 28-05-2013 12:32, Johannes Waldmann wrote:

Jose A. Lopes  ist.utl.pt> writes:


 unionWith :: Ord k => (a -> b -> c) -> Map k a -> Map
 k b -> Map k c

what should be the result of

unionWith undefined (M.singleton False 42) (M.singleton True "bar")  ?

perhaps you mean intersectionWith, which already has the type you want.

- J.W.



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


--
José António Branquinho de Oliveira Lopes
Instituto Superior Técnico
Technical University of Lisbon


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Generalizing unionWithKey, unionWith, ...

2013-05-28 Thread Johannes Waldmann
Jose A. Lopes  ist.utl.pt> writes:

> unionWith :: Ord k => (a -> b -> c) -> Map k a -> Map
> k b -> Map k c

what should be the result of

unionWith undefined (M.singleton False 42) (M.singleton True "bar")  ?

perhaps you mean intersectionWith, which already has the type you want.

- J.W.



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Generalizing unionWithKey, unionWith, ...

2013-05-28 Thread Jose A. Lopes

Hello everyone,

unionWithKey and unionWith have the following types

unionWith :: Ord k => (a -> a -> a) -> Map k a -> Map k a -> Map k a
unionWithKey :: Ord k => (k -> a -> a -> a) -> Map k a -> Map k a -> Map k a

Since they are implemented by means of mergeWithKey,
wouldn't it be possible to generalize these functions to the
following types ?

unionWith :: Ord k => (a -> b -> c) -> Map k a -> Map k b -> Map k c
unionWithKey :: Ord k => (k -> a -> b -> c) -> Map k a -> Map k b -> Map k c

Cheers,
Jose

--
José António Branquinho de Oliveira Lopes
Instituto Superior Técnico
Technical University of Lisbon

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] mapFst and mapSnd

2013-05-28 Thread Dominique Devriese
2013/5/28 Tikhon Jelvis :
> These are present in Control.Arrow as (***), first and second respectively.

Right, thanks. Strange that neither Hayoo nor Hoogle turned these up..

Dominique

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] mapFst and mapSnd

2013-05-28 Thread Andrew Butterfield
I have them defined for my stuff.

Generally I find it much quicker  to "roll my own" than to
(1) ask on this list if someone else has done it...
(2) look at arrows or 
MyFavouriteCategoryTheoryBitOfFPBecauseICantGetAbstractEnough
and the try to figure out what is going on.

The joy of Haskell is both that rolling your own is often so easy,
and that there are lots of approaches out there that allow you to get abstract 
as well...


Regards,
  Andrew (Engineering graduate, feet still firmly embedded in concrete :-)



On 28 May 2013, at 09:54, Dominique Devriese wrote:

> Hi all,
> 
> I often find myself needing the following definitions:
> 
>  mapPair :: (a -> b) -> (c -> d) -> (a,c) -> (b,d)
>  mapPair f g (x,y) = (f x, g y)
> 
>  mapFst :: (a -> b) -> (a,c) -> (b,c)
>  mapFst f = mapPair f id
> 
>  mapSnd :: (b -> c) -> (a,b) -> (a,c)
>  mapSnd = mapPair id
> 
> But they seem missing from the prelude and Hoogle or Hayoo only turn
> up versions of them in packages like scion or fgl.  Has anyone else
> felt the need for these functions?  Am I missing some generalisation
> of them perhaps?
> 
> Regards,
> Dominique
> 
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe


Andrew Butterfield Tel: +353-1-896-2517 Fax: +353-1-677-2204
Lero@TCD, Head of Foundations & Methods Research Group
Director of Teaching and Learning - Undergraduate,
School of Computer Science and Statistics,
Room G.39, O'Reilly Institute, Trinity College, University of Dublin
  http://www.scss.tcd.ie/Andrew.Butterfield/



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] mapFst and mapSnd

2013-05-28 Thread Gregory Collins
On Tue, May 28, 2013 at 10:54 AM, Dominique Devriese <
dominique.devri...@cs.kuleuven.be> wrote:

> Hi all,
>
> I often find myself needing the following definitions:
>
>   mapPair :: (a -> b) -> (c -> d) -> (a,c) -> (b,d)
>   mapPair f g (x,y) = (f x, g y)
>

That's Control.Arrow.(***), e.g.:

ghci> (+3) *** (*5) $ (20,30)
(23,150)


>
>   mapFst :: (a -> b) -> (a,c) -> (b,c)
>   mapFst f = mapPair f id
>
>   mapSnd :: (b -> c) -> (a,b) -> (a,c)
>   mapSnd = mapPair id
>

That's Control.Arrow.{first, second}:

ghci> first (+10) (1,1)
(11,1)
ghci> second (+10) (1,1)
(1,11)

G
-- 
Gregory Collins 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] mapFst and mapSnd

2013-05-28 Thread Tikhon Jelvis
These are present in Control.Arrow as (***), first and second respectively.

They are easy to overlook because they work for *all* arrows, not just
functions. So the type signatures look like:

first :: Arrow a => a b c -> a (b, d) (c, d)

If you replace a with (->), you'll see that this is exactly like your
mapFst.


On Tue, May 28, 2013 at 1:54 AM, Dominique Devriese <
dominique.devri...@cs.kuleuven.be> wrote:

> Hi all,
>
> I often find myself needing the following definitions:
>
>   mapPair :: (a -> b) -> (c -> d) -> (a,c) -> (b,d)
>   mapPair f g (x,y) = (f x, g y)
>
>   mapFst :: (a -> b) -> (a,c) -> (b,c)
>   mapFst f = mapPair f id
>
>   mapSnd :: (b -> c) -> (a,b) -> (a,c)
>   mapSnd = mapPair id
>
> But they seem missing from the prelude and Hoogle or Hayoo only turn
> up versions of them in packages like scion or fgl.  Has anyone else
> felt the need for these functions?  Am I missing some generalisation
> of them perhaps?
>
> Regards,
> Dominique
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] mapFst and mapSnd

2013-05-28 Thread Benjamin Edwards
You might want to look at the arrow type class and the instance for (->).

Ben
On 28 May 2013 09:56, "Dominique Devriese" <
dominique.devri...@cs.kuleuven.be> wrote:

> Hi all,
>
> I often find myself needing the following definitions:
>
>   mapPair :: (a -> b) -> (c -> d) -> (a,c) -> (b,d)
>   mapPair f g (x,y) = (f x, g y)
>
>   mapFst :: (a -> b) -> (a,c) -> (b,c)
>   mapFst f = mapPair f id
>
>   mapSnd :: (b -> c) -> (a,b) -> (a,c)
>   mapSnd = mapPair id
>
> But they seem missing from the prelude and Hoogle or Hayoo only turn
> up versions of them in packages like scion or fgl.  Has anyone else
> felt the need for these functions?  Am I missing some generalisation
> of them perhaps?
>
> Regards,
> Dominique
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] mapFst and mapSnd

2013-05-28 Thread Dominique Devriese
Hi all,

I often find myself needing the following definitions:

  mapPair :: (a -> b) -> (c -> d) -> (a,c) -> (b,d)
  mapPair f g (x,y) = (f x, g y)

  mapFst :: (a -> b) -> (a,c) -> (b,c)
  mapFst f = mapPair f id

  mapSnd :: (b -> c) -> (a,b) -> (a,c)
  mapSnd = mapPair id

But they seem missing from the prelude and Hoogle or Hayoo only turn
up versions of them in packages like scion or fgl.  Has anyone else
felt the need for these functions?  Am I missing some generalisation
of them perhaps?

Regards,
Dominique

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Munich Haskell Meeting

2013-05-28 Thread Heinrich Hördegen

Dear all,

once again, our monthly Haskell Meeting in Munich will take place. We 
meet on Thursday, 30 of May, 19h30. The venue is as usually, Cafe Puck.


Please go here for details and click the button if you plan to join:

http://www.haskell-munich.de/dates

Have a successful day!
Heinrich


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe