Re: [Haskell-cafe] proposal: HaBench, a Haskell Benchmark Suite

2007-01-28 Thread Andy Georges

Hi,

Following up and the threads on haskell and haskell-cafe, I'd like  
to gather ideas, comments and suggestions for a standarized Haskell  
Benchmark Suite.


The idea is to gather a bunch of programs written in Haskell, and  
which are representative for the Haskell community (i.e. apps,  
libraries, ...). Following the example of SPEC (besides the fact  
that the SPEC benchmarks aren't available for free), we would like  
to build a database containing performance measurements for the  
various benchmarks in the suite. Users should be able to submit  
their results. This will hopefully stimulate people to take  
performance into account when writing a Haskell program/library,  
and will also serve as a valuable tool for further optimizing both  
applications written in Haskell and the various Haskell compilers  
out there (GHC, jhc, nhc, ...).


This thread is meant to gather peoples thought on this subject.
Which programs should we consider for the first version of the  
Haskell benchmark suite?
How should we standarize them, and make them produce reliable  
performance measurement?
Should we only use hardware performance counters, or also do more  
thorough analysis such as data locality studies, ...
Are there any papers available on this subject (I know about the  
paper which is being written as we speak ICFP, which uses PAPI as a  
tool).


I think that we should have, as David Roundy pointed out, a  
restriction to code that is actually used frequently. However, I  
think we should make a distinction between micro-benchmarks, that  
test some specific item, and real-life benchmarks. When using micro  
benchmarks, the wrong conclusions may be drawn, because e.g., code or  
data can be completely cached, there are no TLB misses after startup,  
etc. I think that is somebody is interested in knowing how Haskell  
performs, and if he should use it for his development, it is nice to  
know that e.g., Data.ByteString performs as good as C, but is would  
be even nicer to see that large, real-life apps can reach that same  
performance. There is more to the Haskell runtime than simply  
executing application code, and these things should also be taken  
into account.


Also, I think that having several compilers for the benchmark set is  
a good idea, because, afaik, they can provide a different runtime  
system as well. We know that in Java, the VM can have a significant  
impact on behaviour on the microprocessor. I think that Haskell may  
have similar issues.


Also, similar to SPEC CPU, it would be nice to have input sets for  
each benchmark that gets included into the set. Furthermore, I think  
that we should provide a rigorous analysis of the benchmarks on as  
many platforms as is feasible. See e.g., the analysis done for the  
Dacapo Java benchmark suite, published at OOPSLA 2006.


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


Re: [Haskell-cafe] State of OOP in Haskell

2007-01-28 Thread Lennart Augustsson

OOHaskell is ingenious, but it's a terrible way to use Haskell.
It's very unidiomatic Haskell, and it makes you do things in the
same old OO way.  Presumably people are using Haskell to do things
differently?
But as I said, I consider OOHaskell itself a work of genius. :)

-- Lennart

On Jan 27, 2007, at 22:24 , Alexy Khrabrov wrote:


What about this OOHaskell:

http://homepages.cwi.nl/~ralf/OOHaskell/

-- how is it received in the café?  :)

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


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


Re: [Haskell-cafe] Re: IO in lists

2007-01-28 Thread Yitzchak Gale

Hi Magnus,

You wrote:

This piece has type problems.  I couldn't get ghci to
accept it without making some changes...


You are absolutely correct, and I apologize for the errors.
I will try one more time to give a corrected version below.

Let me point out, though, that this does not exactly solve the
problem you originally stated. Here is a summary and
clarification of what we have come up with together so far:

First, I said that it sounds like what you really want is ListT.

But you pointed out that my ListT solution gave you the wrong
order of interaction.

The reason for this problem is a bug in the implementation
of ListT in the standard libraries, which is explained on the
wiki page:

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

Dan Piponi posted a solution to your problem that works
the way you want it, and without unsafeInterleaveIO.
Dan's solution is just ListT in disguise, except that Dan
used the corrected form of ListT like on the wiki page.

My code in which you found the errors is a translation
of Dan's solution back into ListT notation. So if you
use that with the broken ListT currently in the standard
libraries, you'll go back to the problem we had at the
beginning.

Here is the bottom line:

You can solve your problem - without unsafeInterleaveIO -
either by using one of the corrected versions of ListT
listed on the wiki page, or by writing out an implementation
of ListT that is hard-wired for your application like Dan
did.

OK, so here is my translation of Dan's code back
into ListT notation again. I hope this version is now correct:

test = do
a - liftIO getChar
guard $ a /= 'q'
return a `mplus` test

test2 = (= liftIO . print)

Run it with:

runListT $ test2 test

Note that you probably want putChar instead of print.
Also, Dan's version drops the 'q' at the end, while
your code prints the 'q'.

Hope this helps.

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


[Haskell-cafe] OOP parametric polymorphism

2007-01-28 Thread apfelmus
Donald Bruce Stewart wrote:
 deliverable:
 ...In the tradition of the letters of an ignorant newbie...

 What's the consensus on the OOP in Haskell *now*?  There're some
 libraries such as OOHaskell, O'Haskell, and Haskell~98's own qualified
 type system with inheritance.

 If I have GHC, which way to do anything OOP-like is considered right 
 today?
 
 Using existentials and typeclasses to do some OO things wouldn't be
 considered unidiomatic (particularly, using existentials to package up
 interfaces to values).
 
 In general though, using a functional approach will produce better
 (simpler) Haskell code, and make it more likely others will understand it.
 Personally, I run in fear from OO Haskell ;)

Instead of OOP, Haskell uses (parametric) polymorphism which is more
powerful than OOP. For instance, the function

   length :: [a] - Int

or, with an explicit forall

   length :: forall a . [a] - Int

counts the number of elements in a list [a], regardless of what type
a those elements have. Moreover, it is guaranteed that length does
not inspect or change the elements, because it must work for all types
a the same way (this is called parametricity). Another example is

   map :: (a - b) - [a] - [b]

which maps a function over all elements in the list.

In addition, Haskell has type classes (which are similar to interfaces
in OOP). The most basic example is

   class Eq a where
  (==) :: a - a - Bool

Thus, you have an equality test available on all types that are
instances of this class. For example, you can test whether two Strings
are equal, because String is an instance of Eq. More generally, you say
whether two lists are equal if you know how to test elements for equality:

   instance Eq a = Eq [a] where
  [] == [] = True
  (x:xs) == (y:ys) = (x == y)  (xs == ys)
  _  == _  = False



The important thing I want to point out in this post is that parametric
polymorphism is indeed more powerful than OOP: already a concept like Eq
is impossible to implement in OOP. The problem is best illustrated with
the class Ord (*), which provides an ordering relation. Let's
concentrate on the smaller than function

   () :: Ord a = a - a - Bool

Can I create an interface that expresses the same thing?

   public interface Comparable {
boolean smaller_than(?? y);
   }

No, because there is no type I can attribute to the second argument of
smaller_than. The problem is that I can only compare to values of the
*same* type, i.e. the type which implements the interface.

Can I create a class the expresses the same thing?

   public class Comparable {
boolean smaller_than(Comparable y);
   }

This seems like a solution, but it is not. The problem is subtyping: if
i make integers and strings members of this class, i would be able to
compare the number 1 against the string hello, which should be
reported as a type error.

I have no formal proof, but I think that the  function cannot be
expressed in a type correct way in OOP. AFAIK, only Java Generics can
express the requirement we want:

   interface OrdA {
boolean smaller_than(A x, A y);
   }

   class String implements OrdString { ... }

But Generics are a considerable extension to OOP. In fact, there is
nothing really object oriented in here anymore, we're just on our way to
parametric polymorphism.


My final remark is about what this means for the existential quantifier
in Haskell. Because of the injection

   inject :: forall a . a - (exists a . a)

the existential quantifier can be thought of as implementing some form
of subtyping, i.e. (exists a . a) is a supertype of every a. The point
now is: given

   type ExistsOrd = exists a . Ord a = a

there is *no*

   instance Ord ExistsOrd where ...

because we could compare arbitrary subtypes of ExistsOrd then. In the
end, the existental quantifier has limited use for data abstraction,
it's forall that makes things happen.



Regards,
apfelmus


(*) We don't consider Eq because given a test on type equality, we can
generalize the signature of (==)

   (==) :: (Eq a, Eq b) = a - b - Bool

Indeed, this is what OOP equality does.

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


Re: [Haskell-cafe] proposal: HaBench, a Haskell Benchmark Suite

2007-01-28 Thread Joel Reymont


On Jan 28, 2007, at 8:51 AM, Andy Georges wrote:

it is nice to know that e.g., Data.ByteString performs as good as  
C, but is would be even nicer to see that large, real-life apps can  
reach that same performance.


What about using darcs as a benchmark? I heard people say it's slow.  
The undercurrent is that it's slow because it's written in Haskell.


--
http://wagerlabs.com/





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


Re: [Haskell-cafe] Channel9 Interview: Software Composability and t heFu ture of Languages

2007-01-28 Thread Malcolm Wallace
 Maybe they just don't want to have to
 take graduate-level classes in category theory to get their job done.

If I wanted to purchase a large, complex, and unique, physical system
(like a new bridge, say), you can be sure that I would employ an
engineer who had taken graduate classes on all sorts of technical stuff
related to bridge-building.  Why should I accept that large, complex,
and unique software systems should be built by non-experts, who shy away
from education that could help them get their job done better?

I imagine that if bridge-designers could insert a legal clause in their
contract stating THIS BRIDGE IS ACCEPTED AS IS, WITHOUT ANY
WARRANTY... then we might see fewer engineers bothering to take
graduate classes as well.

There is a myth that software is easy, and anything that seems to make
it more difficult can be brushed off.  But what if in fact the
difficulties are inherent?  Then tools that reveal the difficulty (and
help to tame it) should be welcomed.

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


Re: [Haskell-cafe] Channel9 Interview: Software Composability and theFu ture of Languages

2007-01-28 Thread Yitzchak Gale

