Re: [Haskell-cafe] Issues(Bugs?) with GHC Type Families

2008-03-06 Thread Ryan Ingram
On Thu, Mar 6, 2008 at 7:16 PM, Luke Palmer <[EMAIL PROTECTED]> wrote:
>  I agree that this would be nice.  But I think that the situation is
>  stickier than it looks on the surface.  Consider this:
>
> instances GShow [a] where
> instance [Char] where gShow = id
> instance [a] where gShow x = "list(" ++ length x ++ ")"
>
> gShow' :: [a] -> String
> gShow' = gShow

I'm not so sure.  It's not that hard to imagine a compiler where the
core-language expansion of this code looks like this:

data GShowDict a = GShowDict { gShow :: a -> String }

id :: (a :: *) -> a -> a
id A a = a

length :: (a :: *) -> [a] -> Int
-- definition elided

gShow' :: (a :: *) -> [a] -> String
gShow' A = gShow (mkDict_GShow_List A)

mkDict_GShow_List :: (a :: *) -> GShowDict [a]
mkDict_GShow_List A =
   typecase A of
   Char -> GShowDict (id [A])
   _ -> GShowDict (\xs -> length A xs)

Now, it's true that this means that you can no longer do full type
erasure, but I'm not convinced of the importance of that anyways; if
you look at mainstream languages you generally only get type erasure
for a restricted subset of the types and that's good enough for
performance:
   1) In Java, you only get type erasure for primitive types;
everything else needs its type tag so it can be safely downcasted from
Object.
   2) In C++ only primitive types and structs/classes with no virtual
functions get type erasure; if a class has virtual functions its
virtual function table is implicitly a "type tag".

I don't think the cost is that great; the compiler can easily flag
polymorphic functions that require type information for some or all
arguments and in many cases the type evidence can be passed
"just-in-time" when calling from a non-polymorphic function into a
polymorphic function.

>  When we get to more complex examples like the one you gave
>  above involving constraints, in order to solve for the constraints
>  needed for an instance of C [a] you need a *disjunction* constraint,
>  which vastly increases the likelihood of an undecidable solution.

This is definitely an issue.  I don't have a full understanding of the
methods used for typechecking/inference of typeclasses; I'm just a
programmer who wants MORE POWER :)

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


Re: [Haskell-cafe] Re: Small displeasure with associated type synonyms

2008-03-06 Thread Tom Schrijvers

Am I correct in thinking this would have worked if it were an
associated type instead of an associated type synonym?

ie,

class C a where
   data T a
   val :: T a


Yes, you are. Associate data type constructors (as well as ordinary 
algebraic data constructors) are injective. So we have:


forall a b . T a = T b <=> a = b

Cheers,

Tom

--
Tom Schrijvers

Department of Computer Science
K.U. Leuven
Celestijnenlaan 200A
B-3001 Heverlee
Belgium

tel: +32 16 327544
e-mail: [EMAIL PROTECTED]
url: http://www.cs.kuleuven.be/~toms/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Build dependency problem with bytestring.

2008-03-06 Thread Don Stewart
jstrait:
> Hi all,
> 
> I'm upgrading HAppS from my 0.9.2 to the current 0.9.2.1 in Hackage.  
> Some HAppS components have built and installed (IxSet and Util).  
> Halfway through the HAppS-State build, the GHC runtime linker gives a 
> fatal error on finding a duplicate definition for symbol fps_minimum 
> while loading bytestring 0.9.0.4 after having already loaded bytestring 
> 0.9.0.1.  From trial and error, I'm guessing that HAppS-State needs 
> 0.9.0.1 but one of its build dependencies was built with 0.9.0.4.   
> Using GHC 6.8.2 Linux here.
> 
> Any suggestions on how best to currently approach this situation?
> .

you need to uninstall your happs build, uninstall bytestring 0.9.0.1,
and start over, so all packages link against 0.9.0.4 only.

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


[Haskell-cafe] Build dependency problem with bytestring.

2008-03-06 Thread Jon Strait

Hi all,

I'm upgrading HAppS from my 0.9.2 to the current 0.9.2.1 in Hackage.  
Some HAppS components have built and installed (IxSet and Util).  
Halfway through the HAppS-State build, the GHC runtime linker gives a 
fatal error on finding a duplicate definition for symbol fps_minimum 
while loading bytestring 0.9.0.4 after having already loaded bytestring 
0.9.0.1.  From trial and error, I'm guessing that HAppS-State needs 
0.9.0.1 but one of its build dependencies was built with 0.9.0.4.   
Using GHC 6.8.2 Linux here.


Any suggestions on how best to currently approach this situation?

Thanks,
Jon


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


Re: [Haskell-cafe] Analysing Haskell with Graph Theory

2008-03-06 Thread Ivan Miljenovic
On 07/03/2008, Vimal <[EMAIL PROTECTED]> wrote:
>
> Will the graph be completely computed before the analysis begins? Or
>  will you try to build the graph lazily as and when you require more
>  information?

Probably beforehand.

>
> Are you looking for Haskell functions that can be used to solve the
>  above problems? I guess once you come up with the algorithms,
>  translating it into Haskell shouldnt be much of a problem.

No, I'm just asking people what else they think I should be looking for.


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


Re: [Haskell-cafe] Issues(Bugs?) with GHC Type Families

2008-03-06 Thread David Menendez
On Thu, Mar 6, 2008 at 9:52 PM, Ryan Ingram <[EMAIL PROTECTED]> wrote:
>  This is actually a general issue with the way typeclasses are defined
>  in Haskell; the accepted solution is what the "Show" typeclass does:
>
>
>  > class C a where
>  >c :: a
>  >cList :: [a]
>  >cList = [c,c]
>
>
>  > instance C Char where
>  >c = 'a'
>  >cList = "a" -- replaces instance for String above
>
> > instance C a => C [a] where
>  >c = cList
>  > cc = c :: String
>
>  I don't really like this solution; it feels like a hack and it relies
>  on knowing when you define the typeclass what sort of overlap you
>  expect.

The pattern above can be thought of as a specialized version of this:

class C a where
c :: a

class ListOfC a where
listOfC :: [a]

instance (ListOfC a) => C [a] where
c = listOfC

This works for an arbitrary number of type constructors (good!), but
requires a ListOfC instance for everything you might want to put into
a list (cumbersome!).

You can make things slightly less verbose by putting a sensible
default in ListOfC,

class (C a) => ListOfC a where
listOfC :: [a]
listOfC = default_c

-- 
Dave Menendez <[EMAIL PROTECTED]>

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


Re: [Haskell-cafe] Re: Small displeasure with associated type synonyms

2008-03-06 Thread David Menendez
On Thu, Mar 6, 2008 at 3:57 PM, ChrisK <[EMAIL PROTECTED]> wrote:
> Okay, I get the difference.
>
>  The "T a" annotation in "val :: T a)"and "val :: T a" does not help choose 
> the
>  "C a" dictionary.
>  But the "val :: a-> T a" and "val (undefined :: a)" allows "a" to 
> successfully
>  choose the "C a" dictionary.
>
>  val :: T a fixes "T a" but does not imply "C a".
>  (undefined :: a) fixes "a" and does imply "C a".
>  I now see how the functional dependency works here (which I should have 
> tried to
>  do in the first place -- I should have thought more and relied on the mailing
>  list less).
>
>  "class C a b | a -> b" is here "class C a where type T a = b".
>  So only knowing "T a" or "b" does not allow "a" to be determined.

Am I correct in thinking this would have worked if it were an
associated type instead of an associated type synonym?

ie,

class C a where
data T a
val :: T a

-- 
Dave Menendez <[EMAIL PROTECTED]>

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


Re: [Haskell-cafe] Issues(Bugs?) with GHC Type Families

2008-03-06 Thread Luke Palmer
On Thu, Mar 6, 2008 at 7:52 PM, Ryan Ingram <[EMAIL PROTECTED]> wrote:
>  I wish there was some form of instance declaration that let you do
>  case analysis; something similar to the following:
>
>  instances C [a] where
>
> instance C String where
> c = "a"
>
> instance C a => C [a] where
> c = [c,c]
> instance Num a => C [a] where
> c = [0]
>
>  When trying to find a constraint for C [a] for some type a, the
>  instances would be checked in order:
>  1) If a was Char, the first instance would be selected.
>  2) Otherwise, if there was an instance for C a, the second instance
>  would be selected.
>  3) Otherwise, if there was an instance for Num a, the third instance
>  would be selected.
>  4) Otherwise a type error would occur.

I agree that this would be nice.  But I think that the situation is
stickier than it looks on the surface.  Consider this:

instances GShow [a] where
instance [Char] where gShow = id
instance [a] where gShow x = "list(" ++ length x ++ ")"

gShow' :: [a] -> String
gShow' = gShow

For any implementation which keeps implementations polymorphic (i.e.
no required inlining like C++), despite what the program *says*,
gShow' would not be equal to gShow.  When gShow' calls gShow, it needs
a GShow dictionary; so it does constraint solving and finds a
dictionary for [a].  a is not Char, so it uses the [a] dictionary, not
the [Char] dictionary.  Therefore:

gShow "hello" = "hello"
gShow' "hello" = "list(5)"

That's just the first issue, and that alone is enough to make me not
want this.  When we get to more complex examples like the one you gave
above involving constraints, in order to solve for the constraints
needed for an instance of C [a] you need a *disjunction* constraint,
which vastly increases the likelihood of an undecidable solution.

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


Re: [Haskell-cafe] CABAL: conditional executable?

2008-03-06 Thread Duncan Coutts

On Thu, 2008-03-06 at 16:29 +, Magnus Therning wrote:
> On 3/6/08, Magnus Therning <[EMAIL PROTECTED]> wrote:
> On 3/6/08, Magnus Therning <[EMAIL PROTECTED]> wrote:
> On 3/4/08, Thomas Schilling <[EMAIL PROTECTED]>
> wrote:

> Oh, right.  That's a bug in Cabal 1.2 (fixed
> in HEAD).  Use:
> 
>buildable: False
> 
> OK, that solved that problem, now onto the next.
> Rather surprisingly to me, buildability has an impact
> on what's included in the source tar-ball created with
> "sdist".  What's the reason for that behaviour?
> 
> It seems the source isn't even included on the platform where
> the executable *is* buildable.  I'll see if I can put together
> a small example and raise a bug.
> 
> Done, http://hackage.haskell.org/trac/hackage/ticket/257

Fixed, thanks.

Duncan


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


[Haskell-cafe] "Hello World" in Haskell for web browser

2008-03-06 Thread Dimitry Golubovsky
Hi,

I have noticed that some people tried to compile a traditional Haskell
program using IO monad to show "Hello World" using Yhc Web Service.

Thanks for your interest, and here are some clues.

The programming paradigm chosen for Haskell Web programming is not
based on monads. It is based on CPS-style calls to DOM functions by
Haskell code compiled to Javascript. Further on, additional layers may
stack up (such as Haskell Web Toolkit) to provide more convenient
APIs, but DOM is the basis.

So here is an example of "Hello World" program written this way:

-- begin pasteable code --

module HelloWorldDOM where

import CPS
import UnsafeJS
import CDOM.Level2.DomUtils
import DOM.Level2.Dom
import DOM.Level2.Html2
import DOM.Level2.HTMLElement
import DOM.Level2.HTMLDivElement

main = getHTMLDocument $ \doc ->
   documentBody doc $ \body ->
   mkText doc "Hello World" $ \txt ->
   mkDiv doc $ \dv ->
   addChild txt dv $ \_ ->
   addChild dv body $ id

-- end   pasteable code --

The meaning of this:
  * get reference to the HTML document node first (it is the parent of
everything),
  * extract the  tag node, create at text element with "Hello World",
  * create a  tag node,
  * insert the text node into div,
  * insert div into body

Or, same in HTML:


  

  Hello World

  


but filled in dynamically.

Using Haskell Web Toolkit API, the same may be expressed in more
compact fashion:

-- begin pasteable code --

module HelloWorldHsWTK where

import DOM.Level2.HTMLDivElement
import Graphics.UI.HsWTK

main = docBodyC (mkDiv |<< textP "Hello World")

-- end   pasteable code --

Here, docBodyC is roughly equivalent of the first two DOM calls, mkDiv
is same as above, |<< means "insert into container", and textP is a
wrapper around mkText.

Earlier, I posted the link to Haddock-generated documentation which
also includes the Haskell DOM API. Here it is again:

http://www.golubovsky.org:5984/_utils/yhcws/index.html

Hopefully this example along with the documentation provided helps
shed some light on Haskell Web programming techniques.

Feel free to ask questions.

Thanks.

-- 
Dimitry Golubovsky

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


Re: [Haskell-cafe] Issues(Bugs?) with GHC Type Families

2008-03-06 Thread Ryan Ingram
2008/3/6 Hugo Pacheco <[EMAIL PROTECTED]>:
> How could I compile such an example, assuming that I want to use the
> instance C String for Strings only and the more general instance for the
> rest?

> class C a where
> c :: a
> instance C Char where
> c = 'a'
> instance C a => C [a] where
> c = [c :: a,c :: a]
> instance C String where
> c = "a"
> cc = c :: String

This is actually a general issue with the way typeclasses are defined
in Haskell; the accepted solution is what the "Show" typeclass does:

> class C a where
>c :: a
>cList :: [a]
>cList = [c,c]

> instance C Char where
>c = 'a'
>cList = "a" -- replaces instance for String above
> instance C a => C [a] where
>c = cList
> cc = c :: String

I don't really like this solution; it feels like a hack and it relies
on knowing when you define the typeclass what sort of overlap you
expect.

I wish there was some form of instance declaration that let you do
case analysis; something similar to the following:

instances C [a] where
instance C String where
c = "a"
instance C a => C [a] where
c = [c,c]
instance Num a => C [a] where
c = [0]

When trying to find a constraint for C [a] for some type a, the
instances would be checked in order:
1) If a was Char, the first instance would be selected.
2) Otherwise, if there was an instance for C a, the second instance
would be selected.
3) Otherwise, if there was an instance for Num a, the third instance
would be selected.
4) Otherwise a type error would occur.

Then overlapping instances wouldn't be required nearly as often; the
relevant instances would all have to be defined in one place, but
that's often the case anyways.  In exchange for giving up some of the
openness of typeclasses, you would get the benefit of being able to
have better control over instance definitions.

You could also use this to create "closed" typeclasses using
"instances C a where ..."; the compiler would then know that all
possible instances were defined at that location; any other definition
would clearly overlap and so the compiler could rule out their
existence immediately.  There might be some benefit in this case in
terms of removing ambiguities that currently arise due to open
typeclasses.

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


Re: [Haskell-cafe] Analysing Haskell with Graph Theory

2008-03-06 Thread Vimal
>  be tentatively stored as a directed graph with the nodes being
>  functions and the edges being function calls, i.e. if f calls g, there
>  is a directed edge from f to g):
>

Will the graph be completely computed before the analysis begins? Or
will you try to build the graph lazily as and when you require more
information?

And
>  * root finding -> find nodes with no incoming edges (in a program,
>  you'd ideally want only main to be such a node)
>
>  * cycle detection -> find a possibly recursive cycle in your code: if
>  the cycle is too big, then you may wish to consider refactoring
>
>  * depth analysis -> find leaves that have a depth from the root node
>  that is extremely large compared to the others (if a function is 50
>  calls down from main compared to an average of 15, you may wish to
>  refactor)
>
>  * chain detection -> find connected functions that have only one
>  incoming and one outgoing edge, e.g. : f -> g -> h : if g isn't used
>  anywhere else, you may wish to combine it inside either f or g
>
>  * node popularity -> get a count of how many functions use a
>  particular function and how many other functions it calls (related to
>  chain detection above)
>
>  * clique detection -> probably not as relevant to source code, but if
>  you have a large number of functions that are all pairwise
>  co-recursive than you may wish to refactor
>
>  Can anyone think of any other kind of functions that would be useful
>  in this kind of source code analysis?
>

Are you looking for Haskell functions that can be used to solve the
above problems? I guess once you come up with the algorithms,
translating it into Haskell shouldnt be much of a problem.

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


Re: [Haskell-cafe] Issues(Bugs?) with GHC Type Families

2008-03-06 Thread Hugo Pacheco
What I said is not true since overlapping instances are not that much
decidable.
Btw, in previous versions of GHC this worked well, but now I suppose order
does not suffices to define instances overlapping

How could I compile such an example, assuming that I want to use the
instance C String for Strings only and the more general instance for the
rest?

class C a where
c :: a

instance C Char where
c = 'a'

instance C a => C [a] where
c = [c :: a,c :: a]

instance C String where
c = "a"

cc = c :: String

Sorry for the newbie question.
hugo
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Analysing Haskell with Graph Theory

2008-03-06 Thread Ivan Miljenovic
Back in December, I posted that I was thinking about doing a project
for my honours year on using graph theory for analysis on Haskell
source code, amongst others:

http://thread.gmane.org/gmane.comp.lang.haskell.cafe/32912

Well, I've officially started this project, and my supervisor and I
have come up with the following functions that would probably be
relevant to analysing _any_ piece of source code (the actual code will
be tentatively stored as a directed graph with the nodes being
functions and the edges being function calls, i.e. if f calls g, there
is a directed edge from f to g):

* root finding -> find nodes with no incoming edges (in a program,
you'd ideally want only main to be such a node)

* cycle detection -> find a possibly recursive cycle in your code: if
the cycle is too big, then you may wish to consider refactoring

* depth analysis -> find leaves that have a depth from the root node
that is extremely large compared to the others (if a function is 50
calls down from main compared to an average of 15, you may wish to
refactor)

* chain detection -> find connected functions that have only one
incoming and one outgoing edge, e.g. : f -> g -> h : if g isn't used
anywhere else, you may wish to combine it inside either f or g

* node popularity -> get a count of how many functions use a
particular function and how many other functions it calls (related to
chain detection above)

* clique detection -> probably not as relevant to source code, but if
you have a large number of functions that are all pairwise
co-recursive than you may wish to refactor

Can anyone think of any other kind of functions that would be useful
in this kind of source code analysis?

Also, I'm going to be using haskell-src for for the parsing of the
Haskell code so that I don't waste my time writing a parser, when my
project is technically on the graph-theory side of things.  I know
that it focuses mainly on H98 with only a few extensions... is this
likely to be a problem if I want to try running my eventual program on
say ghc or xmonad as test examples?

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


Re: [Haskell-cafe] Issues(Bugs?) with GHC Type Families

2008-03-06 Thread Hugo Pacheco
>
>
>
> >If the equality does not hold, you should get a type error because
> >your program is not type correct.  So, what is it that you would like
> >different?
>
> I would simply like the compiler not to use that instance if the equality
> constraint does not hold, like some another instance dependency constraint,
> but I assume that is not possible.


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


Re: [Haskell-cafe] Re: Small displeasure with associated type synonyms

2008-03-06 Thread Manuel M T Chakravarty

Stefan Holdermans:
The problem is ambiguity. The type checker can't determine which  
val function to use, i.e. which dictionary to pass to val.


I see. Still, maybe a type-error message in terms of good old  
"unresolved top-level overloading" would be a bit more useful  
here... ;-)


I agree the error message is appalling.  Could you put this as a bug  
in the bug tracker?


Thanks,
Manuel

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


Re: [Haskell-cafe] Issues(Bugs?) with GHC Type Families

2008-03-06 Thread Manuel M T Chakravarty

Hugo Pacheco:

Just something I have been wondering.

I would like to implement somehting like:

type family F a :: * -> *
...
class C a b where ...
instance (F a ~ F b) => C a b where ...

But apparently type equality coercions can not be used as a single  
context. If I enable -fallow-undecidable-instances, whenever the  
equality does not hold, the instance returns a compile error, what  
does make sense.


Is there any way I could overcome this?


I think I don't understand your question fully.  This class instance  
requires both -XFlexibleInstances and -fallow-undecidable-instances to  
compile.


If the equality does not hold, you should get a type error because  
your program is not type correct.  So, what is it that you would like  
different?


Manuel

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


Re: [Haskell-cafe] Connection helpers: for people interested in network code

2008-03-06 Thread brad clawsie
"Gwern Branwen" <[EMAIL PROTECTED]> writes:

>>  i offered some time ago to look at building a cabal package and
>>  documentation for this. i would offer up excuses as to why this hasn't
>>  appeared yet, but between kids, work and ski season i just haven't
>>  allocated the time yet. sorry to all. i still hope to look into this,
>>  but fair to say i dropped the ball.
>
> Dunno. I just downloaded the git repo, and I'm not sure what's
> stopping anyone from uploading it to Hackage. It builds cleanly and
> with essentially no warning on 6.8.2, the Haddock docs build, and so
> on. The Cabal file itself is quite good; out of boredom, I tweaked it
> a little:

awesome! that means someone has indeed recognized my lameness and
subbed in to do what i didn't. thanks to whoever you are! sorry again
for promising and not delivering

[gwern, hope you don't mind if i redirect your personally reply to the 
 list for context preservation]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Small displeasure with associated type synonyms

2008-03-06 Thread Stefan Holdermans

Tom,

Thanks for your quick answer.

The problem is ambiguity. The type checker can't determine which val  
function to use, i.e. which dictionary to pass to val.



I see. Still, maybe a type-error message in terms of good old  
"unresolved top-level overloading" would be a bit more useful  
here... ;-)


Cheers,

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


[Haskell-cafe] Re: Small displeasure with associated type synonyms

2008-03-06 Thread ChrisK

Okay, I get the difference.

The "T a" annotation in "val :: T a)"and "val :: T a" does not help choose the 
"C a" dictionary.
But the "val :: a-> T a" and "val (undefined :: a)" allows "a" to successfully 
choose the "C a" dictionary.


val :: T a fixes "T a" but does not imply "C a".
(undefined :: a) fixes "a" and does imply "C a".
I now see how the functional dependency works here (which I should have tried to 
do in the first place -- I should have thought more and relied on the mailing 
list less).


"class C a b | a -> b" is here "class C a where type T a = b".
So only knowing "T a" or "b" does not allow "a" to be determined.

--
Chris

Tom Schrijvers wrote:

I don't see how your example explains this particular error.
I agree Int cannot be generalized to (T Int) or (T Bool).


Generalized is not the right word here. In my example T Int, T Bool and 
Int are all equivalent.


I see Stefan's local type signature is not (val :: a) like your (val 
::Int) but (val :: T a) which is a whole different beast.


Not all that different. As in my example the types T Int, T Bool and Int 
are equivalent, whether one writes val :: Int, val :: T Int or val :: T 
Bool. My point is that writing val :: T Int or val :: T Bool does not 
help determining whether one should pick the val implementation of 
instance C Int or C Bool.



And (T a) is the type that ghc should assign here.


As my example tries to point out, there is not one single syntactic form 
to denote a type.


Consider the val of in the first component. Because of val's signature 
in the type class the type checker infers that the val expression has a 
type equivalent to T a2 for some a2. The type checker also expects a 
type equivalent to T a, either because of the type annotation or because 
of the left hand side. So the type checker must solve the equation T a ~ 
T a2 for some as yet to determine type a2 (a unification variable). This 
is precisely where the ambiguity comes in. The type constructor T is not 
injective. That means that the equation may hold for more than one value 
of a2 (e.g. for T Int ~ T a2, a2 could be Int or Bool). Hence, the type 
checker complains:


Couldn't match expected type `T a2' against inferred type `T a'.

Maybe you don't care what type is chosen, if multiple ones are possible. 
My example tried to show that this can effect the values computed by 
your program. So it does matter.


For this particular example, it seems that the type checker does not 
have have more than alternative for a2 in scope. However, it is not 
aware of that fact. It uniformly applies the same general strategy for 
solving equations in all contexts. This is a trade-off in type system 
complexity vs. expressivity.


There is an opportunity for exploring another point in the design space 
here.


Tom

--
Tom Schrijvers

Department of Computer Science
K.U. Leuven
Celestijnenlaan 200A
B-3001 Heverlee
Belgium

tel: +32 16 327544
e-mail: [EMAIL PROTECTED]
url: http://www.cs.kuleuven.be/~toms/


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


Re: [Haskell-cafe] Re: Small displeasure with associated type synonyms

2008-03-06 Thread Tom Schrijvers

I don't see how your example explains this particular error.
I agree Int cannot be generalized to (T Int) or (T Bool).


Generalized is not the right word here. In my example T Int, T Bool and 
Int are all equivalent.


I see Stefan's local type signature is not (val :: a) like your (val ::Int) 
but (val :: T a) which is a whole different beast.


Not all that different. As in my example the types T Int, T Bool and Int 
are equivalent, whether one writes val :: Int, val :: T Int or val :: T 
Bool. My point is that writing val :: T Int or val :: T Bool does not help 
determining whether one should pick the val implementation of instance C 
Int or C Bool.



And (T a) is the type that ghc should assign here.


As my example tries to point out, there is not one single syntactic form 
to denote a type.


Consider the val of in the first component. Because of val's signature in 
the type class the type checker infers that the val expression has a type 
equivalent to T a2 for some a2. The type checker also expects a type 
equivalent to T a, either because of the type annotation or because of the 
left hand side. So the type checker must solve the equation T a ~ T a2 for 
some as yet to determine type a2 (a unification variable). This is 
precisely where the ambiguity comes in. The type constructor T is not 
injective. That means that the equation may hold for more than one value 
of a2 (e.g. for T Int ~ T a2, a2 could be Int or Bool). Hence, the type 
checker complains:


Couldn't match expected type `T a2' against inferred type `T a'.

Maybe you don't care what type is chosen, if multiple ones are possible. 
My example tried to show that this can effect the values computed by your 
program. So it does matter.


For this particular example, it seems that the type checker does not have 
have more than alternative for a2 in scope. However, it is not aware of 
that fact. It uniformly applies the same general strategy for solving 
equations in all contexts. This is a trade-off in type system complexity 
vs. expressivity.


There is an opportunity for exploring another point in the design space 
here.


Tom

--
Tom Schrijvers

Department of Computer Science
K.U. Leuven
Celestijnenlaan 200A
B-3001 Heverlee
Belgium

tel: +32 16 327544
e-mail: [EMAIL PROTECTED]
url: http://www.cs.kuleuven.be/~toms/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Small displeasure with associated type synonyms

2008-03-06 Thread ChrisK

Tom Schrijvers wrote:

Stefan,


I tried lexically scoped type variables, but to no avail:

instance forall a b. (C a, C b) => C (a, b) where
  type T (a, b) = (T a, T b)
  val   = (val :: T a, val :: T b)


The problem is ambiguity. The type checker can't determine which val 
function to use, i.e. which dictionary to pass to val. Assume:


  instance C Int where
type T Int = Int
val= 0

  instance C Bool where
type T Bool = Int
val = 1

Now, if you want some val :: Int, which one do you get? The one of C Int 
of C Bool? Depending on the choice you may get a different result. We 
can't have that in a deterministic functional language. Hence the error.

Adding a type signature doesn't change the matter.


I don't see how your example explains this particular error.
I agree Int cannot be generalized to (T Int) or (T Bool).

I see Stefan's local type signature is not (val :: a) like your (val ::Int) but 
(val :: T a) which is a whole different beast.  And (T a) is the type that ghc 
should assign here.


The C (a,b) instance wants val :: T (a,b),  The T (a,b) is declared as "(T a, T 
b)".  The annotated val returns "(T a, T b)".  One never needs the sort of Int 
to (T Int) generalization.


So what is a better explanation or example to clarify why GHC cannot accept the 
original code?


--
Chris

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


[Haskell-cafe] If Version Control Systems were Airlines

2008-03-06 Thread Justin Bailey
Way off topic, but this is the cafe. The below is well worth reading.

  
http://changelog.complete.org/posts/698-If-Version-Control-Systems-were-Airlines.html

For the click-impaired, here's Darcs Airlines:

"Darcs Airlines:  Unlike every other airline, this one uses physicists
instead of engineers to design its airplanes. One brilliant Darcs
physicist has finally come up with The Theory of Everything, and as
such, Darcs knows where you want to go before even you do. Darcs
airlines prides itself on customer service, and asks your preference
for even the tiniest details about your trip.

Each seat pocket features a copy of the Theory of Everything for your
reading enjoyment, but nobody actually understands it.

Occasionally, you will find that Darcs pilots get into angry conflicts
with the control tower in mid-flight. This results in the control
tower revoking your permission to land. Legend has it that one Darcs
pilot of a plane with exceptionally large fuel tanks actually resolved
his conflict with the tower and landed two weeks after taking off.
Experienced Darcs users board with several parachutes: one for
themselves, and a few more for the newbies.

The Darcs physicists claim that the Theory of Everything predicted the
pilots would act this way, and that all pilots eventually act this way
throughout the entire universe. They toil day and night finding a way
to adjust the gravitational constant of the universe, thereby reducing
the anger factor of the pilots.

Main competitor: OS/2 airlines."

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


[Haskell-cafe] Re: Small displeasure with associated type synonyms

2008-03-06 Thread Tom Schrijvers

Stefan,


I tried lexically scoped type variables, but to no avail:

instance forall a b. (C a, C b) => C (a, b) where
  type T (a, b) = (T a, T b)
  val   = (val :: T a, val :: T b)


The problem is ambiguity. The type checker can't determine which val 
function to use, i.e. which dictionary to pass to val. Assume:


  instance C Int where
type T Int = Int
val= 0

  instance C Bool where
type T Bool = Int
val = 1

Now, if you want some val :: Int, which one do you get? The one of C Int 
of C Bool? Depending on the choice you may get a different result. We 
can't have that in a deterministic functional language. Hence the error.

Adding a type signature doesn't change the matter.

Providing an additional argument, as you propose, resolves the ambiguity.

I hope this helps.

Cheers,

Tom

--
Tom Schrijvers

Department of Computer Science
K.U. Leuven
Celestijnenlaan 200A
B-3001 Heverlee
Belgium

tel: +32 16 327544
e-mail: [EMAIL PROTECTED]
url: http://www.cs.kuleuven.be/~toms/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Starting Haskell with a web application

2008-03-06 Thread Bjorn Bringert
On Wed, Mar 5, 2008 at 8:00 PM, Don Stewart <[EMAIL PROTECTED]> wrote:
> bos:
>
> > Jonathan Gardner wrote:
>  >
>  > > Where do I get started in writing a web app with Haskell? I am looking
>  > > more for a framework like Pylons and less like Apache, if that helps.
>  >
>  > The closest we currently have to a web framework is Happs
>  > (http://happs.org/), but it uses the kitchen sink of advanced and
>  > unusual language extensions, which I think might be why it hasn't got
>  > all that much momentum.
>  >
>  > There's also WASH, but that has an even lower profile.  I couldn't tell
>  > you if it sees much use, or even builds with recent compilers.
>
>  Perhaps it is time for a haskell web apps wiki page, if there isn't one,
>  outlining the approaches, with a structure like:
>
> * HAppS
> * CGI
> - FastCGI
>
> * Database solutions
> - HDBC
> - Takusen
>
> * Templating
> - HStringTemplate
>
> * JSON rpc
>
>  etc.

There's this:

http://www.haskell.org/haskellwiki/Practical_web_programming_in_Haskell

It doesn't mention many of the above, but they would be nice
additions. The page should probably be split into several though.

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


Re: [Haskell-cafe] Small displeasure with associated type synonyms

2008-03-06 Thread Hugo Pacheco
I don't know if this is exactly what you were expecting as a dummy argument,
but I solve this kind of issues like this:

_L = undefined

class C a where
type TT a
val :: a -> TT a

instance C () where
type TT () = ()
val _ = ()

instance (C a, C b) => C (a, b) where
type TT (a,b) = (TT a, TT b)
val _ = (val (_L :: a),val (_L :: b))

Why normal unification (val :: TT a) does not work I can't say why, but this
kind of behavior is not solely for type families.

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


[Haskell-cafe] Re: ANN: Parsec 3.0.0

2008-03-06 Thread John MacFarlane
> * A "compatibility" Text.ParserCombinators.Parsec tree for the old 
>   Parsec.  It's not perfect, but it should work with most Parsec 2
>   code.

A data point: I recompiled pandoc with the new Text.ParserCombinators.Parsec
compatibility module, and performance is much worse than with
parsec 2.1 (approximately twice as slow on my standard benchmark).

That aside, this is a very welcome release!

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


Re: [Haskell-cafe] Starting Haskell with a web application

2008-03-06 Thread Adam Langley
On Thu, Mar 6, 2008 at 3:08 AM, Bayley, Alistair
<[EMAIL PROTECTED]> wrote:
>  Do you (both) have repos that I could download from? I quite interested
>  in both projects, esp. the WSGI clone.

There was a Hackage release of network-minihttp[1], which I think
would serve files from the filesystem quite happily. The darcs repo is
just a mess at the moment. (darcs.imperialviolet.org/network-minihttp)

[1] 
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/network-minihttp-0.1

AGL

-- 
Adam Langley [EMAIL PROTECTED] http://www.imperialviolet.org
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Small displeasure with associated type synonyms

2008-03-06 Thread Stefan Holdermans

Dear all,

I was doing a little experimentation with associated type synonyms and  
ran into a small but unforeseen annoyance. The following, contrived,  
example snippets illustrate my pain:


First, let us declare some of the simplest classes exhibiting  
associated type synonyms that I can think of,


  class C a where
type T a
val :: T a

together with a trivial instance for nullary products:

  instance C () where
type T () = ()
val   = ()

But then, let us try an instance for binary products:

  instance (C a, C b) => C (a, b) where
type T (a, b) = (T a, T b)
val   = (val, val)

I really thought this would work out nicely, but GHC (version 6.8.2)  
gracefully gives me


  Couldn't match expected type `T a2' against inferred type `T a'
Expected type: T (a2, b)
Inferred type: (T a, T a1)
  In the expression: (val, val)
  In the definition of `val': val = (val, val)

  Couldn't match expected type `T b' against inferred type `T a1'
Expected type: T (a2, b)
Inferred type: (T a, T a1)
  In the expression: (val, val)
  In the definition of `val': val = (val, val)

while I think I deserve better than that.

Can someone (Tom?) please explain (a) why the required unifications  
fail, (b) whether or not it is reasonable to expect the unifications  
to succeed, and (c) how I can overcome problems like these? Surely, I  
can have val take a dummy argument, but I am hoping for something a  
bit more elegant here.


I tried lexically scoped type variables, but to no avail:

  instance forall a b. (C a, C b) => C (a, b) where
type T (a, b) = (T a, T b)
val   = (val :: T a, val :: T b)

gives me

  Couldn't match expected type `T a2' against inferred type `T a'
  In the expression: val :: T a
  In the expression: (val :: T a, val :: T b)
  In the definition of `val': val = (val :: T a, val :: T b)

etc.

Cheers,

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


Re: [Haskell-cafe] Connection helpers: for people interested in network code

2008-03-06 Thread brad clawsie
> I wonder, though, what happened to the curl bindings for Haskell?

i offered some time ago to look at building a cabal package and
documentation for this. i would offer up excuses as to why this hasn't
appeared yet, but between kids, work and ski season i just haven't
allocated the time yet. sorry to all. i still hope to look into this,
but fair to say i dropped the ball.

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


Re: [Haskell-cafe] CABAL: conditional executable?

2008-03-06 Thread Magnus Therning
On 3/6/08, Magnus Therning <[EMAIL PROTECTED]> wrote:
>
> On 3/6/08, Magnus Therning <[EMAIL PROTECTED]> wrote:
> >
> > On 3/4/08, Thomas Schilling <[EMAIL PROTECTED]> wrote:
> >
> > >
> > > On 4 mar 2008, at 11.37, Magnus Therning wrote:
> > >
> > > > On 3/4/08, Thomas Schilling <[EMAIL PROTECTED]> wrote:
> > > > executable foo
> > > >main-is: bla
> > > >if !os(windows):
> > > >  buildable: false
> > > >
> > > > Unfortunately this gives rather unhelpful error messages when used
> > > > with flags, but it works well enough for now.
> > > >
> > > > / Thomas
> > > >
> > > > Hmmm, I don't seem to get this to work the way I want it.  I get a
> > > > "Parse of field 'buildable' failed:" which means configure failed
> > > > and then I can't proceed to build the second executable, bar, in
> > > > the same package.
> > >
> > >
> > > Oh, right.  That's a bug in Cabal 1.2 (fixed in HEAD).  Use:
> > >
> > >buildable: False
> >
> >
> > OK, that solved that problem, now onto the next.  Rather surprisingly to
> > me, buildability has an impact on what's included in the source tar-ball
> > created with "sdist".  What's the reason for that behaviour?
> >
>
> It seems the source isn't even included on the platform where the
> executable *is* buildable.  I'll see if I can put together a small example
> and raise a bug.
>

Done, http://hackage.haskell.org/trac/hackage/ticket/257

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


Re: [Haskell-cafe] CABAL: conditional executable?

2008-03-06 Thread Magnus Therning
On 3/6/08, Magnus Therning <[EMAIL PROTECTED]> wrote:
>
> On 3/4/08, Thomas Schilling <[EMAIL PROTECTED]> wrote:
>
> >
> > On 4 mar 2008, at 11.37, Magnus Therning wrote:
> >
> > > On 3/4/08, Thomas Schilling <[EMAIL PROTECTED]> wrote:
> > > executable foo
> > >main-is: bla
> > >if !os(windows):
> > >  buildable: false
> > >
> > > Unfortunately this gives rather unhelpful error messages when used
> > > with flags, but it works well enough for now.
> > >
> > > / Thomas
> > >
> > > Hmmm, I don't seem to get this to work the way I want it.  I get a
> > > "Parse of field 'buildable' failed:" which means configure failed
> > > and then I can't proceed to build the second executable, bar, in
> > > the same package.
> >
> >
> > Oh, right.  That's a bug in Cabal 1.2 (fixed in HEAD).  Use:
> >
> >buildable: False
>
>
> OK, that solved that problem, now onto the next.  Rather surprisingly to
> me, buildability has an impact on what's included in the source tar-ball
> created with "sdist".  What's the reason for that behaviour?
>

It seems the source isn't even included on the platform where the executable
*is* buildable.  I'll see if I can put together a small example and raise a
bug.

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


[Haskell-cafe] [GSoC] Project proposal: Hoogle 4

2008-03-06 Thread Neil Mitchell
Hi

I would like to be a Summer of Code student, doing the project "Hoogle
4" (http://haskell.org/hoogle/)

PROJECT GOALS:

There are two main themes:

1) Make Hoogle more useful to the community, along the same path as it
is currently used.

2) Make Hoogle suitable to use as the standard interface to Hackage.

This requires adding the following features to Hoogle, to form a
Hoogle 4 release:

* Faster searching (1000x faster at least, perhaps more like 100x
for text searching)
* Generalised text searching (i.e. searching .cabal fields)
* Removal of all bugs :-)
* Support for higher-kinded type classes (i.e. Monads)
* Support for some Haskell type extensions (i.e. Multi-Parameter type classes)
* Support for multiple packages
* Generalised interface to all of Cabal

Progress on Hoogle 4 has already started, but has currently stalled
due to lack of time. I am writing up my PhD currently, and will be
available to start at the beginning of the Summer to work on Hoogle.

Duncan Coutts has agreed to mentor this project. The position of
backup mentor is still available. I do not expect to need a great deal
of supervision :-)

Please respond with any suggestions, requests for further information
or just general comments.

Thanks

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


Re: [Haskell-cafe] CABAL: conditional executable?

2008-03-06 Thread Magnus Therning
On 3/4/08, Thomas Schilling <[EMAIL PROTECTED]> wrote:
>
>
> On 4 mar 2008, at 11.37, Magnus Therning wrote:
>
> > On 3/4/08, Thomas Schilling <[EMAIL PROTECTED]> wrote:
> > executable foo
> >main-is: bla
> >if !os(windows):
> >  buildable: false
> >
> > Unfortunately this gives rather unhelpful error messages when used
> > with flags, but it works well enough for now.
> >
> > / Thomas
> >
> > Hmmm, I don't seem to get this to work the way I want it.  I get a
> > "Parse of field 'buildable' failed:" which means configure failed
> > and then I can't proceed to build the second executable, bar, in
> > the same package.
>
>
> Oh, right.  That's a bug in Cabal 1.2 (fixed in HEAD).  Use:
>
>buildable: False


OK, that solved that problem, now onto the next.  Rather surprisingly to me,
buildability has an impact on what's included in the source tar-ball created
with "sdist".  What's the reason for that behaviour?

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


[Haskell-cafe] Re: [Haskell] Google summer of code

2008-03-06 Thread Neil Mitchell
Hi

>  There are some ideas still there from last year, in the trac tickets.
>  However, due to the amount of spam accumulating there, I suggest that
>  this year, we use the haskell-cafe email list as a place to put out
>  project ideas, solicit feedback on them, and look for interested people.
>  Prefix any message subject line with with [GSoC] to help others find
>  them.

I like the idea of a bug tracker for these projects, but trac is
obviously not sufficient. Why not use the best bug tracker there is,
namely the Google Code Bug Tracker. I worry that emails will end up
getting lost in the crowd, or that the replies from the list may not
reflect the view of the potential mentors accurately.

Thanks

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


[Haskell-cafe] Google summer of code

2008-03-06 Thread Malcolm Wallace
Reply-To: haskell-cafe@haskell.org

Google Summer of Code

As many of you will already know, Google is running its "Summer of Code"
project again this year, and haskell.org is once again going to apply to
be a mentoring organisation.  Are you a student who would like to earn
money for hacking in Haskell?  Or are you a non-student who has a cool
idea for a coding project but no time to do it yourself?

Well, our wiki to gather ideas is now up-and-running again:
http://hackage.haskell.org/trac/summer-of-code

Add yourself to the list of interested people!  Especially potential
mentors.

There are some ideas still there from last year, in the trac tickets.
However, due to the amount of spam accumulating there, I suggest that
this year, we use the haskell-cafe email list as a place to put out
project ideas, solicit feedback on them, and look for interested people.
Prefix any message subject line with with [GSoC] to help others find
them.

Google will start accepting student applications on 24th March, but now
is the time to start gathering thoughts and matching up interesting
ideas with interested people.

The official timeline is as follows:

 March 12: Mentoring organization application deadline
 March 17: List of accepted mentoring organizations published
 March 24: Student application period opens
 March 31: Student application deadline

 Interim Period: we review and rank student proposals
 April 14: List of accepted student applications published

 Interim Period: Students learn more about their project communities
 May 26: Students begin coding; Google begins issuing initial payments
 July 14: Google begins issuing mid-term payments
 August 11: Suggested end of coding
 August 18: Definite end of coding
 Sept 1: Final evaluation deadline; Google begins issuing final payments
 Sept 3: Students upload code to Google (required)

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


Re: [Haskell-cafe] Starting Haskell with a web application

2008-03-06 Thread Lars Viklund
On Wed, Mar 05, 2008 at 10:52:07AM -0800, Bryan O'Sullivan wrote:
> Jonathan Gardner wrote:
> 
> There's also WASH, but that has an even lower profile.  I couldn't tell
> you if it sees much use, or even builds with recent compilers.

The HTML component of WASH builds rather cleanly with GHC 6.8.2 after
enabling the following extensions:
MultiParamTypeClasses FlexibleContexts FlexibleInstances TypeSynonymInstances

I use it for my statically generated blog, together with sqlite3. I've
modified WASH/HTML to spit out reasonably correct XHTML as well.

As for the rest of WASH, I have no idea since I had no need for it.

--
Lars Viklund | [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Starting Haskell with a web application

2008-03-06 Thread Johan Tibell
>  Do you (both) have repos that I could download from? I quite interested
>  in both projects, esp. the WSGI clone.

Yes and no. The code [1] is in my darcs repository but is in an
unusable state until I've fixed my incremental parser (in
Hyena/Parser.hs) which I plan to do next week. I would like the first
release to be nice and polished so I'm trying to not release anything
prematurely.

1. http://darcs.johantibell.com/hyena/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] SimpleArgs

2008-03-06 Thread Henning Thielemann

On Thu, 6 Mar 2008, Ketil Malde wrote:

> Often when I write small scripts, I find I just want a couple of
> command line arguments but don't want to go the whole GetOpt route.
> SimpleArgs is an attempt to make the raw getArgs somewhat less raw,
> and quick and dirty scripts a bit less dirty without sacrificing the
> quickness.

I also thought command line parsing is cumbersome until I found:
   http://www.haskell.org/haskellwiki/High-level_option_handling_with_GetOpt

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


[Haskell-cafe] SimpleArgs

2008-03-06 Thread Ketil Malde

Hi,

Often when I write small scripts, I find I just want a couple of
command line arguments but don't want to go the whole GetOpt route.
SimpleArgs is an attempt to make the raw getArgs somewhat less raw,
and quick and dirty scripts a bit less dirty without sacrificing the
quickness.

Since I find this quite useful, I thought I'd advertise the code here,
ask what people think, and invite suggestions for improvement.  It's
at:
 http://malde.org/~ketil/simpleargs

-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] Starting Haskell with a web application

2008-03-06 Thread Bayley, Alistair
> From: [EMAIL PROTECTED] 
> [mailto:[EMAIL PROTECTED] On Behalf Of Johan Tibell
> 
> I'm writing a web application server which I'm trying to make as
> simple to manage as Mongrel [1], a popular Ruby web server used to
> host web application written in e.g. Ruby on Rails. It uses Oleg style
> enumerators and ByteString internally to safely an efficiently manage
> resources. The web application interface is that of Python's WSGI [2]
> but adapted to a Haskell style. I've been busy lately but starting
> this weekend I will have much more time to work on it and can
> hopefully make a first release.
> 
> 1. http://mongrel.rubyforge.org/ - I believe the original author left
> the project so the projects original website is gone.
> 2. http://www.python.org/dev/peps/pep-0333/

Do you (both) have repos that I could download from? I quite interested
in both projects, esp. the WSGI clone.

Alistair
*
Confidentiality Note: The information contained in this message,
and any attachments, may contain confidential and/or privileged
material. It is intended solely for the person(s) or entity to
which it is addressed. Any review, retransmission, dissemination,
or taking of any action in reliance upon this information by
persons or entities other than the intended recipient(s) is
prohibited. If you received this in error, please contact the
sender and delete the material from any computer.
*

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


Re: [Haskell-cafe] Starting Haskell with a web application

2008-03-06 Thread Johan Tibell
On Wed, Mar 5, 2008 at 8:25 PM, Adam Langley <[EMAIL PROTECTED]> wrote:
> On Wed, Mar 5, 2008 at 11:07 AM, Bryan O'Sullivan <[EMAIL PROTECTED]> wrote:
>  >  Indeed.  In addition to the code you mention, people like Adam Langley
>  >  and Johan Tibbell are taking on corners of the web app problem space in
>  >  a more modern context.
>
>  I should probably speak up then ;)

Me too! ;)

I'm writing a web application server which I'm trying to make as
simple to manage as Mongrel [1], a popular Ruby web server used to
host web application written in e.g. Ruby on Rails. It uses Oleg style
enumerators and ByteString internally to safely an efficiently manage
resources. The web application interface is that of Python's WSGI [2]
but adapted to a Haskell style. I've been busy lately but starting
this weekend I will have much more time to work on it and can
hopefully make a first release.

1. http://mongrel.rubyforge.org/ - I believe the original author left
the project so the projects original website is gone.
2. http://www.python.org/dev/peps/pep-0333/

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