Re: [Haskell-cafe] Why Not Haskell?

2006-08-09 Thread Antti-Juhani Kaijanaho

Albert Lai wrote:

Let's have a fun quiz!  Guess the mainstream languages in question:


Spoilers for the quiz




































0. What language would allow

  4[hello world]

   when a normal person would just write

  hello world[4]


This is a classic C misfeature.


1. What language, supporting a kind of both parametric polymorphism
   and subclass polymorphism, allows and actually features such a class
   declaration as

 class EnumT extends EnumT { ... }


I have to guess here. Java.


2. What language allows you to test primality in constant runtime?
   That is, move all the work to compile time, using its polymorphism.


C++, also a classic feature. There are even books that discuss this 
technique, and I believe a SPJ paper referring to it.

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


Re: [Haskell-cafe] Re: Why Not Haskell?

2006-08-09 Thread Immanuel Litzroth
Reilly Hayes [EMAIL PROTECTED] writes:

 On Aug 8, 2006, at 1:42 AM, Immanuel Litzroth wrote:


 Reilly Hayes [EMAIL PROTECTED] writes:





 I don't understand your argument. How exactly does the GPL get in the
 way of selling software as an instantiation of business expertise?
 Are you saying that you have the business expertise but customers
 still prefer not to buy your software? Doesn't that just mean that
 your expertise isn't worth much (economic evaluation :-). Or that your
 idea that they were buying expertise was not correct, they were just
 buying the software after all, and now they have an alternative?



 I failed to communicate my case clearly.  The software *is* what is being
 sold.  The *reason* it is valuable is the business expertise required to build
 it.  There are markets with very small populations of people who both
 understand the business thoroughly and can implement solutions.  It makes
 software valuable and makes licensing the most effective way to monetize that
 value.

I am not arguing that licensing would not be a very effective way to
monetize value. 


 Yes I know the business model. Sell them some overpriced software
 charge them through the nose for support, features, training,
 installation, updates 
 Your resentment against the GPL stems from the fact that it makes
 squeezing the last buck out of your clients somewhat harder (in some
 markets). It probably annoys you that you are not dealing with a
 competitor who is making shitloads of money, making some price fixing
 or secret agreements not feasable. Your problem is that just as your
 business practice is not illegal, neither is the GPL.


 This paragraph is way out of line.  You have taken a discussion of the merits
 of using GPL software and turned it into a personal attack.  Attack the
 argument, not the arguer.  It would be both polite and reasonable to tone down
 the hostility if you actually want a discussion.

Yeah, it might have been harsh and I apologize. But I just describe
what I have seen in some of the companies I worked for.  

 I don't have a problem with the GPL.  In my professional life,  I am careful 
 to
 avoid GPL software in those cases where the GPL would interfere with the 
 firm's
 commercial interests.  I certainly don't resent the GPL or those who choose to
 release software under the GPL.  In fact, I can imagine wanting to release 
 some
 kinds of software under the GPL.

 The point I was making was that the GPL *does* get in the way of *some* 
 optimal
 mechanisms of making money.  Which is *fine*.  That is one of the *intents* of
 the GPL.  The argument that I am trying to counter is the one that says open
 source is *always* better for everybody. 

I don't think the *intent* of the GPL is to get in the way of some
optimal ways of making money. Can you tell me which part of the GPL
makes you think? It might have that side-effect though.

 Sometimes, the best thing for the
 owner of the intellectual property is to keep it closed.  There *are* markets
 where monetization of IP is a zero sum game, or worse (if the IP is public,
 nobody makes any money).

I wonder who you see as the participants in this game? A worse than
zero sum game might be interesting if you are one of the people who
score positive and some of the other people have to pay for it. 
Gambling is a fine example.

 I'm not making (or getting involved in) the moral argument about free
 or open
 software.  I will point out that the current good health of Haskell
 owes a
 great deal to Microsoft through the computer scientists they employ. 
 I'm sure
 Haskell has benefitted from the largesse of other companies as well.


 That is definitely wrong. Haskell would be in even greater shape if
 some people who shall remain unnamed had not gone over to Microsoft. I
 foresee an interesting discussion here.


 I don't see how you can say Haskell would be better OR worse off if people
 hadn't gone to work for Microsoft.  It's an entirely hypothetical case and 
 it's
 just not knowable.  My point is much simpler.  Haskell  GHC do benefit from
 the efforts of people being paid by Microsoft.  Microsoft is planning to hire 
 a
 full-time contractor to work on GHC.

It seems irony gets lost so easily in these conversations. You have no
way of knowing what the state of haskell would have been had certain
key contributors to GHC and Haskell not taken jobs at Microsoft. 
Therefore you statement is meaningless and only good for producing
approving nods among people who already agree with what you say. 

 The snarky comment about people who shall remain unnamed is rude.
I did not mean to be rude, and would like to apologize if anyone felt 
personally attacked by this. 
Immanuel

-- 
***
I can, I can't.
Tubbs Tattsyrup

--
Immanuel 

[Haskell-cafe] AJAX applications in Haskell

2006-08-09 Thread tittoassini








Hi,



Those among you who have an interest in AJAX-style web
development  that is to say the development of web applications that run
entirely into the browser environment, calling back to the server back-end only
to get raw data -- will probably have noticed the recent appearance of the
Google Web Toolkit (http://code.google.com/webtoolkit).



The main idea behind it is very simple: you write your Ajax application in Java and
your code is compiled down to _javascript_/HTML (rather then to Java Virtual
Machine bytecode) so that it can be executed in any browser.





The main advantages of this solution are:

- Development using a typed language with good compile-time checks
and debugger support 

- No plugins (e.g. a Java VM) required on the user machine





The disadvantages are:

- An additional compilation step

- Probably, a significant loss of performance with respect
to hand-written code





Assuming that the balance is positive, this naturally raises
the question: why not doing the same with our favourite language?



This would require to:

-
Retarget one of the existing Haskell
compilers to generate _javascript_ (other possible targets would be Flash or
higher level UI languages such as OpenLaszlo that in turn compiles down to
either Flash or _javascript_/HTML)

-
Write a suitable runtime library
(including support for native _javascript_ or Flash UI components, remote method
invocations, multi-threading, etc.)

-
Port a usable subset of the Haskell
Libraries

-
Select an approach to write user
interfaces in Haskell. There have been many attempts in this direction but I am
unsure if any of them has proven particularly successful.



All considered, quite a significant amount of work -- that would
require a concerted group effort -- with a rather uncertain pay-off.





Is anyone working on anything similar or that might be
interested in such a project?





And has anyone any thoughts to offer on what
compilers/libraries/UI frameworks would be more suitable for the task?







Regards,



 titto assini


























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


Re: [Haskell-cafe] Why Not Haskell?

2006-08-09 Thread Robert Dockins

On Aug 8, 2006, at 5:36 PM, Albert Lai wrote:


Brian Hulley [EMAIL PROTECTED] writes:


Also, the bottom line imho is that Haskell is a difficult language to
understand, and this is compounded by the apparent cleverness of
unreadable code like:

 c = (.) . (.)

when a normal person would just write:

 c f g a b = f (g a b)


All mainstream languages are also difficult to understand, with
similarly clever, unreadable code.  Let's have a fun quiz!  Guess the
mainstream languages in question:


[snip]


2. What language allows you to test primality in constant runtime?
   That is, move all the work to compile time, using its polymorphism.


GHC-Haskell (with enough extensions enabled)?  We're most of the way  
there already with type arithmetic.  I bet putting together a nieve  
primality test would be pretty doable.  In fact, I suspect that GHC's  
type-checker is turing-complete with MPTCs, fundeps, and undecidable  
instances.  I've been contemplating the possibility of embedding the  
lambda calculus for some time (anybody done this already?)


Oops.  I see now the qualifier mainstream.  The point still stands,  
however.



Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


Re: [Haskell-cafe] Abstract Data Types

2006-08-09 Thread Robert Dockins


On Aug 9, 2006, at 5:27 AM, Johan Grönqvist wrote:


Hi,

I have a question:

Short version: If I want to hide the implementation of a data-type  
Stack a from the rest of the program,  do I need to put its  
definition in a separate file?




This is the usual way, as you've probably gathered.



Long version:

I want to use a stack, and I might implement it as a list, but I  
want to hide the implementation from the rest of the program. This  
is how I understand abstract data type.


In The Craft of Functional Programming, this seems to be  
implemented by putting each data type into a separate module and  
only exporting parts of the definitions.


In The Haskell School of Expression, this seems not to be used at  
all.


In the lecture notes at (http://www.dcs.shef.ac.uk/~mps/courses/ 
com2020/adts.pdf), type classes are used for abstract data types.  
It seems to me that this approach does not hide any parts of any  
definition, but only requires that all instances of class stack  
have functions pop and push of the correct types. I am interested  
in hiding parts of definitions.


In the report, I did not find any mention of a requirement to have  
different modules in separate files, but I have not managed to put  
several modules in the same file using ghci.



I think all current implementations require separate files for  
separate modules, although I believe you are correct that is is not  
required by the report.



I would like to keep my small program in one literate-haskell tex- 
file and still be able to hide some definitions from others.


Is this possible?

One option would of course be to write a script that separates the  
code into different and then compiles the entire program.




There are two other basic ways that I know of to achieve data type  
abstraction.



1) Parametric polymorphism

Create a typeclass with the appropriate operations.  Then, in  
functions which use stack operations, always write, eg:



doSomething :: Stack s = s a - Bool

rather than

doSomething :: ConcreteStackType a - Bool



This is abstraction at the point of use if you will.  You'll see  
this technique pretty often used to abstract over different Monads,  
for example.




2) Exestential datatypes.  You can create a sort of poor-man's  
substitute for ML style module systems by using existential data  
types.  Its a little fiddly, but it mostly works:



{-# OPTIONS -fglasgow-exts #-}

import Data.Maybe (isJust)


data StackRec a = forall s. Show (s a) = StackRec (s a) (a - s a -  
s a) (s a - s a) (s a - Maybe a)

listStackRec =
   StackRec
  []
  (:)
  (\xs - case xs of (_:ys) - ys; [] - [])
  (\xs - case xs of (y:_) - Just y; [] - Nothing)


fauxModule :: IO ()
fauxModule =
  case listStackRec of { StackRec empty push pop peek - do

print (isJust (peek (pop (pop (push 'a' empty)
print (push 'b' empty)

-- doesn't typecheck
--print (push 'c' [])

  }

main = fauxModule




Unfortunately, the case statement gives you monomorphic bindings for  
the stack methods, and let bindings don't play nice with  
existentials.  I'm not sure if there's a way around this or not.




Thanks in advance!

/ johan grönqvist



Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


Re: [Haskell-cafe] HWS - With Plugins

2006-08-09 Thread Henning Thielemann

On Tue, 8 Aug 2006, Johan Tibell wrote:

 The HWS - With Plugins tarball is unavailable at the author's website
 (http://www.mdstud.chalmers.se/~md9ms/hws-wp/) and his email address
 doesn't work so this is desperate attempt to reach him. So, Martin
 Sjögren, are you here somewhere?

I tried this too, with no success and eventually settled on WASH's variant 
of the original Haskell Webserver.
 http://www.informatik.uni-freiburg.de/~thiemann/WASH/#wsp

 P.S. If someone else knows where I could get hold of the source or at
 least the source of the original HWS I would be greatful.

http://cvs.haskell.org/cgi-bin/cvsweb.cgi/fptools/hws/

However I found it hard to compile and when it run, it didn't do so for
long time, because a space leak eventually brought the server down.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why Not Haskell?

2006-08-09 Thread Donald Bruce Stewart
robdockins:
 On Aug 8, 2006, at 5:36 PM, Albert Lai wrote:
 
 Brian Hulley [EMAIL PROTECTED] writes:
 
 Also, the bottom line imho is that Haskell is a difficult language to
 understand, and this is compounded by the apparent cleverness of
 unreadable code like:
 
  c = (.) . (.)
 
 when a normal person would just write:
 
  c f g a b = f (g a b)
 
 All mainstream languages are also difficult to understand, with
 similarly clever, unreadable code.  Let's have a fun quiz!  Guess the
 mainstream languages in question:
 
 [snip]
 
 2. What language allows you to test primality in constant runtime?
That is, move all the work to compile time, using its polymorphism.
 
 GHC-Haskell (with enough extensions enabled)?  We're most of the way  
 there already with type arithmetic.  I bet putting together a nieve  
 primality test would be pretty doable.  In fact, I suspect that GHC's  
 type-checker is turing-complete with MPTCs, fundeps, and undecidable  
 instances.  I've been contemplating the possibility of embedding the  
 lambda calculus for some time (anybody done this already?)

http://haskell.org/haskellwiki/Type_arithmetic#A_Really_Advanced_Example_:_Type-Level_Lambda_Calculus

also

http://haskell.org/haskellwiki/Type_arithmetic#An_Advanced_Example_:_Type-Level_Quicksort

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


[Haskell-cafe] Re: Haskell-Cafe Digest, Vol 36, Issue 29

2006-08-09 Thread Mark Haniford
It seems irony gets lost so easily in these conversations. You have no
way of knowing what the state of haskell would have been had certainkey contributors to GHC and Haskell not taken jobs at Microsoft.Therefore you statement is meaningless and only good for producingapproving nods among people who already agree with what you say.
What's meaningless are GPL jihadists who are bitter that not everybody is joining their religion.Yeah...that's personal. 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] AJAX applications in Haskell

2006-08-09 Thread Jared Updike

This would require to:

- Retarget one of the existing Haskell compilers to generate JavaScript
(other possible targets would be Flash or higher level UI languages such as
OpenLaszlo that in turn compiles down to either Flash or JavaScript/HTML)


As I've noticed from experience, you can just write JavaScript itself!
(You will end up doing this a lot anyway because any library is bound
to be missing some feature you need, say, input textbox history w/
up/down keys, or, say, autoscroll to bottom of iframe when content
added, etc. as here):

 http://www.ugcs.caltech.edu/~lordkaos/calc.cgi

(source available here http://www.ugcs.caltech.edu/~lordkaos/calc.tar.gz)


Is anyone working on anything similar or that might be interested in such a
project?


I'm definitely interested in this. I would love to be able to deploy a
Haskell application in the web browser w/out having to drain server
computing resources. Imagine reading a Haskell tutorial and providing
interactive applications that run in the reader's browser, etc.

Also, I really would love to see something in Haskell that can compete
with the Web Services / Web Forms stuff from Visual Studio 2005/C# in
terms of simplicity and power and feature-completeness: just write
your app and it generates all the HTML/CSS/JavaScript on the client
and the XML request stuff on the serve. Perhaps in Haskell we could
have something fugdets-like but deployable in any (relatively recent)
browser w/ no downloads.

 Jared.
--
http://www.updike.org/~jared/
reverse )-:
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: beginner's haskell question

2006-08-09 Thread Jens Theisen

J. Garrett Morris wrote:

The ghc flag -fwarn-incomplete-patterns might be what you're looking for.


Donald Bruce Stewart wrote:
 You might just want to always use:
 -Wall -Werror

Thanks, I should have read the manual...

Jens

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


[Haskell-cafe] Re: Type hackery help needed!

2006-08-09 Thread Niklas Broberg

| It seems you might benefit from local functional dependencies, which
| are asserted per instance rather than for the whole class. They are
| explained in
|
| http://pobox.com/~oleg/ftp/Haskell/typecast.html

Unfortunately I come crawling back with a failure. Either my fu was
not strong enough to fully tame the power of the TypeCast, or there's
something here that's trickier than I realize.

This message is a literate haskell source file, and I'll set the scene
more carefully this time. Note that many of my definitions here are
not really definitions but part of the literate comments.


{-# OPTIONS_GHC -fglasgow-exts #-}
{-# OPTIONS_GHC -fallow-overlapping-instances #-}
{-# OPTIONS_GHC -fallow-undecidable-instances #-}
module GenXML where


We start out with a (very simplified) datatype for XML:


data XML = Element String [XML] | CDATA String


We want to be able to generate XML values of this type using a
function (not that this is still a comment)

 build :: String - [XML] - XML
 build = Element

The intended use of build is as the unsugared counterpart of HSP-style
XML-like syntax, for instance

 p c = p% c %/p  =desugar= p c = build p [embed c]

However, we also want to use this syntax to generate values of other
possible representations of XML, so we put the function definition in
a type class:


class Build xml child | xml - child where
  build :: String - [child] - xml
  asChild :: xml - child


Read out, we can build values of type xml holding children of type
child. The use of asChild will be evident below. Clearly XML should
fit for this, so we define the instance


instance Build XML XML where
 build = Element
 asChild = id


The next step is to allow values of different types to be embedded
inside XML elements using the embed function:


class Build xml child = Embed a xml child where
  embed :: xml - a - child


In English, we can embed values of type a into a tree of type xml, by
turning it into something of type child. (The first argument to
'embed' is only there to guide type inference, instantiations of the
class are not allowed to look at it.)

As an example, now we can embed String values into a tree of type XML:


instance Embed String XML XML where
 embed _ = CDATA


Clearly we also want to be able to embed XML values as children of
some element, so we could define (comment)

 instance Embed XML XML XML where
  embed _ = id

Now we can define p as


p c = let x = build p [embed x c] in x


and define a test function (comment)

 test :: XML
 test1 = p (p foo)

and if we do we get the following error from GHCi:

GenXML.hs:25:8:
   No instance for (Embed a xml XML)
 arising from use of `p' at GenXML.hs:25:8
   Probable fix: add an instance declaration for (Embed a xml XML)
   In the definition of `test1': test1 = p (p foo)

GenXML.hs:25:11:
   No instance for (Embed [Char] xml child)
 arising from use of `p' at GenXML.hs:25:11
   Probable fix: add an instance declaration for (Embed [Char] xml child)
   In the first argument of `p', namely `(p foo)'
   In the definition of `test1': test1 = p (p foo)


The problem is that the type of the intermediate value (p foo)
cannot be determined. Looking at the type of p we see

 p :: (Build a1 child, Embed a xml child) = a - a1

This is pretty obvious, we have no way of knowing what the result of p
should be just by its use, it is polymorphic in its result type, and
we get no help with inference from the usage site either since it then
occurs in a polymorphic position too.

But my intention here, which is really the core of my problem, is that
I want to disambiguate this problem, by stating (somehow) that if the
result of a build is embedded inside another build, the result types
of the two should be identical. That is, if we want to generate
subtrees of some tree, we should generate them as having the correct
type immediately.

My first attempt was to define the instance

 instance (Build xml child) = Embed xml xml child where
  embed _ x = asChild x

but it didn't quite work out, the instance selection still couldn't
know what the result of the generation should be, so I still get the
same error as above.

When I saw TypeCast I thought I had the answer to my problems, and
tried to define


class TypeCast   a b   | a - b, b-a   where typeCast   :: a - b
class TypeCast'  t a b | t a - b, t b - a where typeCast'  :: t-a-b
class TypeCast'' t a b | t a - b, t b - a where typeCast'' :: t-a-b
instance TypeCast'  () a b = TypeCast a b where typeCast x = typeCast' () x
instance TypeCast'' t a b = TypeCast' t a b where typeCast' = typeCast''
instance TypeCast'' () a a where typeCast'' _ x  = x



instance (Build xml child, TypeCast x xml) = Embed x xml child where
   embed _ x = asChild (typeCast x :: xml)


(Btw, why is the type signature needed for typeCast? Shouldn't it be
given by the FD from the TypeCast 

[Haskell-cafe] IA64 porting: spill code in the mangler

2006-08-09 Thread C Rodrigues

Hi folks,

I've been trying to compile a new ia64 port.  I've cross-compiled an 
unregisterised compiler that generated working binaries the first time it 
was built, which was a pleasant experience.  But I ran into issues with the 
registerised build.  The mangler is choking on floating-point spill code:


Prologue junk?: .global __divdf3#
   .global GHCziFloat_zdwlogBase_entry#
   .proc GHCziFloat_zdwlogBase_entry#
GHCziFloat_zdwlogBase_entry:
   mov r16 = r12
   .save.f 0x1
   stf.spill [r16] = f2
   .body

This saves floating-point register 2 on the stack; it's loaded again later.  
I could change the mangler to remove this code, if that's the right 
approach.  What should the mangler do about it?



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


[Haskell-cafe] AJAX applications in Haskell

2006-08-09 Thread Adam Peacock

On 8/10/06, Jared Updike [EMAIL PROTECTED] wrote:
[..]

  http://www.ugcs.caltech.edu/~lordkaos/calc.cgi

(source available here http://www.ugcs.caltech.edu/~lordkaos/calc.tar.gz)


I've only recently joined this mailing list, and there seems to be a
considerable amount of talk about Haskell and web applications.
Although I can't seem find any commercial sites using Haskell. I'm not
after examples like the WASH gallery, I'm after non-trivial, real or
commercial applications using Haskell and the web.

Does anyone know of any?

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