Frederick Ross wrote:

here's my completely anecdotal view of the history
of hard in programming...


This history is accurate and insightful.


...when the kids... and the professors pretend that it was always
this way... then they will grow up... Until then, I
will continue to hear people say that [Haskell] is... scary


It does not have to wait until then. And it should not.
The resulting mess across the entire software
industry would really be a shame.

Haskell is _not_ inherently hard - any more than any other
programming language. But it is different. So right now,
Haskell is hard only because we need more
documentation that is designed to make Haskell
seem easy.

Literature for university students sometimes needs
to give the message: Things are not as easy as they
look; you need to learn to think in new ways.
Much of the Haskell literature is written in this style.

Literature for programmers in industry needs
to give the opposite message: This is easy, even fun.
You can start getting real work done right away.
And then, look at all of the advantages.

This interview illustrates how much people are
noticing Haskell of late - Haskell is hot. If there
were more written in the second style, a lot
more people would start using Haskell.

I think it can be done. Some nice work has
been done in this direction, but it is only
a start.


they characterize Haskell as being an
impractical language, only useful for research...
programming in Haskell is too hard...
like assembly programming!


These are people whose opinions should not
be taken lightly. So then, how can they say these
things that to us seem so obviously false?

The answer, in my opinion, is that it's not the
language. It's the documentation.

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


Re: [Haskell-cafe] Simple HTTP lib for Windows?

2007-01-28 Thread Yitzchak Gale

Daniel McAllansmith wrote:

The cheap and cheerful solution might be to invoke cURL.


Or MissingPy.

The bottom line is that URL loading is not the same as
HTTP. It is higher level. While Haskell does have a nice
HTTP library, it does not have a URL loading library
yet as far as I can see from this thread.

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


Re: [Haskell-cafe] proposal: HaBench, a Haskell Benchmark Suite

2007-01-28 Thread Neil Mitchell

Hi


What about using darcs as a benchmark? I heard people say it's slow.
The undercurrent is that it's slow because it's written in Haskell.


