Re: [Haskell-cafe] Wikipedia article

2009-12-05 Thread Ketil Malde
Simon Marlow marlo...@gmail.com writes:

 There's no need to do any page moving or anything; the new version can
 just be pasted in.

 Ok, done!
 http://en.wikipedia.org/wiki/Haskell_%28programming_language%29

After conferring briefly with people on IRC (yeah, on a Saturday
morning, who am I kidding?), I moved the talk page to an archive, and
started a new one.  (The archive is linked from the new talk page.)

Most of the discussion seemed to be quite outdated, many of the issues
had been addressed, and since we got a new structure on the main page,
it seemed like a good idea to stow the old stuff and start afresh.

But it was a long page, so if you had a cause you feel needs more
arguing, please copy back from the old page or, perhaps better, restate
your issues on the new one.

Okay?

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] What is the rank of a polymorphic type?

2009-12-05 Thread Eugene Kirpichov
Hello.

Consider the type: (forall a . a) - String.

On one hand, it is rank-2 polymorphic, because it abstracts over a
rank-1 polymorphic type.
On the other hand, it is monomorphic because it isn't actually
quantified itself: in my intuitive view, a parametrically polymorphic
type has infinitely many instantiations (for example, Int - Int is an
instantiation of forall a . a - a, and String - String also is), and
this type doesn't have any instantiations at all.

Which is correct? Is there really a contradiction? What is the
definition of rank of a polymorphic type?

-- 
Eugene Kirpichov
Web IR developer, market.yandex.ru
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Wikipedia article

2009-12-05 Thread Deniz Dogan
2009/12/4 Simon Marlow marlo...@gmail.com:
 As noted before, the Wikipedia article for Haskell is a disorganised mess.

 http://en.wikipedia.org/wiki/Haskell_%28programming_language%29

 earlier this year, dons suggested reorganising it and posted a template on
 the Haskell wiki:

 http://haskell.org/haskellwiki/WikipediaArticleDesign

 I've made a start on a new version of the page:

 http://en.wikipedia.org/wiki/User:Simonmar/Haskell_%28programming_language%29

 I've kept most of the existing information, but reorganised it more or less
 according to Don's template, and I filled out the overview section.  Also I
 fixed numerous things, but the page still has a long way to go

 Does anyone mind if I spam the existing Haskell article with this new one,
 or do people think we should continue editing the sandbox version until it's
 in better shape?

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


Could someone please do something about the horrible syntax
highlighting for strings in the Wikipedia article? Black on dark
green, really?

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


Re: [Haskell-cafe] Re: From function over expression (+, *) derive function over expression (+)

2009-12-05 Thread Martijn van Steenbergen

Radek Micek wrote:

Hi,

thank you for your reply but your MulExpr
does not support expressions like

(2*3)+5


Oh! You're right, how silly of me.

Martijn.

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


Re: [Haskell-cafe] SYB looping very, very mysteriously

2009-12-05 Thread Andrea Vezzosi
On Fri, Dec 4, 2009 at 8:51 PM, Jeremy Shaw jer...@n-heptane.com wrote:
 I have stripped things down to the bare minimum, and test under GHC 6.10,
 GHC 6.12, Linux, and Mac OS X. Results are consistent.

 In the following code,

  1. if you load the code into ghci and evaluate e it will hang, but
 (defaultValueD dict) :: Expression returns fine
  2. if you change the gunfold instance for Proposition to, error gunfold
 it stops hanging -- even though this code is never called.
  3. if you change, ( Data ctx [Expression], Sat (ctx Expression) = Data ctx
 Expression, to (Data ctx Expression, ) = ... it stops hanging.

 If someone could explain why each of these cases perform as they do, that
 would be awesome! Right now it is a big mystery to me.. e calls dict .. and
 there is only one instance of dict available, which should call error right
 away. I can't see how something could get in the way there...


It's less of a mystery if you think about the actual dictionaries ghc
uses to implement typeclasses.
The instance for Data ctx [a] depends on Data ctx a, so by requiring
Data ctx [Expression] in the Data ctx Expression instance you're
indeed making a loop there, though typeclasses do allow this, and the
implementation has to be lazy enough to permit it.
Strange that with a direct Data ctx Expression = Data ctx Expression
loop we don't get the same problem.
The reason the implementation of Proposition's gunfold matters is
probably that k gets passed the dictionary for Data DefaultD
Expression at the site of its call and some optimization is making it
stricter than necessary.

Looks like we need a ghc dev here to fully unravel the mystery, in the
meantime i'll try to reduce the test case even further.
 - jeremy

 {-# LANGUAGE DeriveDataTypeable, FlexibleContexts, FlexibleInstances,
 MultiParamTypeClasses, UndecidableInstances, RankNTypes,
 ScopedTypeVariables, KindSignatures, EmptyDataDecls,
 NoMonomorphismRestriction #-}
 module Main where

 import qualified Data.Data as Data
 import Data.Typeable

 --- syb-with-class

 data Constr = Constr deriving (Eq, Show)

 data Proxy (a :: * - *)

 class Sat a where
    dict :: a

 class (Typeable a, Sat (ctx a)) = Data ctx a where
     gunfold :: Proxy ctx
             - (forall b r. Data ctx b = c (b - r) - c r)
             - (forall r. r - c r)
             - Constr
             - c a

 instance (Sat (ctx [a]),Data ctx a) = Data ctx [a]

 --- Default

 class (Data DefaultD a) = Default a where
    defaultValue :: a

 data DefaultD a = DefaultD { defaultValueD :: a }

 instance Default t = Sat (DefaultD t) where
    dict = error Sat (DefaultD t) not implemented

 instance Default a = Default [a] where
    defaultValue = error Default [a] not implemented

 --- Trouble

 data Proposition = Proposition Expression  deriving (Show, Data.Data,
 Typeable)
 data Expression = Conjunction Expression deriving (Show, Data.Data,
 Typeable)

 -- instance (Sat (ctx [Expression]), Sat (ctx Expression), Sat (ctx
 Proposition)) = Data ctx Proposition where
 instance Data DefaultD Proposition  where
    gunfold _ k z c = k (z Proposition)
 --    gunfold _ k z c = error gunfold

 instance Default Proposition

 -- Change Data ctx [Expression] to Data ctx Expression and main works.
 instance ( Data ctx [Expression]
         , Sat (ctx Expression)
         ) = Data ctx Expression

 instance Default Expression

 e :: Expression
 e = defaultValueD (dict :: DefaultD Expression)

 main = print e

 ___
 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] What is the rank of a polymorphic type?

2009-12-05 Thread Martijn van Steenbergen

Eugene Kirpichov wrote:

Hello.

Consider the type: (forall a . a) - String.

On one hand, it is rank-2 polymorphic, because it abstracts over a
rank-1 polymorphic type.
On the other hand, it is monomorphic because it isn't actually
quantified itself: in my intuitive view, a parametrically polymorphic
type has infinitely many instantiations (for example, Int - Int is an
instantiation of forall a . a - a, and String - String also is), and
this type doesn't have any instantiations at all.

Which is correct? Is there really a contradiction? What is the
definition of rank of a polymorphic type?


There's a nice paper about this:

Simon Peyton Jones, Dimitrios Vytiniotis, Stephanie Weirich and Mark Shields
Practical type inference for arbitrary-rank types
http://research.microsoft.com/en-us/um/people/simonpj/papers/higher-rank/putting.pdf

Section 3.1 of that paper defines what rank types have: The rank of a 
type describes the depth at which universal quantifiers appear 
contravariantly


Looking at the examples that are then given I'd say your example has 
rank 2 (but I'm no expert). It only mentions the depth of the forall, 
not whether it has any instantiations.


HTH,

Martijn.

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


[Haskell-cafe] Do you need Windows USB in Haskell?

2009-12-05 Thread Maurí­cio CA

Hi,

I keep this direct binding to libusb-1.0.x:

  http://hackage.haskell.org/package/bindings-libusb

on top of which Bas maintains a nice USB library:

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

Work has been done to support libusb-1.0.x in Windows. So, as long
as my bindings-libusb works properly with that, Bas' as well as
any other library based on it will work too.

Problem is: I don't have a Windows machine where I could test
this. So, if you need USB in windows, please keep in touch. I
wouldn't ask you to write any code, but I need to know what builds
and what doesn't.

Best,
Maurício

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


[Haskell-cafe] ANN: hakyll-0.1

2009-12-05 Thread Jasper van der Jeugt

Hello all,

Hakyll is a simple static site generator library, mostly aimed at blogs. 
It supports markdown, tex and html templates.


It is inspired by the ruby Jekyll program. It has a very small codebase 
because it makes extensive use of the excellent pandoc and Text.Template 
libraries.


More information can be found on:
http://hackage.haskell.org/package/hakyll-0.1
http://github.com/jaspervdj/Hakyll

Kind regards,
Jasper Van der Jeugt
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Wikipedia article

2009-12-05 Thread Gwern Branwen
On Sat, Dec 5, 2009 at 4:53 AM, Deniz Dogan deniz.a.m.do...@gmail.com wrote:
 2009/12/4 Simon Marlow marlo...@gmail.com:
 As noted before, the Wikipedia article for Haskell is a disorganised mess.

 http://en.wikipedia.org/wiki/Haskell_%28programming_language%29

 earlier this year, dons suggested reorganising it and posted a template on
 the Haskell wiki:

 http://haskell.org/haskellwiki/WikipediaArticleDesign

 I've made a start on a new version of the page:

 http://en.wikipedia.org/wiki/User:Simonmar/Haskell_%28programming_language%29

 I've kept most of the existing information, but reorganised it more or less
 according to Don's template, and I filled out the overview section.  Also I
 fixed numerous things, but the page still has a long way to go

 Does anyone mind if I spam the existing Haskell article with this new one,
 or do people think we should continue editing the sandbox version until it's
 in better shape?

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


 Could someone please do something about the horrible syntax
 highlighting for strings in the Wikipedia article? Black on dark
 green, really?


Syntax highlighting on En for Haskell snippets is done, I believe,
through GeSHi: http://www.mediawiki.org/wiki/Extension:SyntaxHighlight_GeSHi
So complain to them?

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


Re: [Haskell-cafe] What is the rank of a polymorphic type?

2009-12-05 Thread Stefan Holdermans

Eugene,


Consider the type: (forall a . a) - String.


It's of rank 2.


What is the definition of rank of a polymorphic type?


The minimal rank of a type is given by

  rank (forall a. t) = 1 `max` rank t
  rank (t - u)  = (if rank t == 0 then 0 else rank t + 1) `max`  
rank u

  rank _ = 0

HTH,

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


Re: [Haskell-cafe] Finding HP

2009-12-05 Thread Andrew Coppin

Malcolm Wallace wrote:
The suggestion was to have a single Download button, leading to a 
*page* of suitably described links, allowing the user to choose 
whether they only wanted the basics (a choice of compiler/interpreter 
+ cabal), or the whole Platform, or something else.  It would be the 
ideal place to explain what cabal is and how to use hackage to get 
more libraries than are contained in the platform.  It would perhaps 
reduce the clutter on the front page that some people complained of 
(although I don't personally think it cluttered).


It seems I'm contraversial even when I'm trying to be uncontraversial. :-}

Anyway, the above suggestion sounds most optimal to me. Haskell tends to 
suffer from a frustrating degree of information dragmentation (I love 
whoever came up with that term...), and collecting a bunch of 
information in one place like this sounds very useful.


I guess in a way, the current implementations page could become this 
page (or this new page makes the existing implementations page obsolete...)


I also think it might be worth mentioning HP from the GHC homepage, just 
in case anybody has that bookmarked directly...


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


[Haskell-cafe] HP + Gtk2hs?

2009-12-05 Thread Andrew Coppin
So I decided to try out the Haskell Platform instead of just installing 
GHC directly. To be honest, I didn't really notice much difference, 
except for the files being installed in a different place. But then, 
initially HP ~= GHC; presumably the plan is for it to grow as time goes on.


Anyway, I'm sure you can all see where I'm going with this: Latest 
Gtk2hs binary for Windows doesn't seem to like the latest HP installation.


A few things:

- It is unclear to be which Gtk2hs binaries require which GHC version. 
Can we tabulate this information somewhere?


- It is also unclear to me which HP versions contain what stuff. The HP 
page tells you all about the *current* HP version, and contains a link 
to a raw directory listing for the older versions. (I especially love 
the way the server truncates the filenames to just before where the 
version number starts. Very helpful. :-D ) Can we get propper 
descriptions for _all_ releases of HP? A table summarising the GHC 
version and major packages/versions in each release would be nice.


- Any idea why the HP says beta on it?

- Apart from HP providing GHC 6.10.4 while Gtk2hs currently requires 
6.10.3, it appears that the Gtk2hs installer package doesn't like GHC 
being installed in a path with spaces. Apparently Gtk2hs has a bug 
tracker. (I only just discovered this, so perhaps it needs to be more 
prominent?) Somebody pointed out this bug 6 months ago. Somebody else 
posted a potential fix a month ago. There is no visible activity from 
the developers. (I emphasize visible. Maybe they've seen this and 
they're working on it, but there's no visible indication of activity.)


Gtk2hs is currently the *only* GUI binding that actually works on 
Windows. It's always been slightly frustrating that every time a new 
version of GHC comes out, us Windows users have to beg for somebody to 
build a new binary. (Linux users, on the other hand, can just download 
the sources and compile them with any compiler they like.) Presumably 
going forward Gtk2hs will synchronise to the (less frequent) HP releases 
rather than the individual GHC releases, so many this particular 
frustration will be reduced. (It would be even less frustrating if 
Gtk2hs was *in* HP, but I gather this won't ever happen.)


Of course, being able to actually build C bindings on Windows would be 
even better, but this is apparently infeasible... :-( That being the 
case, I'll settle for just a little bit more documentation.



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


[Haskell-cafe] Haskell-Newbie and Char-Function

2009-12-05 Thread MeAdAstra

Hi guys,
I only started learning Haskell some days ago. Maybe one of you can give me
a hint on how to implement a function that needs a character in the range
(a,b,...z) and an integer number k and returns the k-next neighbor of the
character? For example, fct a 5 would result in output f.

Tobias 
-- 
View this message in context: 
http://old.nabble.com/Haskell-Newbie-and-Char-Function-tp26656676p26656676.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] Low Level Audio - Writing bytes to the sound card?

2009-12-05 Thread Andrew Coppin

M Xyz wrote:


 if you get it to work

As a spoiled Java programmer, this new role as pioneer is a bit 
intimidating, but I will give it a shot. :)


I wish there was a multimedia standard library for beginners like me. 
Writing audio to the speakers shouldn't be such a journey.




Unfortunately, I've yet to find a single Haskell package that binds to C 
which will actually compile on Windows. :-(


(It still makes me chuckle that even the COM bindings - which, by 
definition, can *only* work on Windows - also don't compile. One wonders 
how the author managed to test it...)


Fortunately, for GUI work we have Gtk2hs, which works just fine on 
Windows. (Although obviously, Windows boxes don't usually have GTK+ 
installed.) But most of the really interesting stuff on Hackage is just 
unusable on Windows, sadly.


If you ever do manage to get audio working, I'd be interested to know how.

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


Re: [Haskell-cafe] Haskell-Newbie and Char-Function

2009-12-05 Thread Jochem Berndsen
MeAdAstra wrote:
 Hi guys,
 I only started learning Haskell some days ago. Maybe one of you can give me
 a hint on how to implement a function that needs a character in the range
 (a,b,...z) and an integer number k and returns the k-next neighbor of the
 character? For example, fct a 5 would result in output f.

You might want to use the functions ord and chr from Data.Char, and the
mod function from the Prelude.

Regards, Jochem

-- 
Jochem Berndsen | joc...@functor.nl | joc...@牛在田里.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] New Hackage category: Error Handling

2009-12-05 Thread Michael Snoyman
Careful Gregory, you've hit a hot-button issue: you have dared to refer to
exceptions as errors!

For the record, I find this pedanticism misplaced, as the line between the
two is rather blurry. Nonetheless, for control-monad-failure and attempt, we
purposely refer to the whole slew of things not succeeding as failures.
Not to be confused with public enemy number 2 of Haskell users: the fail
function.

/tongue-in-cheek

Michael

On Fri, Dec 4, 2009 at 5:57 PM, Henning Thielemann 
lemm...@henning-thielemann.de wrote:

 Gregory Crosswhite schrieb:

  When I uploaded my new package, error-message, I also went ahead and
 created a new category:  Error Handling.

 Error handling is the same as debugging for you? I hope it is not
 intended for generating further confusion about exception handling and
 debugging (= help programmers to analyse errors).

 ___
 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] HP + Gtk2hs?

2009-12-05 Thread Bulat Ziganshin
Hello Andrew,

Saturday, December 5, 2009, 6:40:23 PM, you wrote:

 prominent?) Somebody pointed out this bug 6 months ago. Somebody else
 posted a potential fix a month ago. There is no visible activity from 
 the developers.

Developer. many Haskell problems is due to the fact that we have a few
volunteers doing things and lot of consumers begging for features :)

 Gtk2hs is currently the *only* GUI binding that actually works on
 Windows.

