[Haskell-cafe] I 'd like to set up shop in Re: Haskell's market

2006-03-29 Thread Shae Matijs Erisson
Pete Chown <[EMAIL PROTECTED]> writes:

> One snag is that I doubt you could ring up an agency and ask for half a dozen
> Haskell programmers.  You could probably get people who did a bit of
> functional programming as part of a computer science degree, but that may not
> be enough for your needs.  (Having said that, if you did manage to find
> contract Haskell programmers, you would probably get people who were highly
> skilled, and enthusiastic about the chance to use the language.)

Me me! Pick me! Oh I'd love to do contract work with Haskell.

> In other words, Haskell might be a good answer technically, but it could
> paint the client into a corner business-wise.

I could easily come up with a bunch of resumes or CVs from smart #haskell
people who would enjoy doing contract work in Haskell.
(where bunch = at least ten, and probably more than twenty)

> I currently have a small amount of business logic that is implemented in
> Haskell, and I want to see it increase, but I'm always worried that this is
> going to happen.  I don't want a job for life maintaining this stuff, I want
> to delegate it to others at an appropriate time.

Me me! Pick me!

> You might find that Java, for example, would have more support for this type
> of application, out of the box.  Although Java is an unimaginative language,
> I find that productivity isn't too bad, mainly because there is plenty of
> library support for typical applications.  With Haskell, writing the business
> logic is quicker, but some of the time saved gets spent implementing things
> that come as standard with Java.

Libraries need to be implemented only once, after that everything gets faster.
Plus there's a lot more Haskell code out there than most people know about.
If you're looking for something specific, ask on the #haskell channel or here
on the mailing lists.

> I'm finding this quite a struggle, to be honest.  I can cope easily with the
> various homework assignments that get posted here, but I find it hard
> thinking about large applications in functional terms.  I'm building up to
> larger applications, but I'd feel nervous tackling something the size you are
> talking about at the moment.

I'm fond of monad transformers for structuring larger applications.
More details upon request...
-- 
I've tried to teach people autodidactism,| ScannedInAvian.com
but it seems they always have to learn it for themselves.| Shae Matijs Erisson

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


Pragmatic concurrency Re: [Haskell-cafe] multiple computations, same input

2006-03-29 Thread Jon Fairbairn
On 2006-03-28 at 08:02+0200 Tomasz Zielonka wrote:
> I wonder if it would be possible to remove the space-leak by running both
> branches concurrently, and scheduling threads in a way that would
> minimise the space-leak. I proposed this before
> 
>   http://www.haskell.org/pipermail/haskell-cafe/2005-December/013428.html
> 
> I would like to hear opinions from some compiler gurus.

This is something I've been thinking about on and off for a
long time (probably since John Hughes mentioned the case of
"average"). I even kept Tomasz's original message in my
inbox until today in the hope that I'd get round to sending
a response, but my flaky health gets in the way. So here,
and I hope people will allow for the fact that I'm half
asleep as I write this, is an attempt.

There are some observations I'd like to make, and a
proposal. Since the proposal relates (in a small way) to
concurrency and is, I think worthwhile, I've cc'd this
message to haskell-prime.

1) choosing the optimal reduction strategy is undecidable

2) we shouldn't (in general) attempt to do undecidable
   things automatically

3) Separation of concerns: Pragmatic decisions about
   evaluation order should be kept separate from the
   denotational aspect of the code. By this token, seq
   shouldn't be a function (because it isn't one), but a
   pragma.  The fact that it's shorter to write seq a b than
   {-# SEQ a #-} b is a matter of syntax, so shouldn't rate
   highly in language design decisions. Perhaps we want a
   different syntax for this kind of pragma, but that's a
   side issue.

So, to take Tomasz's example of wc, we want to be able to
define it essentially this way:

wc cs = (ll, ww, cc) where ll = lines cs
   ww = words cs
   cc = length cs

but add [a] pragma[s] to the effect that evaluation should
be input driven, and that ll, ww, and cc are to be given
equal time. Something like {-# STEPPER cs; ROUND_ROBIN
ll,ww,cc #-} (please do not take this as a suggestion of
real syntax!).

The way I would implement this is to add a new primitive,
STEP, which is like seq except that it only evaluates its
argument until it encounters another STEP. (It really isn't
much different to seq).

So after the compiler understood the pragma, it would
replace wc with this (allowing the compiler to pretend step
is a function):

wc cs = (ll, ww, cc) where ll = lines cs'
   ww = words cs'
   cc = length cs'
   cs' = foldr (\a -> STEP ll . STEP ww . STEP cc . 
(a:))
   []
   cs

