[Haskell-cafe] message-passing IPC for Haskell?

2008-07-31 Thread Galchin, Vasili
Hello,

 I have seen postings about work on message-passing IPCs for Haskell. I
like STM but want to keep an open mind ... I can't find those postings. Can
something remind of this work and where/how I can read about?

Very kind regards, Vasili
___
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-31 Thread wren ng thornton

Ryan Ingram wrote:

Hmm, I'm kind of confused by this now.  I feel like the following code
really should compile, but it doesn't.  There's no use of existentials
to hide type information at all.  The functional dependency seems like
it should give us the constraint (b1 ~ b2) allowing Refl to typecheck.


It may be worth noting that GADTs subsume existential types. Not that 
that matters here.




{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies, GADTs #-}
module DeriveType where

class DeriveType a b | a - b
data TypeEq a b where Refl :: TypeEq a a

test :: (DeriveType a b1, DeriveType a b2) = a - TypeEq b1 b2
test _ = Refl


But...

derivetype.hs:8:9:
Couldn't match expected type `b1' against inferred type `b2'


Like I was saying, contexts are only ever verified as constraints on 
polymorphism, they never drive the type inference algorithm. Think of 
them as something that happens after the fact, delayed constraints if 
you will.


The constructor Refl defines a constant of type (forall t. TypeEq t t). 
This constrains the return type of 'test' to have the same type, namely 
that the two arguments to the TypeEq type constructor are both the same. 
The signature you gave is more polymorphic than that, it allows for the 
possibility that they might be different. This is the same as the 
previous example using 'id' and wanting to give it the type (b - B).


If we simplify the example it might be more apparent why it fails.

[0] [EMAIL PROTECTED]:~/test $ cat wacky2.lhs  ghci wacky2.lhs
 module DeriveType where

 data TypeEq a b = TE

 refl :: TypeEq a a
 refl  = TE

 test  :: a - TypeEq b1 b2
 test _ = refl

GHCi, version 6.8.2: http://www.haskell.org/ghc/  :? for help
Loading package base ... linking ... done.
[1 of 1] Compiling DeriveType   ( wacky2.lhs, interpreted )

wacky2.lhs:9:11:
Couldn't match expected type `b1' against inferred type `b2'
  `b1' is a rigid type variable bound by
   the type signature for `test' at wacky2.lhs:8:22
  `b2' is a rigid type variable bound by
   the type signature for `test' at wacky2.lhs:8:25
  Expected type: TypeEq b1 b2
  Inferred type: TypeEq b2 b2
In the expression: refl
In the definition of `test': test _ = refl
Failed, modules loaded: none.
Prelude


In your version we'd like the fundeps to kick in and say there can be 
only one type paired with 'a' and so we can infer that 'b1' and 'b2' are 
the same, but fundeps are part of type classes and so they too are just 
delayed constraints.[1]


At the time of determining what the principal type of the function is, 
we don't see the type classes or the fundeps associated with them. While 
inferring the principal type we build up a set of delayed constraints 
(i.e. requisite type class instances, based on the functions used). 
After we've determined the principal type, we then verify that we can 
fulfill all the delayed requirements if we assume the type class 
instances in the context actually exist. If we pass type inference and 
context verification, then we deem the function OK.


The main use of fundeps is to assist type inference at *use* sites for 
the function. Say we have a function (foo :: DeriveType a b = a - b). 
If somewhere we use that function in the expression (foo x), if we've 
already determined that x has type A, this will let us infer some type B 
for specializing the polymorphism of foo in this expression. Without 
fundeps we would have to give a type signature in order to clarify which 
B should be used, if it couldn't otherwise be inferred. But this is all 
fundeps do, they don't help in determining what the type of foo itself 
is when we're defining it.


There are some cute tricks that can be played with fundeps in order to 
do type arithmetic and such, but Haskell doesn't really have dependent 
types and so it doesn't really use contexts to drive inference either. 
Sadly fundeps aren't quite as well integrated or general as they could 
be, but trying to resolve the MPTC/fundep/type families/... stuff into a 
single coherent approach is part of what the haskell' committee is 
trying to work out. One of the tricks in all this is to figure out how 
to have enough of dependent typing to do what we want, but without 
sacrificing decidability(/verifiability) of type inference.




[1] Also, Haskell has only one way of representing that two types are 
identical, namely unification i.e. using the same type variable. So even 
if fundeps did drive type inference, that type signature would still be 
wrong because the principal type is (DeriveType a b = a - TypeEq b b) 
since it's guaranteed that DeriveType a is defined at only one 'b'.


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


Re: [Haskell-cafe] Network.FastCGI does not emit stderr outputs to lighttpd's error.log?

2008-07-31 Thread Agent Zhang
On Thu, Jul 31, 2008 at 1:56 AM, Don Stewart [EMAIL PROTECTED] wrote:

 We've had no problems with this and apache at least. Is lighttpd
 doing something funny with error logging?

It seems that Apache is doing something funny :) According to my
teammate chaoslawful, apache redirects stderr to its error log files
(if any) but the fastcgi spec actually says everything should go
through the socket. And lighttpd seems to be following the spec
exactly :)

chaoslawful++ finally come up with the following patch for lighttpd
1.4.19 to make lighttpd behave in the same way as apache. Devel.Debug
is now finally working for me for my Haskell fastcgi hacking :))

 --- lighttpd-1.4.19/src/log.c2007-08-22 01:40:03.0 +0800
+++ lighttpd-1.4.19-patched/src/log.c2008-07-31 15:13:10.0 +0800
@@ -83,9 +83,14 @@
/* move stderr to /dev/null */
if (close_stderr 
-1 != (fd = open(/dev/null, O_WRONLY))) {
-close(STDERR_FILENO);
+// XXX: modified by chaoslawful, don't close stderr
when log into file
+close(STDERR_FILENO);
+if (srv-errorlog_mode == ERRORLOG_FILE 
srv-errorlog_fd =0 ) {
+dup2(srv-errorlog_fd,STDERR_FILENO);
+} else {
dup2(fd, STDERR_FILENO);
-close(fd);
+}
+close(fd);
}
return 0;
}

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


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

2008-07-31 Thread Dominic Steinitz
fero frantisek.kocun at gmail.com writes:

 
 What do you think about Categories and Computer Science (Cambridge Computer
 Science Texts) at
 http://www.amazon.com/Categories-Computer-Science-Cambridge-
Texts/dp/0521422264/ref=si3_rdr_bb_product
 ?
 

I couldn't see monads or the Yoneda lemma in the index. As a Haskell 
programmer, the lack of the former might be a concern; the latter is a 
standard result.

Dominic.

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


Re: [Haskell-cafe] Re: www.haskell.org is currently very slow in responding to HTTP requests

2008-07-31 Thread Bryan O'Sullivan
On Wed, Jul 30, 2008 at 2:54 AM, Ashley Yakeley [EMAIL PROTECTED] wrote:

 Other software versions:

 Linux 2.4.21 (latest is 2.6.26)
 Apache 2.0.46 (latest is 2.2.9)
 MySQL 3.23.58 (latest is 5.0.51a)
 PHP 4.3.2 (latest is 5.2.6)
 MediaWiki 1.5.4 (latest is 1.12)
 http://www.haskell.org/haskellwiki/Special:Version

 It might be worth upgrading some of that, though if that includes Linux or
 RHEL overall it would probably require physical access to the box.

The concurrent connection problem is a baked-in limitation of Apache,
and is unfortunately not something that will be fixed by a painful
upgrade.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Network.FastCGI does not emit stderr outputs to lighttpd's error.log?

2008-07-31 Thread Don Stewart
agentzh:
 On Thu, Jul 31, 2008 at 1:56 AM, Don Stewart [EMAIL PROTECTED] wrote:
 
  We've had no problems with this and apache at least. Is lighttpd
  doing something funny with error logging?
 
 It seems that Apache is doing something funny :) According to my
 teammate chaoslawful, apache redirects stderr to its error log files
 (if any) but the fastcgi spec actually says everything should go
 through the socket. And lighttpd seems to be following the spec
 exactly :)
 
 chaoslawful++ finally come up with the following patch for lighttpd
 1.4.19 to make lighttpd behave in the same way as apache. Devel.Debug
 is now finally working for me for my Haskell fastcgi hacking :))
 
  --- lighttpd-1.4.19/src/log.c2007-08-22 01:40:03.0 +0800
 +++ lighttpd-1.4.19-patched/src/log.c2008-07-31 15:13:10.0 +0800
 @@ -83,9 +83,14 @@
 /* move stderr to /dev/null */
 if (close_stderr 
 -1 != (fd = open(/dev/null, O_WRONLY))) {
 -close(STDERR_FILENO);
 +// XXX: modified by chaoslawful, don't close stderr
 when log into file
 +close(STDERR_FILENO);
 +if (srv-errorlog_mode == ERRORLOG_FILE 
 srv-errorlog_fd =0 ) {
 +dup2(srv-errorlog_fd,STDERR_FILENO);
 +} else {
 dup2(fd, STDERR_FILENO);
 -close(fd);
 +}
 +close(fd);
 }
 return 0;
 }
 
 Best,
 -agentzh

Interesting result, thanks for looking into this.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Haskell Weekly News: Issue 79 - July 31, 2008

2008-07-31 Thread Brent Yorgey
---
Haskell Weekly News
http://sequence.complete.org/hwn/20080731
Issue 79 - July 31, 2008
---

   Welcome to issue 79 of HWN, a newsletter covering developments in the
   [1]Haskell community.

   Apologies for the slightly late issue this week, attributable to a
   combination of having to transfer all my files onto a different
   computer (my former employer had the audacity to request the return of
   their laptop, now that I no longer work for them) and packing up to
   move to Philadelphia on Saturday. At any rate, some exciting news this
   week, including #haskell passing the 500 mark and a new release of Yi
   -- enjoy!

Community News

   Correction from last week's issue: congratulations were bestowed upon a
   certain Dr. Johansson who does not, in fact, exist, having been
   replaced almost a year ago by the happily married but otherwise
   identical Dr. Mikael Vejdemo-Johansson.

Announcements

   A fancier Get monad or two (a la binary and binary-strict). Chris
   Kuklewicz [2]announced two new Get-like monads for binary data, with a
   number of additional features.

   #haskell irc channel reaches 500 users. Don Stewart [3]announced that
   6 1/2 years after its inception, under the guiding hand of Shae Erisson
   (aka shapr), the [4]#haskell IRC channel on freenode has finally
   reached 500 users! This puts the channel at around the 12th largest
   (and mostest friendliest) community of the 7000 freenode channels.

   RandomDotOrg-0.1. Austin Seipp [5]announced the release of the
   [6]RandomDotOrg package, an interface to the [7]random.org random
   number generator.

   Mueval 0.3.1, 0.4, 0.4.5, 0.4.6, 0.5. Gwern Branwen [8]announced a
   number of releases of [9]Mueval, a package allowing dynamic runtime
   evaluation of Haskell expressions. As far as anyone knows, all possible
   security holes have been plugged, and it's missing only a few features
   before it can replace hs-plugins as lambdabot's evaluation mechanism.

   Need functional programmers for debugging study. Chris Bogart [10]asked
   for functional programmers currently developing or maintaining a medium
   to large-sized program, willing to let him look over their shoulder
   while they do debugging or coding on the project.

   Yi 0.4.1. Jean-Philippe Bernardy [11]announced the 0.4.1 release of the
   Yi editor, a text editor written and extensible in Haskell. The
   long-term goal of the Yi project is to provide the editor of choice for
   Haskell programmers.

   Hipmunk 0.1 and HipmunkPlayground 0.1. Felipe Lessa [12]announced the
   availability of [13]Hipmunk, containing bindings for the [14]Chipmunk
   2D physics engine, and [15]Hipmunk Playground, where you may see some
   of Hipmunk's features in action. The bindings are low-level but try to
   hide most of the nasty details of the C code.

   faster BLAS bindings. Patrick Perry [16]announced that he has
   [17]largely closed the C performance gap with his recent [18]Haskell
   BLAS bindings. Expect a new release shortly.

   FPers in Northwest Arkansas?. Nathan Bloomfield [19]is wondering if
   there are any Haskellers in the NW Arkansas region to start a
   functional programming interest group in the area.

   Italian Haskellers Summer Meeting. Pasqualino 'Titto' Assini
   [20]announced something about a summer meeting for Italian Haskellers.
   If you would like to know precisely what it was that was announced, I
   suggest you learn Italian.

   InterleavableIO. Marco Tulio Gontijo e Silva [21]announced a package,
   [22]interleavableIO, based on Jules Bean (quicksilver)'s [23]monadic
   tunneling code.

Google Summer of Code

   Progress updates from participants in the 2008 [24]Google Summer of
   Code.

   Hoogle 4. Neil Mitchell (ndm) is working on [25]Hoogle 4. [26]This
   week, he rewrote type search: after three days of coding, it required
   only a few minor debugging tweaks to get it to work. Haskell FTW!
   Expect a public beta of the command line interface next week.

   Generic tries. Jamie Brandon is working on a library for efficient maps
   using generalized tries. [27]This week, he has finally got everything
   up and running bug free on the new API, except the internals are still
   using association lists instead of AVL trees. He also exhibits a
   promising benchmark.

   DPH physics engine. Roman Cheplyaka (Feuerbach) is working on a
   [28]physics engine using [29]Data Parallel Haskell.

   GHC plugins. Max Bolingbroke is working on dynamically loaded plugins
   for GHC.

   Cabal dependency framework. Andrea Vezzosi (Saizan) is working on a
   [30]make-like dependency analysis framework for Cabal.

   Language.C. Benedikt Huber (visq) is [31]working on Language.C, a
   standalone parser/pretty printer library for C99.

   GHC API. Thomas Schilling (nominolo) is working on [32]improvements

Re: [Haskell-cafe] message-passing IPC for Haskell?

2008-07-31 Thread Thomas M. DuBuisson

  I have seen postings about work on message-passing IPCs for
 Haskell. I like STM but want to keep an open mind ... I can't find
 those postings. Can something remind of this work and where/how I can
 read about?

I made a quick hack composing BSD sockets from Network.Socket for higher level 
IPC.  It was for a one use deal, but you're free to use and improve on the 
library - called 'ipc' on hackage.

Tom


Hackage:
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/ipc

Basic homepage:
http://www.haskell.org/haskellwiki/IPC


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


Re: [Haskell-cafe] array fusion interface

2008-07-31 Thread Henning Thielemann

On Tue, 22 Jul 2008, Evan Laforge wrote:

 With all the noise lately about high performance array libraries with
 list-like interfaces, such as bytestring, storablevector, uvector, and
 vector, I thought I would try to make use of one in a project of mine,
 and I'm either bumping up against the limits of its expressiveness, or
 am missing out on how to express my problem.

 I have streams of samples with irregular sampling rates, so they look
 like [(Time, SampleVal)].  In practice, this means [(Double, Double)].

Maybe I have already mentioned my eventlist package on Hackage which
supports such resampling operations - but is based on lists.
   http://hackage.haskell.org/cgi-bin/hackage-scripts/package/event-list
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Point-free style in guards

2008-07-31 Thread Henning Thielemann

On Tue, 22 Jul 2008, L29Ah wrote:

 outStanza | (isMessage) = outMessage
 | (isPresence) = outPresence
 | (isIQ) = outIQ

 Why such a style doesn't work, so I must write ugly code like that:

 outStanza a | (isMessage a) = outMessage a
 | (isPresence a) = outPresence a
 | (isIQ a) = outIQ a

 so, guards can't be useful in point-free function definitions in any way

It's sad that syntactic sugar makes people want even more syntactic sugar
(some people thus call it syntactic heroin).

You can easily achieve the wanted effect by a function like 'select'
  http://www.haskell.org/haskellwiki/Case
 and that way you can also avoid guards in many cases.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Exceptions

2008-07-31 Thread Henning Thielemann

On Sun, 27 Jul 2008, Adrian Neumann wrote:

 Hello,

 I think it'd be nice if the compiler could warn me if there are any
 exceptions which I'm not catching, similar to checked exceptions in
 Java. Does anyone know of a possibility to do that in Haskell?

Please refer to the long extensible extension thread:
   http://www.haskell.org/pipermail/libraries/2008-July/010095.html
  In my posts I sketched possibilities to do that.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] an array of pointers in FFI?

2008-07-31 Thread Galchin, Vasili
Hello,

 Is a (Ptr (Ptr a)) a polymorphic representation of an array of pointers
of type a? I want to pass an array of pointers to a C function.

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


[Haskell-cafe] category theory tutorial pdfs .....

2008-07-31 Thread Galchin, Vasili
Hello,

Prof. Harold Simmons' tutorial IMO are like a Russian matroshka doll ...
first layer is for newbie ... inner layers require more sophistication. IMO
a very subtle writer ... I have every book imaginable on cat theory and
topos theory so I think can compare a little.

   1) http://www.cs.man.ac.uk/~hsimmons/BOOKS/books.html  ... an earlier
version ... An Intro to Category Theory in Four Easy Movements ... this
version delves a little into Topos Theory ... pretty subtle .. cool

   2) http://www.cs.man.ac.uk/~hsimmons/MAGIC-CATS/magic-cats.html  ...
newer version which also has its cool merits IMO!

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


Re: [Haskell-cafe] an array of pointers in FFI?

2008-07-31 Thread Bulat Ziganshin
Hello Vasili,

Friday, August 1, 2008, 9:08:05 AM, you wrote:

  Is a (Ptr (Ptr a)) a polymorphic representation of an array of
 pointers of type a? I want to pass an array of pointers to a C function.

use Ptr (Ptr ())

Ptr ()  in haskell is like void* in C, it's used to represent pointer
to arbitrary type. you can use castPtr to cast pointers between different
types


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] an array of pointers in FFI?

2008-07-31 Thread Galchin, Vasili
Thanks Bulat! So since we are talking ;^)  is there a function already
in Foreign that will allow me to ...

[a] - Ptr (Ptr ()) i.e. map a list of type a to an array of ptrs of type
a?

Kind regards, Vasili

On Fri, Aug 1, 2008 at 12:53 AM, Bulat Ziganshin
[EMAIL PROTECTED]wrote:

 Hello Vasili,

 Friday, August 1, 2008, 9:08:05 AM, you wrote:

   Is a (Ptr (Ptr a)) a polymorphic representation of an array of
  pointers of type a? I want to pass an array of pointers to a C
 function.

 use Ptr (Ptr ())

 Ptr ()  in haskell is like void* in C, it's used to represent pointer
 to arbitrary type. you can use castPtr to cast pointers between different
 types


 --
 Best regards,
  Bulatmailto:[EMAIL PROTECTED]


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