i thought that wx and even qt are in rather good shape now


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


[Haskell-cafe] Re: Binding to C in Windows (was: Low Level Audio - Writing bytes to the sound card?)

2009-12-05 Thread Maurí­cio CA

 Unfortunately, I've yet to find a single Haskell package that
 binds to C which will actually compile on Windows. :-(

Do you know how can we check dependencies to C libraries in
Windows? Is pkg-config available? What about packages with
no pkg-config configuration?

Thanks,
Maurício

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


Re: [Haskell-cafe] Low Level Audio - Writing bytes to the sound card?

2009-12-05 Thread Stephen Tetley
Hello Andrew

Plenty compile on Windows:

Some OpenVG, OpenGL[1] (still? - I'm a bit behind the times) only
compile with MinGW.

Others are fine with Cygwin provided you have the dev packages
installed (readline, pcre-light...).

Yet others - no chance...

If you can get the raw C library to work in either Cygwin or MinGW,
you should have a good chance. The only sound software I've had
working on Cygwin has been ChucK though I haven't tried many - ChucK
uses RtAudio to talk to the soundcard which probably isn't easy to
write a binding for as its C++. I had ChucK working two years ago,
maybe things have improved in the Cygwin world regarding sound since
then and other systems now work.

http://www.music.mcgill.ca/~gary/rtaudio/

Best wishes

Stephen

[1] OpenGL worked fine when it was bundled with GHC, when it got
unbundled things seemed to go amiss, plus it seemed to be the thing to
use freeglut - hence the complicated instructions here:
http://netsuperbrain.com/blog/posts/freeglut-windows-hopengl-hglut/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] New Hackage category: Error Handling

2009-12-05 Thread Ross Paterson
On Sat, Dec 05, 2009 at 05:52:11PM +0200, Michael Snoyman wrote:
 For the record, I find this pedanticism misplaced, ...

I think you'll find that's pedantry.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] New Hackage category: Error Handling

2009-12-05 Thread Michael Snoyman
On Sat, Dec 5, 2009 at 7:41 PM, Ross Paterson r...@soi.city.ac.uk wrote:

 On Sat, Dec 05, 2009 at 05:52:11PM +0200, Michael Snoyman wrote:
  For the record, I find this pedanticism misplaced, ...

 I think you'll find that's pedantry.


Hoped someone would comment exactly that ;).

 ___
 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] Avoiding undecidables

2009-12-05 Thread Michael Snoyman
Hi all,

Well, I've got two problems which both want to be solved with undecidable
and overlapping instances. Obviously, I'd like to try and avoid them. For
the record, the problems have to do with the control-monad-failure and
convertible packages. The code below *should* make clear what I'm trying to
accomplish:

-- failure should not be limited to just monads, so...
class Failure e f where
failure :: e - f v
class (Functor f, Failure e f) = FunctorFailure e f
instance (Functor f, Failure e f) = FunctorFailure e f -- undecidable,
overlaps
class (Applicative f, Failure e f) = ApplicativeFailure e f
instance (Applicative f, Failure e f) = ApplicativeFailure e f --
undecidable, overlaps
class (Monad f, Failure e f) = MonadFailure e f
instance (Monad f, Failure e f) = MonadFailure e f -- undecidable, overlaps

And now the convertible issue. I want two type classes: Convert for anything
which *might* be convertible, but might not. For example, sometimes a String
can be converted to an Int (like the string 5), but sometimes it will fail
(like five). TotalConvert is when something *is* convertible, such as Int
to String (simply the show function). Thus the following:

class Convert x y where
convert :: x - Maybe y
class Convert x y = TotalConvert x y where
totalConvert :: x - y
instance TotalConvert x y = Convert x y where -- Boom!
convert = Just . totalConvert

Any ideas are most welcome. Both of these seem like cases where the compiler
could do some DWIMery, but isn't.

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


Re: [Haskell-cafe] HP + Gtk2hs?

2009-12-05 Thread M Xyz



- Apart from HP providing GHC 6.10.4 while Gtk2hs currently requires 6.10.3, it 
appears that the Gtk2hs installer package doesn't like GHC being installed in a 
path with spaces. Apparently Gtk2hs has a bug tracker. (I only just discovered 
this, so perhaps it needs to be more prominent?) Somebody pointed out this bug 
6 months ago. Somebody else posted a potential fix a month ago. There is no 
visible activity from the developers. (I emphasize visible. Maybe they've 
seen this and they're working on it, but there's no visible indication of 
activity.)

Thank you so much for this post. I tried to install Gtk2hs yesterday to play 
with
its Cairo bindings and I hit the Setup found what appears to be a
 non-working installation of GHC brickwall. I found a closed ticket about this 
problem: http://hackage.haskell.org/trac/gtk2hs/ticket/1117
I posted this issue on the Gtk2hs-devel mailing list and got a response today:
http://sourceforge.net/mailarchive/forum.php?thread_name=EF0EE62B-259C-4F62-9BF2-65FA1F01949E%40di.ens.frforum_name=gtk2hs-devel

I don't think I have the will to uninstall the Haskell Platform and everything 
I've set up just to install in a path with no spaces. :)



  


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


[Haskell-cafe] ANN: readline-statevar-1.0.1.0

2009-12-05 Thread Krzysztof Skrzętnicki
Hello

I am happy to announce a release of small package called readline-statevar.
It's a small wrapping library around readline, which in turn wraps
libreadline. The reason I wrote it is because I wasn't happy with the API of
readline. It was composed of tons of functions like setX/getX, where there
could be just one StateVar instead, yielding OpenGL-kind API.

This version aims to match readline-1.0.1.0. (Hence the version number
chosen). I wrote it mostly manually, with a little help from my emacs-fu, so
there is a chance I missed a thing or two.

There is git repo available [1], along with issue tracker [2] and Hackage
page [3]. Feel encouraged to:
 cabal update
 cabal install readline-statevar
And give it a try!

Best regards

Krzysztof Skrzętnicki

[1] http://github.com/Tener/haskell-readline-statevar/
[2] http://github.com/Tener/haskell-readline-statevar/issues
[3] http://hackage.haskell.org/package/readline-statevar
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] HP + Gtk2hs?

2009-12-05 Thread Andrew Coppin

M Xyz wrote:




- Apart from HP providing GHC 6.10.4 while Gtk2hs currently
requires 6.10.3, it appears that the Gtk2hs installer package
doesn't like GHC being installed in a path with spaces. Apparently
Gtk2hs has a bug tracker. (I only just discovered this, so perhaps
it needs to be more prominent?) Somebody pointed out this bug 6
months ago. Somebody else posted a potential fix a month ago.
There is no visible activity from the developers. (I emphasize
visible. Maybe they've seen this and they're working on it, but
there's no visible indication of activity.)

Thank you so much for this post. I tried to install Gtk2hs yesterday 
to play with
its Cairo bindings and I hit the Setup found what appears to be a 
non-working installation of GHC brickwall. I found a closed ticket 
about this problem: http://hackage.haskell.org/trac/gtk2hs/ticket/1117
I posted this issue on the Gtk2hs-devel mailing list and got a 
response today:

http://sourceforge.net/mailarchive/forum.php?thread_name=EF0EE62B-259C-4F62-9BF2-65FA1F01949E%40di.ens.frforum_name=gtk2hs-devel

I don't think I have the will to uninstall the Haskell Platform and 
everything I've set up just to install in a path with no spaces. :)




My information is from here:

http://hackage.haskell.org/trac/gtk2hs/ticket/1165

In case it makes any difference to you. :-)

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


Re: [Haskell-cafe] HP + Gtk2hs?

2009-12-05 Thread Andrew Coppin

Bulat Ziganshin wrote:

Hello Andrew,

Saturday, December 5, 2009, 6:40:23 PM, you wrote:

  

prominent?) Somebody pointed out this bug 6 months ago. Somebody else
posted a potential fix a month ago. There is no visible activity from 
the developers.



Developer. many Haskell problems is due to the fact that we have a few
volunteers doing things and lot of consumers begging for features :)
  


That *does* in fact seem to be a recurring problem, yes.

Now, how to fix this...?


Gtk2hs is currently the *only* GUI binding that actually works on
Windows.



i thought that wx and even qt are in rather good shape now
  


I did try to get wxHaskell going once or twice. And the SDL binding. (I 
wasn't aware we have Qt now...) I've never got any of them to work yet. :-(


Interestingly, while you can't compile bindings to external C libraries, 
GHC does appear to ship with all the header files for Windows, which is 
odd. It seems if you try to FFI to a standard Win32 function, it 
magically knows where the hell the header files are, and it Just 
Works(tm). Hell, I even followed a C++ guide to Win32 programming and 
managed to translate an open a blank window program to Haskell, and it 
worked. Maybe somebody just needs to sit down and write a nice binding 
for doing native GUI stuff under Win32?


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


Re: [Haskell-cafe] Low Level Audio - Writing bytes to the sound card?

2009-12-05 Thread wren ng thornton

Andrew Coppin wrote:
Unfortunately, I've yet to find a single Haskell package that binds to C 
which will actually compile on Windows. :-(


Take a look at logfloat[1], it builds cleanly on Windows XP using GHC 
6.10.1 without needing Cygwin nor Mingw/Msys (however GHCi has some DLL 
errors[2]).


Not that that has anything to do with audio ;)


[1] http://hackage.haskell.org/cgi-bin/hackage-scripts/package/logfloat

[2] If you know how to resolve these, I'd be much obliged. I don't have 
a Windows machine to test on but I've been much irked that there's still 
this outstanding portability bug.


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] HP + Gtk2hs?

2009-12-05 Thread Bulat Ziganshin
Hello Andrew,

Saturday, December 5, 2009, 10:14:17 PM, you wrote:

 I did try to get wxHaskell going once or twice. And the SDL binding. (I
 wasn't aware we have Qt now...) I've never got any of them to work yet.

it depends on when you have tried. wx made significant progress in
last year or two


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] HP + Gtk2hs?

2009-12-05 Thread Daniel Fischer
Am Samstag 05 Dezember 2009 20:14:17 schrieb Andrew Coppin:
 Bulat Ziganshin wrote:
  Hello Andrew,
 
  Saturday, December 5, 2009, 6:40:23 PM, you wrote:
  prominent?) Somebody pointed out this bug 6 months ago. Somebody else
  posted a potential fix a month ago. There is no visible activity from
  the developers.
 
  Developer. many Haskell problems is due to the fact that we have a few
  volunteers doing things and lot of consumers begging for features :)

 That *does* in fact seem to be a recurring problem, yes.

 Now, how to fix this...?

How about:

get the sources, try proposed fix, if it works, send Duncan(*) the patch?
Even better, become a gtk2hs developer yourself (though that's more work and 
probably 
requires some serious knowledge of gtk).

(*) for gtk2hs, would be somebody else for other packages of course.


  Gtk2hs is currently the *only* GUI binding that actually works on
  Windows.
 
  i thought that wx and even qt are in rather good shape now

 I did try to get wxHaskell going once or twice. And the SDL binding. (I
 wasn't aware we have Qt now...) I've never got any of them to work yet. :-(

 Interestingly, while you can't compile bindings to external C libraries,
 GHC does appear to ship with all the header files for Windows, which is
 odd. It seems if you try to FFI to a standard Win32 function, it
 magically knows where the hell the header files are, and it Just
 Works(tm). Hell, I even followed a C++ guide to Win32 programming and
 managed to translate an open a blank window program to Haskell, and it
 worked. Maybe somebody just needs to sit down and write a nice binding
 for doing native GUI stuff under Win32?

Maybe you could try to be that somebody? I'm sure the Windows folks would 
appreciate it 
very much.
Or, if you think that's beyond your ken, try organising the writing.
Perhaps create a windows-haskell mailing list where Windows users can help each 
other 
making things work on Windows.

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


Re: [Haskell-cafe] Haskell-Newbie and Char-Function

2009-12-05 Thread Chaddaï Fouché
On Sat, Dec 5, 2009 at 4:48 PM, Jochem Berndsen joc...@functor.nl wrote:
 MeAdAstra wrote:
 Hi guys,
 I only started learning Haskell some days ago. Maybe one of you can give me
 a hint on how to implement a function that needs a character in the range
 (a,b,...z) and an integer number k and returns the k-next neighbor of the
 character? For example, fct a 5 would result in output f.

 You might want to use the functions ord and chr from Data.Char, and the
 mod function from the Prelude.

Right, and by the way I would suggest you reverse the parameter order
of your function so that it takes the shift first, then you can write
:

 shift :: Int - Char - Char
 shift n c ...

 rot13 :: String - String
 rot13 = map (shift 13)

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


Re: [Haskell-cafe] HP + Gtk2hs?

2009-12-05 Thread Stephen Tetley
2009/12/5 Andrew Coppin andrewcop...@btinternet.com:

 Interestingly, while you can't compile bindings to external C libraries,


Ah Mr Coppin,  maybe you should change you to I.

I had (Haskell bindings) SDL-0.5.3 working August last year - so I
think I would be using GHC 6.8.3 at that time, the version of the SDL
C library was 1.2.13.

SDL has no prepared package in the Cygwin package manager, so you have
to download it yourself. I seem to remember it being more tricky to
get SDL working under Cygwin as a C library (you need extra DirectX
header files at least), than it was to compile the Haskell binding
once the C library was working. Instructions for compiling the C
library for Cygwin are on the SDL website.

I haven't tried it since as I don't need SDL for anything I do, but
don't I think it would be any harder (lemmih's binding seems to be
pretty stable and at the time I used it, it was impressively tidy).

Best wishes again

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


Re: [Haskell-cafe] HP + Gtk2hs?

2009-12-05 Thread Andrew Coppin

Daniel Fischer wrote:

Am Samstag 05 Dezember 2009 20:14:17 schrieb Andrew Coppin:
  

Bulat Ziganshin wrote:


Developer. many Haskell problems is due to the fact that we have a few
volunteers doing things and lot of consumers begging for features :)
  

That *does* in fact seem to be a recurring problem, yes.

Now, how to fix this...?



How about:

get the sources, try proposed fix, if it works, send Duncan(*) the patch?
Even better, become a gtk2hs developer yourself (though that's more work and probably 
requires some serious knowledge of gtk).
  


In order to do this, I'd have to know how to build Gtk2hs from source on 
Windows. I imagine this is quite nontrivial.



Interestingly, while you can't compile bindings to external C libraries,
GHC does appear to ship with all the header files for Windows, which is
odd. It seems if you try to FFI to a standard Win32 function, it
magically knows where the hell the header files are, and it Just
Works(tm). Hell, I even followed a C++ guide to Win32 programming and
managed to translate an open a blank window program to Haskell, and it
worked. Maybe somebody just needs to sit down and write a nice binding
for doing native GUI stuff under Win32?


Maybe you could try to be that somebody? I'm sure the Windows folks would appreciate it 
very much


The thought has certainly crossed my mind. If I could write such a 
package, I imagine a lot of people would find it seriously useful. 
Native Windows GUI programs, without any 3rd party DLLs to distribute 
with your compiled binary... It'd be great, wouldn't it?


Of course, thinking about how great it would be doesn't get the code 
written. ;-) I'd have to learn how to call Win32 from C first, for a 
start... o_O


The various I/O libraries sometimes return weird results, and I'm told 
this is because GHC is using the emulated POSIX interfaces rather than 
native Win32 calls. I did think about turning my attention to fixing 
that. However, I notice the next version of GHC seems to have a 
radically reworked set of I/O libraries, so maybe it's already fixed?


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


Re: [Haskell-cafe] Low Level Audio - Writing bytes to the sound card?

2009-12-05 Thread Andrew Coppin

Stephen Tetley wrote:

Hello Andrew

Plenty compile on Windows:

Some OpenVG, OpenGL[1] (still? - I'm a bit behind the times) only
compile with MinGW.

Others are fine with Cygwin provided you have the dev packages
installed (readline, pcre-light...).
  


You're talking about MinGW and Cygwin. So... Unix emulators, basically.

I don't think it should be necessary to install a Unix emulator just so 
that I can write Windows programs. Maybe others disagree.



If you can get the raw C library to work in either Cygwin or MinGW,
you should have a good chance.


I'm by no means an expert here, but isn't it usual for C libraries on 
Windows to be supplied as a compiled DLL and a header file for using it? 
I don't quite understand why you need a C compiler.



[1] OpenGL worked fine when it was bundled with GHC, when it got
unbundled things seemed to go amiss.


Apparently there is some talk of removing OpenGL from the Haskell 
Platform. And if this happens, it'll be one more thing I can't use on 
Windows. :-(


Personally, I'd like to see *more* C bindings in HP, so that I can start 
doing cool stuff on Windows.


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


Re: [Haskell-cafe] Avoiding undecidables

2009-12-05 Thread José Iborra

On Dec 5, 2009, at 6:58 PM, Michael Snoyman wrote:

 Hi all,
 
 Well, I've got two problems which both want to be solved with undecidable and 
 overlapping instances. Obviously, I'd like to try and avoid them. For the 
 record, the problems have to do with the control-monad-failure and 
 convertible packages. The code below *should* make clear what I'm trying to 
 accomplish:
 
 -- failure should not be limited to just monads, so...
 class Failure e f where
 failure :: e - f v
 class (Functor f, Failure e f) = FunctorFailure e f
 instance (Functor f, Failure e f) = FunctorFailure e f -- undecidable, 
 overlaps
 class (Applicative f, Failure e f) = ApplicativeFailure e f
 instance (Applicative f, Failure e f) = ApplicativeFailure e f -- 
 undecidable, overlaps
 class (Monad f, Failure e f) = MonadFailure e f
 instance (Monad f, Failure e f) = MonadFailure e f -- undecidable, overlaps
 

(Functor|Monad|Applicative)Failure are little more than class synonyms, right ?
Or equivalently, do you envision the need of writing, say, a MonadFailure 
instance for a type A which which works differently than the existing Failure 
instance for A?
If the answer is no as I presume, then you don't want overlapping instances.

Regarding undecidable instances, I will say that from my point of view they do 
not constitute a language extension.
MPTCs are the language extension here. Since MPTCs can lead to non-terminating 
type checking,
a compiler can either allow any use of them, employ a termination prover to 
ensure that only well-behaved instances are defined,
or impose a set of restrictions that ensure termination. GHC does the latter, 
rather conservatively in some cases, and undecidable
instances is just a compiler flag that puts the burden of termination checking 
on the user.

In this case it is obvious that non-termination is not going to be a problem 
for the instances defined above.
Since you have already decided MPTCs are ok, in my opinion undecidable 
instances are fine here.
But I realize this is not the usual stance, so I might be wrong.


 And now the convertible issue. I want two type classes: Convert for anything 
 which *might* be convertible, but might not. For example, sometimes a String 
 can be converted to an Int (like the string 5), but sometimes it will fail 
 (like five). TotalConvert is when something *is* convertible, such as Int 
 to String (simply the show function). Thus the following:
 
 class Convert x y where
 convert :: x - Maybe y
 class Convert x y = TotalConvert x y where
 totalConvert :: x - y
 instance TotalConvert x y = Convert x y where -- Boom!
 convert = Just . totalConvert


In this case Convert is not just a class synonym, so you are going to run into 
trouble with that code.

I would do this as follows:

class Convert x y = TotalConvert x y where
totalConvert :: x - y
totalConvert = fromJust . convert

For instance,

instance Convert Integer Double where convert = Just . fromIntegral
instance TotalConvert Double-- that's all


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


Re: [Haskell-cafe] Low Level Audio - Writing bytes to the sound card?

2009-12-05 Thread Miguel Mitrofanov
I'm constantly amused by those who manage to use Windows without  
installing Cygwin.


On 5 Dec 2009, at 23:33, Andrew Coppin wrote:


Stephen Tetley wrote:

Hello Andrew

Plenty compile on Windows:

Some OpenVG, OpenGL[1] (still? - I'm a bit behind the times) only
compile with MinGW.

Others are fine with Cygwin provided you have the dev packages
installed (readline, pcre-light...).



You're talking about MinGW and Cygwin. So... Unix emulators,  
basically.


I don't think it should be necessary to install a Unix emulator just  
so that I can write Windows programs. Maybe others disagree.



If you can get the raw C library to work in either Cygwin or MinGW,
you should have a good chance.


I'm by no means an expert here, but isn't it usual for C libraries  
on Windows to be supplied as a compiled DLL and a header file for  
using it? I don't quite understand why you need a C compiler.



[1] OpenGL worked fine when it was bundled with GHC, when it got
unbundled things seemed to go amiss.


Apparently there is some talk of removing OpenGL from the Haskell  
Platform. And if this happens, it'll be one more thing I can't use  
on Windows. :-(


Personally, I'd like to see *more* C bindings in HP, so that I can  
start doing cool stuff on Windows.


___
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-Newbie and Char-Function

2009-12-05 Thread ??????? ??????

fct a n = (snd $ break (==a) ['a'..'z']) !! n

Hi guys,
I only started learning Haskell some days ago. Maybe one of you can give me
a hint on how to implement a function that needs a character in the range
(a,b,...z) and an integer number k and returns the k-next neighbor of the
character? For example, fct a 5 would result in output f.

Tobias 
  


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


Re: [Haskell-cafe] Avoiding undecidables

2009-12-05 Thread Michael Snoyman
On Sat, Dec 5, 2009 at 10:33 PM, José Iborra pepeibo...@gmail.com wrote:


 On Dec 5, 2009, at 6:58 PM, Michael Snoyman wrote:

  Hi all,
 
  Well, I've got two problems which both want to be solved with undecidable
 and overlapping instances. Obviously, I'd like to try and avoid them. For
 the record, the problems have to do with the control-monad-failure and
 convertible packages. The code below *should* make clear what I'm trying to
 accomplish:
 
  -- failure should not be limited to just monads, so...
  class Failure e f where
  failure :: e - f v
  class (Functor f, Failure e f) = FunctorFailure e f
  instance (Functor f, Failure e f) = FunctorFailure e f -- undecidable,
 overlaps
  class (Applicative f, Failure e f) = ApplicativeFailure e f
  instance (Applicative f, Failure e f) = ApplicativeFailure e f --
 undecidable, overlaps
  class (Monad f, Failure e f) = MonadFailure e f
  instance (Monad f, Failure e f) = MonadFailure e f -- undecidable,
 overlaps
 

 (Functor|Monad|Applicative)Failure are little more than class synonyms,
 right ?
 Or equivalently, do you envision the need of writing, say, a MonadFailure
 instance for a type A which which works differently than the existing
 Failure instance for A?
 If the answer is no as I presume, then you don't want overlapping
 instances.

 Regarding undecidable instances, I will say that from my point of view they
 do not constitute a language extension.
 MPTCs are the language extension here. Since MPTCs can lead to
 non-terminating type checking,
 a compiler can either allow any use of them, employ a termination prover to
 ensure that only well-behaved instances are defined,
 or impose a set of restrictions that ensure termination. GHC does the
 latter, rather conservatively in some cases, and undecidable
 instances is just a compiler flag that puts the burden of termination
 checking on the user.

 In this case it is obvious that non-termination is not going to be a
 problem for the instances defined above.
 Since you have already decided MPTCs are ok, in my opinion undecidable
 instances are fine here.
 But I realize this is not the usual stance, so I might be wrong.

 Sounds reasonable to me. I'm waiting for the boogey man to jump out though
and explain why undecidables here will get me gored to death by a raptor
[1].


  And now the convertible issue. I want two type classes: Convert for
 anything which *might* be convertible, but might not. For example, sometimes
 a String can be converted to an Int (like the string 5), but sometimes it
 will fail (like five). TotalConvert is when something *is* convertible,
 such as Int to String (simply the show function). Thus the following:
 
  class Convert x y where
  convert :: x - Maybe y
  class Convert x y = TotalConvert x y where
  totalConvert :: x - y
  instance TotalConvert x y = Convert x y where -- Boom!
  convert = Just . totalConvert


 In this case Convert is not just a class synonym, so you are going to run
 into trouble with that code.

 I would do this as follows:

 class Convert x y = TotalConvert x y where
totalConvert :: x - y
 totalConvert = fromJust . convert

 For instance,

 instance Convert Integer Double where convert = Just . fromIntegral
 instance TotalConvert Double-- that's all

 Interestng approach. The current approach is *almost* the same, just leaves
off the default definition. I'd be wary of putting in a definition like
that; although it saves a line of typing, it let's a partial function get in
which could cause trouble for unsuspecting users. But it is a possibility.


 Cheers,
 pepe


[1] http://xkcd.com/292/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Low Level Audio - Writing bytes to the sound card?

2009-12-05 Thread Stephen Tetley
Hi Andrew



2009/12/5 Andrew Coppin andrewcop...@btinternet.com:

 I don't think it should be necessary to install a Unix emulator just so that
 I can write Windows programs. Maybe others disagree.


...


 I'm by no means an expert here, but isn't it usual for C libraries on
 Windows to be supplied as a compiled DLL and a header file for using it? I
 don't quite understand why you need a C compiler.

The thing is, all the bindings on Hackage (or at least something most
likely above 95%) are to Unix C libraries so you need a C compiler
and a Unix emulator to use them. I do have have some sympathy with
your point though - it is possible to get things to compile once you
have Cygwin, but deployment on any other machine Windows thereafter is
'challenging' to say the least.




 Apparently there is some talk of removing OpenGL from the Haskell Platform.
 And if this happens, it'll be one more thing I can't use on Windows. :-(


I didn't realise until I looked today that OpenGL was in the Haskell
Platform. If the proposal to remove it is from Sven Panne then fair
enough, otherwise it would be a bit disappointing - it always just
worked when it was part of GHCs extralibs...

Best wishes

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


Re: [Haskell-cafe] What is the rank of a polymorphic type?

2009-12-05 Thread Eugene Kirpichov
2009/12/5 Stefan Holdermans ste...@cs.uu.nl:
 Eugene,

 Consider the type: (forall a . a) - String.

 It's of rank 2.

 What is the definition of rank of a polymorphic type?

 The minimal rank of a type is given by

  rank (forall a. t) = 1 `max` rank t
  rank (t - u)      = (if rank t == 0 then 0 else rank t + 1) `max` rank u
  rank _             = 0


Thanks!
1) Does there exist an authoritative source saying the same? Not that
I'm doubting, just supposing that the source would have other
interesting information, too :)
2) Is it true that rank (forall a . a, forall a . a) == 0 ?

 HTH,

  Stefan




-- 
Eugene Kirpichov
Web IR developer, market.yandex.ru
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Low Level Audio - Writing bytes to the sound card?

2009-12-05 Thread Andrew Coppin

Miguel Mitrofanov wrote:
I'm constantly amused by those who manage to use Windows without 
installing Cygwin.


I'm constantly puzzled by those who think that Cygwin is a mandatory 
part of Windows. ;-)


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


Re: [Haskell-cafe] HP + Gtk2hs?

2009-12-05 Thread Daniel Fischer
Am Samstag 05 Dezember 2009 21:31:39 schrieb Andrew Coppin:
 Daniel Fischer wrote:
  Am Samstag 05 Dezember 2009 20:14:17 schrieb Andrew Coppin:
  Bulat Ziganshin wrote:
  Developer. many Haskell problems is due to the fact that we have a few
  volunteers doing things and lot of consumers begging for features :)
 
  That *does* in fact seem to be a recurring problem, yes.
 
  Now, how to fix this...?
 
  How about:
 
  get the sources, try proposed fix, if it works, send Duncan(*) the patch?
  Even better, become a gtk2hs developer yourself (though that's more work
  and probably requires some serious knowledge of gtk).

 In order to do this, I'd have to know how to build Gtk2hs from source on
 Windows. I imagine this is quite nontrivial.

I thought in this case, it was a proposed change in the installer, so you'd 
only have to 
change that and could leave the gtk2hs binary untouched. Of course that can 
only work if 
Windows installers are some sort of script or otherwise customisable. Are they?


  Interestingly, while you can't compile bindings to external C libraries,
  GHC does appear to ship with all the header files for Windows, which is
  odd. It seems if you try to FFI to a standard Win32 function, it
  magically knows where the hell the header files are, and it Just
  Works(tm). Hell, I even followed a C++ guide to Win32 programming and
  managed to translate an open a blank window program to Haskell, and it
  worked. Maybe somebody just needs to sit down and write a nice binding
  for doing native GUI stuff under Win32?
 
  Maybe you could try to be that somebody? I'm sure the Windows folks would
  appreciate it very much

 The thought has certainly crossed my mind. If I could write such a
 package, I imagine a lot of people would find it seriously useful.
 Native Windows GUI programs, without any 3rd party DLLs to distribute
 with your compiled binary... It'd be great, wouldn't it?

 Of course, thinking about how great it would be doesn't get the code
 written. ;-) I'd have to learn how to call Win32 from C first, for a
 start... o_O

Yes, of course, ultra posse nemo obligatur.
As long as you can't do something, you can only hope somebody else can and does.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Low Level Audio - Writing bytes to the sound card?

2009-12-05 Thread Daniel Fischer
Am Samstag 05 Dezember 2009 21:43:13 schrieb Miguel Mitrofanov:
 I'm constantly amused by those who manage to use Windows without  
 installing Cygwin.

I'm constantly amazed by those who manage to use Windows.


(In case you want to misunderstand, it's not a Windows bashing, I just never 
managed to 
work with it)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: error-message

2009-12-05 Thread Brent Yorgey
On Thu, Dec 03, 2009 at 01:50:06PM -0800, Gregory Crosswhite wrote:
 
 Or, even more concisely:
 
 ==
 sumWithError_3 = liftM2 (+)
 ==
 
 Unfortunately though, neither of these definitions have the same semantics as 
 the original @sumWithError@, as using both we get the following error message 
 for @showSumOrErrorOf (-1) (-2)@:
 
 ==
 Error computing the square root of -1:
 Square roots cannot be taken of negative numbers.
 ==
 
 That is, we have lost the second of the two error messages.  The reason for 
 this is that 'Monad'-style error processing expresses the computation as a 
 sequence, and gives up as soon as it sees any error.  In this case of 
 @sumWithError@, however, the evaluation of the second argument can proceed 
 even if there was an error in the first argument.  Thus, rather than using a 
 'Monad' pattern, we use an 'Applicative' pattern:
 
 ==
 sumWithError_4 = liftA2 (+)
 ==
 
 Now both error messages are displayed.

I see no inherent reason that liftM2 (+) cannot collect both error
messages.  No one says that monad-style error processing *must* stop
as soon as it sees an error. And having different semantics for liftA2
and liftM2 (etc.)  is strange at best.  They ought to be equivalent
for any type constructor with both Monad and Applicative instances.

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


[Haskell-cafe] Re: Optimizing Parsec 3 -- was: Wiki software?

2009-12-05 Thread Howard B. Golden
On Friday December 4, 2009, John MacFarlane wrote:

 I used criterion to compare pandoc compiled with parsec2 to
 pandoc compiled with your version of parsec3.  (The benchmark
 is converting testsuite.txt from markdown to HTML.) The difference
  was minor:
 
 parsec2:
 mean: 67.66576 ms, lb 67.56722 ms, ub 67.88983 ms, ci 0.950
 std dev: 722.3878 us, lb 323.0343 us, ub 1.356013 ms, ci 0.950
 
 parsec3:
 mean: 68.20847 ms, lb 68.16387 ms, ub 68.26284 ms, ci 0.950
 std dev: 252.7773 us, lb 204.5512 us, ub 325.2424 us, ci 0.950
 
 So, once you release the new parsec3, I am prepared to remove the
 parsec  3 restriction from the libraries I maintain: pandoc,
 highlighting-kate, filestore, gitit, and yst.

I don't know what the performance of the current parsec3 is compared to 
parsec2. It would be helpful if you could run your benchmark for that 
also and include it.

If the only issue is performance, I respectfully request that you remove 
the parsec  3 requirement even before the new version of parsec3 is 
released. Thank you.

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


Re: [Haskell-cafe] Avoiding undecidables

2009-12-05 Thread Daniel Fischer
Am Samstag 05 Dezember 2009 21:51:26 schrieb Michael Snoyman:
 On Sat, Dec 5, 2009 at 10:33 PM, José Iborra pepeibo...@gmail.com wrote:
  Since you have already decided MPTCs are ok, in my opinion undecidable
  instances are fine here.
  But I realize this is not the usual stance, so I might be wrong.
 

As far as I understand, all UndecidableInstances does is tell the compiler 
Maybe instance 
checking won't terminate, try anyway, so they're dangerous *only during 
compilation*, 
once things compile, everything's dandy.

 Sounds reasonable to me. I'm waiting for the boogey man to jump out
 though

 and explain why undecidables here will get me gored to death by a raptor
 [1].

They won't. They might suck you into a black hole, but raptors are very 
specialised.


 
  instance Convert Integer Double where convert = Just . fromIntegral
  instance TotalConvert Double-- that's all

instance TotalConvert Integer Double

 
 Interestng approach. The current approach is *almost* the same, just
 leaves

 off the default definition. I'd be wary of putting in a definition like
 that; although it saves a line of typing, it let's a partial function get
 in which could cause trouble for unsuspecting users. But it is a
 possibility.

But only if they declare misbehaved instances of TotalConvert. Whenever a 
reasonable 
instance TotalConvert x y exists, the Convert instance should satisfy the 
demands of the 
default definition.


  Cheers,
  pepe

 [1] http://xkcd.com/292/

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


Re: [Haskell-cafe] What is the rank of a polymorphic type?

2009-12-05 Thread Stefan Holdermans

Eugene,


1) Does there exist an authoritative source saying the same? Not that
I'm doubting, just supposing that the source would have other
interesting information, too :)


You may want to have a look at the already mentioned JFP-article by  
Peyton Jones et al. and perhaps the work of Kfoury and Wells.



2) Is it true that rank (forall a . a, forall a . a) == 0 ?


No, for pairs one takes the maximum of the constituent types. So, here  
you'd get rank 1.


Note that this is an impredicative type, which is yet another  
extension of the standard Hindley-Milner typing discipline.


Cheers,

  Stefan





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


[Haskell-cafe] Re: Optimizing Parsec 3 -- was: Wiki software?

2009-12-05 Thread John MacFarlane
+++ Howard B. Golden [Dec 05 09 13:36 ]:
 On Friday December 4, 2009, John MacFarlane wrote:
 
  I used criterion to compare pandoc compiled with parsec2 to
  pandoc compiled with your version of parsec3.  (The benchmark
  is converting testsuite.txt from markdown to HTML.) The difference
   was minor:
  
  parsec2:
  mean: 67.66576 ms, lb 67.56722 ms, ub 67.88983 ms, ci 0.950
  std dev: 722.3878 us, lb 323.0343 us, ub 1.356013 ms, ci 0.950
  
  parsec3:
  mean: 68.20847 ms, lb 68.16387 ms, ub 68.26284 ms, ci 0.950
  std dev: 252.7773 us, lb 204.5512 us, ub 325.2424 us, ci 0.950
  
  So, once you release the new parsec3, I am prepared to remove the
  parsec  3 restriction from the libraries I maintain: pandoc,
  highlighting-kate, filestore, gitit, and yst.
 
 I don't know what the performance of the current parsec3 is compared to 
 parsec2. It would be helpful if you could run your benchmark for that 
 also and include it.

parsec 2.1.0.1 from HackageDB:
mean: 67.71456 ms, lb 67.65181 ms, ub 67.82660 ms, ci 0.950
std dev: 416.1303 us, lb 274.0063 us, ub 761.6995 us, ci 0.950

parsec 3.0.1 from HackageDB:
mean: 188.5380 ms, lb 188.3217 ms, ub 188.7615 ms, ci 0.950
std dev: 1.136199 ms, lb 964.3489 us, ub 1.366720 ms, ci 0.950

parsec 3.0.1 from Antoine:
mean: 69.29665 ms, lb 69.22450 ms, ub 69.48016 ms, ci 0.950
std dev: 551.3562 us, lb 263.7954 us, ub 1.156183 ms, ci 0.950

 If the only issue is performance, I respectfully request that you remove 
 the parsec  3 requirement even before the new version of parsec3 is 
 released. Thank you.

Sorry, I don't want to do that. Lots of people have both parsec-2 and
parsec-3 installed, and if I remove the restriction, their pandoc (and
gitit and...) will be much slower unless they take special steps.

John

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


Re: [Haskell-cafe] HP + Gtk2hs?

2009-12-05 Thread M Xyz


--- On Sat, 12/5/09, Daniel Fischer daniel.is.fisc...@web.de wrote:


I thought in this case, it was a proposed change in the installer, so you'd 
only have to 
change that and could leave the gtk2hs binary untouched. Of course that can 
only work if 
Windows installers are some sort of script or otherwise customisable. Are they?

If they used a tool like NSIS then it would be as easy as modifying the script. 
I emailed a Gtk developer offering to help if that were the case.




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


Re: [Haskell-cafe] Low Level Audio - Writing bytes to the sound card?

2009-12-05 Thread Andrew Coppin

Daniel Fischer wrote:

I'm constantly amazed by those who manage to use Windows.


(In case you want to misunderstand, it's not a Windows bashing, I just never managed to 
work with it


I've not had a lot of luck with Linux. I imagine this is merely due to 
having a lot more experience with Windows.


FWIW, I used to hate Windows too - AmigaOS is far nicer. ;-)

But now we're drifting wildly off-topic. For better or worse, Windows is 
the most popular desktop OS currently.


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


Re: [Haskell-cafe] Low Level Audio - Writing bytes to the sound card?

2009-12-05 Thread Stephen Tetley
Compiling the C PortAudio library for either Cygwin or MinGW will be
challenging at the moment.

The current release doesn't compile as is, and although there should
be patch for the configure script as an attachment to this message it
seems to have gone amiss:

http://music.columbia.edu/pipermail/portaudio/2009-May/009116.html

I'd look for a different library to talk to the sound card...

Best wishes

Stephen


2009/12/4 M Xyz functionallyharmoni...@yahoo.com

 What is the most minimal (preferably platform independent) library available 
 for writing bytes to the sound card? I see 60 wonderful libraries on Hackage, 
 but I really just need the Haskell equivalent of an audio.write(byte[]) 
 method. What sound api are these 60 libraries using?

 I think the portaudio library is the only contender but when I try to install 
 it I get:

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


Re: [Haskell-cafe] Low Level Audio - Writing bytes to the sound card?

2009-12-05 Thread Miguel Mitrofanov

Try Mac.

/commercial

On 6 Dec 2009, at 01:00, Andrew Coppin wrote:


Daniel Fischer wrote:

I'm constantly amazed by those who manage to use Windows.


(In case you want to misunderstand, it's not a Windows bashing, I  
just never managed to work with it


I've not had a lot of luck with Linux. I imagine this is merely due  
to having a lot more experience with Windows.


FWIW, I used to hate Windows too - AmigaOS is far nicer. ;-)

But now we're drifting wildly off-topic. For better or worse,  
Windows is the most popular desktop OS currently.


___
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] Low Level Audio - Writing bytes to the sound card?

2009-12-05 Thread Andrew Coppin

Miguel Mitrofanov wrote:

Try Mac.

/commercial


You're not the first to suggest this either. ;-)

Maybe once I get hired by some financial modelling consultants and get 
paid shedloads of money to write Haskell all day, I'll be able to afford 
a Mac. But until then...


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


Re: [Haskell-cafe] ANNOUNCE: error-message

2009-12-05 Thread Gregory Crosswhite
Recall that the definition of liftM2 is

==
liftM2  :: (Monad m) = (a1 - a2 - r) - m a1 - m a2 - m r
liftM2 f m1 m2  = do { x1 - m1; x2 - m2; return (f x1 x2) }
==

which, if I understand correctly, desugars to

==
liftM2 f m1 m2 =
m1 =
(
\x1 -
m2 =
(   
\x2 -
return (f x1 x2)
)
)
==

The problem comes from the fact that = takes a *function* as its second 
argument, and so if the first argument is an error then we can't evaluate the 
second argument in order to see if it has an error as well.  For example, 
consider the following script:

===
import Control.Applicative
import Control.Monad

import Data.ErrorMessage

newtype E a = E (Either String a)


instance Functor E where
   fmap _ (E (Left error)) = E (Left error)
   fmap f (E (Right argument)) = E (Right (f argument))

instance Applicative E where
   pure = E . Right
   (*) (E (Left error2)) (E (Left error1)) = E (Left (error1 ++ error2))
   (*) (E (Left error)) _ = E (Left error)
   (*) _ (E (Left error)) = E (Left error)
   (*) (E (Right function)) (E (Right argument)) = E (Right (function 
argument))

instance Monad E where
  return= E . Right
  E (Left  l) = _ = E (Left l)
  E (Right r) = f = f r
  fail msg  = E (Left msg)

sum_using_monad :: Either String Int
(E sum_using_monad) = (liftM2 (+)) (E (Left A)) (E (Left B))

sum_using_applicative :: Either String Int
(E sum_using_applicative) = (liftA2 (+)) (E (Left A)) (E (Left B))

main = do
 putStrLn . show $ sum_using_monad
 putStrLn . show $ sum_using_applicative
===

(Sorry about all of the annoying E's;  I needed to do this in order to override 
the instance declaration for Either String.)

Run this script and you will see:

Left A
Left BA

Thus, the difference in the semantics is inherent from the way that = and 
liftM2 are defined.  The only way that I can think to get around this is change 
the definition of = so that if the first argument is an error then it calls 
the second argument with undefined;  if this returns a (Left error) then 
combine the two errors, and if it returns anything else or throws an exception 
(e.g. Prelude.undefined) then ignore it and just return the first argument.

Cheers,
Greg

On Dec 5, 2009, at 1:28 PM, Brent Yorgey wrote:

 On Thu, Dec 03, 2009 at 01:50:06PM -0800, Gregory Crosswhite wrote:
 
 Or, even more concisely:
 
 ==
sumWithError_3 = liftM2 (+)
 ==
 
 Unfortunately though, neither of these definitions have the same semantics 
 as the original @sumWithError@, as using both we get the following error 
 message for @showSumOrErrorOf (-1) (-2)@:
 
 ==
Error computing the square root of -1:
Square roots cannot be taken of negative numbers.
 ==
 
 That is, we have lost the second of the two error messages.  The reason for 
 this is that 'Monad'-style error processing expresses the computation as a 
 sequence, and gives up as soon as it sees any error.  In this case of 
 @sumWithError@, however, the evaluation of the second argument can proceed 
 even if there was an error in the first argument.  Thus, rather than using a 
 'Monad' pattern, we use an 'Applicative' pattern:
 
 ==
sumWithError_4 = liftA2 (+)
 ==
 
 Now both error messages are displayed.
 
 I see no inherent reason that liftM2 (+) cannot collect both error
 messages.  No one says that monad-style error processing *must* stop
 as soon as it sees an error. And having different semantics for liftA2
 and liftM2 (etc.)  is strange at best.  They ought to be equivalent
 for any type constructor with both Monad and Applicative instances.
 
 -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] binding to C libraries on Windows was Low Level Audio - Writing bytes to the sound card?

2009-12-05 Thread john lask

I think there are some misapprehensions here:-

many haskell packages binding to c libraries will compile with ghc 
without problems on windows - without cygwin, without mingw/msys system.

Some such packages build out of the box on windows, like the zlib 
package which contains the c source for the c zlib library. GHC is able 
to compile and build this packages without any other c 
compiler/libraries/unix emulators etc because ghc itself contains part 
of the gcc c compiler tool chain and comes with all c standard headers, 
c++ headers and c/c++ runtime libraries.

Other packages such as SDL package are relatively straightforward to 
build on windows - all that is required is to have an import library 
corresponding to your dll (or static lib) and the headers. You then 
update the library path field in the cabal file and include path. There 
is only one gotch-ya - you need to have a import library for the gcc 
tool chain (thats what ghc uses) i.e. a .a library and not the native 
windows .LIB import library. If you don't have .a import library 
but have the dll then the '.a' import library be built for any dll 
relativley easily.

The correct '.a' import libraries and the libraries themselves for many
standard unix/gnu packages can be found under the gnuwin32 project. Many 
unix libraries provide a windows build based on the mingw port of the 
gcc tool chain which will contain the correct import library.

the bigest problem hamperring cleaner builds of haskell packages on 
windows is the lack of any standardised scheme for the installation of 
c-libraries and header files (and of course the availability of a 
suitable build of the library)

Another problem hampering the install of haskell packages on windows is 
the use of the unix autoconf build system (./configure) , for which 
there is no substitute on windows other than cygwin and to lesser extent 
msys/mingw, this problem could be obviated by the provision of a 
standard win32 conf (forgetting about win64 for the moment) - package 
writters note!


 Date: Sat, 5 Dec 2009 20:58:14 +
 Subject: Re: [Haskell-cafe] Low Level Audio - Writing bytes to the sound card?
 From: stephen.tet...@gmail.com
 To: Haskell-Cafe@haskell.org
 CC: 
 
 Hi Andrew
 
 
 
 2009/12/5 Andrew Coppin andrewcop...@btinternet.com:
 
  I don't think it should be necessary to install a Unix emulator just so that
  I can write Windows programs. Maybe others disagree.
 
 
 ...
 
 
  I'm by no means an expert here, but isn't it usual for C libraries on
  Windows to be supplied as a compiled DLL and a header file for using it? I
  don't quite understand why you need a C compiler.
 
 The thing is, all the bindings on Hackage (or at least something most
 likely above 95%) are to Unix C libraries so you need a C compiler
 and a Unix emulator to use them. I do have have some sympathy with
 your point though - it is possible to get things to compile once you
 have Cygwin, but deployment on any other machine Windows thereafter is
 'challenging' to say the least.
 
 
 
 
  Apparently there is some talk of removing OpenGL from the Haskell Platform.
  And if this happens, it'll be one more thing I can't use on Windows. :-(
 
 
 I didn't realise until I looked today that OpenGL was in the Haskell
 Platform. If the proposal to remove it is from Sven Panne then fair
 enough, otherwise it would be a bit disappointing - it always just
 worked when it was part of GHCs extralibs...
 
 Best wishes
 
 Stephen
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
  
_
If It Exists, You'll Find it on SEEK Australia's #1 job site
http://clk.atdmt.com/NMN/go/157639755/direct/01/___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] New Hackage category: Error Handling

2009-12-05 Thread Henning Thielemann


On Sat, 5 Dec 2009, Michael Snoyman wrote:


On Sat, Dec 5, 2009 at 7:41 PM, Ross Paterson r...@soi.city.ac.uk wrote:
  On Sat, Dec 05, 2009 at 05:52:11PM +0200, Michael Snoyman wrote:
   For the record, I find this pedanticism misplaced, ...

  I think you'll find that's pedantry.


Hoped someone would comment exactly that ;).