Its slow because some algorithms are O(stupid value). Some operations
(I've been told) would take 100's of years to terminate. That has
nothing to do with Haskell.

Also its not written in Haskell, its written in GHC-Haskell. This
benchmark suite should try where possible to be a Haskell benchmark.

Thanks

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


Re: [Haskell-cafe] Simple HTTP lib for Windows?

2007-01-28 Thread Neil Mitchell

Hi Daniel,



Adding in
 hPutStrLn h (Connection: close\r\n)
or
  hPutStrLn h (Connection: keep-alive\r\n)
as appropriate should sort that.


Works like a charm.


This is responding with a 302, the resource has been found but is temporarily
at another location indicated in the responses Location header.
So, now you'll have to start parsing responses.
In this case the Location header is www.cs.york.ac.uk/public.php


I didn't get as far as getting the 302, but it works now.


The cheap and cheerful solution might be to invoke cURL.


My standard solution was to invoke wget, but a Haskell solution would
be nicer. For my purpose following redirects etc. isn't required, so
thanks very much for your help. I will be releasing this function as
part of a library shortly, so will be giving you credit for your help!

Thanks

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


Re: [Haskell-cafe] Channel9 Interview: Software Composability and theFu ture of Languages

2007-01-28 Thread Michael T. Richter
On Fri, 2007-26-01 at 22:01 -0600, Collin Winter wrote:

 I find it incredibly insulting for you to assert that people who
 complain about Haskell's difficulty are too lazy and aren't really
 interested in a better solution. Maybe they just don't want to have to
 take graduate-level classes in category theory to get their job done.


That would be a good way to think, yes.  I look for practical solutions
to real problems in my work.  Haskell looks like it has these solutions,
but extracting them from the noise level of ivory tower debates is a
real problem.

I think many of the users of Haskell forget that there are a lot of
people out there who are not career academics working with pure
mathematics day-in and day-out.  My last math class?  Was over fifteen
years ago.  And in, you know, the real world of programming you don't
face mathematical problems as your bread and butter.  You face problems
in a messy world of too-short deadlines, too-few resources,
too-poorly-communicated requirements and too-many-hours work.

I would like to see a guide to Haskell that shows Haskell's place in
those problems, not in Yet Another Elegant Mathematical Proof of the
utterly useless in real life.

Now given my privileged position of having escaped that ghetto of toos
five years ago, I actually have the time and the energy to work this
stuff out on my own.  But your average working programmer?  Just doesn't
have the damned time to decode the arcane and obtuse wording and
mathematics to get to what in the end turns out to be concepts verging
on the trivial.  (I'm looking at monads here)

Maybe I'm the one that has to write the book Haskell for the Working
Programmer sometime.  You know.  When I understand the language enough
to write it.

-- 
Michael T. Richter
Email: [EMAIL PROTECTED], [EMAIL PROTECTED]
MSN: [EMAIL PROTECTED], [EMAIL PROTECTED]; YIM:
michael_richter_1966; AIM: YanJiahua1966; ICQ: 241960658; Jabber:
[EMAIL PROTECTED]

I have never seen the poor people being so familiar with their heads of
state as they were with [Michele Duvalier]. It was a beautiful lesson
for me. I've learned something from it. --Mother Theresa


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Lazy ByteString Problem

2007-01-28 Thread Dominic Steinitz
I've been playing around with streams as a way of implementing cryptographic 
functions as they seem to allow you to write code that reads more like the 
specification.

However, I believe (and profiling seems to confirm this) that this builds up a 
large expression which only gets evaluated at the very end. I naively thought 
that using lazy bytestrings would solve the problem but the bytestring 
version just hangs even for small numbers.

So two questions:

1. Are lazy bytestrings the answer but I am using them incorrectly?

2. What techniques are there to force evaluation and throw things that are no 
longer needed away? And can this be done without losing the spirit of the 
specification?

Dominic.

module Main(main) where

import Data.Word
import Data.Bits
import Data.Char
import System.Environment

import qualified Data.ByteString.Lazy as BS

-- ByteString version

cbcl iv ps =
   ciphers where
  ciphers = 0xff `BS.cons` (BS.pack (BS.zipWith (+) feedIns ciphers))
  feedIns = BS.pack (BS.zipWith xor (iv `BS.cons` ciphers) ps)

-- Made up function to illustrate problem

cbc iv ps =
   ciphers where
  ciphers = 0xff:(zipWith (+) feedIns ciphers)
  feedIns = zipWith xor (iv:ciphers) ps

testl n =
   BS.last (cbcl 0x55 ((BS.pack . take n . repeat . fromIntegral . ord) 'a'))

test :: Int - Word8
test n =
   last (cbc 0x55 ((take n . repeat . fromIntegral . ord) 'a'))

main =
   do progName - getProgName
  args - getArgs
  if length args /= 1
 then putStrLn (Usage:  ++ progName ++  length of string)
 else (putStrLn . show . test . read) (args!!0)

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


[Haskell-cafe] Re: Lazy ByteString Problem

2007-01-28 Thread Dominic Steinitz
On Sunday 28 January 2007 15:01, Dominic Steinitz wrote:
 I've been playing around with streams as a way of implementing
 cryptographic functions as they seem to allow you to write code that reads
 more like the specification.

 However, I believe (and profiling seems to confirm this) that this builds
 up a large expression which only gets evaluated at the very end. I naively
 thought that using lazy bytestrings would solve the problem but the
 bytestring version just hangs even for small numbers.

 So two questions:

 1. Are lazy bytestrings the answer but I am using them incorrectly?

 2. What techniques are there to force evaluation and throw things that are
 no longer needed away? And can this be done without losing the spirit of
 the specification?

 Dominic.

 module Main(main) where

 import Data.Word
 import Data.Bits
 import Data.Char
 import System.Environment

 import qualified Data.ByteString.Lazy as BS

 -- ByteString version

 cbcl iv ps =
ciphers where
   ciphers = 0xff `BS.cons` (BS.pack (BS.zipWith (+) feedIns ciphers))
   feedIns = BS.pack (BS.zipWith xor (iv `BS.cons` ciphers) ps)

 -- Made up function to illustrate problem

 cbc iv ps =
ciphers where
   ciphers = 0xff:(zipWith (+) feedIns ciphers)
   feedIns = zipWith xor (iv:ciphers) ps

 testl n =
BS.last (cbcl 0x55 ((BS.pack . take n . repeat . fromIntegral . ord)
 'a'))

 test :: Int - Word8
 test n =
last (cbc 0x55 ((take n . repeat . fromIntegral . ord) 'a'))

 main =
do progName - getProgName
   args - getArgs
   if length args /= 1
  then putStrLn (Usage:  ++ progName ++  length of string)
  else (putStrLn . show . test . read) (args!!0)

Hmmm I've just seen this which may explain why the lazy bytesting version was 
hanging. But I think my questions are still valid.

Dominic.

http://www.haskell.org/ghc/docs/latest/html/libraries/base/Data-ByteString-Lazy.html#3

O(1) cons is analogous to '(:)' for lists. Unlike '(:)' however it is strict 
in the ByteString that we are consing onto. More precisely, it forces the 
head and the first chunk. It does this because, for space efficiency, it may 
coalesce the new byte onto the first 'chunk' rather than starting a 
new 'chunk'.

So that means you can't use a lazy recursive contruction like this:

 let xs = cons c xs in xs

You can however use repeat and cycle to build infinite lazy ByteStrings. 

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


Re: [Haskell-cafe] Glasgow Distributed Haskell

2007-01-28 Thread [EMAIL PROTECTED]

Paul Johnson пишет:


Joel Reymont [EMAIL PROTECTED] wrote:

I'm after Erlang in Haskell, if you will, for fault-tolerance and 
scalability.




I think the way to do Erlang in Haskell is to build a middleware layer 
on top of the language, not try to make the language into something it 
is not. In this kind of environment you need to be able to upgrade 
components while the system is running. The careful Haskell habit of 
separating stateful operations from pure functions is useful here. I 
gather that the HAppS project is working along similar lines, and for 
similar reasons. Take a look at it.


I think I should point you to:
http://www.cs.umd.edu/~mwh/papers/neamtiu06dsu.html
---
*Practical Dynamic Software Updating for C*. Iulian Neamtiu, Michael 
Hicks, Gareth Stoyle, and Manuel Oriol. In /Proceedings of the ACM 
Conference on Programming Language Design and Implementation (PLDI)/, 
pages 72-83, June 2006.


Software updates typically require stopping and restarting an 
application, but many systems cannot afford to halt service, or would 
prefer not to. /Dynamic software updating/ (DSU) addresses this 
difficulty by permitting programs to be updated while they run. DSU is 
appealing compared to other approaches for on-line upgrades because it 
is quite general and requires no redundant hardware. The challenge is in 
making DSU /practical/: it should be flexible, and yet safe, efficient, 
and easy to use.


In this paper, we present Ginseng, a DSU implementation for C that aims 
to meet this challenge. We compile programs specially so that they can 
be dynamically patched, and generate most of a dynamic patch 
automatically. Ginseng performs a series of analyses that when combined 
with some simple runtime support ensure that an update will not violate 
type-safety while guaranteeing that data is kept up-to-date. We have 
used Ginseng to construct and dynamically apply patches to three 
substantial open-source server programs-/Very Secure FTP daemon/, 
/OpenSSH sshd daemon/, and /GNU Zebra/. In total, we dynamically patched 
each program with three years' worth of releases. Though the programs 
changed substantially, the majority of updates were easy to generate. 
Performance experiments show that all patches could be applied in less 
than 5 /ms/, and that the overhead on application throughput due to 
updating support ranged from 0 to at most 32%.

---

So, it is not completely impossible for haskell being updated on-the-fly.

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


Re: [Haskell-cafe] Channel9 Interview: Software Composability and theFu ture of Languages

2007-01-28 Thread Chris Kuklewicz
Hi,

  As I am taking a break from writing code and doing laundry, here are my 
thoughts.

Restating the obvious: I agree with you that it is amazing how use of the word
Monad has brought out so many people's feeling towards math.

Obligatory disclaimer: Like many people, I have learned to write code in Haskell
and I never took a course in Category theory. Nor do I have a CS degree.  My
math and physics degrees were not applicable to learning Haskell.

I had never use a similar type system or type inferencing.  The combination of
the new type system and the new approach to IO took a little while to sink in.
(I had learned BASIC, Pascal, Turbo Pascal with Objects, C, some Fortran, C++,
Scheme, Java)

But I think the biggest advance in Haskell is the explicit separation of IO
operations enforced by the type system / compiler.  Other languages may get type
inference and may get closer to parametric polymorphism (java generics) and they
may even get STM but they are unlikely to be able to evolve this IO separation
and maintain much backward compatibility.

Michael T. Richter wrote:
 On Fri, 2007-26-01 at 22:01 -0600, Collin Winter wrote:
 I find it incredibly insulting for you to assert that people who
 complain about Haskell's difficulty are too lazy and aren't really
 interested in a better solution. Maybe they just don't want to have to
 take graduate-level classes in category theory to get their job done.

It is probably true that having such a course would let you directly understand
the mathematical structure.  But such understanding is different from knowing
how to read and write Haskell programs.

 That would be a good way to think, yes.  I look for practical solutions
 to real problems in my work.  Haskell looks like it has these solutions,
 but extracting them from the noise level of ivory tower debates is a
 real problem.

There are CS PhD people who publish papers and who talk about Haskell.  These
are largely irrelevant to reading and writing Haskell.  Some papers are relevant
to designing extensions to Haskell, but unless you are trying to build a new
Haskell compiler extension these are not needed.

 I think many of the users of Haskell forget that there are a lot of
 people out there who are not career academics working with pure
 mathematics day-in and day-out. 

GHC seems to be developed by several people at Microsoft Research.  They are not
career academics.  I am less familiar with the other compilers.

For example: The latest extension proposal on haskell-cafe mailing list is about
View patterns.  This is all about making the code easier and clearer to write
and to encourage interfaces that hide implementation details.  That is about
practical changes to help people and not about academics.

 My last math class?  Was over fifteen
 years ago.  And in, you know, the real world of programming you don't
 face mathematical problems as your bread and butter.

If you have already created the algorithm or data structure then you are right.
If you can simply reuse existing libraries and solutions you are right.

But creating algorithms is a type of math.  And Haskell exposes this better than
most languages.

 You face problems
 in a messy world of too-short deadlines, too-few resources,
 too-poorly-communicated requirements and too-many-hours work.

The bottom line: Learning Haskell without a background in similar languages
takes time.  If you cannot take that time from the world, then Haskell will be
very hard to acquire.  The previous post about educating the next generation at
Universities makes the same point.

Aside: One could make a good case that there there is a synergy between learning
Haskell and learning the use the up and coming features of Visual Basic (LINQ)
and C# (STM) and Java (Generics vs Type Classes and Parametric Polymorphism) and
even Perl 6 (since it is taking so many ideas from Haskell).  And thus taking
the time to learn Haskell is useful.

Haskell is not the one and only cutting edge source of such language features,
but it does let you use many of them simultaneously and has good compilers
available today.  Note that I have not mentioned laziness.  This is because it
only helps to solve problems more elegantly -- other languages can model
infinite computations / data structures when it is useful to do so.

 I would like to see a guide to Haskell that shows Haskell's place in
 those problems, not in Yet Another Elegant Mathematical Proof of the
 utterly useless in real life.

Perhaps: http://haskell.org/haskellwiki/Why_Haskell_Matters

There are many learning links at hakell.org, though many resources may be newer
than when you learned Haskell:

http://haskell.org/haskellwiki/Haskell_in_5_steps

http://haskell.org/haskellwiki/Learning_Haskell
  (such as Haskell Tutorial for C Programmers)

http://haskell.org/haskellwiki/Books_and_tutorials
  (such as Programming in Haskell published January 31, 2007)
  (such as 

Re: [Haskell-cafe] Channel9 Interview: Software Composability and theFu ture of Languages

2007-01-28 Thread Chris Eidhof

Haskell is _not_ inherently hard - any more than any other
programming language. But it is different. So right now,
Haskell is hard only because we need more
documentation that is designed to make Haskell
seem easy.
Well, I think it's harder to get a program compiled in Haskell than  
in Java, for example. It's not too hard, although debugging might be  
a little difficult. I think this has to do with the type system.  
Althought it sounds bad, it's actually a good thing. Once you get a  
Haskell program compiled, chances are much higher that it's correct.  
You do a bit more work up front, but chances of a bug are way lower.


The way I see it, programming in Haskell is an investment. If you're  
from a OOP-background, some (trivial) things might take a lot more  
time. But in the end, it does make you more productive. You spend  
less time tracking bugs, and it's easier to refactor. Not everybody  
is willing to make an investment when they've got something that works.


For example, if you know one imperative language, you can switch to  
another without taking too much risk. On the other hand, if you  
switch to a language that is completely different, you don't know if  
it will get your job done. It doesn't feel safe.


-chris

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


Re: [Haskell-cafe] Channel9 Interview: Software Composability and theFu ture of Languages

2007-01-28 Thread Kirsten Chevalier

On 1/28/07, Chris Kuklewicz [EMAIL PROTECTED] wrote:

 I think many of the users of Haskell forget that there are a lot of
 people out there who are not career academics working with pure
 mathematics day-in and day-out.

GHC seems to be developed by several people at Microsoft Research.  They are not
career academics.  I am less familiar with the other compilers.


There's no need for the seems to be. The excellent History of Haskell paper:
http://research.microsoft.com/~simonpj/papers/history-of-haskell/index.htm
discusses the history of every extant Haskell compiler, in section 9.
If I'm reading correctly, every one of these compilers (except
possibly for jhc, it's not clear) began as an academic research
project at a university -- that includes GHC, which was developed by
academics at the University of Glasgow (hence the G in GHC), and
it was only later that some of them moved to MSR.

Be careful about conflating academic with not practical. It's true
that academics haven't always had time to explain the useful,
practical techniques they discover in ways that are understandable by
programmers who don't have formal mathematical backgrounds (and be
careful about conflating having a PhD with having mathematical
background or experience, too). In the same way that programmers have
jobs to do and thus have limited time to puzzle out new languages,
academics have jobs that don't tend to reward them for spending time
making those puzzles clearer to practitioners. As a challenge to
everyone posting on this thread: rather than excoriating academia for
its sins, why not start creating the documentation (or tutorials or
libraries or applications) you wish to see?

Cheers,
Kirsten

--
Kirsten Chevalier* [EMAIL PROTECTED] *Often in error, never in doubt
No one's actually said 'O great America, thank you for saving us from the evil
communist bug-eyed aliens, and, can we have fries with that?' yet have they?
-- Debra Boyask
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Numeric Class Problem

2007-01-28 Thread Dennis Buchmann

I've got a little problem i don't understand.
I need to calculate an index for a list (by use of !!).
It should look like this:
floor(j * (n / p2n))
where j is an Integer, n is the length of a list, therefore Integer too,
and p2n is 2^n.

When i use the former line in my Haskell code (pasted at the end of  
this mail),

i get the following error message:

qc.lhs:464:16:
No instance for (RealFrac Int)
  arising from use of `floor' at qc.lhs:464:16-36
Possible fix: add an instance declaration for (RealFrac Int)
In the expression: floor (j * (n / p2n))
In the definition of `i': i = floor (j * (n / p2n))
In the definition of `genUf'':
genUf' f j n
 | j == p2n = []
 | otherwise
 = [(replicate (j + (y1 - y0)) 0)
  ++
([1] ++ (replicate (p2n - ((j + (y1 - y0)) + 1))  
0))]

 ++
   (genUf' f (j + 1) n)
 where
 y0 = mod j 2
 y1 = xor y0 (f !! i)
 xor a b = mod (a + b) 2
 p2n = (2 ^ n)
 i = floor (j * (n / p2n))
Failed, modules loaded: none.



genUf :: [Int] - QOp
genUf f = (QOp(genUf' f 0 (length f)))
   where p2n = 2 ^ (length f) {- ok -}
genUf' f j n
   | j == p2n = [] {- ok -}
   | otherwise =
  [(replicate (j+(y1-y0)) 0)
  ++ [1] ++
  (replicate (p2n-(j+(y1-y0)+1)) 0)]
  ++ (genUf' f (j+1) n)
  where y0 = mod j 2
y1 = xor y0 (f!!i)
xor a b = mod (a+b) 2
p2n = (2 ^ n)
i = floor (j * (n / p2n))

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


Re: [Haskell-cafe] Numeric Class Problem

2007-01-28 Thread Neil Mitchell

Hi Dennis,

(/) :: Fractional a = a - a - a
div :: Integral a = a - a - a

Basically, use / on Float/Double like things, and div on Int/Integer
like things:

If you do want to use double like things throughout, then using
fromInteger around the place will help:

floor (fromInteger j * (fromInteger n / fromInteger p2n))

This converts easy value from an Integer to a number thing, which will
allow you to treat it like a Double/Float thing. If you are using Int
(rather than Integer) you might need fromInteger (toInteger x) around
the place.

Thanks

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


Re: [Haskell-cafe] Numeric Class Problem

2007-01-28 Thread Brandon S. Allbery KF8NH


On Jan 28, 2007, at 13:01 , Dennis Buchmann wrote:


It should look like this:
floor(j * (n / p2n))
where j is an Integer, n is the length of a list, therefore Integer  
too,

and p2n is 2^n.

When i use the former line in my Haskell code (pasted at the end of  
this mail),

i get the following error message:

qc.lhs:464:16:
No instance for (RealFrac Int)
  arising from use of `floor' at qc.lhs:464:16-36


It's telling you you're trying to take the floor of an Int (not a  
type in class RealFrac, which would be Float or Double).  This makes  
sense because everything there is in fact an Int ((^) is defined as  
taking things of class Integral (Integer, Int) and returning  
something in class Num, which in this case will be Int because it's  
used in an Int expression).  In other words, floor is unnecessary.


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



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


Re: [Haskell-cafe] Channel9 Interview: Software Composability and t heFu ture of Languages

2007-01-28 Thread Tomasz Zielonka
On Sat, Jan 27, 2007 at 02:04:32PM -0500, Steve Schafer wrote:
 This is not just a progrmaming issue; I encounter the same phenomenon
 pretty much everywhere: I'm currently trying to build a house, and I've
 found that most of the people who are in the business of building houses
 don't want to try anything new, even if it might be a better way that
 has the potential to save them money and/or result in a better end
 product. They want to continue building houses the way they've always
 built houses. The fraction of house builders who do want to learn new
 and possibly better ways of building is, and always will be, a small
 one.

This may change with the arrival of the first home building robots we've
been reading about recently. They won't mind building in new ways, so
the human builders will be forced to choose between becoming more
flexible or changing their jobs.

http://property.timesonline.co.uk/article/0,,14029-2546574,00.html

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


[Haskell-cafe] Converting Types to Terms

2007-01-28 Thread Klaus Ostermann

I would like to have a program that can synthesize programs for a
given type, composing only functions from a given library.

For example, suppose my library has

isZero :: Int - Bool
map :: (a - b) - [a] - [b]
and :: Bool - Bool - Bool
fold :: (a - b - a) - a - [b] - a
True :: Bool
(.) :: (b - c) - (a - b) - a - c

then I want to ask, say, for a program of type

 [Int] - Bool

and get as answer

(fold and True) . (map isZero)

I have found two approaches in this direction. The first one
is the De-Typechecker
http://www.haskell.org/pipermail/haskell/2005-March/015423.html

and the other one is Djinn
http://permalink.gmane.org/gmane.comp.lang.haskell.general/12747

However, with none of these approaches I managed to do anything with list 
functions.


What else is available (besides Djinn and De-Typechecker)? Are lists a problem? 
In general, what are the practical and theoretical limits of these program 
synthesizers? Are there any overview papers for this topic?


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


Re: [Haskell-cafe] OOP parametric polymorphism

2007-01-28 Thread Steve Downey

Well, it depends what you mean by OO. In a proper OO system, equality
means not just are these two things in the same state, but do they
refer to a single object. Invoking behavior on one will affect the
other, and the equality relation will still hold.
There are three properties that entities have in a OO model:
1 Identity
2 State
3 Behavior

objects are not values. Values don't have identity. This 7 is the same
as that 7, with no way of distinguishing them. They also don't have
state.You don't add 1 to 7 and turn it into 8 (unless you're in a very
old FORTRAN, where constants weren't). The result is a new value.
Values also don't do things. Functions map values to new values.

Of course, when most people are looking for OO, they're looking for
encapsulation, subtyping, inheritance, polymorphism, dynamic dispatch
and so on. Many of those are dead simple in Haskell. Others less so.

Unfortunately, it seems that most people trying to get these answers
are also trying to apply a design that is suboptimal for the language.

By the way, equality is a particularly nasty example given subtyping.
There is no good way to define equality that is fully polymorphic that
is also transitive and reflexive. Which is annoying no end.



On 1/28/07, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote:

Donald Bruce Stewart wrote:
 deliverable:
 ...In the tradition of the letters of an ignorant newbie...

 What's the consensus on the OOP in Haskell *now*?  There're some
 libraries such as OOHaskell, O'Haskell, and Haskell~98's own qualified
 type system with inheritance.

 If I have GHC, which way to do anything OOP-like is considered right
 today?

 Using existentials and typeclasses to do some OO things wouldn't be
 considered unidiomatic (particularly, using existentials to package up
 interfaces to values).

 In general though, using a functional approach will produce better
 (simpler) Haskell code, and make it more likely others will understand it.
 Personally, I run in fear from OO Haskell ;)

Instead of OOP, Haskell uses (parametric) polymorphism which is more
powerful than OOP. For instance, the function

   length :: [a] - Int

or, with an explicit forall

   length :: forall a . [a] - Int

counts the number of elements in a list [a], regardless of what type
a those elements have. Moreover, it is guaranteed that length does
not inspect or change the elements, because it must work for all types
a the same way (this is called parametricity). Another example is

   map :: (a - b) - [a] - [b]

which maps a function over all elements in the list.

In addition, Haskell has type classes (which are similar to interfaces
in OOP). The most basic example is

   class Eq a where
  (==) :: a - a - Bool

Thus, you have an equality test available on all types that are
instances of this class. For example, you can test whether two Strings
are equal, because String is an instance of Eq. More generally, you say
whether two lists are equal if you know how to test elements for equality:

   instance Eq a = Eq [a] where
  [] == [] = True
  (x:xs) == (y:ys) = (x == y)  (xs == ys)
  _  == _  = False



The important thing I want to point out in this post is that parametric
polymorphism is indeed more powerful than OOP: already a concept like Eq
is impossible to implement in OOP. The problem is best illustrated with
the class Ord (*), which provides an ordering relation. Let's
concentrate on the smaller than function

   () :: Ord a = a - a - Bool

Can I create an interface that expresses the same thing?

   public interface Comparable {
boolean smaller_than(?? y);
   }

No, because there is no type I can attribute to the second argument of
smaller_than. The problem is that I can only compare to values of the
*same* type, i.e. the type which implements the interface.

Can I create a class the expresses the same thing?

   public class Comparable {
boolean smaller_than(Comparable y);
   }

This seems like a solution, but it is not. The problem is subtyping: if
i make integers and strings members of this class, i would be able to
compare the number 1 against the string hello, which should be
reported as a type error.

I have no formal proof, but I think that the  function cannot be
expressed in a type correct way in OOP. AFAIK, only Java Generics can
express the requirement we want:

   interface OrdA {
boolean smaller_than(A x, A y);
   }

   class String implements OrdString { ... }

But Generics are a considerable extension to OOP. In fact, there is
nothing really object oriented in here anymore, we're just on our way to
parametric polymorphism.


My final remark is about what this means for the existential quantifier
in Haskell. Because of the injection

   inject :: forall a . a - (exists a . a)

the existential quantifier can be thought of as implementing some form
of subtyping, i.e. (exists a . a) is a supertype of every a. The point
now is: given

   type ExistsOrd = exists a . Ord a = 

Re: [Haskell-cafe] Converting Types to Terms

2007-01-28 Thread Stefan O'Rear
On Sun, Jan 28, 2007 at 09:11:33PM +0100, Klaus Ostermann wrote:
 I would like to have a program that can synthesize programs for a
 given type, composing only functions from a given library.
 
 For example, suppose my library has
 
 isZero :: Int - Bool
 map :: (a - b) - [a] - [b]
 and :: Bool - Bool - Bool
 fold :: (a - b - a) - a - [b] - a
 True :: Bool
 (.) :: (b - c) - (a - b) - a - c

Why just (.) ?  I also assume your logic has modus ponens (curry howard: 
application)

 then I want to ask, say, for a program of type
 
  [Int] - Bool
 
 and get as answer
 
 (fold and True) . (map isZero)

 However, with none of these approaches I managed to do anything with list 
 functions.
 
 What else is available (besides Djinn and De-Typechecker)? Are lists a 
 problem? In general, what are the practical and theoretical limits of these 
 program synthesizers? Are there any overview papers for this topic?

A system (with the full axioms of intuitionist logic) would be much more likely
to answer your query with \_ - True .  Not very helpful, eh?

Lists are recursive types, and it is very easy for a list calculus to lose 
strong
normalization.  Without strong normalization, any nontrivial query will be 
answered
with 'undefined'.  Not helpful.

The only other system I know of is my short theorem prover (on the wiki); it 
has no
architectural reason to not allow list functions, but it has many shallow 
reasons -
slow, obfuscated, doesn't currently track proofs, doesn't currently support 
higher
kinds.  Not likely to be usable.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Converting Types to Terms

2007-01-28 Thread Neil Mitchell

Hi,

I have got loads of requests to allow Hoogle to do this, usually
something like if you search [Bool] - [Bool] it should suggest map
not, or something - combining functions into the one you want.

Unfortunately the search space would be huge for even the smallest
library. Worse still, the second you allow id :: a - a, you have an
infinite number of matching terms.

Some work I have seen which seems related to what you are asking is:
http://www.cs.ioc.ee/tfp-icfp-gpce05/tfp-proc/14num.pdf Systematic
search for lambda expressions by Susumu Katayama.

Thanks

Neil


On 1/28/07, Stefan O'Rear [EMAIL PROTECTED] wrote:

On Sun, Jan 28, 2007 at 09:11:33PM +0100, Klaus Ostermann wrote:
 I would like to have a program that can synthesize programs for a
 given type, composing only functions from a given library.

 For example, suppose my library has

 isZero :: Int - Bool
 map :: (a - b) - [a] - [b]
 and :: Bool - Bool - Bool
 fold :: (a - b - a) - a - [b] - a
 True :: Bool
 (.) :: (b - c) - (a - b) - a - c

Why just (.) ?  I also assume your logic has modus ponens (curry howard: 
application)

 then I want to ask, say, for a program of type

  [Int] - Bool

 and get as answer

 (fold and True) . (map isZero)

 However, with none of these approaches I managed to do anything with list
 functions.

 What else is available (besides Djinn and De-Typechecker)? Are lists a
 problem? In general, what are the practical and theoretical limits of these
 program synthesizers? Are there any overview papers for this topic?

A system (with the full axioms of intuitionist logic) would be much more likely
to answer your query with \_ - True .  Not very helpful, eh?

Lists are recursive types, and it is very easy for a list calculus to lose 
strong
normalization.  Without strong normalization, any nontrivial query will be 
answered
with 'undefined'.  Not helpful.

The only other system I know of is my short theorem prover (on the wiki); it 
has no
architectural reason to not allow list functions, but it has many shallow 
reasons -
slow, obfuscated, doesn't currently track proofs, doesn't currently support 
higher
kinds.  Not likely to be usable.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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


Re: [Haskell-cafe] State of OOP in Haskell

2007-01-28 Thread Alexy Khrabrov

And OOHaskell didn't compile for me on GHC 6.6...  tells you about
currency of use.

On 1/28/07, Lennart Augustsson [EMAIL PROTECTED] wrote:

OOHaskell is ingenious, but it's a terrible way to use Haskell.
It's very unidiomatic Haskell, and it makes you do things in the
same old OO way.  Presumably people are using Haskell to do things
differently?
But as I said, I consider OOHaskell itself a work of genius. :)

