Re: [Haskell-cafe] Data Types a la Carte - automatic injections (help!)

2008-07-29 Thread Nicolas Frisby
I have accomplished this in two ways. Either drop the reflexive rule
and introduce a void sentinel type or use TypeEq (... you said
everything was fair game!) to explicitly specify the preference for
the reflexive case over the inductive case. An advantage of TypeEq is
that you can avoid overlapping (and also incoherent) instances and so
play nice with functional dependencies. A disadvantage is its
hyper-instability in terms of regressions via compiler development
(none yet, though).

There are better participants in the cafe for explaining the details
if you choose this path.

HTH

On Mon, Jul 28, 2008 at 11:03 PM, Brandon S. Allbery KF8NH
[EMAIL PROTECTED] wrote:

 On 2008 Jul 28, at 23:23, Kenn Knowles wrote:

 What confuses me is that IncoherentInstances is on, but it is still
 rejected by GHC 6.8.3 seemingly for being incoherent.  I haven't tried
 it with any other version.  Am I missing something?  Any suggestions
 or pointers?

 Er?  Looks to me like it wants the OverlappingInstances language extension.

 --
 brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
 system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
 electrical and computer engineering, carnegie mellon universityKF8NH


 ___
 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] carry state around ....

2008-07-29 Thread Ketil Malde
Galchin, Vasili [EMAIL PROTECTED] writes:

 ok guys .. what is this phantom type concept? Is it a type theory thing or
 just Haskell type concept?

Here's another example.  Say you want to use bytestrings with
different encodings.  You obviously don't want to concatenate a string
representing Latin characters with a string in Cyrillic.

One way to do this, is to define phantom types for the encodings, and
a bytestring type that takes additional type parameter

   data KOI8
   data ISO8859_1
 :

   data Bytestring enc = MkBS ...

Operations like concat work on same-typed bytestrings:

   concat :: Bytestring e - Bytestring e - Bytestring e

The parameter (enc) isn't used on the right hand side, so all
Bytestrings will have the same representation, but Bytestring KOI8 and
Bytestring ISO8859_1 will have different types, so although the
runtime won't know the difference, trying to 'concat' them will give
you a type error at compile time. 

-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


Re: [Haskell-cafe] Using fundeps to resolve polymorphic types to concrete types

2008-07-29 Thread wren ng thornton

Bryan Donlan wrote:

Hi,

Is there any theoretical reason that functional dependencies can't be used
to resolve a polymorphic type to a concrete type? For example:


-- compile with -fglasgow-exts

class DeriveType a b | a - b

data A = A
data B = B

instance DeriveType A B




simpleNarrow :: DeriveType A b = b - B
simpleNarrow = id


I'm not entirely sure what your use case is, but the reason this fails 
is that you gave a type signature which is more general than what the 
body can possibly be.


Even with fundeps, the signature is claiming that the function works for 
*any* b provided it happens to be the right one for DeriveType A. That 
is, the signature is somewhat agnostic to whatever actual 
implementations happen to exist [though it must be consistent with 
them]. A true (DeriveType A b = b - B) function would work even if we 
edited the instance declaration to be for DeriveType A C instead.


And naturally 'id' is (a - a) so giving a return type of B requires 
that the input type must also be B. It compiles just fine with 
(DeriveType A b = b - b) after all, which resolves directly to (B - 
B) [which I think is what you want?]. Though again, if we changed the 
instance then it would resolve to (C - C) instead.




The motivation is this case:


data ComplexType a where
SomeConstructor :: DeriveType a b = a - b - ComplexType a

specialCaseFunc :: ComplexType A - B
specialCaseFunc (SomeConstructor _ b) = b


Again the issue is that while the instance declaration says that the 
result happens to be B now, that's not what the real type of the 
result is-- it's (DeriveType A b = b) where b is *exactly* the one from 
the SomeConstructor signature, and hence the signature (DeriveType A b 
= ComplexType A - b) doesn't work either since that's a different b.


Since b --whatever it happens to be-- is fixed by A it seems like the 
(DeriveType A b = ComplexType A - b) signature should work and 
consider it the same b. However, since the GADT is doing existential 
quantification, even though the b type is fixed we've lost that 
information and so we can't be certain that it *really* is the same b.


If you're familiar with existential quantification then the behavior 
makes sense, though I agree it isn't quite what would be expected at 
first. I'm not sure off hand whether it should really be called a bug 
however.