:-)

Nonetheless: Although there might be cases, where it is not immediately 
clear what is error and what is exception (not to mention, that 
different people prefer to use the words for the corresponding concepts in 
a different way, if they would do so consistently, it would be ok), in 
most cases it is clear. Have you ever tried to handle an array index out 
of range situation at run-time? I think, it cannot be sensibly handled by 
the program automatically. Thus there is no other way than terminating the 
program. Thus I'd call this situation an error not an exception. Of 
course, people like to throw in here a web server as counterexample. So to 
speak: With respect to exceptions web servers are an exception.


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


Re: [Haskell-cafe] New Hackage category: Error Handling

2009-12-05 Thread Michael Snoyman
On Sun, Dec 6, 2009 at 12:17 AM, Henning Thielemann 
lemm...@henning-thielemann.de wrote:


 On Sat, 5 Dec 2009, Michael Snoyman wrote:

  On Sat, Dec 5, 2009 at 7:41 PM, Ross Paterson r...@soi.city.ac.uk
 wrote:
  On Sat, Dec 05, 2009 at 05:52:11PM +0200, Michael Snoyman wrote:
   For the record, I find this pedanticism misplaced, ...

  I think you'll find that's pedantry.


 Hoped someone would comment exactly that ;).


 :-)

 Nonetheless: Although there might be cases, where it is not immediately
 clear what is error and what is exception (not to mention, that
 different people prefer to use the words for the corresponding concepts in a
 different way, if they would do so consistently, it would be ok), in most
 cases it is clear. Have you ever tried to handle an array index out of
 range situation at run-time? I think, it cannot be sensibly handled by the
 program automatically. Thus there is no other way than terminating the
 program. Thus I'd call this situation an error not an exception. Of
 course, people like to throw in here a web server as counterexample. So to
 speak: With respect to exceptions web servers are an exception.

 I think there are plenty of examples like web servers. A text editor with
plugins? I don't want to lose three hours worth of work just because some
plugin wasn't written correctly. For many classes of programs, the
distinction between error and exception is not only blurred, it's fully
irrelevant. Harping on people every time they use error in the wrong sense
seems unhelpful.

Hope my commenting on this subject doesn't become my own form of *pedantry*.

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


Re: [Haskell-cafe] New Hackage category: Error Handling

2009-12-05 Thread Henning Thielemann


On Sun, 6 Dec 2009, Michael Snoyman wrote:


I think there are plenty of examples like web servers. A text editor with 
plugins? I
don't want to lose three hours worth of work just because some plugin wasn't 
written
correctly. For many classes of programs, the distinction between error and 
exception is
not only blurred, it's fully irrelevant. Harping on people every time they use 
error in
the wrong sense seems unhelpful.

Hope my commenting on this subject doesn't become my own form of *pedantry*.


In an earlier thread I have explained that one can consider a software 
architecture as divided into levels. What is an error in one level (text 
editor plugin, web server thread, operating system process) is an 
exception in the next higher level (text editor, web server, shell 
respectively). This doesn't reduce the importance to distinguish between 
errors and exceptions within one level. All approaches so far that I have 
seen in Haskell just mix exceptions and errors in an arbitrary way.

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


Re: [Haskell-cafe] New Hackage category: Error Handling

2009-12-05 Thread Michael Snoyman
On Sun, Dec 6, 2009 at 12:55 AM, Henning Thielemann 
lemm...@henning-thielemann.de wrote:


 On Sun, 6 Dec 2009, Michael Snoyman wrote:

  I think there are plenty of examples like web servers. A text editor with
 plugins? I
 don't want to lose three hours worth of work just because some plugin
 wasn't written
 correctly. For many classes of programs, the distinction between error and
 exception is
 not only blurred, it's fully irrelevant. Harping on people every time they
 use error in
 the wrong sense seems unhelpful.

 Hope my commenting on this subject doesn't become my own form of
 *pedantry*.


 In an earlier thread I have explained that one can consider a software
 architecture as divided into levels. What is an error in one level (text
 editor plugin, web server thread, operating system process) is an exception
 in the next higher level (text editor, web server, shell respectively). This
 doesn't reduce the importance to distinguish between errors and exceptions
 within one level. All approaches so far that I have seen in Haskell just mix
 exceptions and errors in an arbitrary way.


I think we can all appreciate why it would be a bad thing is we treat
exceptions as errors. For example, I don't want my program to crash on a
file not found.

On the other hand, what's so bad about treating errors as exceptions? If
instead of the program crashing on an array-out-of-bound or pattern-match it
throws an exception which can be caught, so what?

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


Re: [Haskell-cafe] Low Level Audio - Writing bytes to the sound card?

2009-12-05 Thread M Xyz

Stephen, 
I had no problem compiling the portaudio binaries on Windows. It came with a 
msvc project that worked. The problem I'm getting currently is that when I 
cabal install portaudio etc etc I get a c2hs.exe does not exist error when 
c2hs.exe clearly exists and is in my system path. Just like this post from 
months ago: http://www.mail-archive.com/haskell-...@lurk.org/msg00101.html

--- On Sat, 12/5/09, Stephen Tetley stephen.tet...@gmail.com wrote:

From: Stephen Tetley stephen.tet...@gmail.com
Subject: Re: [Haskell-cafe] Low Level Audio - Writing bytes to the sound card?
To: haskell-cafe@haskell.org
Date: Saturday, December 5, 2009, 5:00 PM

Compiling the C PortAudio library for either Cygwin or MinGW will be
challenging at the moment.

The current release doesn't compile as is, and although there should
be patch for the configure script as an attachment to this message it
seems to have gone amiss:

http://music.columbia.edu/pipermail/portaudio/2009-May/009116.html

I'd look for a different library to talk to the sound card...

Best wishes

Stephen


2009/12/4 M Xyz functionallyharmoni...@yahoo.com

 What is the most minimal (preferably platform independent) library available 
 for writing bytes to the sound card? I see 60 wonderful libraries on Hackage, 
 but I really just need the Haskell equivalent of an audio.write(byte[]) 
 method. What sound api are these 60 libraries using?

 I think the portaudio library is the only contender but when I try to install 
 it I get:

___
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] New Hackage category: Error Handling

2009-12-05 Thread Gregory Crosswhite

On Dec 5, 2009, at 3:00 PM, Michael Snoyman wrote:

 I think we can all appreciate why it would be a bad thing is we treat 
 exceptions as errors. For example, I don't want my program to crash on a file 
 not found.
 
 On the other hand, what's so bad about treating errors as exceptions? If 
 instead of the program crashing on an array-out-of-bound or pattern-match it 
 throws an exception which can be caught, so what?

As I understand it, an error is a problem which aborts a computation and an 
exception is a problem that simply needs to be dealt with before the 
computation can continue.

You are correct that there should be as few irrecoverable errors as possible in 
an application.  In particular, if we think of an application as being a whole 
bunch of sub-computation tied together into a larger computation, then in a 
sense what we want is for no the failure of no sub-computation to cause the 
whole application-wide computation to fail.  This, however, does not mean that 
there will be no circumstances under which any sub-computation fails, such as 
in the case of discovering in the middle of leading a file that it is 
irrecoverably corrupt.  When these circumstances occur, one has an error and 
not an exception because there is no way to finish loading the file.  However, 
at a higher lever, the sub-computation of loading the file was not necessary 
for the application to keep running, and so an error in the sub-computation 
becomes merely an exception when propagated up to the application level.

Cheers,
Greg

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


Re: [Haskell-cafe] Low Level Audio - Writing bytes to the sound card?

2009-12-05 Thread Daniel Fischer
Am Sonntag 06 Dezember 2009 00:10:05 schrieb M Xyz:
 Stephen,
 I had no problem compiling the portaudio binaries on Windows. It came with
 a msvc project that worked. The problem I'm getting currently is that when
 I cabal install portaudio etc etc I get a c2hs.exe does not exist error
 when c2hs.exe clearly exists and is in my system path. Just like this post
 from months ago:
 http://www.mail-archive.com/haskell-...@lurk.org/msg00101.html

Try

cabal install --with-c2hs=C:\path\to\c2hs.exe portaudio

maybe that'll work. If not, run cabal --verbose=3 install portaudio,
perhaps that gives more information about what went wrong.


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


Re: [Haskell-cafe] Low Level Audio - Writing bytes to the sound card?

2009-12-05 Thread M Xyz


--- On Sat, 12/5/09, Daniel Fischer daniel.is.fisc...@web.de wrote:

Try

cabal install --with-c2hs=C:\path\to\c2hs.exe portaudio

maybe that'll work. If not, run cabal --verbose=3 install portaudio,
perhaps that gives more information about what went wrong.

Daniel, Thank you for your thoughtful reply. I didn't know about those flags. 
The log is fairly long, and as I'm new to Haskell and Cabal it is mostly 
meaningless to me. I see very many incidences of searching for ___ in path. 
Cannot find ___ on the path so maybe this is all as simple as me not setting 
my environment correctly. 

Log:

cabal install portaudio --verbose=3 --with-c2hs=C:\Program 
Files\Haskell\bin\c2hs.exe 
--extra-include-dirs=C:\A\install\programming\portaudio\portaudio\include 
--extra-lib-dirs=C:\A\install\programming\portaudio\portaudio\build\msvc\Win32\Release
 log.txt

searching for ghc in path.
found ghc at C:\Program Files\Haskell Platform\2009.2.0.2\bin\ghc.exe
(C:\\Program Files\\Haskell 
Platform\\2009.2.0.2\\bin\\ghc.exe,[--numeric-version])
C:\Program Files\Haskell Platform\2009.2.0.2\bin\ghc.exe is version 6.10.4
looking for package tool: ghc-pkg near compiler in C:\Program Files\Haskell
Platform\2009.2.0.2\bin
found package tool in C:\Program Files\Haskell
Platform\2009.2.0.2\bin\ghc-pkg.exe
(C:\\Program Files\\Haskell 
Platform\\2009.2.0.2\\bin\\ghc-pkg.exe,[--version])
C:\Program Files\Haskell Platform\2009.2.0.2\bin\ghc-pkg.exe is version 6.10.4
(C:\\Program Files\\Haskell 
Platform\\2009.2.0.2\\bin\\ghc.exe,[--supported-languages])
Reading installed packages...
(C:\\Program Files\\Haskell 
Platform\\2009.2.0.2\\bin\\ghc-pkg.exe,[dump,--global])
Reading available packages...
Resolving dependencies...
selecting portaudio-0.0.1 (hackage) and discarding mtl-1.0
selecting mtl-1.1.0.2 (installed or hackage) and discarding mtl-1.1.0.0 and
1.1.0.1
selecting haskell98-1.0.1.0 (installed or hackage) and discarding
haskell98-1.0
selecting random-1.0.0.1 (installed or hackage) and discarding random-1.0.0.0
selecting process-1.0.1.1 (installed or hackage) and discarding filepath-1.0
and process-1.0.0.0
selecting directory-1.0.0.3 (installed or hackage) and discarding
directory-1.0.0.0
selecting old-time-1.0.0.2 (installed or hackage) and discarding
old-time-1.0.0.0
selecting old-locale-1.0.0.1 (installed or hackage) and discarding
old-locale-1.0.0.0
selecting filepath-1.1.0.2 (installed or hackage) and discarding
filepath-1.1.0.0 and 1.1.0.1
selecting Win32-2.2.0.0 (installed or hackage) and discarding Win32-2.1 and
2.1.0.0
selecting bytestring-0.9.1.4 (installed or hackage) and discarding
bytestring-0.9, 0.9.0.1, 0.9.0.2, 0.9.0.3, 0.9.0.4, 0.9.1.0, 0.9.1.1, 0.9.1.2,
0.9.1.3 and 0.9.1.5
selecting ghc-prim-0.1.0.0 (installed)
selecting rts-1.0 (installed)
selecting array-0.2.0.0 (installed or hackage) and discarding array-0.1.0.0
selecting base-3.0.3.1 (installed) and 4.1.0.0 (installed) and discarding
syb-0.1.0.0 and 0.1.0.1
selecting integer-0.1.0.1 (installed)
selecting syb-0.1.0.1 (installed)
In order, the following would be installed:
portaudio-0.0.1 (new package)
portaudio-0.0.1 has already been downloaded.
Extracting C:\Documents and Settings\M\Application
Data\cabal\packages\hackage.haskell.org\portaudio\0.0.1\portaudio-0.0.1.tar.gz
to C:\DOCUME~1\M\LOCALS~1\Temp\portaudio-0.0.13824...
Using internal setup method with build-type Simple and args:
[configure,--verbose=3,--ghc,--global,--extra-include-dirs=C:\\A\\install\\programming\\portaudio\\portaudio\\include,--extra-lib-dirs=C:\\A\\install\\programming\\portaudio\\portaudio\\build\\msvc\\Win32\\Release,--constraint=base
==3.0.3.1,--constraint=haskell98 ==1.0.1.0,--constraint=mtl
==1.1.0.2,--with-c2hs=C:\\Program Files\\Haskell\\bin\\c2hs.exe]
Configuring portaudio-0.0.1...
Creating dist (and its parents)
searching for ghc in path.
found ghc at C:\Program Files\Haskell Platform\2009.2.0.2\bin\ghc.exe
(C:\\Program Files\\Haskell 
Platform\\2009.2.0.2\\bin\\ghc.exe,[--numeric-version])
C:\Program Files\Haskell Platform\2009.2.0.2\bin\ghc.exe is version 6.10.4
looking for package tool: ghc-pkg near compiler in C:\Program Files\Haskell
Platform\2009.2.0.2\bin
found package tool in C:\Program Files\Haskell
Platform\2009.2.0.2\bin\ghc-pkg.exe
(C:\\Program Files\\Haskell 
Platform\\2009.2.0.2\\bin\\ghc-pkg.exe,[--version])
C:\Program Files\Haskell Platform\2009.2.0.2\bin\ghc-pkg.exe is version 6.10.4
(C:\\Program Files\\Haskell 
Platform\\2009.2.0.2\\bin\\ghc.exe,[--supported-languages])
Reading installed packages...
(C:\\Program Files\\Haskell 
Platform\\2009.2.0.2\\bin\\ghc-pkg.exe,[dump,--global])
Dependency base 3  ==3.0.3.1: using base-3.0.3.1
Dependency haskell98 -any  ==1.0.1.0: using haskell98-1.0.1.0
Dependency mtl =1.1.0.0  ==1.1.0.2: using mtl-1.1.0.2
searching for alex in path.
found alex at C:\Program Files\Haskell
Platform\2009.2.0.2\extralibs\bin\alex.exe
(C:\\Program Files\\Haskell 
Platform\\2009.2.0.2\\extralibs\\bin\\alex.exe,[--version])
C:\Program 

Re: [Haskell-cafe] Low Level Audio - Writing bytes to the sound card?

2009-12-05 Thread Daniel Fischer
Am Sonntag 06 Dezember 2009 00:47:38 schrieb M Xyz:
 Daniel, Thank you for your thoughtful reply. I didn't know about those
 flags. The log is fairly long, and as I'm new to Haskell and Cabal it is
 mostly meaningless to me. I see very many incidences of searching for ___
 in path. Cannot find ___ on the path so maybe this is all as simple as me
 not setting my environment correctly.

If you have cpphs, hugs, jhc, greencard etc., it is probably something about 
your 
environment. If you don't have them, it's clear that they aren't found.

On the other hand, that doesn't explain

Using c2hs version 0.16.0 given by user at: C:\Program
Files\Haskell\bin\c2hs.exe

-- so it finds c2hs, and can apparently run c2hs --version

(C:\\Program 
Files\\Haskell\\bin\\c2hs.exe,[--include=dist\\build,--cppopts=-
D__GLASGOW_HASKELL__=610,--cppopts=-IC:
\\A\\install\\programming\\portaudio\\portaudio\\include,--output-dir=dist\\build,--
output=Sound\\PortAudio\\Base.hs,.\\Sound\\PortAudio\\Base.chs])
c2hs.exe: does not exist
C:\Program Files\Haskell\bin\c2hs.exe returned ExitFailure 1

-- bang

To ascertain whether c2hs works at all, can you try to run it manually?

(cd to an appropriate directory,

cabal unpack portaudio

cd portaudio (or whatever, so that Base.chs is found via 
.\Sound\PortAudio\Base.chs

md dist\build

c2hs.exe  --include=dist\build --cppopts=-D__GLASGOW_HASKELL__=610 
--cppopts=-IC:
\A\install\programming\portaudio\portaudio\include --output-dir=dist\build --
output=Sound\PortAudio\Base.hs .\Sound\PortAudio\Base.chs
)
If that works, the problem is somewhere in cabal, otherwise in c2hs, either 
way, we'll 
know more.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Low Level Audio - Writing bytes to the sound card?

2009-12-05 Thread Daniel Fischer
Am Sonntag 06 Dezember 2009 01:49:49 schrieb M Xyz:

I just had another idea.

da...@linux-mkk1:~ c2hs -o memyself.hs memyself.chs
c2hs: does not exist

it's not that c2hs isn't found or something, c2hs doesn't find Base.chs!

Try installing from the unpacked sources (cd portaudio; cabal install) or the 
old-
fashioned way:

cd portaudio-0.0.1

ghc --make Setup

./Setup configure --help
(choose your options, prefix, profiling, ...)

./Setup configure $OPTIONS
./Setup build

if all's well,

./Setup haddock
./Setup install

(dies for me with
dist/build/Sound/PortAudio/Base.chs.h:1:23: error: portaudio.h: Datei oder 
Verzeichnisnicht gefunden
c2hs: Error during preprocessing custom header file
cabal: Error: some packages failed to install:
portaudio-0.0.1 failed during the building phase. The exception was:
exit: ExitFailure 1
because I don't have portaudio installed)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] New Hackage category: Error Handling

2009-12-05 Thread Henning Thielemann


On Sat, 5 Dec 2009, Henning Thielemann wrote:


On Sun, 6 Dec 2009, Michael Snoyman wrote:

I think there are plenty of examples like web servers. A text editor with 
plugins? I
don't want to lose three hours worth of work just because some plugin 
wasn't written
correctly. For many classes of programs, the distinction between error and 
exception is
not only blurred, it's fully irrelevant. Harping on people every time they 
use error in

the wrong sense seems unhelpful.

Hope my commenting on this subject doesn't become my own form of 
*pedantry*.


In an earlier thread I have explained that one can consider a software 
architecture as divided into levels. What is an error in one level (text 
editor plugin, web server thread, operating system process) is an exception 
in the next higher level (text editor, web server, shell respectively). This 
doesn't reduce the importance to distinguish between errors and exceptions 
within one level. All approaches so far that I have seen in Haskell just mix 
exceptions and errors in an arbitrary way.



I have just written more details on this topic:
   http://www.haskell.org/haskellwiki/Error_vs._Exception
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Low Level Audio - Writing bytes to the sound card?

2009-12-05 Thread M Xyz


--- On Sat, 12/5/09, Daniel Fischer daniel.is.fisc...@web.de wrote:


cd portaudio-0.0.1

ghc --make Setup

../Setup configure --help
(choose your options, prefix, profiling, ...)

../Setup configure $OPTIONS
../Setup build


Everything went well until Setup build which yielded our friend c2hs.exe 
does not exist.


C:\A\install\programming\portaudio\haskell\portaudio-0.0.1ghc --make Setup
[1 of 1] Compiling Main ( Setup.hs, Setup.o )
Linking Setup.exe ...

C:\A\install\programming\portaudio\haskell\portaudio-0.0.1Setup configure --hel
p
Usage: Setup configure [FLAGS]

Flags for configure: ...(edited out)

C:\A\install\programming\portaudio\haskell\portaudio-0.0.1Setup configure --ext
ra-include-dirs=C:\A\install\programming\portaudio\portaudio\include --extra-l
ib-dirs=C:\A\install\programming\portaudio\portaudio\build\msvc\Win32\Release
Configuring portaudio-0.0.1...

C:\A\install\programming\portaudio\haskell\portaudio-0.0.1Setup build
Preprocessing library portaudio-0.0.1...
c2hs.exe: does not exist






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


RE: [Haskell-cafe] Low Level Audio - Writing bytes to the sound card?

2009-12-05 Thread M Xyz
I am going to give this a try. Thanks.
Where can I get the pexports and dlltool utilities?

Google yields:
http://www.emmestech.com/software/pexports-0.43/download_pexports.html
http://sourceware.org/binutils/

Are those correct?

--- On Sat, 12/5/09, john lask jvl...@hotmail.com wrote:

From: john lask jvl...@hotmail.com
Subject: RE: [Haskell-cafe] Low Level Audio - Writing bytes to the sound card?
To: daniel.is.fisc...@web.de, functionallyharmoni...@yahoo.com
Cc: haskell-cafe@haskell.org
Date: Saturday, December 5, 2009, 9:03 PM






I don't know whether this will help you but I just downloaded an built
the haskell portaudio package ... (I had a windows msvc build of
portaudio dll already) the process I used ... ghc 6.10.4, portaudio-19

make an import lib for ghc from dll:
pexports libpa19.dll  libpa19.def
dlltool --input-def libpa19.def --output-lib libpa19.a

edit the .cabal file or use command line flags

  extra-Libraries: pa19
  extra-lib-dirs: c:\portaudio19\lib
  include-dirs:   c:\portaudio19\include

 runghc setup configure

make sure you have cpp i.e. the c-preprocessor on your exe path,
otherwise you will get
'cpp' is not recognized as an internal or external command,
operable program or batch file.
c2hs.exe: Error during preprocessing custom header file

runghc setup build

builds ok ...??


 From: daniel.is.fisc...@web.de
 To: functionallyharmoni...@yahoo.com
 Subject: Re: [Haskell-cafe] Low Level Audio - Writing bytes to the sound card?
 Date: Sun, 6 Dec 2009 02:34:17 +0100
 CC: haskell-cafe@haskell.org
 
 Am Sonntag 06 Dezember 2009 01:49:49 schrieb M Xyz:
 
 I just had another idea.
 
 da...@linux-mkk1:~ c2hs -o memyself.hs memyself.chs
 c2hs: does not exist
 
 it's not that c2hs isn't found or something, c2hs doesn't find Base.chs!
 
 Try installing from the unpacked sources (cd portaudio; cabal install) or the 
 old-
 fashioned way:
 
 cd portaudio-0.0.1
 
 ghc --make Setup
 
 ./Setup configure --help
 (choose your options, prefix, profiling, ...)
 
 ./Setup configure $OPTIONS
 ./Setup build
 
 if all's well,
 
 ./Setup haddock
 ./Setup install
 
 (dies for me with
 dist/build/Sound/PortAudio/Base.chs.h:1:23: error: portaudio.h: Datei oder 
 Verzeichnisnicht gefunden
 c2hs: Error during preprocessing custom header file
 cabal: Error: some packages failed to install:
 portaudio-0.0.1 failed during the building phase. The exception was:
 exit: ExitFailure 1
 because I don't have portaudio installed)
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
  
Australia's #1 job site If It Exists, You'll Find it on SEEK 



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


[Haskell-cafe] PortAudio library successfully built on Windows

2009-12-05 Thread M Xyz

John Lask, 
The steps you enumerated below successfully built portaudio for me! Thank you!

I wonder though, you said to rename the dll to libpa19.dll from 
portaudio_x86.dll
and to change the .cabal entry from extra-Libraries: portaudio to 
extra-Libraries: pa19.
Since my .dll name and .cabal file entry were mismatched, was that what could 
have been wrong all along? Was the creation of a .a file necessary?
I would delete the .a file and retry with libportaudio.dll but I won't push my 
luck.

Now if I could just get Gtk2hs working now, I could be happy *and* productive. 
:)

--- On Sat, 12/5/09, john lask jvl...@hotmail.com wrote:

From: john lask jvl...@hotmail.com
Subject: RE: [Haskell-cafe] Low Level Audio - Writing bytes to the sound card?
To: daniel.is.fisc...@web.de, functionallyharmoni...@yahoo.com
Cc: haskell-cafe@haskell.org
Date: Saturday, December 5, 2009, 9:03 PM






I don't know whether this will help you but I just downloaded an built
the haskell portaudio package ... (I had a windows msvc build of
portaudio dll already) the process I used ... ghc 6.10.4, portaudio-19

make an import lib for ghc from dll:
pexports libpa19.dll  libpa19.def
dlltool --input-def libpa19.def --output-lib libpa19.a

edit the .cabal file or use command line flags

  extra-Libraries: pa19
  extra-lib-dirs: c:\portaudio19\lib
  include-dirs:   c:\portaudio19\include

 runghc setup configure

make sure you have cpp i.e. the c-preprocessor on your exe path,
otherwise you will get
'cpp' is not recognized as an internal or external command,
operable program or batch file.
c2hs.exe: Error during preprocessing custom header file

runghc setup build

builds ok ...??


 From: daniel.is.fisc...@web.de
 To: functionallyharmoni...@yahoo.com
 Subject: Re: [Haskell-cafe] Low Level Audio - Writing bytes to the sound card?
 Date: Sun, 6 Dec 2009 02:34:17 +0100
 CC: haskell-cafe@haskell.org
 
 Am Sonntag 06 Dezember 2009 01:49:49 schrieb M Xyz:
 
 I just had another idea.
 
 da...@linux-mkk1:~ c2hs -o memyself.hs memyself.chs
 c2hs: does not exist
 
 it's not that c2hs isn't found or something, c2hs doesn't find Base.chs!
 
 Try installing from the unpacked sources (cd portaudio; cabal install) or the 
 old-
 fashioned way:
 
 cd portaudio-0.0.1
 
 ghc --make Setup
 
 ./Setup configure --help
 (choose your options, prefix, profiling, ...)
 
 ./Setup configure $OPTIONS
 ./Setup build
 
 if all's well,
 
 ./Setup haddock
 ./Setup install
 
 (dies for me with
 dist/build/Sound/PortAudio/Base.chs.h:1:23: error: portaudio.h: Datei oder 
 Verzeichnisnicht gefunden
 c2hs: Error during preprocessing custom header file
 cabal: Error: some packages failed to install:
 portaudio-0.0.1 failed during the building phase. The exception was:
 exit: ExitFailure 1
 because I don't have portaudio installed)
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
  
Australia's #1 job site If It Exists, You'll Find it on SEEK 



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


[Haskell-cafe] When are undecidables ok?

2009-12-05 Thread Michael Snoyman
I know this is basically a rewording of a previous e-mail, but I realized
this is the question I *really* wanted to ask.

We have this language extension UndecidableInstances (not to mention
OverlappingInstances), which seem to divide the Haskell camp into two
factions:

* Hey, GHC said to turn on this flag. Ok!
* Undecidables are the devil!

I get the feeling the truth lies in the middle. As I understand it (please
correct me if I am wrong), the problem with undecidables is that they can
create non-terminating instances. However, for certain cases the programmer
should be able to prove to him/herself that the instances will terminate. My
question is: how can you make such a proof?

I've had to cases in particular that made me want undecidables. Both of
them, IMO, could be solved by creating new extensions to GHC which would not
require undecidables. Nonetheless, for now we only have undecidables at our
disposal. The examples are:

* Context synonyms (eg, MonadFailure = Monad + Failure).
* Subclass function defaulting

For an example of the second, a nifty definition of Monad would be:

class Applicative m = Monad m where
  = ...
  return ...
  pure = return
  (*) = ap
  fmap = liftM

Of course, neither of these is possible in Haskell, so we can use
undecidables. How can a programmer prove that a set of instances is, in
fact, safe? And if they make a mistake and right a bad set of
undecidable/overlapping instances, what's the worst case scenario? Is it a
compile-time or run-time error*?

Michael

* Yes, I mean error.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] When are undecidables ok?

2009-12-05 Thread Luke Palmer
On Sat, Dec 5, 2009 at 10:04 PM, Michael Snoyman mich...@snoyman.com wrote:
 I know this is basically a rewording of a previous e-mail, but I realized
 this is the question I *really* wanted to ask.

 We have this language extension UndecidableInstances (not to mention
 OverlappingInstances), which seem to divide the Haskell camp into two
 factions:

 * Hey, GHC said to turn on this flag. Ok!
 * Undecidables are the devil!

 I get the feeling the truth lies in the middle. As I understand it (please
 correct me if I am wrong), the problem with undecidables is that they can
 create non-terminating instances. However, for certain cases the programmer
 should be able to prove to him/herself that the instances will terminate. My
 question is: how can you make such a proof?

Well, the reasoning for the devil camp (which I admit to being
firmly in[1]) is that such proofs must rely on the algorithm the
compiler uses to resolve instances.  You might be able to prove it,
but the proof is necessarily only valid for (possibly current versions
of) GHC.  The typeclass resolution algorithm is not in the report, and
there are several conceivable ways of of going about it.

So it is fine to use them if you are okay with making your code
unportable and future-brittle. I am typically against the mere
existence of code that that is future-brittle, because it encourages
compiler authors not to innovate  (and by that token, unportable too,
because it discourages compiler competition).

Luke

[1] http://lukepalmer.wordpress.com/2008/04/08/stop-using-undecidable-instances/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] When are undecidables ok?

2009-12-05 Thread Michael Snoyman
On Sun, Dec 6, 2009 at 7:36 AM, Luke Palmer lrpal...@gmail.com wrote:

 On Sat, Dec 5, 2009 at 10:04 PM, Michael Snoyman mich...@snoyman.com
 wrote:
  I know this is basically a rewording of a previous e-mail, but I realized
  this is the question I *really* wanted to ask.
 
  We have this language extension UndecidableInstances (not to mention
  OverlappingInstances), which seem to divide the Haskell camp into two
  factions:
 
  * Hey, GHC said to turn on this flag. Ok!
  * Undecidables are the devil!
 
  I get the feeling the truth lies in the middle. As I understand it
 (please
  correct me if I am wrong), the problem with undecidables is that they can
  create non-terminating instances. However, for certain cases the
 programmer
  should be able to prove to him/herself that the instances will terminate.
 My
  question is: how can you make such a proof?

 Well, the reasoning for the devil camp (which I admit to being
 firmly in[1]) is that such proofs must rely on the algorithm the
 compiler uses to resolve instances.  You might be able to prove it,
 but the proof is necessarily only valid for (possibly current versions
 of) GHC.  The typeclass resolution algorithm is not in the report, and
 there are several conceivable ways of of going about it.

 So it is fine to use them if you are okay with making your code
 unportable and future-brittle. I am typically against the mere
 existence of code that that is future-brittle, because it encourages
 compiler authors not to innovate  (and by that token, unportable too,
 because it discourages compiler competition).

 Luke

 [1]
 http://lukepalmer.wordpress.com/2008/04/08/stop-using-undecidable-instances/


So in that case, perhaps the compiler authors can give us some ideas as to
when it's safe to use undecidables? Seems like we should go straight to the
horse's mouth.

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


Re: [Haskell-cafe] ANNOUNCE: error-message

2009-12-05 Thread Ariel J. Birnbaum
 In particular, the motivation for this package was that I have written
 a build system, and I wanted to collect as many errors in the build as
 possible and show them all to the user at once.

YMMV, but at least for me a deluge of errors is less helpful than a
short list I can fix quickly, then try again. Often by fixing one error
from the list a sizeable portion of the rest just vanish (I forget the
English term for that kind of error).

(In before you can use sth like quickfix to go through the first few
errors and compile again whenever you feel like it.)

-- 
Ariel J. Birnbaum

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


Re: [Haskell-cafe] What is the rank of a polymorphic type?

2009-12-05 Thread Eugene Kirpichov
2009/12/6 Stefan Holdermans ste...@cs.uu.nl:
 Eugene,

 1) Does there exist an authoritative source saying the same? Not that
 I'm doubting, just supposing that the source would have other
 interesting information, too :)

 You may want to have a look at the already mentioned JFP-article by Peyton
 Jones et al. and perhaps the work of Kfoury and Wells.

 2) Is it true that rank (forall a . a, forall a . a) == 0 ?

 No, for pairs one takes the maximum of the constituent types. So, here you'd
 get rank 1.

 Note that this is an impredicative type, which is yet another extension of
 the standard Hindley-Milner typing discipline.

OK, thanks.
However, isn't the type (forall a . a) - String impredicative because
it instantiates a type variable of the type constructor (-) p q with
p = forall a . a?


 Cheers,

  Stefan






-- 
Eugene Kirpichov
Web IR developer, market.yandex.ru
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: universal binary version of Haskell Platform?

2009-12-05 Thread Benjamin L . Russell
On Thu, 03 Dec 2009 10:52:35 +, Duncan Coutts
duncan.cou...@googlemail.com wrote:

[...]

There no binary platform installer for OSX PPC. You'll have to grab
ghc-6.10.4 for PPC from the ghc download page and then install the
platform from the generic source tarball.

Ah, that's too bad.  That means that I won't be able to invoke GHC
outside of the Terminal application by default, and that even if I
create a Darwin shell script and alias to invoke it from Aqua, the
icon for that shell script will only be generic by default.  I'd
rather click on an application icon in the Dock.


If you'd like to help us next time to make a platform binary for PPC
then that'd be great. I don't think we have the setup to make universal
binaries but it should be possible to make a PPC build if we have a
volunteer.

Sure, barring job-related time constraints, I'd be happy to volunteer.
My Mac just went out of service because of a hardware problem with the
memory, so I'm order new replacement RAM this weekend.  As soon as
that arrives and I install it, the problem should be resolved.

What should I do?

-- Benjamin L. Russell

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


Re: [Haskell-cafe] What is the rank of a polymorphic type?

2009-12-05 Thread Dan Doel
On Sunday 06 December 2009 1:42:34 am Eugene Kirpichov wrote:
 OK, thanks.
 However, isn't the type (forall a . a) - String impredicative because
 it instantiates a type variable of the type constructor (-) p q with
 p = forall a . a?

There's probably no clear cut answer to this independent of how you think of 
(-). For instance, if we explain the Haskell type system by way of a pure 
type system, (-) is a special case of a pi type, which looks like:

  pi x : k. t

where any xs in t are bound by the pi. We then have:

  p - q  = pi _ : p. q
  forall a : k. b = pi a : k. b

pi types are given types by sets of rules, which look like triples. If (s,t,u) 
is a rule, then:

  G |- k : sG, a : k |- b : t
  ---
  G |- (pi a : k. b) : u

is the corresponding typing rule. Type systems like Haskell's are commonly 
thought of in terms of the lambda cube, which has constant sorts * and [], 
with * : []. The rule (*,*,*) gives you ordinary functions. (*,[],[]) gives 
you dependent types, so that's out.

([],*,*) is an impredicative rule for polymorphism. This says that, for 
instance:

  forall a. a - a = (pi a : *. pi _ : a. a) : *

because (pi _ : a. a) : * if a : *, by the (*,*,*) rule, and then we apply the 
impredicative rule for the universal quantification. One could also use the 
predicative rule ([],*,[]), which would result in forall a. a - a having type 
[].

However, Haskell also has arbitrarily higher-order types. This is given by the 
rule ([],[],[]), which allows expressions like:

   (* - *) - * = pi _ : (pi _ : *. *). *

This type system is called F_omega, while just the ([],*,?) rule is known as 
F_2.
 
However, the F_omega rule also allows for arbitrary rank polymorphism even 
with the predicative universal quantifier rule above (predicative F_2 allows a 
little, but it's very limited*). For instance, the higher rank type:

  forall a. (forall b. b) - a

checks thusly:

  (forall b. b)  : [] via ([],*,[])
  ((forall b. b) - a)   : [] via ([],*,[])
  (forall a. (forall b. b) - a) : [] via ([],[],[])

Data types, by contrast, have kinds like * - *, so using say,

  Maybe (forall a. a - a)

genuinely relies on the impredicative rule. GHC's type system isn't exactly 
set up in this way, but (-) is similarly special in that it somehow isn't 
quite just another type constructor with kind * - * - * (or even whatever 
special kinds GHC uses to support unboxed values and such).

Hope that wasn't too confusing. :)

-- Dan

* Predicative F_2 will essentially allow one universal quantifier somewhere in 
the type. This can be:

  forall a. a - a

or it can be:

  (((forall a. a) - T) - U) - V

for T, U and V of kind * (the only kind in F_2), which is a rank-4 type. It 
doesn't allow:

  forall a b. a - b

even, because the inner (forall b. a - b) : [], so adding the forall a 
requires the F_omega rule.

Predicative F_2 and F_w also blow up with quantification on the right of an 
arrow, because it looks like the rule for dependent types:

  T - (forall a. a)

  T : *, (forall a. a) : []

so the rule (*,[],[]) would be invoked.

GHC doesn't have this sort of hierarchy, and so doesn't have these sorts of 
weird cases, despite being predicative of a sort. Instead it distinguishes 
somehow between monotypes ([Float], String - Int, a - b) and polytypes 
(forall a. a, ...), although it doesn't really display the difference. 
Quantifiers are only supposed to range over kinds that classify monotypes (or 
monotype constructors), which keeps the predicativity (although, even this 
gets fudged some: If I have forall a. a - a, I can instantiate a to the 
polytype forall a. a - a with rank-n polymorphism, because it only seems to 
worry about the validity of the resulting type, and (-) is special; by 
contrast, the same cannot be said for forall a. Maybe a, because Maybe 
genuinely only accepts monotypes without -XImpredicativeTypes).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe