[Haskell-cafe] BayHac '13

2013-03-12 Thread Mark Lentczner
Please join us for a weekend of Haskell hacking:

*BayHac '13*
*May 17th ~ 19th, 2013*
*Hacker Dojo*
*Mountain View, CA*


Full details on the Haskell Wiki: BayHac
'13

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


[Haskell-cafe] Lazy object deserialization

2013-03-12 Thread Scott Lawrence

Hey all,

All the object serialization/deserialization libraries I could find (pretty 
much just binary and cereal) seem to be strict with respect to the actual data 
being serialized. In particular, if I've serialized a large [Int] to a file, 
and I want to get the first element, it seems I have no choice but to 
deserialize the entire data structure. This is obviously an issue for large 
data sets.


There are obvious workarounds (explicitly fetch elements from the "database" 
instead of relying on unsafeInterleaveIO to deal with it all magically), but 
it seems like it should be possible to build a cereal-like library that allows 
proper lazy deserialization. Does it exist, and I've just missed it?


Thanks,

--
Scott Lawrence

Linux baidar 3.7.10-1-ARCH #1 SMP PREEMPT Thu Feb 28 09:50:17 CET 2013 x86_64 
GNU/Linux

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


[Haskell-cafe] ANN: retry 0.1 - retry combinators for monadic actions that often fail

2013-03-12 Thread Ozgun Ataman
Dear Cafe, 

I'm happy to announce the availability of the retry package on Hackage[1] and 
Github[2]. The package provides a few useful combinators for monadic actions 
that often fail and should be retried in cases of a certain set of exceptions 
(or failure modes). Such cases are quite common when querying databases (e.g. 
ResponseTimeout) or uploading files (e.g. socket closed), particularly in busy 
production systems.

The library exposes 'retrying' for failures encoded explicitly in the type and 
'recovering' for failures through exceptions, respectively. You can choose 
either an "exponential back off" series of delays or a simple static delay 
between retries. In either case, there is a ceiling for the number of total 
retries. The haddocks provide further documentation and a few examples.

This library simply wraps around the given actions and does not really do 
anything fancy or unexpected. Nevertheless, the widespread applicability of 
this functionality justified a generic package to address the need centrally.

Suggestions and bug reports are most welcome.

[1] http://hackage.haskell.org/package/retry
[2] https://github.com/Soostone/retry

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


Re: [Haskell-cafe] Open-source projects for beginning Haskell students?

2013-03-12 Thread Alp Mestanogullari
[1]: http://github.com/alpmestan/hnn


On Wed, Mar 13, 2013 at 1:03 AM, Alp Mestanogullari wrote:

> Hi,
>
> My suggestion may sound a bit odd, but if they're looking for a
> challenging but still simple enough project, I'd love for people to test
> out the new version of hnn (not yet released, but on github [1]) and make
> something fun with it. I'd love to mentor this and add things to the
> library altogether as they progress and give some feedback. The biggest
> issue with that proposal is that they either have to know a bit about
> neural networks before or must be able to learn very quickly. This can
> however be compensated by that warm feeling you have when your neural net
> finally does what you want it to.
>
>
> On Mon, Mar 11, 2013 at 4:48 PM, Brent Yorgey wrote:
>
>> Hi everyone,
>>
>> I am currently teaching a half-credit introductory Haskell class for
>> undergraduates.  This is the third time I've taught it.  Both of the
>> previous times, for their final project I gave them the option of
>> contributing to an open-source project; a couple groups/individuals
>> took me up on it and I think it ended up being a modest success.
>>
>> So I'd like to do it again this time around, and am looking for
>> particular projects I can suggest to them.  Do you have an open-source
>> project with a few well-specified tasks that a relative beginner (see
>> below) could reasonably make a contribution towards in the space of
>> about four weeks? I'm aware that most tasks don't fit that profile,
>> but even complex projects usually have a few "simple-ish" tasks that
>> haven't yet been done just because "no one has gotten around to it
>> yet".
>>
>> If you have any such projects, I'd love to hear about it!  Just send
>> me a paragraph or so describing your project and explaining what
>> task(s) you could use help with --- something that I could put on the
>> course website for students to look at.
>>
>> Here are a few more details:
>>
>> * The students will be working on the projects from approximately the
>>   end of this month through the end of April.  During the next two
>>   weeks they would be contacting you to discuss the possibility of
>>   working on your project.
>>
>> * By "relative beginner" I mean someone familiar with the material
>>   listed here: http://www.cis.upenn.edu/~cis194/lectures.html and just
>>   trying to come to terms with Applicative and Monad.  They definitely
>>   do not know much if anything about optimization/profiling, GADTs,
>>   the mtl, or Haskell-programming-in-the-large.  (Although part of the
>>   point of the project is to teach them a bit about
>>   programming-in-the-(medium/large)).
>>
>> * What I would hope from you is a willingness to exchange email and/or
>>   chat with the student(s) over the course of the project, to give
>>   them a bit of guidance/mentoring.  I am certainly willing to help on
>>   that front, but of course I probably don't know much about your
>>   particular project.
>>
>> Thanks!
>> -Brent
>>
>> ___
>> Haskell-Cafe mailing list
>> Haskell-Cafe@haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>
>
>
> --
> Alp Mestanogullari
>



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


Re: [Haskell-cafe] Open-source projects for beginning Haskell students?

2013-03-12 Thread Alp Mestanogullari
Hi,

My suggestion may sound a bit odd, but if they're looking for a challenging
but still simple enough project, I'd love for people to test out the new
version of hnn (not yet released, but on github [1]) and make something fun
with it. I'd love to mentor this and add things to the library altogether
as they progress and give some feedback. The biggest issue with that
proposal is that they either have to know a bit about neural networks
before or must be able to learn very quickly. This can however be
compensated by that warm feeling you have when your neural net finally does
what you want it to.


On Mon, Mar 11, 2013 at 4:48 PM, Brent Yorgey wrote:

> Hi everyone,
>
> I am currently teaching a half-credit introductory Haskell class for
> undergraduates.  This is the third time I've taught it.  Both of the
> previous times, for their final project I gave them the option of
> contributing to an open-source project; a couple groups/individuals
> took me up on it and I think it ended up being a modest success.
>
> So I'd like to do it again this time around, and am looking for
> particular projects I can suggest to them.  Do you have an open-source
> project with a few well-specified tasks that a relative beginner (see
> below) could reasonably make a contribution towards in the space of
> about four weeks? I'm aware that most tasks don't fit that profile,
> but even complex projects usually have a few "simple-ish" tasks that
> haven't yet been done just because "no one has gotten around to it
> yet".
>
> If you have any such projects, I'd love to hear about it!  Just send
> me a paragraph or so describing your project and explaining what
> task(s) you could use help with --- something that I could put on the
> course website for students to look at.
>
> Here are a few more details:
>
> * The students will be working on the projects from approximately the
>   end of this month through the end of April.  During the next two
>   weeks they would be contacting you to discuss the possibility of
>   working on your project.
>
> * By "relative beginner" I mean someone familiar with the material
>   listed here: http://www.cis.upenn.edu/~cis194/lectures.html and just
>   trying to come to terms with Applicative and Monad.  They definitely
>   do not know much if anything about optimization/profiling, GADTs,
>   the mtl, or Haskell-programming-in-the-large.  (Although part of the
>   point of the project is to teach them a bit about
>   programming-in-the-(medium/large)).
>
> * What I would hope from you is a willingness to exchange email and/or
>   chat with the student(s) over the course of the project, to give
>   them a bit of guidance/mentoring.  I am certainly willing to help on
>   that front, but of course I probably don't know much about your
>   particular project.
>
> Thanks!
> -Brent
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



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


Re: [Haskell-cafe] cabal install oddities

2013-03-12 Thread Manuel Gómez
On Tue, Mar 12, 2013 at 3:10 PM, Tycho Andersen  wrote:
> On Tue, Mar 12, 2013 at 03:28:08PM -0400, Brandon Allbery wrote:
>>
>> "cabal install" unpacks a package into /tmp in order to build it. My guess
>> is your OS has /tmp mounted noexec. I don't know offhand how you override
>> this in cabal.
>
> Yep, you're exactly right. Thank you! I also couldn't figure out a way
> to override it.