Evaluation would start as normal (a wrinkle here is that the
way I've written it, whichever element of the tuple is
evaluated first gets two goes at the start, but that's a
compiler detail). when it came to evaluating cs', it would
be looking at a thunk something like

STEP ll (STEP ww (STEP cc ('x': ...)))

update the thunk to 

(STEP ww (STEP cc ('x': ...)))

evaluate ll until (and if) it hits the thunk again, update
it to

(STEP cc ('x': ...))

evaluate ww until it hits the thunk, update it to 

'x' : (STEP ...)

evaluate cc, and so on.

It seems to me that this wouldn't take much effort to
implement, but it would provide a simple means of removing
space leaks from a whole bunch of programmes without
mangling the source code much.

  Jón


-- 
Jón Fairbairn  Jon.Fairbairn at cl.cam.ac.uk


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


Re: Pragmatic concurrency Re: [Haskell-cafe] multiple computations, same input

2006-03-29 Thread Robin Green
On Wed, 29 Mar 2006 12:50:02 +0100
Jon Fairbairn <[EMAIL PROTECTED]> wrote:
> There are some observations I'd like to make, and a
> proposal. Since the proposal relates (in a small way) to
> concurrency and is, I think worthwhile, I've cc'd this
> message to haskell-prime.
> 
> 1) choosing the optimal reduction strategy is undecidable
> 
> 2) we shouldn't (in general) attempt to do undecidable
>things automatically
> 
> 3) Separation of concerns: Pragmatic decisions about
>evaluation order should be kept separate from the
>denotational aspect of the code. By this token, seq
>shouldn't be a function (because it isn't one), but a
>pragma.  The fact that it's shorter to write seq a b than
>{-# SEQ a #-} b is a matter of syntax, so shouldn't rate
>highly in language design decisions. Perhaps we want a
>different syntax for this kind of pragma, but that's a
>side issue.

I don't like pragmas because (at least in C) they are defined to be
optional and can be ignored by the compiler. We need optimisation
methods that work across all Haskell implementations (of a given
Haskell standard).

I suggest that a Haskell program should be treated as an executable
specification. In some cases the compiler can't optimise the program
well enough, so we (by which I mean, ordinary programmers, not compiler
geeks) should be able to explicitly provide our own optimisations, as
rewrite rules (generalised ones, or specialised ones for individual
functions). Democratise the means of automated optimisation! Then we
should be able to prove formally that our rewrite rules preserve
functional correctness. This is the approach I am pursuing in the
programming language I am working on, which is a derivative of Haskell.

(In principle you could write rewrite rules in Template Haskell, but I
don't know if anyone has tried that.)

This way of looking at it is nice, because then we don't have to shut
off whole avenues of fruitful thought, on the grounds of "Oh no, the
compiler is far too stupid to do that", or "Oh no, that's far too much
of a special case for this particular example, and it would bloat the
compiler too much to include little things like this".

The way I would optimise the wc example in my language is as follows:

First translate it into a monadic pipeline in the State monad:

wc = evalState $ do
w <- passthru (length . words)
l <- passthru (length . lines)
c <- passthru length
return (w,l,c)
where
passthru = gets

Then convert that monadic action into a semi-lazy imperative pipeline on
lists (semi-lazy because the pipeline is evaluated lazily, but the
side-effects of the pipeline are evaluated strictly - or something
like that - I have difficulty explaining it). This is too involved to go
into here (and I haven't worked out the details of the rewrite rules
yet), but the basic idea looks like this pseudo-shell-script:

words -output w | lines -output l | length -output c >/dev/null
echo "(`cat w`, `cat l`, `cat c`)"
rm -f w l c

Each command in the first line of this pseudo-shell-script copies its
list from standard input to standard output, and stores its result in a
temporary file named by the -output option. (Obviously, in the real
code, temporary files wouldn't be used, and nor would operating system
pipes be used - I just found them convenient in order to analogise my
solution as a shell script.)

Despite the apparent waste of copying a list three times, this is
actually more efficient than the original code because it doesn't need
to store any lists in memory.

There might be better ways to do it, but that's just an idea off the top
of my head.
-- 
Robin
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Pragmatic concurrency Re: [Haskell-cafe] multiple computations, same input

2006-03-29 Thread Brian Hulley

Robin Green wrote:

On Wed, 29 Mar 2006 12:50:02 +0100
Jon Fairbairn <[EMAIL PROTECTED]> wrote:

[snip]
1) choosing the optimal reduction strategy is undecidable

2) we shouldn't (in general) attempt to do undecidable
   things automatically
[snip]

[snip]
I suggest that a Haskell program should be treated as an executable
specification. In some cases the compiler can't optimise the program
well enough, so we (by which I mean, ordinary programmers, not
compiler geeks) should be able to explicitly provide our own
optimisations, as rewrite rules (generalised ones, or specialised
ones for individual functions). Democratise the means of automated
optimisation!


This sounds good. The only thing I'm wondering is what do we actually gain 
by using Haskell in the first place instead of just a strict language? It 
seems that Haskell's lazyness gives a succinct but too inefficient program 
which then needs extra code in the form of rewrite rules/pragmas, or else a 
complete rewrite in terms of seq etc to get it to run fast enough without 
space leaks...


Regards, Brian. 


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


Re: Pragmatic concurrency Re: [Haskell-cafe] multiple computations, same input

2006-03-29 Thread Brian Hulley

Brian Hulley wrote:

Robin Green wrote:

On Wed, 29 Mar 2006 12:50:02 +0100
Jon Fairbairn <[EMAIL PROTECTED]> wrote:

[snip]
1) choosing the optimal reduction strategy is undecidable

2) we shouldn't (in general) attempt to do undecidable
   things automatically
[snip]

[snip]
I suggest that a Haskell program should be treated as an executable
specification. In some cases the compiler can't optimise the program
well enough, so we (by which I mean, ordinary programmers, not
compiler geeks) should be able to explicitly provide our own
optimisations, as rewrite rules (generalised ones, or specialised
ones for individual functions). Democratise the means of automated
optimisation!


This sounds good. The only thing I'm wondering is what do we actually
gain by using Haskell in the first place instead of just a strict
language? It seems that Haskell's lazyness gives a succinct but too
inefficient program which then needs extra code in the form of
rewrite rules/pragmas, or else a complete rewrite in terms of seq etc
to get it to run fast enough without space leaks...


Thinking about this some more, I realised Jon had already answered this 
question in his 3rd point:


On Wed, 29 Mar 2006 12:50:02 +0100
Jon Fairbairn <[EMAIL PROTECTED]> wrote:
> 3) Separation of concerns: Pragmatic decisions about
>evaluation order should be kept separate from the
>denotational aspect of the code. By this token, seq

I wonder if there could be a really large repository of rewrite rules on the 
web somewhere, with heuristics to determine various strategies for applying 
them.


There would also need to be some automated way of proving correctness of 
rewrite rules, so that if someone submitted a new one it would be sure not 
to introduce bugs into the optimization.


In this way, the Haskell community could gradually chip away at the 
undecidableness of automatically optimizing Haskell programs, because it may 
turn out to be the case that most functions are members of a very small 
subset of the possible Haskell functions and could thus be handled by a 
finite set of rewrite rules.


Regards, Brian.


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


[Haskell-cafe] Re: Positive integers

2006-03-29 Thread Aaron Denney
On 2006-03-27, Dylan Thurston <[EMAIL PROTECTED]> wrote:
>
> --===0906829955==
> Content-Type: multipart/signed; micalg=pgp-sha1;
>   protocol="application/pgp-signature"; boundary="3V7upXqbjpZ4EhLz"
> Content-Disposition: inline
>
>
> --3V7upXqbjpZ4EhLz
> Content-Type: text/plain; charset=us-ascii
> Content-Disposition: inline
> Content-Transfer-Encoding: quoted-printable
>
> On Mon, Mar 27, 2006 at 05:02:20AM -0800, John Meacham wrote:
>> well, in interfaces you are going to end up with some specific class or
>> another concretely mentioned in your type signatures, which means you
>> can't interact with code that only knows about the alternate class. like
>>=20
>> genericLength :: Integral a =3D> [b] -> a
>>=20
>> if you have a different 'Integral' you can't call genericLength with it,
>> or anything built up on genericLength. basically there would be no way
>> for 'new' and 'old' polymorphic code to interact.=20
>
> I think the idea would be that the source for genericLength would
> compile using either class hierarchy with no change.  For the case of
> genericLength, this is true for the proposed alternate prelude Hennig
> Theilemann pointed to.  It would be mostly true in general for that
> proposal, with the exception that you would sometimes need to add Show
> or Eq instances.

Right.

>> the inability to evolve the class hierarchy is a serious issue, enough
>> that it very well could be impractical for haskell' unless something
>> like class aliases were widely adopted.
>
> I think that as long as you're not defining classes source compatibility
> would not be hard.  Of course you couldn't hope to link code written
> with one hierarchy against another.

Wouldn't instance declaration also be problematic?

(And yes, we desperately need something like class aliases.)

-- 
Aaron Denney
-><-

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


Re: Pragmatic concurrency Re: [Haskell-cafe] multiple computations, same input

2006-03-29 Thread Philippa Cowderoy
On Wed, 29 Mar 2006, Brian Hulley wrote:

> This sounds good. The only thing I'm wondering is what do we actually gain by
> using Haskell in the first place instead of just a strict language? It seems
> that Haskell's lazyness gives a succinct but too inefficient program which
> then needs extra code in the form of rewrite rules/pragmas, or else a complete
> rewrite in terms of seq etc to get it to run fast enough without space
> leaks...
> 

Often the laziness is useful for purposes of efficiency as well though.

-- 
[EMAIL PROTECTED]

Sometimes you gotta fight fire with fire. Most 
of the time you just get burnt worse though.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Pragmatic concurrency Re: [Haskell-cafe] multiple computations, same input

2006-03-29 Thread John Meacham
On Wed, Mar 29, 2006 at 03:23:04PM +0100, Robin Green wrote:
> I suggest that a Haskell program should be treated as an executable
> specification. In some cases the compiler can't optimise the program
> well enough, so we (by which I mean, ordinary programmers, not compiler
> geeks) should be able to explicitly provide our own optimisations, as
> rewrite rules (generalised ones, or specialised ones for individual
> functions). Democratise the means of automated optimisation! Then we
> should be able to prove formally that our rewrite rules preserve
> functional correctness. This is the approach I am pursuing in the
> programming language I am working on, which is a derivative of Haskell.

have you seen the RULES pragma? it is implemented in both ghc and jhc.
 
http://www.haskell.org/ghc/docs/6.4/html/users_guide/rewrite-rules.html

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Newbie question: inferred type

2006-03-29 Thread David Laffin

Hi,

Newbie question. Given the inferred type for square,
the
inferred types for quad1, quad2 and quad3 are what I
would
expect. Is there a straightforward explanation (i.e.
one
that a newbie would understand) as to why the inferred
type
for quad4 is less general?

Regards,
dl

-- GHC Interactive, version 6.4, for Haskell 98.

Prelude> let square x = x * x
Prelude> :t square
square :: (Num a) => a -> a

Prelude> let quad1 x = square (square x)
Prelude> :t quad1
quad1 :: (Num a) => a -> a

Prelude> let quad2 x = square $ square x
Prelude> :t quad2
quad2 :: (Num a) => a -> a

Prelude> let quad3 x = (square . square) x
Prelude> :t quad3
quad3 :: (Num a) => a -> a

Prelude> let quad4 = square . square
Prelude> :t quad4
quad4 :: Integer -> Integer






___ 
Yahoo! Photos – NEW, now offering a quality print service from just 8p a photo 
http://uk.photos.yahoo.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Newbie question: inferred type

2006-03-29 Thread Neil Mitchell
I think this is the monomorphism restriction, you can see more details
on the web page:

http://www.haskell.org/hawiki/MonomorphismRestriction

On 3/30/06, David Laffin <[EMAIL PROTECTED]> wrote:
>
> Hi,
>
> Newbie question. Given the inferred type for square,
> the
> inferred types for quad1, quad2 and quad3 are what I
> would
> expect. Is there a straightforward explanation (i.e.
> one
> that a newbie would understand) as to why the inferred
> type
> for quad4 is less general?
>
> Regards,
> dl
>
> -- GHC Interactive, version 6.4, for Haskell 98.
>
> Prelude> let square x = x * x
> Prelude> :t square
> square :: (Num a) => a -> a
>
> Prelude> let quad1 x = square (square x)
> Prelude> :t quad1
> quad1 :: (Num a) => a -> a
>
> Prelude> let quad2 x = square $ square x
> Prelude> :t quad2
> quad2 :: (Num a) => a -> a
>
> Prelude> let quad3 x = (square . square) x
> Prelude> :t quad3
> quad3 :: (Num a) => a -> a
>
> Prelude> let quad4 = square . square
> Prelude> :t quad4
> quad4 :: Integer -> Integer
>
>
>
>
>
>
> ___
> Yahoo! Photos – NEW, now offering a quality print service from just 8p a 
> photo http://uk.photos.yahoo.com
> ___
> 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