If you don't really need the existential in there, then this version 
works just fine:


  {-# OPTIONS_GHC -fglasgow-exts #-}
 
  class DeriveType a b | a - b
 
  data A = A
  data B = B
 
  instance DeriveType A B
 
  simpleNarrow :: DeriveType A b = b - b
  simpleNarrow = id
 
  data ComplexType a b where
  SomeConstructor :: DeriveType a b = a - b - ComplexType a b
 
  specialCaseFunc :: ComplexType A b - b
  specialCaseFunc (SomeConstructor _ b) = b


Essentially, if I have a data structure with two types used as fields, and
one uniquely determines the other, I'd like to use these instances to avoid
re-stating the implied one in the type equations, if possible.


If you do want the existential after all, you can keep it provided the 
context restriction [i.e. DeriveType] gives you a method to get it back. 
If all you're doing is type passing then an implementation like this 
works just fine:


  class DeriveType a b | a - b where
  someDestructor :: ComplexType a - b
 
  instance DeriveType A B where
  someDestructor _ = B
 
  data ComplexType a where
  SomeConstructor :: DeriveType a b = a - b - ComplexType a

[1 of 1] Compiling Main ( fundep.hs, interpreted )
Ok, modules loaded: Main.
*Main someDestructor (SomeConstructor undefined undefined :: 
ComplexType A)

B
*Main

But if you have actual values rather than just unit types, note that 
this won't work:


  instance DeriveType A B where
  someDestructor (SomeConstructor _ b) = b

The key to note here is that when we existentially quantify over b and 
loose the type information, any class dictionaries for b are packaged up 
with the value and can still be used to get views onto the value of b. 
We can only get *views* onto b but can't do anything which might recover 
information about the actual type of b, however [aka existential 
escapes]. So this may or may not be sufficient for your needs. The fact 
that existential quantification looses information which can never be 
recovered is one of the reasons why they can be difficult to deal with.


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


[Haskell-cafe] How can I get the mutable array out of an IOUArray for FFI use?

2008-07-29 Thread Ryan Ingram
I wrote some fast bit-twiddling functions in C because my Haskell
performance wasn't good enough.  Now I'm trying to recompile with
GHC6.8.3 and failing.   This code worked on GHC6.6.1.

I get the following error:

 ghc --make main.hs

Bitmap.hs:11:7:
Could not find module `Data.Array.IO.Internals':
  it is hidden (in package array-0.1.0.0)

I suppose I can declare a copy of the internal type and use
unsafeCoerce#, but that seems like a terrible idea if there is a
better way.  What's the right way to make this work?  Can I force that
module to be unhidden?  Should I file a GHC bug?

  -- ryan

{-# OPTIONS_GHC -fffi -fglasgow-exts #-}
{-# INCLUDE bitmap_operations.h #-}

module Bitmap (
clearBitmap,
) where
import Foreign.Ptr
import Data.Array.Base
import Data.Array.IO.Internals
import GHC.Exts
import Data.Word

foreign import ccall unsafe clear_bitmap :: MutableByteArray#
RealWorld - Word32 - Word32 - IO ()

{-# INLINE unsafeGetMutableArray# #-}
unsafeGetMutableArray# :: IOUArray Int Word32 - MutableByteArray# RealWorld
unsafeGetMutableArray# (IOUArray (STUArray _ _ array#)) = array#

clearBitmap :: IOUArray Int Word32 - Word32 - Word32 - IO ()
clearBitmap a1 color size
= clear_bitmap (unsafeGetMutableArray# a1) color size
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Using fundeps to resolve polymorphic types to concrete types

2008-07-29 Thread Ryan Ingram
This seems like an appropriate place to use type families.

{-# LANGUAGE TypeFamilies, GADTs #-}
module DeriveType where

type family DeriveType a

data A = A
data B = B

type instance DeriveType A = B

data ComplexType a where
SomeConstructor :: a - DeriveType a - ComplexType a

specialCaseFunc :: ComplexType A - B
specialCaseFunc (SomeConstructor _ b) = b


On Mon, Jul 28, 2008 at 6:32 PM, Bryan Donlan [EMAIL PROTECTED] wrote:
 Hi,

 Is there any theoretical reason that functional dependencies can't be used
 to resolve a polymorphic type to a concrete type? For example:

 -- compile with -fglasgow-exts

 class DeriveType a b | a - b

 data A = A
 data B = B

 instance DeriveType A B


 simpleNarrow :: DeriveType A b = b - B
 simpleNarrow = id

 Since 'b' is uniquely determined by the fundep in DeriveType, it seems that
 this ought to work; ie, since the only type equation satisfying DeriveType A b
 is B - B, it should reduce to that before trying to fit its type against its
 body.

 The motivation is this case:

 data ComplexType a where
 SomeConstructor :: DeriveType a b = a - b - ComplexType a

 specialCaseFunc :: ComplexType A - B
 specialCaseFunc (SomeConstructor _ b) = b

 Essentially, if I have a data structure with two types used as fields, and
 one uniquely determines the other, I'd like to use these instances to avoid
 re-stating the implied one in the type equations, if possible.

 Is there some theoretical reason for this not to work, or is it just a
 limitation of GHC's current implementation? (Note, I'm testing with GHC 6.8.2,
 so it's possible this might be fixed in trunk already...)

 Thanks,

 Bryan Donlan
 ___
 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] Using fundeps to resolve polymorphic types to concrete types

2008-07-29 Thread Pablo Nogueira
Wren ng thornton wrote:

 It compiles just fine with (DeriveType A b = b - b) after all, which 
 resolves directly to (B - B)

That's not the case:

simpleNarrow :: DeriveType A b = b - b
simpleNarrow = id

 Couldn't match expected type `b' (a rigid variable)
   against inferred type `B'
  `b' is bound by the type signature for `simpleNarrow' ...
When using functional dependencies to combine
  DeriveType A B, arising from the instance declaration ...
  DeriveType A b, arising from is bound by the type signature for
`simpleNarrow' ...

I think Bryan got the order in which type inference/checking works
wrong. The dependency is not resolved before calculating the type as
he suggested.

*Main someDestructor (SomeConstructor undefined undefined :: ComplexType A)
   B

Why not this:

*Main  someDestructor (SomeConstructor A B)
 B

 But if you have actual values rather than just unit types, note that this
 won't work:

   instance DeriveType A B where
   someDestructor (SomeConstructor _ b) = b

I couldn't understand the sentence actual values rather than unit
types. What do you have in mind?

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


Re: [Haskell-cafe] Cabal and Strings and CPP

2008-07-29 Thread Malcolm Wallace
Philip Weaver [EMAIL PROTECTED] wrote:

 I'm trying to use CPP-defined strings in a Haskell module, like this:
main :: IO ()
main = putStrLn FOO
 This of course will not work:
ghc -DFOO=hello world --make Main.hs -o test

Have you tried using ANSI cpp's stringification operator?

{-# LANGUAGE CPP #-}
#define STRING(bar) #bar
main :: IO ()
main = putStrLn FOO

  ghc -DFOO=STRING(hello world) --make Main.hs -o test

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


Re: [Haskell-cafe] Using fundeps to resolve polymorphic types to concrete types

2008-07-29 Thread Pablo Nogueira
 But if you have actual values rather than just unit types, note that this
 won't work:

   instance DeriveType A B where
   someDestructor (SomeConstructor _ b) = b

 I couldn't understand the sentence actual values rather than unit
 types. What do you have in mind?

I didn't pay attention to the |b| value returned. So what you meant
was that only a constant function will do, not a function that returns
the value |b|.
P.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Fw: patch applied (ghc): Remove the OpenGL family of libraries fromextralibs

2008-07-29 Thread Duncan Coutts

On Mon, 2008-07-28 at 11:11 +0100, Malcolm Wallace wrote:
  FYI: Haskell's OpenGL binding has just been dropped from GHC's
  extralibs, which means that it will no longer be kept in sync with GHC
  development, at least not by GHC HQ.
  
  GHC HQ has its hands full and -generally speaking - extralibs are to
  be replaced by H(L)P, the Haskell (Library) Platform:
 
 As someone who uses HOpenGL as a component for my own research, I must
 say that I don't entirely follow the logic of dropping it from
 extralibs.
 
 I mean, I fully appreciate that ghc-HQ wants to remove extralibs from
 its sphere of responsibility.  And I also very much support the new
 Haskell Platform idea.
 
 But I did also get the impression that the HP was going to start from
 extralibs and build outwards. I can't see how dropping existing working
 and tested libraries from a mini-platform, is any help at all to the new
 maintainers of HP. 

I think there's been a bit too much ho ha over this. For one thing it
was only a suggestion to reduce work and for another we've not even got
the infrastructure set up so we don't know how much work it's going to
be. If someone wants to do the work (of the maintainer) then I'm sure
it'll happen, and judging by the number of responses that would seem
likely.

 It is only likely to give grief to users who expect HOpenGL to be part
 of HP, and then later more grief to the HP maintainers when they try
 to re-integrate it, after allowing it to suffer a period of bit-rot.

I don't think that's right. The HP maintainers are not (and cannot be)
the maintainers of each individual package. That just does not scale. If
a package is suffering bit rot then it's the responsibility of the
package maintainer(s) to sort out.

Also, something not being in the platform does not at all imply bit rot.
Lack of a maintainer tends to imply bit rot. It's still on hackage and
has its existing users who would hopefully contribute fixes if the
maintainer was not to be found.

Duncan

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


[Haskell-cafe] Re: Fw: patch applied (ghc): Remove the OpenGL familyof libraries fromextralibs

2008-07-29 Thread Simon Marlow

scodil wrote:

I'll chime in with a me too. I use Haskell and OpenGL for prototyping
scientific visualization software, 3D models and such. Not that I think it
couldn't be used for production software, its just that I just don't produce
much :)

The library really is fantastic. I don't think it gets enough fanfare. The
only
other GL API that rivals it is the C API itself. Most other languages
provide a
shoddy  incomplete interface to that, instead of an idiomatic
interpretation of the OpenGL spec. I can't think of a single language, not
even
python, whose OpenGL bindings come close. 


I get the impression (from a inadequate sample of irc logs and list chatter)
that many Haskellers see HOpenGL as 'just an OpenGL binding', like it was
readline or curses or something. It just plugs a hole in the Haskell/OS
interface, and its worth is merely a function of the size and importance of
that hole. Instead I advocate, as Claus and others have done, that it's a
shining example of how to write a Haskell interface to a well known API.  


If you never used C OpenGL and learned GL using Haskell, you might not
notice
anything special about it. But that's kind of my point, its just so damn
good
it blends into the background. The only people who notice this, I think, are
experienced C OpenGL programmers, and the overlap between them and the
Haskell
community in general is small I bet. Their voice in that community smaller
still.

This probably has little bearing on the issue of whether to keep or drop
HOpenGL in the near future, but I think that if 'the community' (or whoever
has
a say in these things) like the style of HOpenGL, and want to encourage
bindings to be written in that style, they should place the library
prominently
in the pantheon of Haskell libs. Demoting it has the opposite effect. 


Anyway, I just wanted to take advantage of a rare opportunity to sing its
praise.


I have nothing to add except... what a great post.  Thanks for being both 
enlightening and eloquent.


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


Re: [Haskell-cafe] Fw: patch applied (ghc): Remove the OpenGL familyof libraries fromextralibs

2008-07-29 Thread Jefferson Heard
Scott, I couldn't have said it better. My impression has always been
that HOpenGL looks like OpenGL would have looked like if they'd had a
flexible language to work with when they desgned it.  My only quibble
would be with the documentation.  Is there any way out there for
haddock to produce a linked and indexed PDF, so that I can better
guess where one function will be relative to another that feels like
it ought to be related?

On Mon, Jul 28, 2008 at 11:42 PM, scodil [EMAIL PROTECTED] wrote:

 I'll chime in with a me too. I use Haskell and OpenGL for prototyping
 scientific visualization software, 3D models and such. Not that I think it
 couldn't be used for production software, its just that I just don't produce
 much :)

 The library really is fantastic. I don't think it gets enough fanfare. The
 only
 other GL API that rivals it is the C API itself. Most other languages
 provide a
 shoddy  incomplete interface to that, instead of an idiomatic
 interpretation of the OpenGL spec. I can't think of a single language, not
 even
 python, whose OpenGL bindings come close.

 I get the impression (from a inadequate sample of irc logs and list chatter)
 that many Haskellers see HOpenGL as 'just an OpenGL binding', like it was
 readline or curses or something. It just plugs a hole in the Haskell/OS
 interface, and its worth is merely a function of the size and importance of
 that hole. Instead I advocate, as Claus and others have done, that it's a
 shining example of how to write a Haskell interface to a well known API.

 If you never used C OpenGL and learned GL using Haskell, you might not
 notice
 anything special about it. But that's kind of my point, its just so damn
 good
 it blends into the background. The only people who notice this, I think, are
 experienced C OpenGL programmers, and the overlap between them and the
 Haskell
 community in general is small I bet. Their voice in that community smaller
 still.

 This probably has little bearing on the issue of whether to keep or drop
 HOpenGL in the near future, but I think that if 'the community' (or whoever
 has
 a say in these things) like the style of HOpenGL, and want to encourage
 bindings to be written in that style, they should place the library
 prominently
 in the pantheon of Haskell libs. Demoting it has the opposite effect.

 Anyway, I just wanted to take advantage of a rare opportunity to sing its
 praise.

 Scott


 Yes, same here; don't worry, it's not going away.   It would be nice
 to know, though, how many people are using it and what they're using
 it for.  I'm using it for information visualization, and slowly
 evolving/cribbing together something like the Processing
 (http://www.processing.org) framework for Haskell as I do more things.

 On Sat, Jul 26, 2008 at 5:46 AM, Alberto Ruiz [EMAIL PROTECTED] wrote:
 Don Stewart wrote:

 claus.reinke:

 But neither do I believe the rumour that OpenGL isn't much
 used, and forwarding the removal notice gives those users the
 opportunity to speak up now if they prefer no gaps in OpenGL presence,
 or
 forever to hold their peace, as they say.

 I for one have noticed this library *is* actively used. Many of the fun
 new games that have appeared are using it, in particular.

 Such as:

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/frag
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/Monadius

 http://hackage.haskell.org/cgi-bin/hackage-scripts/package/roguestar-gl
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/rsagl
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/Shu-thing
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/topkata

 The tutorial was also translated to the wiki last week,

http://haskell.org/haskellwiki/Opengl

 It's a good, reliable package, in active use, widely ported.

 I'd just like to say that HOpenGL is essential for me. It is one of the
 reasons why I finally decided to use Haskell for all my work...

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




 --
 I try to take things like a crow; war and chaos don't always ruin a
 picnic, they just mean you have to be careful what you swallow.

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



 --
 View this message in context: 
 http://www.nabble.com/Fw%3A-patch-applied-%28ghc%29%3A-Remove-the-OpenGL-family-of-libraries-fromextralibs-tp18655695p18704556.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




-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful 

[Haskell-cafe] Re: Anglo Haskell 2008

2008-07-29 Thread Matthew Sackman
Anglo Haskell is a gathering of all people Haskell-related from
beginners, to seasoned hackers to academic giants. All and more are
welcomed by large fuzzy green lambdas.[0]

Anglo Haskell 2009 is nearly upon us and planning has been going well!
We are delighted to be able to confirm Simon Marlow is headlining this
year's event which is being held at Imperial College, London on the 8th
and 9th of August (Friday and Saturday).

We are also very happy to be able to announce there will be talks on
both days: 5 talks on the Friday and at least 3 and possibly 4 on the
Saturday. There will be an evening meal at local resturant on the
Friday evening followed by the odd drink for those that way inclined; a
lazy brunch on the Saturday morning, and then potentially some group
hacking on the Saturday afternoon and evening. We are truly excited
about this and should very much like to see you *all* there!

Full details are available at:
http://www.haskell.org/haskellwiki/AngloHaskell/2008

Things that are still to be added to that page which will appear over
the next week:
o) Phone numbers for myself and Tristan so that should you get lost you
 can ring one of us;
o) Video or photos of how to navigate to the correct room at Imperial -
 should somehow signs fail to materialise.

Please think about coming along - even if it's just for a single day.
It's FREE after all! If you are coming please put your name down on the
list on the wiki page, and further, if you'd like to come out to dinner
with us on the Friday evening, there's a separate list for that - please
add yourself to that too.

Many thanks,

Matthew
-- 
On behalf of the AH2008 team.

[0] We've been unable to obtain any large fuzzy green lambdas. If anyone
has any knocking about or knows where we can get some, please let us
know.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Fw: patch applied (ghc): Remove the OpenGL family of libraries fromextralibs

2008-07-29 Thread Malcolm Wallace
 I don't think that's right. The HP maintainers are not (and cannot be)
 the maintainers of each individual package. That just does not scale.

Oh absolutely, but I was imagining that (at least part of) the purpose
of the Platform is to generate automatic notifications to package
owners, when a change in either ghc or the packaging infrastructure or
the package's dependencies, leads to their own package breaking.  So the
Platform effectively generates an auto-prompt when maintenance is
required.

Given that such a lot of package-breakage is not due to changes in the
functionality of the library itself, but purely to changes in the
packaging system surrounding it, this would in my eyes shift
a certain amount of responsibility in the right direction.  :-)
(Not the responsibility to fix, but the responsibility to notify.)

As a package author (rather than a user), I would see this as a primary
benefit of having my packages added to the Platform.  And as a package
user (rather than author), there is the corresponding antibenefit of
removing a package like HOpenGL from the Platform: a diminished
likelihood of the maintainer being already aware of packaging flaws.

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


[Haskell-cafe] Problem compiling a CGI script that needs to write to file during its execution

2008-07-29 Thread Jefferson Heard
Please ignore the obvious security holes, as this is not a script
meant for public consumption, but some internal testing and
prototyping.  I would like to write the result of my computation out
to a file inside of cgiMain, but the type of the monad inside cgiMain
is this odd CGIT IO CGIResult.  I tried using liftM on writeFile, but
it then complained that newanns was a string instead of a list of
strings, which I don't understand at all.  Here's the code:

DeleteAnnotation.hs:


import Network.CGI
import Annotations
import Graphics.Rendering.OpenGL.GL (GLfloat)
import Control.Monad (liftM)
import Data.List (filter)

getInput' v = do
  x - getInput v
  case x of
Nothing - fail essential variable not found
Just y - return y

cgiMain :: String - CGI CGIResult
cgiMain anns_dot_txt = do
  ordnl - (liftM read) $ getInput' ordinal
  let anns = (filter (notequal ordnl) . read $ anns_dot_txt) :: [Annotation]
  newanns = show anns
  output $ newanns
  writeFile Annotations.txt $ newanns

notequal :: String - Annotation - Bool
notequal ordnl ann = ordnl == ordinal ann

main :: IO ()
main = do
  f - readFile Annotations.txt
  runCGI (handleErrors (cgiMain f))



$ ghc --make DeleteAnnotation

DeleteAnnotation.hs:19:2:
Couldn't match expected type `CGIT IO CGIResult'
   against inferred type `IO ()'
In the expression: writeFile Annotations.txt $ newanns
In the expression:
do ordnl - (liftM read) $ getInput' ordinal
   let anns = ...
   newanns = show anns
 output $ newanns
 writeFile Annotations.txt $ newanns
In the definition of `cgiMain':
cgiMain anns_dot_txt
  = do ordnl - (liftM read) $ getInput' ordinal
   let anns = ...
   
 output $ newanns
   

If I change writeFile Annotations.txt to (liftM (writeFile
Annotations.txt)):

$ ghc --make DeleteAnnotation

DeleteAnnotation.hs:19:42:
Couldn't match expected type `String' against inferred type `Char'
  Expected type: [String]
  Inferred type: String
In the second argument of `($)', namely `newanns'
In the expression: (liftM (writeFile Annotations.txt)) $ newanns
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Problem compiling a CGI script that needs to write to file during its execution

2008-07-29 Thread allan
Hi

I had this same problem and I'm not sure my way is correct but I used 
'Control.Monad.Trans.liftIO'
Here is some code that I am using

{-
  The main program is pretty simple we just run the CGI action.
-}
main :: IO ()
main =  Cgi.runCGI $ Cgi.handleErrors cgiMain

{-
  To be able to produce graphs which we can then display in the output
  webpage we require that our main function, that is the one which creates
  the page be in the IO monad.
-}
cgiMain :: CGI CGIResult
cgiMain = 
  do visitInfo - getAnalysisData
 page  - Monad.Trans.liftIO $ createPage visitInfo
 Cgi.output $ Xhtml.renderHtml page

createPage :: Visit - IO Html
createPage . blah stuff you don't care about

getAnalysisData :: CGI Visit

Visit is a data type I've made to hold the information obtained from the page.

Hope this helps
allan


Jefferson Heard wrote:
 Please ignore the obvious security holes, as this is not a script
 meant for public consumption, but some internal testing and
 prototyping.  I would like to write the result of my computation out
 to a file inside of cgiMain, but the type of the monad inside cgiMain
 is this odd CGIT IO CGIResult.  I tried using liftM on writeFile, but
 it then complained that newanns was a string instead of a list of
 strings, which I don't understand at all.  Here's the code:
 
 DeleteAnnotation.hs:
 
[snip code]

-- 
The University of Edinburgh is a charitable body, registered in
Scotland, with registration number SC005336.

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


Re: [Haskell-cafe] Problem compiling a CGI script that needs to write to file during its execution

2008-07-29 Thread Jefferson Heard
Beautiful, thank you.  That worked.

On Tue, Jul 29, 2008 at 12:07 PM, allan [EMAIL PROTECTED] wrote:
 Hi

 I had this same problem and I'm not sure my way is correct but I used 
 'Control.Monad.Trans.liftIO'
 Here is some code that I am using

 {-
  The main program is pretty simple we just run the CGI action.
 -}
 main :: IO ()
 main =  Cgi.runCGI $ Cgi.handleErrors cgiMain

 {-
  To be able to produce graphs which we can then display in the output
  webpage we require that our main function, that is the one which creates
  the page be in the IO monad.
 -}
 cgiMain :: CGI CGIResult
 cgiMain =
  do visitInfo - getAnalysisData
 page  - Monad.Trans.liftIO $ createPage visitInfo
 Cgi.output $ Xhtml.renderHtml page

 createPage :: Visit - IO Html
 createPage . blah stuff you don't care about

 getAnalysisData :: CGI Visit

 Visit is a data type I've made to hold the information obtained from the page.

 Hope this helps
 allan


 Jefferson Heard wrote:
 Please ignore the obvious security holes, as this is not a script
 meant for public consumption, but some internal testing and
 prototyping.  I would like to write the result of my computation out
 to a file inside of cgiMain, but the type of the monad inside cgiMain
 is this odd CGIT IO CGIResult.  I tried using liftM on writeFile, but
 it then complained that newanns was a string instead of a list of
 strings, which I don't understand at all.  Here's the code:

 DeleteAnnotation.hs:

 [snip code]

 --
 The University of Edinburgh is a charitable body, registered in
 Scotland, with registration number SC005336.





-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

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


Re: [Haskell-cafe] Cabal and Strings and CPP

2008-07-29 Thread Philip Weaver
On Tue, Jul 29, 2008 at 3:14 AM, Malcolm Wallace 
[EMAIL PROTECTED] wrote:

 Philip Weaver [EMAIL PROTECTED] wrote:

  I'm trying to use CPP-defined strings in a Haskell module, like this:
 main :: IO ()
 main = putStrLn FOO
  This of course will not work:
 ghc -DFOO=hello world --make Main.hs -o test

 Have you tried using ANSI cpp's stringification operator?

{-# LANGUAGE CPP #-}
#define STRING(bar) #bar
 main :: IO ()
main = putStrLn FOO

   ghc -DFOO=STRING(hello world) --make Main.hs -o test


Yes, I have.  It does not seem to be supported.


 Regards,
Malcolm
 ___
 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] Using fundeps to resolve polymorphic types to concrete types

2008-07-29 Thread wren ng thornton
Pablo Nogueira wrote:
 wren ng thornton wrote:
  It compiles just fine with (DeriveType A b = b - b) after all, which
  resolves directly to (B - B)

 That's not the case:

 simpleNarrow :: DeriveType A b = b - b
 simpleNarrow = id

  Couldn't match expected type `b' (a rigid variable)
  against inferred type `B'
   `b' is bound by the type signature for `simpleNarrow' ...
 When using functional dependencies to combine
   DeriveType A B, arising from the instance declaration ...
   DeriveType A b, arising from is bound by the type signature for
 `simpleNarrow' ...

[0] [EMAIL PROTECTED]:~/test $ cat fundep.hs
{-# OPTIONS_GHC -fglasgow-exts #-}

class DeriveType a b | a - b

data A = A
data B = B

instance DeriveType A B

simpleNarrow :: DeriveType A b = b - b
simpleNarrow = id

[0] [EMAIL PROTECTED]:~/test $ ghc --version
The Glorious Glasgow Haskell Compilation System, version 6.8.2

[0] [EMAIL PROTECTED]:~/test $ ghci fundep.hs
GHCi, version 6.8.2: http://www.haskell.org/ghc/  :? for help
Loading package base ... linking ... done.
[1 of 1] Compiling Main ( fundep.hs, interpreted )
Ok, modules loaded: Main.
*Main :t simpleNarrow
simpleNarrow :: B - B


 I think Bryan got the order in which type inference/checking works
 wrong. The dependency is not resolved before calculating the type as
 he suggested.

Indeed. Resolved was a sloppy word choice on my part, but the point is
that after all the inference is done you do end up with (B - B) because B
just so happens to be (DeriveType A b = b). However, the function's
actual type is indeed (DeriveType A b = b - b) since contexts are only a
constraint on polymorphism and never take part in driving the inference.


  *Main :t someDestructor (SomeConstructor undefined undefined ::
ComplexType A)
B

 Why not this:

 *Main  someDestructor (SomeConstructor A B)
  B

That works too, I just didn't have deriving Show in place at the time.


  But if you have actual values rather than just unit types, note that this
  won't work:
 
instance DeriveType A B where
someDestructor (SomeConstructor _ b) = b

 I couldn't understand the sentence actual values rather than unit
 types. What do you have in mind?
[...]
 I didn't pay attention to the |b| value returned. So what you meant
 was that only a constant function will do, not a function that returns
 the value |b|.

Yeah, pretty much.

The types A and B given were both unit types, i.e. they have only one
value each namely A and B. Hence we could do the other version with
someDestructor _ = B since we're throwing away the old value of type (b
quantified by SomeConstructor) and constructing a new value of type
(forall b. DeriveType A b = b). This is safe because we're never actually
peeking into the existential. And yet, since there's only one value of the
type we can safely reconstruct it knowing that we're not leaking any
information about SomeConstructor's internals.

But what happens if there's more than one value of type B? If we tried the
version above in order to return the second field of the ComplexType, that
would allow the existential to escape. Hence my comments that the methods
of DeriveType can only be used to gain views onto the value b but never to
recover its actual type. If we had some non-dependent type that we could
convert the existential into, then we can still safely use that view as
below:


[0] [EMAIL PROTECTED]:~/test $ cat fundep2.hs
{-# OPTIONS_GHC -fglasgow-exts #-}

class DeriveType a b | a - b, b - a where
someDestructor :: b - Int

data A = A   deriving Show
data B = B1 | B2 deriving Show

instance DeriveType A B where
someDestructor B1 = 1
someDestructor B2 = 2

simpleNarrow :: DeriveType A b = b - b
simpleNarrow = id


data ComplexType a where
   SomeConstructor :: DeriveType a b = a - b - ComplexType a

unComplexType :: ComplexType a - Int
unComplexType (SomeConstructor _ b) = someDestructor b

[0] [EMAIL PROTECTED]:~/test $ ghci fundep2.hs
GHCi, version 6.8.2: http://www.haskell.org/ghc/  :? for help
Loading package base ... linking ... done.
[1 of 1] Compiling Main ( fundep.hs, interpreted )
Ok, modules loaded: Main.
*Main unComplexType (SomeConstructor A B1)
1
*Main


The thing to bear in mind with all of this is what should the type
signature of unComplexType be? If someDestructor returned the second field
directly then there would be no way for us to give a type signature to
unComplexType. The b it would return is only scoped in the type of
SomeConstructor and so we have no way of referring to that exact variable.
What we can do however is return a monomorphic type or a non-dependent
polymorphic type [e.g. (forall a. Num a = a) is just fine, even rank-2
types are fine, just not ones that depend on the existential b].

You'll also notice that we had to add a fundep from b back to a in order
to get this to type check. Otherwise we can't be sure that the type a for
the existential b is the same as the a (namely 

Re: [Haskell-cafe] ANN: Hayoo! beta 0.2

2008-07-29 Thread Timo B. Hübel
Hi all,

thanks for all the feedback!

We have just uploaded a new Hayoo! index, which fixes several small glitches 
(for example, in the function descriptions) but the most important thing is, 
that it does include the docs for Gtk2hs now.

Additionally, we are working on a function to restrict the search to specific 
packages and will hopefully finish it this week.

I will also soon have a look into all these interface related JavaScript 
issues, but as this unfortunately does not involve Haskell coding, it may not 
be on my high priority list ;)

Stay tuned!

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


Re: [Haskell-cafe] Fw: patch applied (ghc): Remove the OpenGLfamilyof libraries fromextralibs

2008-07-29 Thread Claus Reinke

Scott, I couldn't have said it better. My impression has always been
that HOpenGL looks like OpenGL would have looked like if they'd had a
flexible language to work with when they desgned it.  My only quibble
would be with the documentation.  Is there any way out there for
haddock to produce a linked and indexed PDF, so that I can better
guess where one function will be relative to another that feels like
it ought to be related?


It is probably a bit obscured in the alphabetically sorted Haddock
main contents listing, but if you look at something like

http://www.haskell.org/ghc/docs/latest/html/libraries/OpenGL/Graphics-Rendering-OpenGL-GL.html
http://www.haskell.org/ghc/docs/latest/html/libraries/GLUT/Graphics-UI-GLUT.html

you'll find that the layout closely follows the relevant specs (at least,
it used to). So you can use the PDF files for the official specs to find what
you need, and then those doc layout pages to translate to HOpenGL.

Just as the examples follow the red book, to make translation easy.

Do I need to mention that I agree with Scott?-)
Claus


On Mon, Jul 28, 2008 at 11:42 PM, scodil [EMAIL PROTECTED] wrote:


I'll chime in with a me too. I use Haskell and OpenGL for prototyping
scientific visualization software, 3D models and such. Not that I think it
couldn't be used for production software, its just that I just don't produce
much :)

The library really is fantastic. I don't think it gets enough fanfare. The
only
other GL API that rivals it is the C API itself. Most other languages
provide a
shoddy  incomplete interface to that, instead of an idiomatic
interpretation of the OpenGL spec. I can't think of a single language, not
even
python, whose OpenGL bindings come close.

I get the impression (from a inadequate sample of irc logs and list chatter)
that many Haskellers see HOpenGL as 'just an OpenGL binding', like it was
readline or curses or something. It just plugs a hole in the Haskell/OS
interface, and its worth is merely a function of the size and importance of
that hole. Instead I advocate, as Claus and others have done, that it's a
shining example of how to write a Haskell interface to a well known API.

If you never used C OpenGL and learned GL using Haskell, you might not
notice
anything special about it. But that's kind of my point, its just so damn
good
it blends into the background. The only people who notice this, I think, are
experienced C OpenGL programmers, and the overlap between them and the
Haskell
community in general is small I bet. Their voice in that community smaller
still.

This probably has little bearing on the issue of whether to keep or drop
HOpenGL in the near future, but I think that if 'the community' (or whoever
has
a say in these things) like the style of HOpenGL, and want to encourage
bindings to be written in that style, they should place the library
prominently
in the pantheon of Haskell libs. Demoting it has the opposite effect.

Anyway, I just wanted to take advantage of a rare opportunity to sing its
praise.

Scott



Yes, same here; don't worry, it's not going away.   It would be nice
to know, though, how many people are using it and what they're using
it for.  I'm using it for information visualization, and slowly
evolving/cribbing together something like the Processing
(http://www.processing.org) framework for Haskell as I do more things.

On Sat, Jul 26, 2008 at 5:46 AM, Alberto Ruiz [EMAIL PROTECTED] wrote:

Don Stewart wrote:


claus.reinke:


But neither do I believe the rumour that OpenGL isn't much
used, and forwarding the removal notice gives those users the
opportunity to speak up now if they prefer no gaps in OpenGL presence,
or
forever to hold their peace, as they say.


I for one have noticed this library *is* actively used. Many of the fun
new games that have appeared are using it, in particular.

Such as:

   http://hackage.haskell.org/cgi-bin/hackage-scripts/package/frag
   http://hackage.haskell.org/cgi-bin/hackage-scripts/package/Monadius

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/roguestar-gl
   http://hackage.haskell.org/cgi-bin/hackage-scripts/package/rsagl
   http://hackage.haskell.org/cgi-bin/hackage-scripts/package/Shu-thing
   http://hackage.haskell.org/cgi-bin/hackage-scripts/package/topkata

The tutorial was also translated to the wiki last week,

   http://haskell.org/haskellwiki/Opengl

It's a good, reliable package, in active use, widely ported.


I'd just like to say that HOpenGL is essential for me. It is one of the
reasons why I finally decided to use Haskell for all my work...

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





--
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

-- Jessica Edwards
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org

[Haskell-cafe] #haskell irc channel reaches 500 users

2008-07-29 Thread Don Stewart
A small announcement :)

6 1/2  years after its inception, under the guiding hand of Shae Erisson
(aka shapr), the #haskell IRC channel[1] on freenode has finally reached
500 users!

To chart the growth, we can note that the channel was founded
in late 2001, and had slow growth till 2006, reaching 200 users in
January of that year. Since then growth in the user base has been far
more rapid, reaching 300 users in Dec 2006, 400 users in August
2007, and 500 users by July 2008.

This puts the channel at around the 12th largest community of the 7000
freenode channels. For comparision, a sample of the state of the other
language communities, with comments comapred to their status a year ago:

   #php 720
   #python  640 -- up from 5th place
   #perl620
   ##c++585
   ##c  530

  #haskell 502

   #rubyonrails 428
   #ruby-lang   350 -- down from 420 max.
   ##javascript 308
   #lisp295
   #erlang  178
   #perl6   129 -- unchanged
   #scheme  148 -- unchanged 
   #lua 120
   #ocaml70 -- unchanged

You can see the growth of the channel over here:

   http://www.cse.unsw.edu.au/~dons/irc

If you've not dropped by the channel yet, feel free to come and chat,
and toss around some lambdas! :)

Cheers,
Don

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


Re: [Haskell-cafe] Fw: patch applied (ghc): Remove the OpenGL family of libraries fromextralibs

2008-07-29 Thread Isaac Dupree

Malcolm Wallace wrote:

As a package author (rather than a user), I would see this as a primary
benefit of having my packages added to the Platform.  And as a package
user (rather than author), there is the corresponding antibenefit of
removing a package like HOpenGL from the Platform: a diminished
likelihood of the maintainer being already aware of packaging flaws.


perhaps we can work on getting set up automatic testing etc.
with a relatively basic Haskell Platform.  If that turns out to be
easily done, we can look at making a facility for all package authors
(at least, ones on Hackage) to volunteer to have their packages
automatically checked for such breakages.  Sure, it could still help a
little to be part of an official Haskell Platform, but there are reasons
we're trying to designate a Haskell Platform smaller than Hackage.

-Isaac

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


Re: [Haskell-cafe] Problem compiling a CGI script that needs to write to file during its execution

2008-07-29 Thread Ryan Ingram
On Tue, Jul 29, 2008 at 8:57 AM, Jefferson Heard
[EMAIL PROTECTED] wrote:
 I tried using liftM on writeFile, but it then complained that newanns
 was a string instead of a list of strings, which I don't understand at all.

liftM isn't what you think it is.

 liftM :: (a - b) - (m a - m b)
which is doing something weird depending how you inserted it:
 liftM (writeFile x) :: Monad m = m String - m (IO ())
which could theoretically have m get forced to be a list as the
typechecker tries to figure out how to decipher this mess...
 liftM (writeFile x) :: [String] - [IO ()]
or something else weird.

You are looking for either lift or liftIO, from Control.Monad.Trans

 lift :: (Monad m, MonadTrans t) = m a - t m a
 liftIO :: MonadIO m = IO a - m a

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


Re: [Haskell-cafe] Problem compiling a CGI script that needs to write to file during its execution

2008-07-29 Thread Luke Palmer
On Tue, Jul 29, 2008 at 3:48 PM, Ryan Ingram [EMAIL PROTECTED] wrote:
 On Tue, Jul 29, 2008 at 8:57 AM, Jefferson Heard
 [EMAIL PROTECTED] wrote:
 I tried using liftM on writeFile, but it then complained that newanns
 was a string instead of a list of strings, which I don't understand at all.

 liftM isn't what you think it is.

 liftM :: (a - b) - (m a - m b)
 which is doing something weird depending how you inserted it:
 liftM (writeFile x) :: Monad m = m String - m (IO ())
 which could theoretically have m get forced to be a list as the
 typechecker tries to figure out how to decipher this mess...
 liftM (writeFile x) :: [String] - [IO ()]
 or something else weird.

Probably:

  writeFile :: FilePath - String - IO ()
  liftM writeFile :: Monad m = m FilePath - m (String - IO ())
  liftM writeFile path

Will unify path::[Char]  with m Filepath.  Instantiate m to [] (by
head matching), but [Char] does not match [Filepath] (= [String]),
giving the error the OP mentioned.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Best book/tutorial on category theory and its applications

2008-07-29 Thread Pierre-Evariste Dagand
 Does _Conceptual Mathematics_ discuss monads?

I'm currently working on it, I'm at section 13 with Monoids but there
are no Monads at the horizon.

I have briefly gone through the end of the book and did not recognize
anything similar to a Monad. But I might not be able to recognize a
Monad in a category theory presentation, though.

However, as a complete n00b in category theory, I find this book
perfect. I tried Mac Lane's book (Categories for the working
mathematician) first but I was distracted by the notations and the
long, painful mathematical sentences. Nevertheless, none of these
books are computer scientist-oriented.

I have been recommended Categories for Types by Crole. I plan to
work on it after Conceptual Mathematic and Mac Lane's book. Right now,
I've now real opinion about it: at first glance, it looks as technical
as Mac Lane's book. I believe some enlightened people here could give
more useful review of it.

HTH,

-- 
Pierre-Evariste DAGAND
http://perso.eleves.bretagne.ens-cachan.fr/~dagand/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Fw: patch applied (ghc): Remove the OpenGL family of libraries fromextralibs

2008-07-29 Thread Duncan Coutts

On Tue, 2008-07-29 at 15:34 +0100, Malcolm Wallace wrote:
  I don't think that's right. The HP maintainers are not (and cannot be)
  the maintainers of each individual package. That just does not scale.
 
 Oh absolutely, but I was imagining that (at least part of) the purpose
 of the Platform is to generate automatic notifications to package
 owners, when a change in either ghc or the packaging infrastructure or
 the package's dependencies, leads to their own package breaking.  So the
 Platform effectively generates an auto-prompt when maintenance is
 required.

I hope that this is something that hackage will provide to all packages,
including those in the platform.

 Given that such a lot of package-breakage is not due to changes in the
 functionality of the library itself, but purely to changes in the
 packaging system surrounding it, this would in my eyes shift
 a certain amount of responsibility in the right direction.  :-)
 (Not the responsibility to fix, but the responsibility to notify.)
 
 As a package author (rather than a user), I would see this as a primary
 benefit of having my packages added to the Platform.  And as a package
 user (rather than author), there is the corresponding antibenefit of
 removing a package like HOpenGL from the Platform: a diminished
 likelihood of the maintainer being already aware of packaging flaws.

I really want to build the platform on the hackage infrastructure and
have all packages benefit from additional checks. Then users and
maintainers can act on that extra information. It should also make it
easier for new packages to join the platform because it'll be easier to
demonstrate that the various quality hoops have been jumped through.

So yes, we might expect platform volunteers to send occasional patches
to keep existing packages working, but really a package being in the
platform requires a maintainer rather than guaranteeing maintenance.

Duncan

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


[Haskell-cafe] A question about mfix

2008-07-29 Thread Wei Hu
What's wrong about giving mfix the following general definition? 


  mfix :: (a - m a) - m a 
  mfix f = (mfix f) = f 


I know it diverges if (=) is strict on the first argument. My 
question is, is this definition correct for all lazy monads? The 
documentation (http://haskell.org/ghc/docs/latest/html/libraries/base/ 
Control-Monad-Fix.html#v%3Amfix) says mfix f executes the action f 
only once, with the eventual output fed back as the input.. So my 
definition looks like a valid one, doesn't it? 

I haven't fully wrapped my head around this monadic fixed-point thing 
yet. So, if you can give an example showing how my definition differs 
from a standard monad, that'll be great. 

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


Re: [Haskell-cafe] A question about mfix

2008-07-29 Thread Ryan Ingram
These aren't equivalent, at least with respect to sharing; consider
the sharing behavior with respect to the Identity monad:

 import Control.Monad.Fix
 import Control.Monad.Identity

 mfixWei f = mfix f = f

 v1, v2 :: [Int]
 v1 = runIdentity $ mfix $ \a - return (0:a)
 v2 = runIdentity $ mfixWei $ \a - return (0:a)

 cons = (:)

While v1 and v2 are both infinite lists of zeros, v1 takes constant memory:
v1 = cons 0 v1

but v2 takes memory linear in size to the last element evaluated:
v2 = cons 0 t0 where
  t0 = cons 0 t1
  t1 = cons 0 t2
  t2 = cons 0 t3
  t3 = ...

This is where the specification about executes the action f only
once comes from; your implementation expands to

mfix f
= mfix f = f
= (mfix f = f) = f
= ((mfix f = f) = f) = f
= ...

As you can see, f might get executed an arbitrary number of times
depending on how lazy = is.

Now, I don't know the answer if you fix (pardon the pun) your
definition of mfix to

 mfixLazy f = let x = x = f in x

which gives the correct sharing results in the runIdentity case.

  -- ryan



On Tue, Jul 29, 2008 at 6:28 PM, Wei Hu [EMAIL PROTECTED] wrote:
 What's wrong about giving mfix the following general definition?


  mfix :: (a - m a) - m a
  mfix f = (mfix f) = f


 I know it diverges if (=) is strict on the first argument. My
 question is, is this definition correct for all lazy monads? The
 documentation (http://haskell.org/ghc/docs/latest/html/libraries/base/
 Control-Monad-Fix.html#v%3Amfix) says mfix f executes the action f
 only once, with the eventual output fed back as the input.. So my
 definition looks like a valid one, doesn't it?

 I haven't fully wrapped my head around this monadic fixed-point thing
 yet. So, if you can give an example showing how my definition differs
 from a standard monad, that'll be great.

 ___
 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] www.haskell.org is currently very slow in responding to HTTP requests

2008-07-29 Thread Benjamin L . Russell
Currently, www.haskell.org is very slow in responding to HTTP
requests, taking over a minute just to display the main home page.
This problem is causing difficulties in displaying options for mailing
lists or in displaying HaskellWiki pages.

Perhaps the server needs to be rebooted?  Could somebody responsible
for maintaining the server please look into this issue?  It seems to
have been persisting for at least about half an hour.  Thank you

-- Benjamin L. Russell

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


[Haskell-cafe] Re: A question about mfix

2008-07-29 Thread Wei Hu
So that's also why the fix function from Data.Function is defined as 

 fix f = let x = f x in x

instead of

 fix f = f $ fix f

right?

But, I think my mfix definition and your mfixLazy definition are still 
semantically equivalent because they expand to the same thing. See the 
following example:

 import Control.Monad.Identity

 -- Strict Identity monad
 data IdentityS a = IdentityS { runIdentityS :: a } deriving Show
 instance Monad IdentityS where
 return = IdentityS
 (IdentityS m) = k  = k m

 mfix' f = mfix' f = f
 mfixLazy f = let x = x = f in x

 facFM f = return (\i -
   if i == 0
 then 1
 else i * f (i - 1)
   )

 -- correctly outputs 3! = 6
 test = runIdentity (mfix facFM) 3 

 -- stack overflows
 test2 = runIdentityS (mfix' facFM) 3

 -- hangs
 test3 = runIdentityS (mfixLazy facFM) 3

Thanks for pointing out the sharing part. My original question is still 
unanswered: for lazy monads, can we give such a general mfix definition?

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