I ran into this once.  I suppose it’s a bit of a dirty workaround, but
you can patch `Cabal` or `directory` to avoid this problem by either
hard-coding a different path for temporary files.
`System.Directory.getTemporaryDirectory` in the `directory` package
has `/tmp` kind-of hardcoded in UNIX.  Or you could hack the places
where it’s used in `Cabal`.  It’s used in these locations in the
latest version:

*   `./Distribution/Simple/GHC.hs`, line 342

*   `./Distribution/Simple/Utils.hs`, line473

*   `./Distribution/Simple/Configure.hs`, line 945

*   `./Distribution/Simple/LHC.hs`, line 203

I say it’s kind-of hardcoded because it actually seems to try taking
the value of the environment variable `TMPDIR`, so you may be able to
override that path quite simply by defining that in your environment.
I have not tested this, though — I didn’t notice it when I faced this
problem a few months ago.  This, of course, would be the best
solution.

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


Re: [Haskell-cafe] Open-source projects for beginning Haskell students?

2013-03-12 Thread Joachim Breitner
Hi,

Am Montag, den 11.03.2013, 11:48 -0400 schrieb Brent Yorgey:
> If you have any such projects, I'd love to hear about it!  Just send
> me a paragraph or so describing your project and explaining what
> task(s) you could use help with --- something that I could put on the
> course website for students to look at.

arbtt, the Automatic Rule-Based Time-Tracker could possibly be an
sufficiently interesting application with lots of corners for
improvement. Someone could for example try to generate graphs from it,
or add other statistical analyses... but I guess you are interested in a
better defined task?

Some pointers:
http://hackage.haskell.org/package/arbtt
http://darcs.nomeata.de/arbtt/doc/users_guide/
https://www.joachim-breitner.de/blog/archives/336-The-Automatic-Rule-Based-Time-Tracker.html
https://lists.nomeata.de/mailman/listinfo/arbtt

Greetings,
Joachim

-- 
Joachim "nomeata" Breitner
Debian Developer
  nome...@debian.org | ICQ# 74513189 | GPG-Keyid: 4743206C
  JID: nome...@joachim-breitner.de | http://people.debian.org/~nomeata



signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Overloading

2013-03-12 Thread Carlos Camarao
>
> On Tue, Mar 12, 2013 at 5:54 PM, Richard A. O'Keefe 
> wrote:
>
> Carlos Camarao wrote:
>
> >> Sorry, I think my sentence:
> >>"To define (+) as an overloaded operator in Haskell,
> >>  you have to define and use a type class."
> >>is not quite correct.  I meant that to define any operator in
> Haskell you have to
> >> have a type class defined with that operator as member.
>
> > No.  Operators and type classes are entirely orthogonal in Haskell.
> > For example, the list concatenation operator (++) is not defined in
> > any type class.  It could be.  Either the `mplus` of
> > MonadPlus or the `mappend` of Monoid would make sense.  But it
> > happens not to be.
>
> I have already corrected myself (repeating, I meant:
>"To define an _overloaded_ name or operator in Haskell you have to
> have a type class defined with that name/operator as member").
>
> >> Yes, but the requirement of using the "predefined" (+) is an extra
> >> requirement (I would call (+) in Haskell not a predefined operator,
> >> but an operator whose type is defined in a class (Num) which is in
> the
> >> Prelude). A Haskell programmer can still define versions of (+)
> where
> >> the arguments are of two different types and the result is a third
> >> (he cannot though use the two type classes, and thus neither
> instances
> >> of these two type classes, in a program).
>
> > I wish we could argue over semantics instead of vocabulary.
> > By calling the (+) of Num "predefined" I meant nothing other than
> > "it is _defined_ in the Haskell report before (_pre_) you or I add
> > any code of our own".  We agree on the facts.
>
> Ok. But the fact that (+) has type a->a->a is a matter (design
> decision) related to the definition of class Num in the Haskell
> Prelude. If (+) had type a->b->c, the fact that
>
>"A Haskell programmer can still define versions of (+) where the
> arguments are of two different types and the result is a third"
>
> would _not_ depend on hiding and redefining a type class. The programmer
> could then just define the desired instances.
>
> > I don't call it an "extra" requirement.  The original context
> > was very clearly that in C++ where you have int+int, int+double,
> > double+int, double+double, char*+int, int+char* and so on all
> > predefined, you can *also* add your own date+period *without*
> > hiding the predefined versions. And _that_ is overloading.
> > If the question is whether Haskell can do overloading, _that_ is
> > what has to be achieved: you can add a *new* interface
> > date+period *without* hiding the ones that were already defined
> > before you started coding.
>


> See above. In this view redefining the type of (+) in class Num

as a->b->c would be sufficient for Haskell to have overloading.
>
> > The interesting challenge here is that we should have
> >Date   + Period -> Date  Date   - Period -> Date
> >Period + Date   -> Date  Period - Date   -> ILLEGAL
> >Period + Period -> DeriodPeriod - Period -> Period
> >Date   + Date   -> ILLEGAL   Date   - Date   -> Date
> > and _also_ (remember we are trying to beat C++ here) Int +/- Int ->
> Int.
> >
> >  I suspect that this can be done using type-level programming (so
> that
> > Date + Date and Period - Date _begin_ to type check but then violate
> > a type constraint) but that's where my Haskell skills are most
> risible.
>

  Without redefining the type of (+) in the Prelude, the challenge can be
met by
  redefining (+) in another type class (and, yes, if Prelude.(+) is also
needed,
  hiding and importing it qualified).

  Note though that in this case _polymorphic_ uses of (+), whose
instantiation
  could be for instances of both classes (Prelude.Num and the other one)
  are not possible.

  Kind regards,

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


Re: [Haskell-cafe] Overloading

2013-03-12 Thread Donn Cave
On Mar 13, 2013, at 12:54 AM, "Richard A. O'Keefe"  wrote:

> The interesting challenge here is that we should have
> 
>Date   + Period -> Date  Date   - Period -> Date
>Period + Date   -> Date  Period - Date   -> ILLEGAL
>Period + Period -> DeriodPeriod - Period -> Period
>Date   + Date   -> ILLEGAL   Date   - Date   -> Date
> 
> and _also_ (remember we are trying to beat C++ here) Int +/- Int -> Int.

I think I would also want

Period * Int -> Period
Period * Period -> ILLEGAL


Donn

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


Re: [Haskell-cafe] Overloading

2013-03-12 Thread David Thomas
If you add NoImplicitPrelude, I think you should also be able to do:

import Prelude hiding (Num)
import qualified Prelude (Num)

instance Num a => Plus a a where
type PlusResult a a = a
a + b = a Prelude.+ b




On Tue, Mar 12, 2013 at 2:24 PM, MigMit  wrote:

> On Mar 13, 2013, at 12:54 AM, "Richard A. O'Keefe" 
> wrote:
> > The interesting challenge here is that we should have
> >
> >Date   + Period -> Date  Date   - Period -> Date
> >Period + Date   -> Date  Period - Date   -> ILLEGAL
> >Period + Period -> DeriodPeriod - Period -> Period
> >Date   + Date   -> ILLEGAL   Date   - Date   -> Date
> >
> > and _also_ (remember we are trying to beat C++ here) Int +/- Int -> Int.
>
> Well, an obvious suggestion would be to use MultiParamTypeClasses and
> TypeFamilies:
>
> {- LANGUAGE MultiParamTypeClasses, TypeFamilies -}
> module Date where
> import Prelude hiding (Num, (+))
> data Date = Date
> data Period = Period
> class Plus a b where
> type PlusResult a b
> (+) :: a -> b -> PlusResult a b
> instance Plus Date Period where
> type PlusResult Date Period = Date
> Date + Period = Date
> instance Plus Period Date where
> type PlusResult Period Date = Date
> Period + Date = Date
> instance Plus Period Period where
> type PlusResult Period Period = Period
> Period + Period = Period
>
> But I suppose you've been thinking about Haskell98. That, I'm afraid,
> doesn't seem possible.
> ___
> 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] Overloading

2013-03-12 Thread MigMit
On Mar 13, 2013, at 12:54 AM, "Richard A. O'Keefe"  wrote:
> The interesting challenge here is that we should have
> 
>Date   + Period -> Date  Date   - Period -> Date
>Period + Date   -> Date  Period - Date   -> ILLEGAL
>Period + Period -> DeriodPeriod - Period -> Period
>Date   + Date   -> ILLEGAL   Date   - Date   -> Date
> 
> and _also_ (remember we are trying to beat C++ here) Int +/- Int -> Int.

Well, an obvious suggestion would be to use MultiParamTypeClasses and 
TypeFamilies:

{- LANGUAGE MultiParamTypeClasses, TypeFamilies -}
module Date where
import Prelude hiding (Num, (+))
data Date = Date
data Period = Period
class Plus a b where
type PlusResult a b
(+) :: a -> b -> PlusResult a b
instance Plus Date Period where
type PlusResult Date Period = Date
Date + Period = Date
instance Plus Period Date where
type PlusResult Period Date = Date
Period + Date = Date
instance Plus Period Period where
type PlusResult Period Period = Period
Period + Period = Period

But I suppose you've been thinking about Haskell98. That, I'm afraid, doesn't 
seem possible.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Open-source projects for beginning Haskell students?

2013-03-12 Thread Simon Michael

[4] http://hub.darcs.net/simon/rss2irc/browse/NOTES.org

On 3/12/13 2:13 PM, Simon Michael wrote:

Hi Brent,

hledger is an existing project whose purpose, code and installation
process is relatively simple. I'm happy to do a bit of mentoring. If
this sounds suitable, I can suggest some easy fixes or enhancements, eg:

...hmm. In fact nothing on my long wishlist[1][2] looks all that quick.
They're kind of tricky, or require a fair bit of architectural
knowledge, or they are unglamorous and boring. (I'd love to be proven
wrong.)

shelltestrunner[3] or rss2irc[4] are much smaller projects, but their
backlogs are not all that pretty either. If any of these are of interest
let me know and I can look harder for suitable jobs.

-Simon


[1]
https://code.google.com/p/hledger/issues/list?can=2&q=&colspec=ID+Type+Status+Summary+Reporter+Opened+Stars&sort=&groupby=&mode=grid&y=Component&x=Status&cells=tiles&nobtn=Update

[2] http://hub.darcs.net/simon/hledger/NOTES.org#2140

[3] http://hub.darcs.net/simon/shelltestrunner/browse/NOTES.org

[4] http://hub.darcs.net/simon/shelltestrunner/browse/NOTES.org





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


Re: [Haskell-cafe] Open-source projects for beginning Haskell students?

2013-03-12 Thread Simon Michael

Hi Brent,

hledger is an existing project whose purpose, code and installation 
process is relatively simple. I'm happy to do a bit of mentoring. If 
this sounds suitable, I can suggest some easy fixes or enhancements, eg:


...hmm. In fact nothing on my long wishlist[1][2] looks all that quick. 
They're kind of tricky, or require a fair bit of architectural 
knowledge, or they are unglamorous and boring. (I'd love to be proven 
wrong.)


shelltestrunner[3] or rss2irc[4] are much smaller projects, but their 
backlogs are not all that pretty either. If any of these are of interest 
let me know and I can look harder for suitable jobs.


-Simon


[1] 
https://code.google.com/p/hledger/issues/list?can=2&q=&colspec=ID+Type+Status+Summary+Reporter+Opened+Stars&sort=&groupby=&mode=grid&y=Component&x=Status&cells=tiles&nobtn=Update


[2] http://hub.darcs.net/simon/hledger/NOTES.org#2140

[3] http://hub.darcs.net/simon/shelltestrunner/browse/NOTES.org

[4] http://hub.darcs.net/simon/shelltestrunner/browse/NOTES.org


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


Re: [Haskell-cafe] newtype a Constraint?

2013-03-12 Thread Max Bolingbroke
On 12 March 2013 13:18, Roman Cheplyaka  wrote:
> Is there a way to newtype a constraint?
>
> Imagine a type class parameterised over constraints. What do I do if I
> want multiple instances for (essentially) the same constraint?

It would make sense to add support for this to newtype directly. I
think it would also make sense to allow newtypes over types of kind #.
"All" that is required is some implementation effort: I looked into
doing this as part of the constraint kinds patches but it is a bit
messy.

Max

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


Re: [Haskell-cafe] Overloading

2013-03-12 Thread Richard A. O'Keefe
Carlos Camarao wrote:

> Sorry, I think my sentence: 
>"To define (+) as an overloaded operator in Haskell, 
>  you have to define and use a type class." 
>is not quite correct.  I meant that to define any operator in Haskell you have 
>to
> have a type class defined with that operator as member. 

No.  Operators and type classes are entirely orthogonal in Haskell.
For example, the list concatenation operator (++) is not defined in
any type class.  It could be.  Either the `mplus` of
MonadPlus or the `mappend` of Monoid would make sense.  But it
happens not to be.

> Yes, but the requirement of using the "predefined" (+) is an extra
> requirement (I would call (+) in Haskell not a predefined operator,
> but an operator whose type is defined in a class (Num) which is in the
> Prelude). A Haskell programmer can still define versions of (+) where
> the arguments are of two different types and the result is a third
> (he cannot though use the two type classes, and thus neither instances
> of these two type classes, in a program).

I wish we could argue over semantics instead of vocabulary.
By calling the (+) of Num "predefined" I meant nothing other than
"it is _defined_ in the Haskell report before (_pre_) you or I add
any code of our own".  We agree on the facts.

I don't call it an "extra" requirement.  The original context was
very clearly that in C++ where you have int+int, int+double,
double+int, double+double, char*+int, int+char* and so on all
predefined, you can *also* add your own date+period *without*
hiding the predefined versions.  And _that_ is overloading.  If the
question is whether Haskell can do overloading, _that_ is what has
to be achieved:  you can add a *new* interface date+period *without*
hiding the ones that were already defined before you started coding.

The interesting challenge here is that we should have

Date   + Period -> Date  Date   - Period -> Date
Period + Date   -> Date  Period - Date   -> ILLEGAL
Period + Period -> DeriodPeriod - Period -> Period
Date   + Date   -> ILLEGAL   Date   - Date   -> Date

and _also_ (remember we are trying to beat C++ here) Int +/- Int -> Int.

I suspect that this can be done using type-level programming (so that
Date + Date and Period - Date _begin_ to type check but then violate
a type constraint) but that's where my Haskell skills are most risible.



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


Re: [Haskell-cafe] monadic DSL for compile-time parser generator, not possible?

2013-03-12 Thread Jeremy Shaw
Mostly, because I want to do other sorts of compile-time inspections
on the parser. Being able to generate the parser is just the easiest
part to get started with.

- jeremy

On Tue, Mar 12, 2013 at 3:36 PM, dag.odenh...@gmail.com
 wrote:
> Why not the parsers package [1]? Write the parser against the Parsing class
> and then use trifecta or write instances for attoparsec or parsec. With
> enough inlining perhaps the overhead of the class gets optimized away?
>
> [1] http://hackage.haskell.org/package/parsers
>
>
> On Tue, Mar 12, 2013 at 9:06 PM, Jeremy Shaw  wrote:
>>
>> It would be pretty damn cool if you could create a data type for
>> generically describing a monadic parser, and then use template haskell
>> to generate a concrete parser from that data type. That would allow
>> you to create your specification in a generic way and then target
>> different parsers like parsec, attoparsec, etc. There is some code
>> coming up in a few paragraphs that should describe this idea more
>> clearly.
>>
>> I would like to suggest that while it would be cool, it is
>> impossible. As proof, I will attempt to create a simple monadic parser
>> that has only one combinator:
>>
>> anyChar :: ParserSpec Char
>>
>> We need the GADTs extension and some imports:
>>
>> > {-# LANGUAGE GADTs, TemplateHaskell #-}
>> > import Control.Monad  (join)
>> > import qualified Text.Parsec.Char as P
>> > import Language.Haskell.TH(ExpQ, appE)
>> > import Language.Haskell.TH.Syntax (Lift(lift))
>> > import Text.Parsec(parseTest)
>> > import qualified Text.Parsec.Char as P
>> > import Text.Parsec.String (Parser)
>>
>> Next we define a type that has a constructor for each of the different
>> combinators we want to support, plus constructors for the functor and
>> monad methods:
>>
>> > data ParserSpec a where
>> > AnyChar :: ParserSpec Char
>> > Return  :: a -> ParserSpec a
>> > Join:: ParserSpec (ParserSpec a) -> ParserSpec a
>> > FMap:: (a -> b) -> ParserSpec a -> ParserSpec b
>> >
>> > instance Lift (ParserSpec a) where
>> > lift _ = error "not defined because we are screwed later anyway."
>>
>> In theory, we would extend that type with things like `Many`, `Some`,
>> `Choice`, etc.
>>
>> In Haskell, we are used to seeing a `Monad` defined in terms of
>> `return` and `>>=`. But, we can also define a monad in terms of
>> `fmap`, `return` and `join`. We will do that in `ParserSpec`, because
>> it makes the fatal flaw more obvious.
>>
>> Now we can define the `Functor` and `Monad` instances:
>>
>> > instance Functor ParserSpec where
>> > fmap f p = FMap f p
>>
>> > instance Monad ParserSpec where
>> > return a = Return a
>> > m >>= f  = Join ((FMap f) m)
>>
>> and the `anyChar` combinator:
>>
>> > anyChar :: ParserSpec Char
>> > anyChar = AnyChar
>>
>> And now we can define a simple parser that parses two characters and
>> returns them:
>>
>> > charPair :: ParserSpec (Char, Char)
>> > charPair =
>> > do a <- anyChar
>> >b <- anyChar
>> >return (a, b)
>>
>> Now, we just need to define a template haskell function that generates
>> a `Parser` from a `ParserSpec`:
>>
>> > genParsec :: (Lift a) => ParserSpec a -> ExpQ
>> > genParsec AnyChar= [| anyChar |]
>> > genParsec (Return a) = [| return a |]
>> > genParsec (Join p)   = genParsec p
>> > -- genParsec (FMap f p) = appE [| f |] (genParsec p) -- uh-oh
>>
>> Looking at the `FMap` case we see the fatal flaw. In order to
>> generate the parser we would need some way to transform any arbitrary
>> Haskell function of type `a -> b` into Template Haskell. Obviously,
>> that is impossible (for some definition of obvious).
>>
>> Therefore, we can assume that it is not possible to use Template
>> Haskell to generate a monadic parser from a monadic specification.
>>
>> We can also assume that `Applicative` is not available either. Seems
>> likely that `Category` based parsers would also be out.
>>
>> Now, we can, of course, do the transformation at runtime:
>>
>> > interpretParsec :: ParserSpec a -> Parser a
>> > interpretParsec AnyChar= P.anyChar
>> > interpretParsec (Return a) = return a
>> > interpretParsec (FMap f a) = fmap f (interpretParsec a)
>> > interpretParsec (Join mm)  = join (fmap interpretParsec (interpretParsec
>> > mm))
>>
>> > test = parseTest (interpretParsec charPair) "ab"
>>
>> My fear is that doing that will result in added runtime overhead. One
>> reason for wanting to create a compile-time parser generator is to have
>> the opportunity to generate very fast parsing code. It seems like here
>> we can only be slower than the parser we are targeting? Though..
>> perhaps not? Perhaps the parser returned by `interpretParsec` has all
>> the interpret stuff removed and is as fast as if we have constructed
>> it by hand? I don't have an intuitive feel for it.. I guess criterion
>> would know..
>>
>> Any thoughts?
>>
>> - jeremy
>>
>> __

Re: [Haskell-cafe] monadic DSL for compile-time parser generator, not possible?

2013-03-12 Thread Jeremy Shaw
On Tue, Mar 12, 2013 at 3:32 PM, Jacques Carette  wrote:
> On 13-03-12 04:06 PM, Jeremy Shaw wrote:

>>> data ParserSpec a where
>>>  AnyChar :: ParserSpec Char
>>>  Return  :: a -> ParserSpec a
>>>  Join:: ParserSpec (ParserSpec a) -> ParserSpec a
>>>  FMap:: (a -> b) -> ParserSpec a -> ParserSpec b
>
>
> does not work.  The flaw is indeed in FMap.  It should not take a function
> as first argument, but rather a *description* of a function (the same way
> ParserSpec gives you a description of a parser).  Then you can make it work,
> if your 'description' language is adequate.

Right. But, then I would not be able to use Haskell's existing do
notation -- and I would have to poorly recreate a subset of Haskell.
And, I think, ParsecSpec would not be a real monad. But.. that is sort
of the conclusion -- if you want to do compile-time generation, then
the data-type can not contain any function values -- at least none
that would need to be lifted into the generated code. And, there is no
way to make a type with a real Monad instance which does not contain
such a function.

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


Re: [Haskell-cafe] monadic DSL for compile-time parser generator, not possible?

2013-03-12 Thread dag.odenh...@gmail.com
Why not the parsers package [1]? Write the parser against the Parsing class
and then use trifecta or write instances for attoparsec or parsec. With
enough inlining perhaps the overhead of the class gets optimized away?

[1] http://hackage.haskell.org/package/parsers


On Tue, Mar 12, 2013 at 9:06 PM, Jeremy Shaw  wrote:

> It would be pretty damn cool if you could create a data type for
> generically describing a monadic parser, and then use template haskell
> to generate a concrete parser from that data type. That would allow
> you to create your specification in a generic way and then target
> different parsers like parsec, attoparsec, etc. There is some code
> coming up in a few paragraphs that should describe this idea more
> clearly.
>
> I would like to suggest that while it would be cool, it is
> impossible. As proof, I will attempt to create a simple monadic parser
> that has only one combinator:
>
> anyChar :: ParserSpec Char
>
> We need the GADTs extension and some imports:
>
> > {-# LANGUAGE GADTs, TemplateHaskell #-}
> > import Control.Monad  (join)
> > import qualified Text.Parsec.Char as P
> > import Language.Haskell.TH(ExpQ, appE)
> > import Language.Haskell.TH.Syntax (Lift(lift))
> > import Text.Parsec(parseTest)
> > import qualified Text.Parsec.Char as P
> > import Text.Parsec.String (Parser)
>
> Next we define a type that has a constructor for each of the different
> combinators we want to support, plus constructors for the functor and
> monad methods:
>
> > data ParserSpec a where
> > AnyChar :: ParserSpec Char
> > Return  :: a -> ParserSpec a
> > Join:: ParserSpec (ParserSpec a) -> ParserSpec a
> > FMap:: (a -> b) -> ParserSpec a -> ParserSpec b
> >
> > instance Lift (ParserSpec a) where
> > lift _ = error "not defined because we are screwed later anyway."
>
> In theory, we would extend that type with things like `Many`, `Some`,
> `Choice`, etc.
>
> In Haskell, we are used to seeing a `Monad` defined in terms of
> `return` and `>>=`. But, we can also define a monad in terms of
> `fmap`, `return` and `join`. We will do that in `ParserSpec`, because
> it makes the fatal flaw more obvious.
>
> Now we can define the `Functor` and `Monad` instances:
>
> > instance Functor ParserSpec where
> > fmap f p = FMap f p
>
> > instance Monad ParserSpec where
> > return a = Return a
> > m >>= f  = Join ((FMap f) m)
>
> and the `anyChar` combinator:
>
> > anyChar :: ParserSpec Char
> > anyChar = AnyChar
>
> And now we can define a simple parser that parses two characters and
> returns them:
>
> > charPair :: ParserSpec (Char, Char)
> > charPair =
> > do a <- anyChar
> >b <- anyChar
> >return (a, b)
>
> Now, we just need to define a template haskell function that generates
> a `Parser` from a `ParserSpec`:
>
> > genParsec :: (Lift a) => ParserSpec a -> ExpQ
> > genParsec AnyChar= [| anyChar |]
> > genParsec (Return a) = [| return a |]
> > genParsec (Join p)   = genParsec p
> > -- genParsec (FMap f p) = appE [| f |] (genParsec p) -- uh-oh
>
> Looking at the `FMap` case we see the fatal flaw. In order to
> generate the parser we would need some way to transform any arbitrary
> Haskell function of type `a -> b` into Template Haskell. Obviously,
> that is impossible (for some definition of obvious).
>
> Therefore, we can assume that it is not possible to use Template
> Haskell to generate a monadic parser from a monadic specification.
>
> We can also assume that `Applicative` is not available either. Seems
> likely that `Category` based parsers would also be out.
>
> Now, we can, of course, do the transformation at runtime:
>
> > interpretParsec :: ParserSpec a -> Parser a
> > interpretParsec AnyChar= P.anyChar
> > interpretParsec (Return a) = return a
> > interpretParsec (FMap f a) = fmap f (interpretParsec a)
> > interpretParsec (Join mm)  = join (fmap interpretParsec (interpretParsec
> mm))
>
> > test = parseTest (interpretParsec charPair) "ab"
>
> My fear is that doing that will result in added runtime overhead. One
> reason for wanting to create a compile-time parser generator is to have
> the opportunity to generate very fast parsing code. It seems like here
> we can only be slower than the parser we are targeting? Though..
> perhaps not? Perhaps the parser returned by `interpretParsec` has all
> the interpret stuff removed and is as fast as if we have constructed
> it by hand? I don't have an intuitive feel for it.. I guess criterion
> would know..
>
> Any thoughts?
>
> - jeremy
>
> ___
> 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] monadic DSL for compile-time parser generator, not possible?

2013-03-12 Thread Jacques Carette

On 13-03-12 04:06 PM, Jeremy Shaw wrote:

It would be pretty damn cool if you could create a data type for
generically describing a monadic parser, and then use template haskell
to generate a concrete parser from that data type. [...]
I would like to suggest that while it would be cool, it is
impossible.


Impossibility proofs are notoriously difficult.  You showed that this 
approach:



data ParserSpec a where
 AnyChar :: ParserSpec Char
 Return  :: a -> ParserSpec a
 Join:: ParserSpec (ParserSpec a) -> ParserSpec a
 FMap:: (a -> b) -> ParserSpec a -> ParserSpec b


does not work.  The flaw is indeed in FMap.  It should not take a 
function as first argument, but rather a *description* of a function 
(the same way ParserSpec gives you a description of a parser).  Then you 
can make it work, if your 'description' language is adequate.


For some strange reason, I am biased towards 'finally tagless' 
descriptions, but YMMV.


Jacques

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


[Haskell-cafe] monadic DSL for compile-time parser generator, not possible?

2013-03-12 Thread Jeremy Shaw
It would be pretty damn cool if you could create a data type for
generically describing a monadic parser, and then use template haskell
to generate a concrete parser from that data type. That would allow
you to create your specification in a generic way and then target
different parsers like parsec, attoparsec, etc. There is some code
coming up in a few paragraphs that should describe this idea more
clearly.

I would like to suggest that while it would be cool, it is
impossible. As proof, I will attempt to create a simple monadic parser
that has only one combinator:

anyChar :: ParserSpec Char

We need the GADTs extension and some imports:

> {-# LANGUAGE GADTs, TemplateHaskell #-}
> import Control.Monad  (join)
> import qualified Text.Parsec.Char as P
> import Language.Haskell.TH(ExpQ, appE)
> import Language.Haskell.TH.Syntax (Lift(lift))
> import Text.Parsec(parseTest)
> import qualified Text.Parsec.Char as P
> import Text.Parsec.String (Parser)

Next we define a type that has a constructor for each of the different
combinators we want to support, plus constructors for the functor and
monad methods:

> data ParserSpec a where
> AnyChar :: ParserSpec Char
> Return  :: a -> ParserSpec a
> Join:: ParserSpec (ParserSpec a) -> ParserSpec a
> FMap:: (a -> b) -> ParserSpec a -> ParserSpec b
>
> instance Lift (ParserSpec a) where
> lift _ = error "not defined because we are screwed later anyway."

In theory, we would extend that type with things like `Many`, `Some`,
`Choice`, etc.

In Haskell, we are used to seeing a `Monad` defined in terms of
`return` and `>>=`. But, we can also define a monad in terms of
`fmap`, `return` and `join`. We will do that in `ParserSpec`, because
it makes the fatal flaw more obvious.

Now we can define the `Functor` and `Monad` instances:

> instance Functor ParserSpec where
> fmap f p = FMap f p

> instance Monad ParserSpec where
> return a = Return a
> m >>= f  = Join ((FMap f) m)

and the `anyChar` combinator:

> anyChar :: ParserSpec Char
> anyChar = AnyChar

And now we can define a simple parser that parses two characters and
returns them:

> charPair :: ParserSpec (Char, Char)
> charPair =
> do a <- anyChar
>b <- anyChar
>return (a, b)

Now, we just need to define a template haskell function that generates
a `Parser` from a `ParserSpec`:

> genParsec :: (Lift a) => ParserSpec a -> ExpQ
> genParsec AnyChar= [| anyChar |]
> genParsec (Return a) = [| return a |]
> genParsec (Join p)   = genParsec p
> -- genParsec (FMap f p) = appE [| f |] (genParsec p) -- uh-oh

Looking at the `FMap` case we see the fatal flaw. In order to
generate the parser we would need some way to transform any arbitrary
Haskell function of type `a -> b` into Template Haskell. Obviously,
that is impossible (for some definition of obvious).

Therefore, we can assume that it is not possible to use Template
Haskell to generate a monadic parser from a monadic specification.

We can also assume that `Applicative` is not available either. Seems
likely that `Category` based parsers would also be out.

Now, we can, of course, do the transformation at runtime:

> interpretParsec :: ParserSpec a -> Parser a
> interpretParsec AnyChar= P.anyChar
> interpretParsec (Return a) = return a
> interpretParsec (FMap f a) = fmap f (interpretParsec a)
> interpretParsec (Join mm)  = join (fmap interpretParsec (interpretParsec mm))

> test = parseTest (interpretParsec charPair) "ab"

My fear is that doing that will result in added runtime overhead. One
reason for wanting to create a compile-time parser generator is to have
the opportunity to generate very fast parsing code. It seems like here
we can only be slower than the parser we are targeting? Though..
perhaps not? Perhaps the parser returned by `interpretParsec` has all
the interpret stuff removed and is as fast as if we have constructed
it by hand? I don't have an intuitive feel for it.. I guess criterion
would know..

Any thoughts?

- jeremy

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


Re: [Haskell-cafe] cabal install oddities

2013-03-12 Thread Tycho Andersen
On Tue, Mar 12, 2013 at 03:28:08PM -0400, Brandon Allbery wrote:
>
> "cabal install" unpacks a package into /tmp in order to build it. My guess
> is your OS has /tmp mounted noexec. I don't know offhand how you override
> this in cabal.

Yep, you're exactly right. Thank you! I also couldn't figure out a way
to override it.

\t

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


Re: [Haskell-cafe] cabal install oddities

2013-03-12 Thread Brandon Allbery
On Tue, Mar 12, 2013 at 3:21 PM, Tycho Andersen  wrote:

> Below is some sample output from a failing package:
>
> ps168825:~/playground$ cabal install network
> Resolving dependencies...
> Configuring network-2.4.1.2...
> configure: WARNING: unrecognized options: --with-compiler, --with-gcc
> checking build system type... x86_64-unknown-linux-gnu
> checking host system type... x86_64-unknown-linux-gnu
> checking for gcc... gcc
> checking whether the C compiler works... yes
> checking for C compiler default output file name... a.out
> checking for suffix of executables...
> checking whether we are cross compiling... configure: error: in
> `/tmp/network-2.4.1.2-28534/network-2.4.1.2':
> configure: error: cannot run C compiled programs.
>

"cabal install" unpacks a package into /tmp in order to build it. My guess
is your OS has /tmp mounted noexec. I don't know offhand how you override
this in cabal.

-- 
brandon s allbery kf8nh   sine nomine associates
allber...@gmail.com  ballb...@sinenomine.net
unix, openafs, kerberos, infrastructure, xmonadhttp://sinenomine.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Open-source projects for beginning Haskell students?

2013-03-12 Thread Kristopher Micinski
The problem with all of these suggestions is that they start from no code.
 I believe Brent is looking for an *existing* project which needs
contributions.  I assume so that beginning Haskellers can learn real code
style in the middle to large, and get input from existing community members.

Kris


On Tue, Mar 12, 2013 at 1:59 PM, Vo Minh Thu  wrote:

> 2013/3/11 Brent Yorgey :
> > Hi everyone,
> >
> > I am currently teaching a half-credit introductory Haskell class for
> > undergraduates.  This is the third time I've taught it.  Both of the
> > previous times, for their final project I gave them the option of
> > contributing to an open-source project; a couple groups/individuals
> > took me up on it and I think it ended up being a modest success.
> >
> > So I'd like to do it again this time around, and am looking for
> > particular projects I can suggest to them.  Do you have an open-source
> > project with a few well-specified tasks that a relative beginner (see
> > below) could reasonably make a contribution towards in the space of
> > about four weeks? I'm aware that most tasks don't fit that profile,
> > but even complex projects usually have a few "simple-ish" tasks that
> > haven't yet been done just because "no one has gotten around to it
> > yet".
> >
> > If you have any such projects, I'd love to hear about it!  Just send
> > me a paragraph or so describing your project and explaining what
> > task(s) you could use help with --- something that I could put on the
> > course website for students to look at.
> >
> > Here are a few more details:
> >
> > * The students will be working on the projects from approximately the
> >   end of this month through the end of April.  During the next two
> >   weeks they would be contacting you to discuss the possibility of
> >   working on your project.
> >
> > * By "relative beginner" I mean someone familiar with the material
> >   listed here: http://www.cis.upenn.edu/~cis194/lectures.html and just
> >   trying to come to terms with Applicative and Monad.  They definitely
> >   do not know much if anything about optimization/profiling, GADTs,
> >   the mtl, or Haskell-programming-in-the-large.  (Although part of the
> >   point of the project is to teach them a bit about
> >   programming-in-the-(medium/large)).
> >
> > * What I would hope from you is a willingness to exchange email and/or
> >   chat with the student(s) over the course of the project, to give
> >   them a bit of guidance/mentoring.  I am certainly willing to help on
> >   that front, but of course I probably don't know much about your
> >   particular project.
>
> Maybe it is a too small project (and not a contribution to an existing
> project), but a Haskell wrapper around PostgreSQL setproctitle code
> would be nice (something similar exists in the Python world).
>
> Otherwise I have began some "infrastructure" projects on GitHub that
> are all pretty simple but could be damn useful: curved is meant to be
> a drop-in-replacement for graphite (it is almost the case), sentry is
> a process-monitoring tool, humming is a job queue on top of
> PostgreSQL, hlinode is a binding to the Linode API, ... They all have
> in common that they are small, self-contained, and quite often just
> massaging around rawSystem calls, database "execute" calls, or
> GET/POST calls.
>
> Thu
>
> ___
> 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] cabal install oddities

2013-03-12 Thread Tycho Andersen
Hi all,

I'm having some strange issues with cabal install. Some packages
installed via `cabal install $foo` are failing for strange (and
seemingly unrelated) reasons, but install just fine when I do
something like:

  cabal unpack network
  cd network
  cabal configure
  cabal install

Below is some sample output from a failing package:

ps168825:~/playground$ cabal install network
Resolving dependencies...
Configuring network-2.4.1.2...
configure: WARNING: unrecognized options: --with-compiler, --with-gcc
checking build system type... x86_64-unknown-linux-gnu
checking host system type... x86_64-unknown-linux-gnu
checking for gcc... gcc
checking whether the C compiler works... yes
checking for C compiler default output file name... a.out
checking for suffix of executables... 
checking whether we are cross compiling... configure: error: in 
`/tmp/network-2.4.1.2-28534/network-2.4.1.2':
configure: error: cannot run C compiled programs.
If you meant to cross compile, use `--host'.
See `config.log' for more details
Failed to install network-2.4.1.2
cabal: Error: some packages failed to install:
network-2.4.1.2 failed during the configure step. The exception was:
ExitFailure 1
ps168825:~/playground 1$ cabal --version
cabal-install version 1.16.0.2
using version 1.16.0 of the Cabal library 
ps168825:~/playground$ ghc --version
The Glorious Glasgow Haskell Compilation System, version 7.6.2

/tmp/network-* doesn't exist (which is why I tried unpack, but
unfortunately that succeeds).

Any thoughts on how I can debug this?

Thanks,

\t

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


Re: [Haskell-cafe] Overloading

2013-03-12 Thread Carlos Camarao
On Tue, Mar 12, 2013 at 3:21 PM, Brandon Allbery wrote:

> On Tue, Mar 12, 2013 at 1:52 PM, Carlos Camarao 
> wrote:
>
>> Sorry, I think my sentence:
>> "To define (+) as an overloaded operator in Haskell,
>>   you have to define and use a type class."
>> is not quite correct.  I meant that to define any operator in Haskell you
>> have to
>> have a type class defined with that operator as member.
>>
>
> What? An operator is just an infix function, taken from the set of
> symbols. Any function can be an operator (and is, via `func` syntax). No
> typeclass is required to define a random operator.
>
> What did you really mean to say there?
>

Sorry, I meant: "To define any _overloaded_ name or operator (i.e. any
name/operator that can be overloaded) in Haskell you have to have a type
class defined with that name/operator as member.

Cheers,

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


Re: [Haskell-cafe] Overloading

2013-03-12 Thread Brandon Allbery
On Tue, Mar 12, 2013 at 1:52 PM, Carlos Camarao wrote:

> Sorry, I think my sentence:
> "To define (+) as an overloaded operator in Haskell,
>   you have to define and use a type class."
> is not quite correct.  I meant that to define any operator in Haskell you
> have to
> have a type class defined with that operator as member.
>

What? An operator is just an infix function, taken from the set of symbols.
Any function can be an operator (and is, via `func` syntax). No typeclass
is required to define a random operator.

What did you really mean to say there?

-- 
brandon s allbery kf8nh   sine nomine associates
allber...@gmail.com  ballb...@sinenomine.net
unix, openafs, kerberos, infrastructure, xmonadhttp://sinenomine.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Open-source projects for beginning Haskell students?

2013-03-12 Thread Vo Minh Thu
2013/3/11 Brent Yorgey :
> Hi everyone,
>
> I am currently teaching a half-credit introductory Haskell class for
> undergraduates.  This is the third time I've taught it.  Both of the
> previous times, for their final project I gave them the option of
> contributing to an open-source project; a couple groups/individuals
> took me up on it and I think it ended up being a modest success.
>
> So I'd like to do it again this time around, and am looking for
> particular projects I can suggest to them.  Do you have an open-source
> project with a few well-specified tasks that a relative beginner (see
> below) could reasonably make a contribution towards in the space of
> about four weeks? I'm aware that most tasks don't fit that profile,
> but even complex projects usually have a few "simple-ish" tasks that
> haven't yet been done just because "no one has gotten around to it
> yet".
>
> If you have any such projects, I'd love to hear about it!  Just send
> me a paragraph or so describing your project and explaining what
> task(s) you could use help with --- something that I could put on the
> course website for students to look at.
>
> Here are a few more details:
>
> * The students will be working on the projects from approximately the
>   end of this month through the end of April.  During the next two
>   weeks they would be contacting you to discuss the possibility of
>   working on your project.
>
> * By "relative beginner" I mean someone familiar with the material
>   listed here: http://www.cis.upenn.edu/~cis194/lectures.html and just
>   trying to come to terms with Applicative and Monad.  They definitely
>   do not know much if anything about optimization/profiling, GADTs,
>   the mtl, or Haskell-programming-in-the-large.  (Although part of the
>   point of the project is to teach them a bit about
>   programming-in-the-(medium/large)).
>
> * What I would hope from you is a willingness to exchange email and/or
>   chat with the student(s) over the course of the project, to give
>   them a bit of guidance/mentoring.  I am certainly willing to help on
>   that front, but of course I probably don't know much about your
>   particular project.

Maybe it is a too small project (and not a contribution to an existing
project), but a Haskell wrapper around PostgreSQL setproctitle code
would be nice (something similar exists in the Python world).

Otherwise I have began some "infrastructure" projects on GitHub that
are all pretty simple but could be damn useful: curved is meant to be
a drop-in-replacement for graphite (it is almost the case), sentry is
a process-monitoring tool, humming is a job queue on top of
PostgreSQL, hlinode is a binding to the Linode API, ... They all have
in common that they are small, self-contained, and quite often just
massaging around rawSystem calls, database "execute" calls, or
GET/POST calls.

Thu

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


Re: [Haskell-cafe] Overloading

2013-03-12 Thread Carlos Camarao
On 12/03/2013, at 3:15 AM, Carlos Camarao wrote:

>> Hi,
>>
>> I just started playing around a bit with Haskell, so sorry in
>> advance for very basic (and maybe stupid) questions. Coming from
>> the C++ world one thing I would like to do is overloading
>> operators. For example I want to write (Date 6 6 1973) + (Period 2
>> Months) for some self defined types Date and Period. Another
>> example would be (Period 1 Years) + (Period 3 Months).
>>
>> Just defining the operator (+) does not work because it collides
>> with Prelude.+. I assume using fully qualified names would work,
>> but that is not what I want.
>>
>> Hi. To define (+) as an overloaded operator in Haskell, you have to
define
>> and use a type class.

> Stop right there.  Overloading in the C++ sense is "ad hoc
> polymorphism" where the signatures of the various definitions need
> not resemble each other in any way.  Haskell just plain does not
> have anything like that.  (+) in Haskell is *not* overloaded; it has
> several implementations and allows you to define as many more as you
> want.  But they all conform to the *SAME* interface.  This is much
> more like OO inheritance.

Sorry, I think my sentence:
"To define (+) as an overloaded operator in Haskell,
  you have to define and use a type class."
is not quite correct.  I meant that to define any operator in Haskell you
have to
have a type class defined with that operator as member.

Then, if there is already a type class defined, a programmer can
either use it (if that is suitable/adequate) or hide it and define
another one. Sorry, that's what I meant.

> In particular, C++ will let you define versions of + where the
> arguments are of two different types and the result is a third.  You
> cannot provide such an implementation for Haskell's predefined (+).

Yes, but the requirement of using the "predefined" (+) is an extra
requirement (I would call (+) in Haskell not a predefined operator,
but an operator whose type is defined in a class (Num) which is in the
Prelude). A Haskell programmer can still define versions of (+) where
the arguments are of two different types and the result is a third
(he cannot though use the two type classes, and thus neither instances
 of these two type classes, in a program).

The suitability/adequacy of the type defined in a class means that the
type of all names/operators in an instance of the class must be an
instance-type of the type specified in the class.

And unsuitability/inadequacy requires the definition and use of
another type class (sorry to repeat that, just reinforcing).

>> Furthermore, Haskell supports a more powerful form of overloading than
>> (any other language I know, including) C++: context-dependent
>> overloading. This means that the type of an expression (f e), and thus
>> of f, can be determined at compile-time (inferred) based on the
>> context where (f e) occurs, not only on the type of the
>> argument (e) of the function's call.

> Ada has had this since Ada 81.  The design goal that forced it was
> the wish to allow the same identifier to be used as an enumeral in
> more than one enumerated type, so that you could do
>type Colour is (Red, Green, Blue);
>type Fruit_State is (Green, Ripe, Rotten);
>X : Colour := Green;
>Y : Fruit_State := Green;
>
> and in particular, since character literals like 'X' are allowed as
> enumerals in Ada, they wished to be able to write
>A: EBCDIC_Character := 'X';
>B: ASCII_Character  := 'X';
> and have A and B be different bytes.  The difference is that Ada
> *does* do this sort of thing using overload resolution and Haskell
> *doesn't*.

Ok. I will have a look at Ada's overloading mechanism. Thanks! I am
trying to emphasize the constrained *polymorphism* that is possible in
Haskell, which allows overloading resolution not to be required in an
use of an operator or constant. I believe that this is a significant
new contribution of the language. (I think Green and 'X' are not
polymorphic, and any use of them required thus that overloading be
resolved).

>> For example, you _could_ in principle use (d+p==d) and (d+p==p),
>> with d::Date, p::Period, and instances of (+) with types
>> Date->Period->Date and Date->Period->Period, if you wish…
> Prelude> :type (+)
> (+) :: Num a => a -> a -> a
> The predefined (+) in Haskell requires its arguments and its result
> to be precisely the same type.
>
> I think you had better justify the claim that Date+Period -> Date and
> Date+Period -> Period are possible at the same time by showing us
> actual code.

I think I have shown it (see previous message): as Miguel Mitrofanov,
hiding and redefining Num.

Kind regards,

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


Re: [Haskell-cafe] newtype a Constraint?

2013-03-12 Thread Roman Cheplyaka
Neat, thanks!

Roman

* Gábor Lehel  [2013-03-12 14:26:38+0100]
> {-# LANGUAGE UndecidableInstances #-}
> 
> class OldConstraint a => NewtypedConstraint a
> instance OldConstraint a => NewtypedConstraint a
> 
> perhaps?
> 
> Nice thing is you don't even need to do wrapping/unwrapping, like you do
> with data newtypes.
> 
> 
> On Tue, Mar 12, 2013 at 2:18 PM, Roman Cheplyaka  wrote:
> 
> > Is there a way to newtype a constraint?
> >
> > Imagine a type class parameterised over constraints. What do I do if I
> > want multiple instances for (essentially) the same constraint?
> >
> > Roman
> >
> > ___
> > Haskell-Cafe mailing list
> > Haskell-Cafe@haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
> >
> 
> 
> 
> -- 
> Your ship was destroyed in a monadic eruption.

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


Re: [Haskell-cafe] newtype a Constraint?

2013-03-12 Thread Gábor Lehel
{-# LANGUAGE UndecidableInstances #-}

class OldConstraint a => NewtypedConstraint a
instance OldConstraint a => NewtypedConstraint a

perhaps?

Nice thing is you don't even need to do wrapping/unwrapping, like you do
with data newtypes.


On Tue, Mar 12, 2013 at 2:18 PM, Roman Cheplyaka  wrote:

> Is there a way to newtype a constraint?
>
> Imagine a type class parameterised over constraints. What do I do if I
> want multiple instances for (essentially) the same constraint?
>
> Roman
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



-- 
Your ship was destroyed in a monadic eruption.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] newtype a Constraint?

2013-03-12 Thread Roman Cheplyaka
Is there a way to newtype a constraint?

Imagine a type class parameterised over constraints. What do I do if I
want multiple instances for (essentially) the same constraint?

Roman

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


Re: [Haskell-cafe] Open-source projects for beginning Haskell students?

2013-03-12 Thread Ivan Lazar Miljenovic
On 12 March 2013 22:46, Tim Docker  wrote:
> On 12/03/13 05:26, Jason Dagit wrote:
>>
>>
>> Myself and several of my friends would find it useful to have a plotting
>> library that we can use from ghci to quickly/easily visualize data.
>> Especially if that data is part of a simulation we are toying with.
>> Therefore, this proposal is for: A gnuplot-, matlab- or plotinum-like
>> plotting API (that uses diagrams as the backend?). The things to emphasize:
>>   * Easy to install: No gtk2hs requirement. Preferably just pure haskell
>> code and similar for any dependencies. Must be cross platform.
>>   * Frontend: graphs should be easy to construct; customizability is not
>> as important
>>   * Backend: options for generating static images are nice, but for the
>> use case we have in mind also being able to render in a window from ghci is
>> very valuable. (this could imply something as purely rendering to
>> JuicyPixels and I could write the rendering code)
>
>
> I maintain the Chart library:
>
> http://hackage.haskell.org/package/Chart
>
> I'd like to see it used more widely, but gtk/cairo seems to be a problem for
> many people.
>
> Is the cairo dependency the reason you are suggesting that an alternative
> plotting library be built?
> Is your problem with cairo the difficulty in setting it up on ms
> windows/osx?
> What graphics API would you suggest using to "render in a window from ghci"?
>
> If there were a good cross platform alternative to cairo, I'd happily target
> this additional 2D drawing API. However, I don't think there currently is
> one. Neither gloss nor the diagrams library currently have adequate text
> support.

This is probably a completely stupid and bonkers idea... but I wonder
whether using Inkscape's ability to be able to export PDF or PS files
that can be imported into LaTeX and let LaTeX deal with the text
placement/rendering would work...  Rather fiddly for just a "give me
an image" library though :)

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



-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
http://IvanMiljenovic.wordpress.com

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


Re: [Haskell-cafe] Open-source projects for beginning Haskell students?

2013-03-12 Thread Tim Docker

On 12/03/13 05:26, Jason Dagit wrote:


Myself and several of my friends would find it useful to have a 
plotting library that we can use from ghci to quickly/easily visualize 
data. Especially if that data is part of a simulation we are toying 
with. Therefore, this proposal is for: A gnuplot-, matlab- or 
plotinum-like plotting API (that uses diagrams as the backend?). The 
things to emphasize:
  * Easy to install: No gtk2hs requirement. Preferably just pure 
haskell code and similar for any dependencies. Must be cross platform.
  * Frontend: graphs should be easy to construct; customizability is 
not as important
  * Backend: options for generating static images are nice, but for 
the use case we have in mind also being able to render in a window 
from ghci is very valuable. (this could imply something as purely 
rendering to JuicyPixels and I could write the rendering code)


I maintain the Chart library:

http://hackage.haskell.org/package/Chart

I'd like to see it used more widely, but gtk/cairo seems to be a problem 
for many people.


Is the cairo dependency the reason you are suggesting that an 
alternative plotting library be built?
Is your problem with cairo the difficulty in setting it up on ms 
windows/osx?

What graphics API would you suggest using to "render in a window from ghci"?

If there were a good cross platform alternative to cairo, I'd happily 
target this additional 2D drawing API. However, I don't think there 
currently is one. Neither gloss nor the diagrams library currently have 
adequate text support.


Tim




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


Re: [Haskell-cafe] Open-source projects for beginning Haskell students?

2013-03-12 Thread Kim-Ee Yeoh
Question is: does the task even have to involve the the production of
Haskell code?

Is it possible that both the student and the community-at-large would
benefit further from expository-style artifacts?

Some possible activities:

(1) producing documentation for popular packages that cater to
different learning styles (e.g. styles: Little Schemer, RWH, LYAHFGG,
etc.)

(2) survey of the various approaches taken by similar packages,
explaining the different choices taken

(3) cheatsheets, whether of GHC extensions, packages, syntax, commonly
used functions, etc.

These don't have to be harder than they sound. Option (2) in
particular could be e.g. a table listing the type signatures of the
various Iteratee packages with regard to Iteratee, Enumerator, and
Enumeratee. Or how a four-line Unix cat is implemented across them.

It's been said that a good teacher doesn't cover material, he
/uncovers/ them, i.e. the few core ideas that underpin everything.

Well, Haskell is just this heap of everything that's pretty hard to dig under.

Failing which, the indefatigable teacher would do well showing how the
student can teach themselves.

-- Kim-Ee


On Mon, Mar 11, 2013 at 10:48 PM, Brent Yorgey  wrote:
> Hi everyone,
>
> I am currently teaching a half-credit introductory Haskell class for
> undergraduates.  This is the third time I've taught it.  Both of the
> previous times, for their final project I gave them the option of
> contributing to an open-source project; a couple groups/individuals
> took me up on it and I think it ended up being a modest success.
>
> So I'd like to do it again this time around, and am looking for
> particular projects I can suggest to them.  Do you have an open-source
> project with a few well-specified tasks that a relative beginner (see
> below) could reasonably make a contribution towards in the space of
> about four weeks? I'm aware that most tasks don't fit that profile,
> but even complex projects usually have a few "simple-ish" tasks that
> haven't yet been done just because "no one has gotten around to it
> yet".
>
> If you have any such projects, I'd love to hear about it!  Just send
> me a paragraph or so describing your project and explaining what
> task(s) you could use help with --- something that I could put on the
> course website for students to look at.
>
> Here are a few more details:
>
> * The students will be working on the projects from approximately the
>   end of this month through the end of April.  During the next two
>   weeks they would be contacting you to discuss the possibility of
>   working on your project.
>
> * By "relative beginner" I mean someone familiar with the material
>   listed here: http://www.cis.upenn.edu/~cis194/lectures.html and just
>   trying to come to terms with Applicative and Monad.  They definitely
>   do not know much if anything about optimization/profiling, GADTs,
>   the mtl, or Haskell-programming-in-the-large.  (Although part of the
>   point of the project is to teach them a bit about
>   programming-in-the-(medium/large)).
>
> * What I would hope from you is a willingness to exchange email and/or
>   chat with the student(s) over the course of the project, to give
>   them a bit of guidance/mentoring.  I am certainly willing to help on
>   that front, but of course I probably don't know much about your
>   particular project.
>
> Thanks!
> -Brent
>
> ___
> 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] ANNOUNCE xml-conduit-generic

2013-03-12 Thread Dmitry Olshansky
Hello, cafe!

I made a package
xml-conduit-generic to
provide conversion from ADT to xml and vice versa.
Conversion works as Conduit (ToXml) or Consumer (FromXml).

Example:

data T4 = T4 {v4 :: Int, n4 :: Maybe T4} deriving (Eq, Show, Generic)
instance ToXml T4
instance FromXml T4

> runToXml $ T4 5 $ Just $ T4 6 Nothing
""

> runFromXml $ "" :: IO (Either String T4)
Right $ T4 5 $ Just $ T4 6 Nothing

It would be great if someone look to the version on github and give me some
notes. Then I am going to put it on hackage.

Unfortunately, I didn't find a way to avoid OverlappingInstances (for
GFromXml class). Any ideas are welcome.

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


Re: [Haskell-cafe] Open-source projects for beginning Haskell students?

2013-03-12 Thread John Lato
There's the "doctest" package: http://hackage.haskell.org/package/doctest,
which looks pretty good and has a number of users (35 direct reverse deps).

It has support for cabal test integration, although I would like to see
better integration with other test tools.  But that can be added in the
test executable I suppose.

My only quibble with this suggestion is that asking beginners to do this
sort of work may do more harm than good.  It would certainly be helpful,
but I don't think most people would find it interesting.



On Tue, Mar 12, 2013 at 3:19 PM, Edward Z. Yang  wrote:

> I also support this suggestion.  Although, do we have the build
> infrastructure
> for this?!
>
> Edward
>
> Excerpts from Michael Orlitzky's message of Mon Mar 11 19:52:12 -0700 2013:
> > On 03/11/2013 11:48 AM, Brent Yorgey wrote:
> > >
> > > So I'd like to do it again this time around, and am looking for
> > > particular projects I can suggest to them.  Do you have an open-source
> > > project with a few well-specified tasks that a relative beginner (see
> > > below) could reasonably make a contribution towards in the space of
> > > about four weeks? I'm aware that most tasks don't fit that profile,
> > > but even complex projects usually have a few "simple-ish" tasks that
> > > haven't yet been done just because "no one has gotten around to it
> > > yet".
> >
> > It's not exciting, but adding doctest suites with examples to existing
> > packages would be a great help.
> >
> >   * Good return on investment.
> >
> >   * Not too hard.
> >
> >   * The project is complete when you stop typing.
> >
>
> ___
> 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] Open-source projects for beginning Haskell students?

2013-03-12 Thread Edward Z. Yang
I also support this suggestion.  Although, do we have the build infrastructure
for this?!

Edward

Excerpts from Michael Orlitzky's message of Mon Mar 11 19:52:12 -0700 2013:
> On 03/11/2013 11:48 AM, Brent Yorgey wrote:
> > 
> > So I'd like to do it again this time around, and am looking for
> > particular projects I can suggest to them.  Do you have an open-source
> > project with a few well-specified tasks that a relative beginner (see
> > below) could reasonably make a contribution towards in the space of
> > about four weeks? I'm aware that most tasks don't fit that profile,
> > but even complex projects usually have a few "simple-ish" tasks that
> > haven't yet been done just because "no one has gotten around to it
> > yet".
> 
> It's not exciting, but adding doctest suites with examples to existing
> packages would be a great help.
> 
>   * Good return on investment.
> 
>   * Not too hard.
> 
>   * The project is complete when you stop typing.
> 

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