-- Lennart

On Jan 27, 2007, at 22:24 , Alexy Khrabrov wrote:

 What about this OOHaskell:

 http://homepages.cwi.nl/~ralf/OOHaskell/

 -- how is it received in the café?  :)

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



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


[Haskell-cafe] Re: Channel9 Interview: Software Composability and the Future of Languages

2007-01-28 Thread apfelmus
Michael T. Richter wrote:
 And in, you know, the real world of programming you don't
 face mathematical problems as your bread and butter.

Can you prove that? ;)

 You face problems
 in a messy world of too-short deadlines, too-few resources,
 too-poorly-communicated requirements and too-many-hours work.

In it's essence, the way of mathematics is to solve an infinite number
of problems at once by generalizing and simplifying them until they read
1 == 1. But that's exactly the kind of stuff you need: thanks to
generalization, you already implemented all requirements before the
customer can even conceive them and thanks to simplification, needed
resources and hours of work shrink to reasonable amounts resulting in
deadlines becoming harmless :)

Well, i mean it seriously.
- Coding a complicated configuration system, no doubt baroque, can it be
simplified by basing it on a simple but powerful macro language with
simple and sane semantics? Can it be based on the lambda calculus? Is
this general enough? Maybe you want to assure that every macro terminates?
- Coding a graphical user interface with lots of forms, can they be
reduced to their essence and generated automatically from a data type?
Perhaps in the style of Functional Forms
(www.st.cs.ru.nl/papers/2005/eves2005-FFormsIFL04.pdf)? Are they general
enough? If they require immediate feedback or interactive error
checking, may tangible values (http://conal.net/papers/Eros/) be an idea
to base on?
- Coding a dynamic website and having to control caching and data
mining, can this logic be separated out, restricting yourself to a
programming model that allows those this to happen transparently? Can
you plunder Google's Map Reduce model for that
(www.cs.vu.nl/~ralf/MapReduce/paper.pdf)?
- Coding data base access or a package management system, can data
integrity be assured by again restricting yourself to a less general
programming model? Like Software Transactional Memory? Or is it just
enough to use strong typing and a simple yet clever data structure
(http://www.galois.com/cufp/slides/2006/CliffordBeshers.pdf)?

The structures behind the repetitions, the generalizations to rule them
all, the simplifications to find them, they all lie there. But they may
resist discovery and you may need cleverness and, well, mathematics to
find them. The point about Haskell is that its type system is pure and
rich enough to enable you to actually express the proof, the insight as
a program. Only few programming languages can do that. And you know:
computers and Haskell itself are products of mathematics.


Regards,
apfelmus

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


[Haskell-cafe] Re: Channel9 Interview: Software Composability and theFu ture of Languages

2007-01-28 Thread Benjamin Franksen
Chris Kuklewicz wrote:
 Note that I have not mentioned laziness.  This
 is because it only helps to solve problems more elegantly -- other
 languages can model infinite computations / data structures when it is
 useful to do so.

Reminds me of yet another quote from Dijkstra
(http://www.cs.utexas.edu/users/EWD/transcriptions/EWD12xx/EWD1284.html): After
more than 45 years in the field, I am still convinced that in computing,
elegance is not a dispensable luxury but a quality that decides between
success and failure.

Ben

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


Re: [Haskell-cafe] proposal: HaBench, a Haskell Benchmark Suite

2007-01-28 Thread Andy Georges


On 28 Jan 2007, at 12:57, Joel Reymont wrote:



On Jan 28, 2007, at 8:51 AM, Andy Georges wrote:

it is nice to know that e.g., Data.ByteString performs as good as  
C, but is would be even nicer to see that large, real-life apps  
can reach that same performance.


What about using darcs as a benchmark? I heard people say it's  
slow. The undercurrent is that it's slow because it's written in  
Haskell.


I have pondered about that. What would the input set be? And how to  
repeatedly run the benchmark? Should we just have a recording phase?  
Or a diff phase? It seems difficult to have a VC system as a benchmark.


-- Andy

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


Re: [Haskell-cafe] Re: [Haskell] ANNOUNCE: binary: high performance, pure binary serialisation

2007-01-28 Thread Tony Finch
On Fri, 26 Jan 2007, Neil Davies wrote:

 existing ecoding system - both the BER (Basic Encoding Rules) and the
 PER (Packed Encoding Rules). If you are looking to target a well
 supported standard - this would be the one.

I'd say that ASN.1 encoding rules are badly, but widely supported. A
surprisingly large number of security problems have been caused by ASN.1
code, and similar bugs have turned up in independent implementations so it
isn't just one widespread shoddy implementation. OTOH ASN.1 is used by
TLS, LDAP, Kerberos, SNMP, S/MIME, H.323, etc. etc.

Tony.
-- 
f.a.n.finch  [EMAIL PROTECTED]  http://dotat.at/
IRISH SEA: NORTHWEST 3 OR 4, OCCASIONALLY 5 AT FIRST. SLIGHT OR MODERATE.
SHOWERS. GOOD.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Channel9 Interview: Software Composability and theFu ture of Languages

2007-01-28 Thread Benjamin Franksen
Chris Kuklewicz wrote:
 Aside on utterly useful proofs: When you write concurrent programs you
 want an API with strong and useful guarantees so you can avoid deadlocks
 and starvation and conflicting data read/writes.  Designing an using such
 an API is a reasoning exercise identical to creating proofs.  Some systems
 makes this possible and even easy (such as using STM).

I have to -- partly -- disagree with your last statement. It is possible
that I missed something important but as I see it, STM has by construction
the disadvantage that absence of starvation is quite hard (if not
impossible) to prove. A memory transaction must be re-started from the
beginning if it finds (when trying to commit) another task has modified one
of the TVars it depends on. This might mean that a long transaction may in
fact /never/ commit if it gets interrupted often enough by short
transactions which modify one of the TVars the longer transaction depends
upon.

IIRC this problem is mentioned in the original STM paper only in passing
(Starvation is surely a possibility or some such comment). I would be
very interested to hear if there has been any investigation of the
consequences with regard to proving progress guarantees for programs that
use STM.

My current take on this is that there might be possibilities avoid this kind
of starvation by appropriate scheduling. One idea is to assign time slices
dynamically, e.g. to double it whenever a task must do a rollback instead
of a commit (due to externally modified TVars), and to reset the time slice
to the default on (successful) commit or exception. Another possibility is
to introduce dynamic task priorities and to increase priority on each
unsuccessful commit. (Unfortunately I have no proof that such measures
would remove the danger of starvation, they merely seem plausible avenues
for further research. I also don't know whether the current GHC runtime
system already implements such heuristics.)

Cheers
Ben

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


[Haskell-cafe] Re: Haskell Weekly News: January 02, 2007

2007-01-28 Thread Björn Buckwalter

Henning Thielemann lemming at henning-thielemann.de writes:


On Tue, 2 Jan 2007, Donald Bruce Stewart wrote:

Dimensional: Statically checked physical dimensions. Björn Buckwalter
[4]announced version 0.1 of [5]Dimensional, a module for statically
checked physical dimensions. The module facilitates calculations with
physical quantities while statically preventing e.g. addition of
quantities with differing physical dimensions.

4. http://article.gmane.org/gmane.comp.lang.haskell.general/14691
5. http://code.google.com/p/dimensional/


Henning,

First, let me apologize for not answering earlier. I have been
reluctant to subscribe to the café due to the volume of messages.
Instead I tend to occasionally browse the archives. Needless to say
your questions eluded me until now. The same is true for Mike Gunter's
message[1] which I will respond to presently.



How is it related to this one:
  http://www.haskell.org/haskellwiki/Dimensionalized_numbers
?


I ashamedly admit that I am guilty of inventing my own wheel. I
haven't looked too closely at Aaron's code but I believe there are
some conceptual similarities. Regarding completeness user my library
supports all seven base dimensions while Aaron's library currently
supports only length and time (I believe it is meant as a proof of
concept (toy example in his own words) rather than a complete
library). My ambition is to provide a reasonably complete library.



It should certainly be mentioned on
  http://www.haskell.org/haskellwiki/Physical_units
  
http://www.haskell.org/haskellwiki/Libraries_and_tools/Mathematics#Physical_units


I have added it to the above pages. Thanks,

Björn Buckwalter


[1] http://www.haskell.org/pipermail/haskell-cafe/2007-January/021069.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] What is the best way to understand large programs?

2007-01-28 Thread Stefan O'Rear
Hello.  I am trying to fully understand yi as quickly as possible.
Yi, like most big programs, consists of a number of modules;
e.g. Yi.UI, Yi.Buffer, etc.  Since I am not smart enough to
understand all the modules at once, I am trying to understand them one
at a time (is this itself the problem?); however, since mutual
dependencies exist, I can't do it that easily, since understanding
module A requires knowledge of the interface of module B requires
knowledge of the implentation of module B requires knowledge of the
interface of module A requires knowledge of the implementation of
module B (and my brain's lazy fix is not very good).  Yi has haddock-style
comments (despite not being a library), so I tried using ./Setup.lhs
haddock for readable side references, however this failed on CPP
markup. After asking on #haskell, newsham noted that he had filed a
cabal bug (#102), but the bug's page notes:

Haddock generates interface documentation. That's only appropriate for
libraries, isn't it?

So, if haddock isn't what I want, what is?  Or am I going at this
completely wrong?  What is the recommended way to approach a largish
program like yi or lambdabot?  (and if haddock is the wrong way to
handle this, why does yi have haddock comments?)

Note: I *have* managed to pretty thourougly understand lambdabot, but
  it took a while, wasn't particularly easy, and anyway
  lambdabot's dependency groups are quite small compared to eg
  lambdabot's.  I'm hoping to make things easier for myself.

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


Re: [Haskell-cafe] Re: Channel9 Interview: Software Composability and theFu ture of Languages

2007-01-28 Thread Chris Kuklewicz
Benjamin Franksen wrote:
 Chris Kuklewicz wrote:
 Aside on utterly useful proofs: When you write concurrent programs you
 want an API with strong and useful guarantees so you can avoid deadlocks
 and starvation and conflicting data read/writes.  Designing an using such
 an API is a reasoning exercise identical to creating proofs.  Some systems
 makes this possible and even easy (such as using STM).
 
 I have to -- partly -- disagree with your last statement. It is possible
 that I missed something important but as I see it, STM has by construction
 the disadvantage that absence of starvation is quite hard (if not
 impossible) to prove. A memory transaction must be re-started from the
 beginning if it finds (when trying to commit) another task has modified one
 of the TVars it depends on. This might mean that a long transaction may in
 fact /never/ commit if it gets interrupted often enough by short
 transactions which modify one of the TVars the longer transaction depends
 upon.

True.

The STM API ensures the program will be deadlock free, the mutable state is
consistent, and that progress will always be made (i.e. _some block_ will 
commit).

The current STM implementation does not otherwise ensure fairness or avoid
starvation.  It is clever enough to put retrying blocks to sleep until one of
the TVars they read is changed.  But it does not have the single-wake up FIFO
fairness of MVars.


 IIRC this problem is mentioned in the original STM paper only in passing
 (Starvation is surely a possibility or some such comment). I would be
 very interested to hear if there has been any investigation of the
 consequences with regard to proving progress guarantees for programs that
 use STM.

The STM API ensures progress for the program as a whole (i.e. commits).  If a
block is failed because of a conflict this is because another block has
committed.  If all the threads of the program call retry then the program is
stuck, but that is not STM's fault, and the STM scheduler will kill the program
in this case rather than hang.

 My current take on this is that there might be possibilities avoid this kind
 of starvation by appropriate scheduling. One idea is to assign time slices
 dynamically, e.g. to double it whenever a task must do a rollback instead
 of a commit (due to externally modified TVars), and to reset the time slice
 to the default on (successful) commit or exception.

With the new GHC using multiple CPU's this would not prevent a fast block from
running  committing on a different CPU and causing the long block to retry.

 Another possibility is
 to introduce dynamic task priorities and to increase priority on each
 unsuccessful commit.

 (Unfortunately I have no proof that such measures
 would remove the danger of starvation, they merely seem plausible avenues
 for further research. I also don't know whether the current GHC runtime
 system already implements such heuristics.)
 
 Cheers
 Ben

What you need to increase fairness/priority for a block is to run that block
until it tries to commit while keeping other blocks that would interfere from
committing.

The scheduler could take the runtime of a failed block into account when
re-attempting it.  It could lock out other blocks that might interfere with a
very-long-delayed much-re-attempted-block until it has had a change to commit.
(Since the scheduler knows which TVars the problem block has needed in the past
any independent blocks can still run).  To keep the progress guarantee: if the
problem block takes a very very long time it must be timed out and another block
be allowed to commit.

This partitioning into fast vs slow blocks is merely based on the
observations of the runtime scheduler.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] What is the best way to understand large programs?

2007-01-28 Thread Neil Mitchell

Hi


Haddock generates interface documentation. That's only appropriate for
libraries, isn't it?


Wrong, its very useful for normal programs as well. That along with a
nice HsColour generated source links with Haddock and you can navigate
the code just a bit quicker. Having a Hoogle database for a large
program is also handy for figuring out where things are and what they
do - especially when the program has introduced new custom data types.

Some sort of module dependancy graph would also be handy, but I'm not
sure any program can yet produce that kind of information.

Thanks

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


Re: [Haskell-cafe] proposal: HaBench, a Haskell Benchmark Suite

2007-01-28 Thread David Roundy
On Sun, Jan 28, 2007 at 10:36:50PM +0100, Andy Georges wrote:
 On 28 Jan 2007, at 12:57, Joel Reymont wrote:
 On Jan 28, 2007, at 8:51 AM, Andy Georges wrote:
 
 it is nice to know that e.g., Data.ByteString performs as good as  
 C, but is would be even nicer to see that large, real-life apps  
 can reach that same performance.
 
 What about using darcs as a benchmark? I heard people say it's  
 slow. The undercurrent is that it's slow because it's written in  
 Haskell.
 
 I have pondered about that. What would the input set be? And how to  
 repeatedly run the benchmark? Should we just have a recording phase?  
 Or a diff phase? It seems difficult to have a VC system as a benchmark.

We darcs folk would love to have a darcs benchmark, and Jason has even put
some work into a simulator driver (which would call various darcs commands
to build up a repository).  But I don't think this would be useful as a
Haskell benchmark.  But we'd love to have automatic performance regression
testing!

Better (for Haskell benchmarking) would be to take a small (but relevant)
part of darcs, and benchmark that.  Which is effectively what a
Data.ByteString benchmark could do.  Darcs spends vast amounts of time
breaking huge files into lines (or it's been doing that for me recently)
and running its LCS algorithm on those lists of lines.  This wouldn't be a
bad benchmark: just a huge LCS job.  You could algorithmically generate two
huge strings and then compute their LCS.  Actually, darcs no longer uses a
true LCS (neither does diff), so you might try our LCS substitute.
-- 
David Roundy
http://www.darcs.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Multiparamater class type-inference error

2007-01-28 Thread Alfonso Acosta

Hi all,

Sorry if this is too GHC-specific. I'm getting this strange
instantiation error when compiling the following code with GHC 6.6:

   No instance for (Synchronous s ((a, b) - a) (a, b) a)
 arising from use of `mapSY' at SynchronousLib.lhs:342:8-16
   Possible fix:
 add an instance declaration for
 (Synchronous s ((a, b) - a) (a, b) a)
   In the expression: mapSY fst
   In the definition of `fstSY': fstSY = mapSY fst

---
data Signal a = NullS
  | a :- Signal a deriving (Eq)

class Synchronous s f1 a b | f1 - a , f1 - b where
mapSY   :: f1 - s  a - s b
delaySY :: a -  s  a - s a

instance Synchronous Signal (a-b) a b where
 mapSY _ NullS  = NullS
 mapSY f (x:-xs)= f x :- (mapSY f xs)
 delaySY e es = e:-es


fstSY = mapSY fst

{--
   No instance for (Synchronous s ((a, b) - a) (a, b) a)
 arising from use of `mapSY' at SynchronousLib.lhs:342:8-16
   Possible fix:
 add an instance declaration for
 (Synchronous s ((a, b) - a) (a, b) a)
   In the expression: mapSY fst
   In the definition of `fstSY': fstSY = mapSY fst
Failed, modules loaded: AbsentExt, Vector, Queue, Signal. --}
--

No error arises if fstSY is declared as

fstSY a = mapSY fst a

Is it GHC bug or am I supposed to declare it like that to assist type inference?

Thanks in advance,

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


[Haskell-cafe] Re: Multiparamater class type-inference error

2007-01-28 Thread Alfonso Acosta

Forgot to mention that no error arises if I explicitly give the type
signature of fstSY

fstSY:: Signal (a,b) - Signal a






On 1/29/07, Alfonso Acosta [EMAIL PROTECTED] wrote:

Hi all,

Sorry if this is too GHC-specific. I'm getting this strange
instantiation error when compiling the following code with GHC 6.6:

No instance for (Synchronous s ((a, b) - a) (a, b) a)
  arising from use of `mapSY' at SynchronousLib.lhs:342:8-16
Possible fix:
  add an instance declaration for
  (Synchronous s ((a, b) - a) (a, b) a)
In the expression: mapSY fst
In the definition of `fstSY': fstSY = mapSY fst

---
data Signal a = NullS
  | a :- Signal a deriving (Eq)

class Synchronous s f1 a b | f1 - a , f1 - b where
 mapSY  :: f1 - s  a - s b
 delaySY:: a -  s  a - s a

instance Synchronous Signal (a-b) a b where
  mapSY _ NullS = NullS
  mapSY f (x:-xs)   = f x :- (mapSY f xs)
  delaySY e es = e:-es


fstSY = mapSY fst

{--
No instance for (Synchronous s ((a, b) - a) (a, b) a)
  arising from use of `mapSY' at SynchronousLib.lhs:342:8-16
Possible fix:
  add an instance declaration for
  (Synchronous s ((a, b) - a) (a, b) a)
In the expression: mapSY fst
In the definition of `fstSY': fstSY = mapSY fst
Failed, modules loaded: AbsentExt, Vector, Queue, Signal. --}
--

No error arises if fstSY is declared as

fstSY a = mapSY fst a

Is it GHC bug or am I supposed to declare it like that to assist type inference?

Thanks in advance,

Alfonso Acosta


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


[Haskell-cafe] How did you stumble on Haskell?

2007-01-28 Thread Alexy Khrabrov

How do people stumble on Haskell?  I've taught ML at UPenn, and many
of my colleagues in Amazon are in SeaFunc -- switching from C funk to
func funk.  I've got Hudak's book a while ago, but didn't have
time/excuse to delve into it until recently.  Then the most fantastic
chain if events triggered it:

-- finally switched to Intel Mac
-- got Parallels
-- got a recent Linux, openSUSE 10.2, to stick into Parallels
-- decided finally to try Gentoo
-- found equery slow, came across Adelie/FQuery as fast equery
-- emerge adelie

To my surprise, saw it emerge GHC!  Realized Adelie is a Haskell way
to hack Portage.  Dug all things Haskell!

I also used Darcs for a long time.  It probably takes several pro et
contra factors to push away from boring things and to be inducted into
interesting FP things.  Again, UPenn focus on ML was invaluable, and
Ullman's book on ML superb -- and thin!

What's folks most interesting ways to arrive at FP?

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


Re: [Haskell-cafe] How did you stumble on Haskell?

2007-01-28 Thread Stefan O'Rear
On Sun, Jan 28, 2007 at 07:01:57PM -0800, Alexy Khrabrov wrote:
 How do people stumble on Haskell?  I've taught ML at UPenn, and many
specific story elided
 What's folks most interesting ways to arrive at FP?

You want weird?  I was referred here by the Unlambda Manual.  Oh if I 
ignore the syntax and squint right unlambda is Really Really Good.  Oh
wait, this language Madore mentions in passing eliminates the need for
squinting.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How did you stumble on Haskell?

2007-01-28 Thread Frederick Ross

On 1/28/07, Alexy Khrabrov [EMAIL PROTECTED] wrote:

How do people stumble on Haskell?


Read Ullman's book on ML.  Look at Haskell at that point, but was
insufficiently mathematically sophisticated to get it (hey, I was
sixteen).  Wrote numerical analysis code in Forth for a year or so.
Hacked on a several hundred thousand line FORTRAN 77 codebase.  Wrote
the simulation code for my physics thesis in C.  Decided I never
wanted to instantiate, destroy, or otherwise manage memory ever again.
Had a hate-hate relationship with MATLAB, decided Mathematica was
rubbish.  Remembered Haskell.  Now creating the programmatic
equivalent of a cyborg, hunchback puppeteer to control a Java image
analysis program in Scheme.

So of course the best work I've done has been completely analytic
mathematical physics without reference to computing of any kind.  And
I'm a biologist.

This is known as being born in the Random monad.

--
Frederick Ross
Graduate Fellow, (|Siggia + |McKinney)/sqrt(2) Lab
The Rockefeller University
Je ne suis pas Fred Cross!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] State of OOP in Haskell

2007-01-28 Thread Frederick Ross

I'm going to be offensive, bigoted, and myopic for a minute here:
programming straight onto the Turing machine (and not too
dissimilarly, the von Neumann machine) is the act of making your
thoughts comprehensible to a little gizmo that exists to zip back and
forth on an infinite ticker tape.  We should therefore abstract.
However, I am only marginally happier about making my thoughts
comprehensible to a tinkertoy set (which is how I regard object
oriented programming).

Why not just stay as close to mathematics as possible?  Why the deep
desire to communicate your loftiest intentions to a tinkertoy set?

There was the Lambada project to map between Java's object hierarchies
and Haskell, however, and there was a lot of effort put into making
Haskell talk properly through COM.  Both of those necessitate a model
of object oriented programming embedded in Haskell which would provide
you with prior art.

On 1/27/07, Alexy Khrabrov [EMAIL PROTECTED] wrote:

...In the tradition of the letters of an ignorant newbie...

What's the consensus on the OOP in Haskell *now*?  There're some
libraries such as OOHaskell, O'Haskell, and Haskell~98's own qualified
type system with inheritance.

If I have GHC, which way to do anything OOP-like is considered right today?


--
Frederick Ross
Graduate Fellow, (|Siggia + |McKinney)/sqrt(2) Lab
The Rockefeller University
Je ne suis pas Fred Cross!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Fixed-point operator (was: seq does not preclude parametricity)

2007-01-28 Thread Matthew Brecknell
On Wed, 24 Jan 2007 10:41:09 -0500, Robert Dockins wrote:

 newtype Mu a = Roll { unroll :: Mu a - a }
 
 omega :: a
 omega = (\x - (unroll x) x) (Roll (\x - (unroll x) x))
 
 fix :: (a - a) - a
 fix f = (\x - f . (unroll x) x) (Roll (\x - f . (unroll x) x)) omega
 
 ones :: [Int]
 ones = fix (1:)
 
 fibs :: [Int]
 fibs = fix (\f a b - a : f b (a+b)) 0 1

That's an interesting definition of fix that I haven't seen before,
though I am a little puzzled by omega. Since I have an irrational fear
of recursion, and I like to take every opportunity I get to cure it, I
decided to take a closer look...

I figure omgea is just a way to write _|_ as an anonymous lambda
expression. But that made me wonder what it's doing in the definition of
fix. I can see that without it, fix would have the wrong type, since
type inference gives the x parameters the type (Mu(b-a)):

 -- A bit like fix, except it's, erm...
 broke :: (a - a) - b - a
 broke f = (\x - f . unroll x x) (Roll (\x - f . unroll x x))

So omega consumes an argument that has unconstrained type, and which
appears to be unused. It's perhaps easier to see the unused argument
with fix rewritten in a more point-full style:

 fix' f = (\x y - f (unroll x x y)) (Roll (\x y - f (unroll x x y))) omega

Performing the application, (fix' f) becomes (f(fix' f)), and so on.

So, I think I follow how this fixed-point operator works, and it seems
reasonable to use _|_ to consume an unused non-strict argument. But I
find it mildly disturbing that this unused argument seems to appear out
of nowhere.

Then I noticed that rewriting fix without (.) seems to work just as well
(modulo non-termination of the GHC inliner), and without the unused
argument:

 fix :: (a - a) - a
 fix f = (\x - f (unroll x x)) (Roll (\x - f (unroll x x)))

Of course, the corollary is that I can introduce as many unused
arguments as I want:

 fix'' f = (\x - (f.).(unroll x x)) (Roll (\x - (f.).(unroll x x))) omega 
 omega
 fix''' f = (\x - ((f.).).(unroll x x)) (Roll (\x - ((f.).).(unroll x x))) 
 omega omega omega
 -- etc...

This gave me a new way to approach the question of where the unused
argument came from. Given a function (f) of appropriate type, I can
write:

 f :: a - a
 (f.) :: (b - a) - (b - a)
 ((f.).) :: (c - b - a) - (c - b - a)

And so on. Nothing strange here. But all of these functions can inhabit
the argument type of fix, so:

 fix :: (a - a) - a
 fix f :: a
 fix (f.) :: b - a
 fix ((f.).) :: c - b - a

Those are some strange types, and I have found those unused arguments
without reference to any particular implementation of fix. Thinking
about it, (forall a b . b - a) is no stranger than (forall a . a).
Indeed, I think the only thing that can have type (forall a . a) is _|_.
Likewise, I can't imagine anything other than the identity function
having the type (forall a . a - a), and it's not too hard to see where
(fix id) would lead.

So perhaps it's not the appearance of the unused argument in the above
definition of the fixed-point operator, but the type of the fixed-point
operator in general that is a bit strange. Certainly, I have always
found fix to be mysterious, even though I am getting quite comfortable
with using it.

I'm wondering: Is any of this related to the preceding discussion about
how fix affects parametricity? Can anyone recommend some
(preferably entry-level) readings?

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


[Haskell-cafe] Re: Extensible static checking of dimensions?

2007-01-28 Thread Björn Buckwalter

Mike Gunter m at ryangunter.com wrote:

| The very nice Buckwalter and Denney dimensional-numbers packages both
| work on a fixed set of base dimensions.  This is a significant
| restriction for me--I want to avoid adding apples to oranges as well
| as avoiding adding meters to grams.  Is it possible to have an
| extensible set of base dimensions?  If so, how usable can such a
| system be made?  Is it very much worse than a system with a fixed set
| of base dimensions?

Mike,

I apologize for not having replied to your message earlier, I have not
been subscribing to the café and only recently noticed your post in
the archives.

As for you question, please see the literate haskell module below. It
allows you to extend the set of SI base dimensions in
'Buckwalter.Dimensional' with an arbitrary number of extra dimensions.
My hope is that it lifts the significant restriction you saw
previously.

As for the usability of such a system, once you have set up the
dimensions relevant to your problem domain usage should be identical
to (and seamless with) the original base dimensions. You will have to
be the judge as to whether it is usable enough for you. I would
certainly appreciate comments on usability. In fact I would also be
interested to hear how you envision applying the functionality you
requested, regardless of this modules usefulness.

Also, I can't promise that the module is rock solid -- I haven't done
a whole lot of testing.

If you don't have the 'Buckwalter.NumTypes' and
'Buckwalter.Dimensional' modules already you can download the latest
tarball with all three modules from the project web site at:
http://code.google.com/p/dimensional/

Thanks,
Björn Buckwalter


~~ BEGIN 'Buckwalter/Dimensional/Extensible.lhs' ~~

Buckwalter.Dimensional.Extensible -- Extensible physical dimensions
Bjorn Buckwalter, [EMAIL PROTECTED]
License: BSD3


= Summary =

On January 3 Mike Gunter asked[1]:

| The very nice Buckwalter and Denney dimensional-numbers packages
| both work on a fixed set of base dimensions.  This is a significant
| restriction for me--I want to avoid adding apples to oranges as
| well as avoiding adding meters to grams.  Is it possible to have
| an extensible set of base dimensions?  If so, how usable can such
| a system be made?  Is it very much worse than a system with a fixed
| set of base dimensions?

In this module we facilitate the addition an arbitrary number of
extra dimensions to the seven base dimensions defined in
'Buckwalter.Dimensional'. A quantity or unit with one or more extra
dimensions will be referred to as an extended dimensional.


= Preliminaries =

Similarly with 'Buckwalter.Dimensional' this module requires GHC
6.6 or later.


{-# OPTIONS_GHC -fglasgow-exts -fallow-undecidable-instances #-}



module Buckwalter.Dimensional.Extensible
  where



import Prelude hiding
  ((*), (/), (+), (-), (^), sqrt, negate, pi, sin, cos, exp)
import qualified Prelude as P ((*), sin, cos, exp)
import Buckwalter.NumType (NumType, Add, Sub, Halve, Negate, Zero, Pos1)
import Buckwalter.Dimensional hiding (square, cubic, sin, cos, exp)



= DExt, Apples and Oranges =

We define the datatype 'DExt' which we will use to increase the
number of dimensions from the seven SI base dimensions to an arbitrary
number of dimensions. We make 'DExt' an instance of 'Dims' allowing
us to use the 'Dimensional' type without change.


data (NumType n, Dims d) = DExt n d
instance Dims (DExt n d)


Using 'DExt' we can define type synonyms for extended dimensions
applicable to our problem domain. For exampel, Mike Gunter could
define the 'Apples' and 'Oranges' dimensions and the corresponding
quantities.

] type DApples  = DExt Pos1 (DExt Zero DOne)
] type DOranges = DExt Zero (DExt Pos1 DOne)

] type Apples   = Quantity DApples
] type Oranges  = Quantity DOranges

And while he was at it he could define corresponding units.

] apple  :: Num a = Unit DApples a
] apple  = Dimensional 1
] orange :: Num a = Unit DOranges a
] orange = Dimensional 1


= Arithmetic =

We get negation, addition and subtracton for free with extended
dimensionals. However, we will need instances of the 'Mul', 'Div'
and 'Sqrt' classes for the corresponding operations to work.


instance (Add n n' n'', Mul d d' d'')
  = Mul (DExt n d) (DExt n' d') (DExt n'' d'')



instance (Sub n n' n'', Div d d' d'')
  = Div (DExt n d) (DExt n' d') (DExt n'' d'')



instance (Halve n n', Sqrt d d') = Sqrt (DExt n d) (DExt n' d')


Now, in order to work seamlessly with the quantities and units
defined in 'Buckwalter.Dimensional' we must be able to automatically
extend their dimensions when multiplying or dividing by an extended
dimensional.


instance (Mul d (Dim l m t i th n j) d') = Mul (DExt x d)
(Dim l m t i th n j)
(DExt x d')
instance (Mul (Dim l m t i th n j) d d') = Mul (Dim l m t i th n j)
  

[Haskell-cafe] Re: Fixed-point operator (was: seq does not preclude parametricity)

2007-01-28 Thread Robert Dockins
On Sunday 28 January 2007 23:19, Matthew Brecknell wrote:
 On Wed, 24 Jan 2007 10:41:09 -0500, Robert Dockins wrote:
  newtype Mu a = Roll { unroll :: Mu a - a }
 
  omega :: a
  omega = (\x - (unroll x) x) (Roll (\x - (unroll x) x))
 
  fix :: (a - a) - a
  fix f = (\x - f . (unroll x) x) (Roll (\x - f . (unroll x) x)) omega
 
  ones :: [Int]
  ones = fix (1:)
 
  fibs :: [Int]
  fibs = fix (\f a b - a : f b (a+b)) 0 1

 That's an interesting definition of fix that I haven't seen before,
 though I am a little puzzled by omega. Since I have an irrational fear
 of recursion, and I like to take every opportunity I get to cure it, I
 decided to take a closer look...

 I figure omgea is just a way to write _|_ as an anonymous lambda
 expression.

Yup.  If you type-erase it, you get the very familiar term:

(\x - x x) (\x - x x)

Which is the canonical non-terminating untyped lambda term.

 But that made me wonder what it's doing in the definition of 
 fix.

I like to think of fix as implementing the semantics of recursion via the 
ascending Kleene chain.  Kleene's fixpoint theorem says that:

least_fixpoint( f ) = least_upper_bound (f^i  _|_   |   i in N )

where f^i means f composed together i times.

If you run it out, you'll see that my definition of fix calculates something 
like:

(f . f . f . f  ... ) _|_

===

f (f (f (f ( ... _|_


 I can see that without it, fix would have the wrong type, since 

 type inference gives the x parameters the type (Mu(b-a)):
  -- A bit like fix, except it's, erm...
  broke :: (a - a) - b - a
  broke f = (\x - f . unroll x x) (Roll (\x - f . unroll x x))

 So omega consumes an argument that has unconstrained type, and which
 appears to be unused. It's perhaps easier to see the unused argument

 with fix rewritten in a more point-full style:
  fix' f = (\x y - f (unroll x x y)) (Roll (\x y - f (unroll x x y)))
  omega

 Performing the application, (fix' f) becomes (f(fix' f)), and so on.

 So, I think I follow how this fixed-point operator works, and it seems
 reasonable to use _|_ to consume an unused non-strict argument. But I
 find it mildly disturbing that this unused argument seems to appear out
 of nowhere.

 Then I noticed that rewriting fix without (.) seems to work just as well
 (modulo non-termination of the GHC inliner), and without the unused

 argument:
  fix :: (a - a) - a
  fix f = (\x - f (unroll x x)) (Roll (\x - f (unroll x x)))

This is another fine way to write it.

 Of course, the corollary is that I can introduce as many unused

 arguments as I want:
  fix'' f = (\x - (f.).(unroll x x)) (Roll (\x - (f.).(unroll x x)))
  omega omega fix''' f = (\x - ((f.).).(unroll x x)) (Roll (\x -
  ((f.).).(unroll x x))) omega omega omega -- etc...

 This gave me a new way to approach the question of where the unused
 argument came from. Given a function (f) of appropriate type, I can

 write:
  f :: a - a
  (f.) :: (b - a) - (b - a)
  ((f.).) :: (c - b - a) - (c - b - a)

 And so on. Nothing strange here. But all of these functions can inhabit

 the argument type of fix, so:
  fix :: (a - a) - a
  fix f :: a
  fix (f.) :: b - a
  fix ((f.).) :: c - b - a

 Those are some strange types, and I have found those unused arguments
 without reference to any particular implementation of fix. Thinking
 about it, (forall a b . b - a) is no stranger than (forall a . a).
 Indeed, I think the only thing that can have type (forall a . a) is _|_.
 Likewise, I can't imagine anything other than the identity function
 having the type (forall a . a - a), and it's not too hard to see where
 (fix id) would lead.

 So perhaps it's not the appearance of the unused argument in the above
 definition of the fixed-point operator, but the type of the fixed-point
 operator in general that is a bit strange. Certainly, I have always
 found fix to be mysterious, even though I am getting quite comfortable
 with using it.

 I'm wondering: Is any of this related to the preceding discussion about
 how fix affects parametricity? Can anyone recommend some
 (preferably entry-level) readings?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How did you stumble on Haskell?

2007-01-28 Thread Michael T. Richter
On Sun, 2007-28-01 at 19:01 -0800, Alexy Khrabrov wrote:

 How do people stumble on Haskell?


I was working at a company I won't name on a product line that was
collapsing under the weight of C++, mismanagement and the typical
arch-conservatism of practicing programmers (for whom UNIX is still
fresh and new).  I was burning out rapidly as I foresaw the impending
collapse of the company and was trying to figure out how to regain the
love I used to have for my job.

I decided that the technology we were using was part of the problem (and
likely the indirect source of all the other problems like the management
ones) and started looking at alternatives including Modula-3, Dylan, ML
dialects, Erlang, etc.  While investigating the MLs I stumbled across a
reference (somewhat disparaging) to Haskell and lazy evaluation.  I
followed up on it (because the disparaging comment looked clannish to
me) and looked at Haskell more closely.

At the time I rejected Haskell as being too academic-oriented in
favour of Dylan.  Not long after that I gave up on software in general
and took a nearly six-year break.  During that time, as I relocated my
initial love for programming, I looked at Haskell again and it took this
time.

-- 
Michael T. Richter
Email: [EMAIL PROTECTED], [EMAIL PROTECTED]
MSN: [EMAIL PROTECTED], [EMAIL PROTECTED]; YIM:
michael_richter_1966; AIM: YanJiahua1966; ICQ: 241960658; Jabber:
[EMAIL PROTECTED]

I find many of the machines of violence very attractive. Tanks,
airplanes, warships, especially aircraft carriers. And the German
U-boats, submarines. --The Dalai Lama


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe