Re: [Haskell-cafe] cabal haddock doesn't work for me on win7

2010-08-11 Thread Stephen Tetley
The problem was noted in this thread a couple of months ago:

http://www.haskell.org/pipermail/haskell-cafe/2010-June/078914.html

I'm not sure what the resolution was.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Haskell in Industry

2010-08-11 Thread Ketil Malde
Henning Thielemann schlepp...@henning-thielemann.de writes:

 about functional programming jobs in investment banking ...

 I don't think this is bad: having talented people recruited to work
 on functional programming will improve the technology for all of us.

 I'm not sure I follow this opinion in general. Analogously I could say:
 Supporting military is a good idea, since they invest in new
 technologies.

Sure, if the premise is that investment banks (or the military) are evil,
then it is morally questionable to support them.  If these are the
major consumers of functional programming, one might question the ethics
of working on FP in general as well.

But as I interpreted this thread, the premise was not about the morality
of specific sectors, but rather that finance takes away too much of
the FP talent.  My opinion is that we should rather appreciate business
or organizations willing to fund FP - perhaps especially for evil
organizations, where funds would otherwise go to more nefarious
purposes.

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Can we come out of a monad?

2010-08-11 Thread Ertugrul Soeylemez
Martijn van Steenbergen mart...@van.steenbergen.nl wrote:

 On 8/2/10 7:09, Ertugrul Soeylemez wrote:
  Given the definition of a Haskell function, Haskell is a pure
  language.  The notion of a function in other languages is not:
 
 int randomNumber();
 
  The result of this function is an integer.  You can't replace the
  function call by its result without changing the meaning of the
  program.

 I'm not sure this is fair. It's perfectly okay to replace a call
 randomNumber() by that method's *body* (1), which is what you argue
 is okay in Haskell.

This is not the same.  In Haskell you can replace the function call by
its /result/, not its body.  You can always do that.  But the result of
an IO-based random number generator is an IO computation, not a value.
It's not source code either, and it's not a function body.  It's a
computation, something abstract without a particular representation.

This is what referential transparency is about.  Not replacing function
calls by function bodies, but by their /results/.  In C you can't
replace

  putchar(33)

by

  33

because that changes the program.  Of course there are some exceptions
like many functions from math.h.  Unlike Haskell you don't write a
program by using a DSL (like the IO monad), but you encode it directly
as a series of statements and function calls.  C has no notion of a
computation the same way Haskell has.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife = sex)
http://ertes.de/


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


[Haskell-cafe] Re: Can we come out of a monad?

2010-08-11 Thread Ertugrul Soeylemez
Edward Z. Yang ezy...@mit.edu wrote:

 Excerpts from Ertugrul Soeylemez's message of Tue Aug 10 03:40:02 -0400 2010:
  Then you can only run evalCont, if r = a, which makes that function
  quite pointless:
 
evalCont :: Cont r r - r
evalCont = runCont id

 Ah, yes, that was what I was imagining.  I don't think the function is
 useless (though it is pointless ;-); it lets you transform
 continuation-style code into normal code.  Also, r is usually not
 fixed (unless you use mapCont or similar), so it might be more
 accurately described as Cont a a - a.

My point was, I would just write 'runCont id'. ;)

The result type of the computation is fixed.  It cannot change between
(=).  Note that 'a' is the result of one subcomputation, i.e. the
result of one particular CPS-style function, while 'r' is the result of
the entire computation.  So runCont should give you an 'r', not an 'a'.
In this case, they just happen to be the same.  But of course this is
really a matter of taste. =)


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife = sex)
http://ertes.de/


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


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-08-11 Thread Thomas Davie

On 11 Aug 2010, at 12:39, Ertugrul Soeylemez wrote:

 Martijn van Steenbergen mart...@van.steenbergen.nl wrote:
 
 On 8/2/10 7:09, Ertugrul Soeylemez wrote:
 Given the definition of a Haskell function, Haskell is a pure
 language.  The notion of a function in other languages is not:
 
   int randomNumber();
 
 The result of this function is an integer.  You can't replace the
 function call by its result without changing the meaning of the
 program.
 
 I'm not sure this is fair. It's perfectly okay to replace a call
 randomNumber() by that method's *body* (1), which is what you argue
 is okay in Haskell.
 
 This is not the same.  In Haskell you can replace the function call by
 its /result/, not its body.  You can always do that.  But the result of
 an IO-based random number generator is an IO computation, not a value.
 It's not source code either, and it's not a function body.  It's a
 computation, something abstract without a particular representation.

It's still rather papering over the cracks to call this pure though.  The IO 
based computation itself still has a result that you *can't* replace the IO 
based computation with.  The fact that it's evaluated by the runtime and not 
strictly in haskell may give us a warm fuzzy feeling inside, but it still means 
we have to watch out for a lot of things we don't normally have to in a very 
pure[1] computation.

Bob

[1] Bob's arbitrary definition 1 – very pure computations are ones which can be 
replaced with their result without changing the behavior of the program *even* 
if said result is computed in the runtime and not by the Haskel 
program.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Can we come out of a monad?

2010-08-11 Thread Ertugrul Soeylemez
Thomas Davie tom.da...@gmail.com wrote:

 On 11 Aug 2010, at 12:39, Ertugrul Soeylemez wrote:

  Martijn van Steenbergen mart...@van.steenbergen.nl wrote:
 
  On 8/2/10 7:09, Ertugrul Soeylemez wrote:
  Given the definition of a Haskell function, Haskell is a pure
  language.  The notion of a function in other languages is not:
 
int randomNumber();
 
  The result of this function is an integer.  You can't replace the
  function call by its result without changing the meaning of the
  program.
 
  I'm not sure this is fair. It's perfectly okay to replace a call
  randomNumber() by that method's *body* (1), which is what you
  argue is okay in Haskell.
 
  This is not the same.  In Haskell you can replace the function call
  by its /result/, not its body.  You can always do that.  But the
  result of an IO-based random number generator is an IO computation,
  not a value.  It's not source code either, and it's not a function
  body.  It's a computation, something abstract without a particular
  representation.

 It's still rather papering over the cracks to call this pure though.
 The IO based computation itself still has a result that you *can't*
 replace the IO based computation with.  The fact that it's evaluated
 by the runtime and not strictly in haskell may give us a warm fuzzy
 feeling inside, but it still means we have to watch out for a lot of
 things we don't normally have to in a very pure[1] computation.

You can always come up with the necessary transformations to replace a
function's call by its body.  But this is a trivial result and not
related to referential transparency.  It's like saying:  You can
replace every while loop by a label and a goto.  What a discovery!

A while loop would be referentially transparent, if it had some notion
of a result and you could replace the entire loop by that.  And a
function is referentially transparent, if you can replace the function's
call or equivalently (!) the function's body by the function's result.

Referntially transparent functions are inherently memoizable.  A C
function is definitely not.

There is a fundamental difference between an IO computation's result and
a Haskell function's result.  The IO computation is simply a value, not
a function.  Its result is something abstract with no concrete
representation in Haskell.  In fact you can come up with mental models,
which make even those computations referentially transparent.  For
example this one:

  type IO = State RealWorld

You can only use (=) to give such a result a name, so you can refer to
it.  But this is not a function's result.  It's a value constructed in
some unspecified way and only accessible while running the program.

Remember:  Referential transparency is a property of source code!


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife = sex)
http://ertes.de/


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


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-08-11 Thread Thomas Davie

On 11 Aug 2010, at 14:17, Ertugrul Soeylemez wrote:
 
 There is a fundamental difference between an IO computation's result and
 a Haskell function's result.  The IO computation is simply a value, not
 a function.

That's a rather odd distinction to make – a function is simply a value in a 
functional programming language.  You're simply wrapping up we're talking 
about haskell functions when we talk about referential transparency, not about 
IO actions in a way that maintains the warm fuzzy feeling.

Bob

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


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-08-11 Thread mokus

 On 11 Aug 2010, at 14:17, Ertugrul Soeylemez wrote:

 There is a fundamental difference between an IO computation's result and
 a Haskell function's result.  The IO computation is simply a value, not
 a function.

 That's a rather odd distinction to make – a function is simply a value in
 a functional programming language.  You're simply wrapping up we're
 talking about haskell functions when we talk about referential
 transparency, not about IO actions in a way that maintains the warm fuzzy
 feeling.

 Bob

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


I don't know whether anyone is calling the execution of IO actions pure -
I would not, at any rate.  At some level, things MUST 'execute', or why
are we programming at all?  Philosophical points aside, there is still a
meaningful distinction between evaluating and executing a monadic action. 
While execution may not be pure, evaluation always is - and in the
examples given so far in this thread, there is (trivial) evaluation
occurring, which is the pure part that people have been referring to
(while ignoring the impure execution aspect).  Consider a variation on the
random integer theme, where the evaluation stage is made non-trivial. 
Assuming existence of some functions randomElement and greet of suitable
types:

 main = do
 putStr What names do you go by (separate them by spaces)? 
 names - fmap words getLine
 greetRandomName names

 greetRandomName [] = putStrLn Hello there!
 greetRandomName names = randomElement names = greet

The result of _evaluating_ greetRandomName name is either @putStrLn
Hello there!@ or @randomElement names = greet@, depending whether the
input list is empty.  This result absolutely can be substituted for the
original expression and potentially further pre-evaluated if names is a
known quantity, without changing the meaning of the program.  And, to
address an idea brought up elsewhere in this thread, it is absolutely true
as pointed out before that given the right (monadic) perspective a C
program shares exactly the same properties.

There is real additional purity in Haskell's case though, and it has
absolutely nothing to do with hand-waving about whether IO is pure, very
pure, extra-super-distilled-mountain-spring-water pure, or anything like
that.  As you rightly point out, executing IO actions at run-time is not
pure at all, and we don't want it to be.  The difference is that while in
Haskell you still have an IO monad that does what C does (if you look at C
in that way), you also have a pure component of the language that can be
(and regularly is, though people often don't realize it) freely mixed with
it.  The monadic exists within the pure and the pure within the monadic. 
'greetRandomName' is a pure function that returns an IO action.  That's
not hand-waving or warm fuzzies, it's fact.  greetRandomName always
returns the same action for the same inputs.  The same distinction is
present in every monad, although in monads that are already pure, such as
Maybe, [], Cont, etc., it's not as big a deal.

The mixture is not as free as some would like; the fact that Haskell has
this distinction between monadic actions and pure values (and the fact
that the former can be manipulated as an instance of the latter) means
that the programmer must specify whether to evaluate (=) or execute
(-) an action, which is a source of endless confusion for beginners and
debate over what pure means.  I don't expect I'll put an end to either,
but I would like to point out anyway that, if you accept that distinction
(the reality of which is attested by the existence of a computable
function - the type checker - for making the distinction), it's fairly
easy to see that evaluation is always pure, excepting abuse of
unsafePerformIO, et al., and execution is not.  Both occur in the context
of do-notation.  Functions returning monadic actions (whether the
resulting action is being evaluated or executed) are still always
evaluated to yield an action.  That evaluation is pure.  The execution of
the action yielded may not be, nor should it have to be - that's the whole
point of IO!  But we still have as much purity as is actually possible,
because we know exactly where _execution_ occurs and we don't pretend it
doesn't by confusing definition with assignment.  = always means = in
Haskell, and - doesn't.  In C, = always means -, even when the RHS
is a simple variable reference (consider x = x;).

-- James

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


Re: [Haskell-cafe] Is there any experience using Software Transactional Memory in substantial applications?

2010-08-11 Thread Ketil Malde
Simon Peyton-Jones simo...@microsoft.com writes:

 In contrast, in a pure functional language there are no reads and
 writes, so all the pure part has zero overhead.  Only when you do
 readTVar' and 'writeTVar' do you pay the overhead; these are a tiny
 fraction of all memory accesses.

I'm curious if there are any work done on the scalability of STM.  Or
rather - I expect the answer to be yes, but I'm curious what the results
are :-)

From my small time experiments, there seems to be a noticeable but
liveable overhead to STM, even without collisions.  This is to be
expected.

But there also seem to be scalability issues, and in particular, the
time a transaction takes, appears to scale superlinearly (in fact, more
than O(n²)) with the number of TVars involved.  Is this correct?

(This is a killer for TArrays if you naïvely try to do:

   x - atomically $ (newListArray (0,n-1) [0..n-1] :: STM (TArray Int Int))
and
   atomically $ unsafeFreeze x

Instead, I had to do:

   x - atomically $ (newArray (0,n-1) 0 :: STM (TArray Int Int))
   sequence_ [atomically $ writeArray x i i | i - [0..n-1]]

and

   a - newArray (0,n-1) empty :: IO (IOArray Int Cluster)
   mapM_ (\i - do v - atomically $ readArray cmap i
   writeArray a i v) [0..n-1]
   unsafeFreeze a

After doing this, I measure roughly a factor of two between
(single-threaded) operations on TArrays and STArrays, which I think is
pretty good.  Remains to be seen how it scales with multiple threads,
though...)

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ghc in macports

2010-08-11 Thread Ozgur Akgun
Dear Cafe,

I wonder who is maintaining the ghc package in macports, and what the
current stategy of doing things is?
http://www.macports.org/ports.php?by=namesubstr=ghc (ghc 6.10.4)

Personally, I'd like to use the macports version, if the ghc version there
was resonably recent (having 2 versions, a stable and an edge could be a
good idea?)

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


[Haskell-cafe] Accepting and returning polyvariadic functions

2010-08-11 Thread Will Jones
Hi all,

I'm trying to write a function (I'll call it `vtuple' for lack of a better
name)
that returns a function that itself returns multiple arguments in the form
of a
tuple. For example:

 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE FunctionalDependencies #-}
 {-# LANGUAGE MultiParamTypeClasses #-}

 f :: Int - IO ()
 f = undefined

 g :: Int - Int - IO ()
 g = undefined

 h :: Int - Int - Int - IO ()
 h = undefined

vtuple f :: IO (Int - (Int, ()))
vtuple g :: IO (Int - Int - (Int, (Int, (

I've tried to type vtuple using a type class; my current effort is something
like:

 class VTuple ia ir a r | r - a, a - ia where
   vtuple :: (ia - ir) - IO (a - r)

 instance VTuple Int (IO ()) Int (Int, ()) where
 --vtuple :: (Int - IO ()) - IO (Int - (Int, ()))
   vtuple = undefined

 instance VTuple ia ir a r
   = VTuple Int (ia - ir) Int (a - (Int, r)) where

 --vtuple :: (Int - ia - ir) - IO (Int - a - (Int, r))
   vtuple = undefined

But this is problematic, since arrows creep in:

For one argument (fine):
  vtuple :: (Int - IO ()) - IO (Int - (Int, ()))

 vf :: IO (Int - (Int, ()))
 vf = vtuple f

For two arguments (also fine):
  vtuple  :: (Int - Int - IO ())
  - IO (Int - Int - (Int, (Int, (

 vg :: IO (Int - Int - (Int, (Int, (
 vg = vtuple g

For three (n!):
  vtuple  :: (Int - Int - IO ())
  - IO (Int - Int - (Int, (Int - (Int32, (Int32, ())

And so on. I've thought about it and it seems impossible to solve this
problem
-- you keep needing to ``split'' the function type one arrow further on. Is
this a job for Template Haskell or is there a solution I'm missing here?
Note
that I'd also like to use types other than Int, but I don't think this is
the
primary complication here (touch wood).

Any help much appreciated, thanks,
Will
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ghc in macports

2010-08-11 Thread Lyndon Maydwell
Seconded.

I've started using the Haskell Platform mainly because the ports
version is out of date.

Unfortunately it keeps getting pulled in as a dependency of something
even though I'm not using it.

On Wed, Aug 11, 2010 at 10:49 PM, Ozgur Akgun ozgurak...@gmail.com wrote:
 Dear Cafe,

 I wonder who is maintaining the ghc package in macports, and what the
 current stategy of doing things is?
 http://www.macports.org/ports.php?by=namesubstr=ghc (ghc 6.10.4)

 Personally, I'd like to use the macports version, if the ghc version there
 was resonably recent (having 2 versions, a stable and an edge could be a
 good idea?)

 Thanks,
 Ozgur


 ___
 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] ANN improve-0.0.4

2010-08-11 Thread Tom Hawkins
Hi,

ImProve [1] is a little imperative DSL that compiles to C code.
Intended for high assurance embedded applications, ImProve is also an
infinite state, unbounded model checker.  Meaning ImProve can verify
assertions in a program will always be true.  Here's an example:

  module Main where
  import Language.ImProve

  launchControl :: Stmt ()
  launchControl = do
presidentialAuthority - input bool presidentialAuthority
buttonPressed - input bool buttonPressed
launchMissiles- bool' launchMissiles $
(presidentialAuthority ||. buttonPressed)
assert conditionsToLaunch $ launchMissiles ==.
(presidentialAuthority . buttonPressed)

  main :: IO ()
  main = verify yices 20 launchControl


Running this program yields:

  verifying conditionsToLaunchFAILED: disproved basis in k = 1 (see trace)


On verification failures, ImProve will emit a counter example showing
the violation, which is essentially a program trace showing how things
could go wrong.  In this case, the trace looks like this:

  initialize launchMissiles := false
  cycle 0
  input presidentialAuthority == true
  input buttonPressed == false
  launchMissiles == true
  assertion FAILED: conditionsToLaunch

This basically means Barack was somehow able to launch on his own.
(Man!  I even voted for the guy!)

Under the hood, ImProve uses Yices [2] for SMT solving, and a method
of unbounded model checking known as k-induction.

Don't expect too much from ImProve; it's a very restrictive language.
It's basically three data types (bool, int, float), variables
assignments, and 'if' statements.  No procedures, no loops, no arrays,
no pointers, etc.  However, it can still do interesting things --
especially with Haskell combinators in play.

Hope you find it useful.  And as always, questions, comments, and
feedback welcome.

-Tom

[1] http://hackage.haskell.org/package/improve
[2] http://yices.csl.sri.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] cabal haddock doesn't work for me on win7

2010-08-11 Thread Ryan Ingram
It looks like there's a bug in the Haskell platform binary build for
Windows.  If someone could point me at their bugtrack database I'd be
happy to submit a report.

  -- ryan

On Wed, Aug 11, 2010 at 12:20 AM, Stephen Tetley
stephen.tet...@gmail.com wrote:
 The problem was noted in this thread a couple of months ago:

 http://www.haskell.org/pipermail/haskell-cafe/2010-June/078914.html

 I'm not sure what the resolution was.
 ___
 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] Accepting and returning polyvariadic functions

2010-08-11 Thread Ryan Ingram
There's no (safe) way to go from

a - IO b

to

IO (a - b)

which is part of what vtuple does.

Consider

foo :: Int - IO String
foo 0 = return zero
foo _ = launchMissles  return fired!

How would you implement foo2 :: IO (Int - String) with the same behavior?

You can't; you would somehow need to know the argument the function
was called at, and when it was going to be called, to implement foo2.

So I think you need a better specification!

  -- ryan

On Wed, Aug 11, 2010 at 8:50 AM, Will Jones w...@sacharissa.co.uk wrote:
 Hi all,

 I'm trying to write a function (I'll call it `vtuple' for lack of a better
 name)
 that returns a function that itself returns multiple arguments in the form
 of a
 tuple. For example:

 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE FunctionalDependencies #-}
 {-# LANGUAGE MultiParamTypeClasses #-}

 f :: Int - IO ()
 f = undefined

 g :: Int - Int - IO ()
 g = undefined

 h :: Int - Int - Int - IO ()
 h = undefined

 vtuple f :: IO (Int - (Int, ()))
 vtuple g :: IO (Int - Int - (Int, (Int, (

 I've tried to type vtuple using a type class; my current effort is something
 like:

 class VTuple ia ir a r | r - a, a - ia where
   vtuple :: (ia - ir) - IO (a - r)

 instance VTuple Int (IO ()) Int (Int, ()) where
 --vtuple :: (Int - IO ()) - IO (Int - (Int, ()))
   vtuple = undefined

 instance VTuple ia ir a r
   = VTuple Int (ia - ir) Int (a - (Int, r)) where

 --vtuple :: (Int - ia - ir) - IO (Int - a - (Int, r))
   vtuple = undefined

 But this is problematic, since arrows creep in:

 For one argument (fine):
   vtuple :: (Int - IO ()) - IO (Int - (Int, ()))

 vf :: IO (Int - (Int, ()))
 vf = vtuple f

 For two arguments (also fine):
   vtuple  :: (Int - Int - IO ())
   - IO (Int - Int - (Int, (Int, (

 vg :: IO (Int - Int - (Int, (Int, (
 vg = vtuple g

 For three (n!):
   vtuple  :: (Int - Int - IO ())
   - IO (Int - Int - (Int, (Int - (Int32, (Int32, ())

 And so on. I've thought about it and it seems impossible to solve this
 problem
 -- you keep needing to ``split'' the function type one arrow further on. Is
 this a job for Template Haskell or is there a solution I'm missing here?
 Note
 that I'd also like to use types other than Int, but I don't think this is
 the
 primary complication here (touch wood).

 Any help much appreciated, thanks,
 Will

 ___
 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] Accepting and returning polyvariadic functions

2010-08-11 Thread Will Jones
Hi Ryan,

Thanks for the reply. The specification I've given is just to illustrate the
kind of relationship I'm trying to establish between the types of the
argument and the result. In reality the type of the argument function is
something a little more usable; you could generalise it with type families
vis:

class HasDual t where
  type Dual t

class VTuple ia ir a r | r - a where
  vtuple :: (ia - ir) - IO (a - r)

-- m is some monad.
instance (HasDual t, Dual t ~ dual) = VTuple dual (m a) t (t, ())

etc.

I hope that clears things up; to be honest I'm not sure it's relevant -- the
more I look at it the more I'm stumped.

Cheers,
Will

On Wed, Aug 11, 2010 at 7:08 PM, Ryan Ingram ryani.s...@gmail.com wrote:

 There's no (safe) way to go from

 a - IO b

 to

 IO (a - b)

 which is part of what vtuple does.

 Consider

 foo :: Int - IO String
 foo 0 = return zero
 foo _ = launchMissles  return fired!

 How would you implement foo2 :: IO (Int - String) with the same behavior?

 You can't; you would somehow need to know the argument the function
 was called at, and when it was going to be called, to implement foo2.

 So I think you need a better specification!

  -- ryan

 On Wed, Aug 11, 2010 at 8:50 AM, Will Jones w...@sacharissa.co.uk wrote:
  Hi all,
 
  I'm trying to write a function (I'll call it `vtuple' for lack of a
 better
  name)
  that returns a function that itself returns multiple arguments in the
 form
  of a
  tuple. For example:
 
  {-# LANGUAGE FlexibleInstances #-}
  {-# LANGUAGE FunctionalDependencies #-}
  {-# LANGUAGE MultiParamTypeClasses #-}
 
  f :: Int - IO ()
  f = undefined
 
  g :: Int - Int - IO ()
  g = undefined
 
  h :: Int - Int - Int - IO ()
  h = undefined
 
  vtuple f :: IO (Int - (Int, ()))
  vtuple g :: IO (Int - Int - (Int, (Int, (
 
  I've tried to type vtuple using a type class; my current effort is
 something
  like:
 
  class VTuple ia ir a r | r - a, a - ia where
vtuple :: (ia - ir) - IO (a - r)
 
  instance VTuple Int (IO ()) Int (Int, ()) where
  --vtuple :: (Int - IO ()) - IO (Int - (Int, ()))
vtuple = undefined
 
  instance VTuple ia ir a r
= VTuple Int (ia - ir) Int (a - (Int, r)) where
 
  --vtuple :: (Int - ia - ir) - IO (Int - a - (Int, r))
vtuple = undefined
 
  But this is problematic, since arrows creep in:
 
  For one argument (fine):
vtuple :: (Int - IO ()) - IO (Int - (Int, ()))
 
  vf :: IO (Int - (Int, ()))
  vf = vtuple f
 
  For two arguments (also fine):
vtuple  :: (Int - Int - IO ())
- IO (Int - Int - (Int, (Int, (
 
  vg :: IO (Int - Int - (Int, (Int, (
  vg = vtuple g
 
  For three (n!):
vtuple  :: (Int - Int - IO ())
- IO (Int - Int - (Int, (Int - (Int32, (Int32, ())
 
  And so on. I've thought about it and it seems impossible to solve this
  problem
  -- you keep needing to ``split'' the function type one arrow further on.
 Is
  this a job for Template Haskell or is there a solution I'm missing here?
  Note
  that I'd also like to use types other than Int, but I don't think this is
  the
  primary complication here (touch wood).
 
  Any help much appreciated, thanks,
  Will
 
  ___
  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] Accepting and returning polyvariadic functions

2010-08-11 Thread Bartek Ćwikłowski
Hello Will,

2010/8/11 Will Jones w...@sacharissa.co.uk:
 I'm trying to write a function (I'll call it `vtuple' for lack of a better
 name)
 that returns a function that itself returns multiple arguments in the form
 of a
 tuple. For example:

 vtuple f :: IO (Int - (Int, ()))
 vtuple g :: IO (Int - Int - (Int, (Int, (

If we drop the IO (as pointed out by Ryan Ingram), vtuple seems weird
- the only sensible function of the type Int - Int - (Int, (Int,
())) is a function that collects its arguments and returns them in a
tuple, so it doesn't touch the input function g at all, it only cares
about g's arity.

Here's the solution:

 vtuple f = eat (arity f) `mcomp` hListToTuple

 class HListToTuple l r | l - r where
 hListToTuple :: l - r

 instance HListToTuple HNil () where
 hListToTuple _ = ()

 instance HListToTuple xs ys = HListToTuple (HCons x xs) (x,ys) where
 hListToTuple (HCons x xs) = (x,hListToTuple xs)

Rest of the code (functions eat, arity and mcomp) is presented here:
http://paczesiowa.blogspot.com/2010/03/generalized-zipwithn.html

Regards,
Bartek Ćwikłowski
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-08-11 Thread Dan Doel
On Wednesday 11 August 2010 9:49:07 am mo...@deepbondi.net wrote:
 The mixture is not as free as some would like; the fact that Haskell has
 this distinction between monadic actions and pure values (and the fact
 that the former can be manipulated as an instance of the latter) means
 that the programmer must specify whether to evaluate (=) or execute
 (-) an action, which is a source of endless confusion for beginners and
 debate over what pure means.  I don't expect I'll put an end to either,
 but I would like to point out anyway that, if you accept that distinction
 (the reality of which is attested by the existence of a computable
 function - the type checker - for making the distinction), it's fairly
 easy to see that evaluation is always pure, excepting abuse of
 unsafePerformIO, et al., and execution is not.  Both occur in the context
 of do-notation.  Functions returning monadic actions (whether the
 resulting action is being evaluated or executed) are still always
 evaluated to yield an action.  That evaluation is pure.  The execution of
 the action yielded may not be, nor should it have to be - that's the whole
 point of IO!  But we still have as much purity as is actually possible,
 because we know exactly where _execution_ occurs and we don't pretend it
 doesn't by confusing definition with assignment.  = always means = in
 Haskell, and - doesn't.  In C, = always means -, even when the RHS
 is a simple variable reference (consider x = x;).

This is the important point, I think. Some folks were arguing in #haskell the 
other day about whether BASIC could be viewed as 'pure,' since it's so simple, 
it's almost like writing a big IO block. If you go to Sabry's[1] definition of 
purity, then you could argue that independence of evaluation order is 
trivially satisfied, because there is no evaluation only execution as 
people call it.

But I think that side-steps something, in that pure on its own isn't 
interesting, certainly if it applies to BASIC that way. To be interesting, you 
have to look at the whole Sabry thesis, which is what is a pure *functional* 
language? For the second part of that, he identifies the requirement that 
your language have some sort of lambda calculus (possibly one enriched with 
datatypes, let, etc. as Haskell does) as a sublanguage.

It is only at that point that purity becomes interesting. A plain lambda 
calculus has certain nice, equational properties to its evaluation. We can 
inline or abstract out arbitrary expressions without changing the meaning of 
the program (at least, up to nontermination). The point of remaining pure, 
then, is to preserve this aspect of the lambda calculus portion of the 
language. This obviously means we can't just add rand :: () - Int, because 
then:

  let x = rand () in x + x  /=  rand () + rand ()

and that breaks the substitutional nature of the lambda calculus portion of 
the language (and it's why unsafePerformIO is clearly impure in this sense).

Instead, Haskell has a DSL for writing down the sort of effectful programs we 
want to write in practice, and the expressions in the DSL are first-class in 
the lambda calculus portion of the language. You can say that from the view 
internal to the DSL, inlining and abstraction are invalid, because:

  rand = \x - x + x  /=  rand = \x - rand = \y - x + y

but the important part (at least, for a lot of people) is that we've preserved 
the property we want for the lambda calculus, which can be used to write large 
portions of the program.

Now, I don't think that this is necessarily tied to functional programming and 
the lambda calculus. There are probably analogous calculi for logic 
programming, and one could attempt to preserve its nice properties while 
adding in a way to do effects for 'real programs', and so on. But, to get back 
to BASIC, or C, if the language you're extending is an empty language that 
does nothing, then remaining pure to it isn't interesting. I can't actually 
write significant portions of my program in such a language, so all I'm left 
with is the DSL, which doesn't (internally) have the nice properties.

(The same applies to the C preprocessor, if you want to try that route. It is 
not a fragment of the language (even granting that it's a fragment at all) 
useful for doing actual work in the program---writing actual programs in the 
preprocessor involves files #including themselves for recursion, and is well 
in the esoteric category; it is entirely for assembling 'DSL' terms which will 
do all the actual work.)

-- Dan

[1] http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.27.7800
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Accepting and returning polyvariadic functions

2010-08-11 Thread Tillmann Rendel

Will Jones wrote:

  f :: Int - IO ()
  f = undefined

  g :: Int - Int - IO ()
  g = undefined

  h :: Int - Int - Int - IO ()
  h = undefined

vtuple f :: IO (Int - (Int, ()))
vtuple g :: IO (Int - Int - (Int, (Int, (

I've tried to type vtuple using a type class; [...]

I've thought about it and it seems impossible to solve this problem
-- you keep needing to ``split'' the function type one arrow further on. 


So you need to use recursion to handle the arbitrary deeply nested
arrows in the type of vtuple's argument. I tried it with type families,
but I don't see a reason why functional dependencies should not work.

{-# LANGUAGE FlexibleInstances, TypeFamilies #-}
module VTupleWithTypeFamilies where

We use two type families to handle the two places where the result type
of vtuple changes for different argument types.

type family F a
type family G a r

So the intention is that the type of vtuple is as follows.

class VTuple a where
  vtuple :: a - IO (G a (F a))

The base case:

type instance F (IO ())   = ()
type instance G (IO ()) r = r

instance VTuple (IO ()) where
  vtuple = undefined

And the step case:

type instance F (a - b)   = (a, F b)
type instance G (a - b) r = a - G b r

instance VTuple b = VTuple (a - b) where
  vtuple = undefined

A test case:

f :: Int - Bool - Char - Double - IO ()
f = undefined

test = do
  vt - vtuple f
  return (vt 5 True 'x' 1.3)

Testing it with ghci yields the following type for test, which looks
good to me.

test :: IO (Int, (Bool, (Char, (Double, ()

HTH, Tillmann

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


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-08-11 Thread Tillmann Rendel

Dan Doel wrote:
But, to get back 
to BASIC, or C, if the language you're extending is an empty language that 
does nothing, then remaining pure to it isn't interesting. I can't actually 
write significant portions of my program in such a language, so all I'm left 
with is the DSL, which doesn't (internally) have the nice properties.


I understand your argument to be the following: Functional languages are 
built upon the lambda calculus, so a *pure* functional language has to 
preserve the equational theory of the lambda calculus, including, for 
example, beta reduction. But since BASIC or C are not built upon any 
formal calculus with an equational theory, there is not notion of purity 
for these languages.


I like your definition of purity, but I disagree with respect to your 
evaluation of BASIC and C. To me, they seem to be built upon the formal 
language of arithmetic expressions, so they should, to be pure 
arithmetic expression languages, adhere to such equations as the 
commutative law for integers.


  forall x y : integer, x + y = y + x

But due to possible side effects of x and y, languages like BASIC and C 
do not adhere to this, and many other laws. I would therefore consider 
them impure. They could be more pure by allowing side effects only in 
statements, but not in expressions.


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


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-08-11 Thread Dan Doel
On Wednesday 11 August 2010 3:13:56 pm Tillmann Rendel wrote:
 I understand your argument to be the following: Functional languages are
 built upon the lambda calculus, so a *pure* functional language has to
 preserve the equational theory of the lambda calculus, including, for
 example, beta reduction. But since BASIC or C are not built upon any
 formal calculus with an equational theory, there is not notion of purity
 for these languages.

In the discussion from #haskell I mentioned, some folks argued that BASIC was 
pure because there was no equivalent of Haskell's evaluation, only execution. 
I was just attempting to translate that to a more Sabry-like explanation, 
where there would be an empty (or otherwise trivial) sublanguage, and so 
purity would be trivial, because evaluation does nothing (or something along 
those lines).

 I like your definition of purity, but I disagree with respect to your
 evaluation of BASIC and C. To me, they seem to be built upon the formal
 language of arithmetic expressions, so they should, to be pure
 arithmetic expression languages, adhere to such equations as the
 commutative law for integers.
 
forall x y : integer, x + y = y + x
 
 But due to possible side effects of x and y, languages like BASIC and C
 do not adhere to this, and many other laws. I would therefore consider
 them impure. They could be more pure by allowing side effects only in
 statements, but not in expressions.

I'm no BASIC expert, but they were talking about very rudimentary BASICs. The 
sort where line numbers and GOTO are your control flow, not even subroutines. 
I'm not sure if that affects your point here or not.

Certainly, if you consider numeric arithmetic to be the core language, C is an 
impure extension of it (the #haskell folks weren't actually arguing that C was 
pure; just the simple BASIC). Not sure about the above BASIC, but a fancier 
BASIC would be, in the same way.

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


Re: [Haskell-cafe] Re: Haskell in Industry

2010-08-11 Thread Gaius Hammond


On 11 Aug 2010, at 08:30, Ketil Malde wrote:


ng on FP in general as well.

But as I interpreted this thread, the premise was not about the  
morality

of specific sectors, but rather that finance takes away too much of
the FP talent.  My opinion is that we should rather appreciate  
business

or organizations willing to fund FP - perhaps especially for evil
organizations, where funds would otherwise go to more nefarious
purposes.




Investment banking has long been at the forefront of adopting niche  
languages ... I know people who worked on APL in banks, and now J (http://www.jsoftware.com/ 
) and Q (http://kx.com/Products/kdb+.php). Even Perl was big in the  
finance industry, before the web brought it into the mainstream. If  
you want to work on real world problems (and asset allocation is a  
real problem) then this is the place to be... Until the rest of the  
world catches up.





Cheers,




G



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


Re: [Haskell-cafe] Re: Haskell in Industry

2010-08-11 Thread Ben Moseley
 Investment banking isn't likely to lead to improvements in zygohistomorphic 
 prepromorphisms. 

Given that an investment bank could (purely hypothetically of course ;-) 
use - say - paramorphisms as their fundamental approach to processing a 
deeply-embedded DSEL, I wouldn't be too quick to rule them out of improvements 
to recursion combinators...

And, more generally, Investment Banking has interesting problems to solve, 
smart people working there, and a willingness to use (and improve) cutting-edge 
technology.

IMHO, all of these are good things.

--Ben

On 10 Aug 2010, at 19:56, wren ng thornton wrote:

 Henning Thielemann wrote:
 about functional programming jobs in investment banking ...
 Ketil Malde schrieb:
 Tom Hawkins tomahawk...@gmail.com writes:
 (Yes, I realize that's were the money is [...])
 Exactly.
 
 I don't think this is bad: having talented people recruited to work
 on functional programming will improve the technology for all of us.
 I'm not sure I follow this opinion in general. Analogously I could say:
 Supporting military is a good idea, since they invest in new
 technologies. That's not my opinion. Maybe the next financial crisis
 leads us into the next world war.
 
 But that analogy is a bit disingenuous. If investment bankers care so much 
 about performance (because a few milliseconds delay in transactions can cost 
 a lot) then getting a lot of talented functional programmers in finance means 
 there will be a good deal of work in figuring out how to improve performance. 
 Thus, anyone who wants performance will benefit directly; regardless of 
 attendant outcomes.
 
 While the military invests in technology, they invest mainly in technology 
 that advances a particular goal. Thus, it's good for them to have smart 
 people if you would like improvements to that particular kind of technology. 
 (Which includes the Internet and natural language processing ---for very 
 militaristic reasons, both of them---, as well as the obvious.) Investment 
 banking isn't likely to lead to improvements in zygohistomorphic 
 prepromorphisms. If that's where you think we need to be improving our 
 technology, then having smart people in investment banking doesn't help. But 
 that's a different claim than the claim that they'd improve performance or 
 overall acceptance in the job market.
 
 -- 
 Live well,
 ~wren
 ___
 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: Haskell in Industry

2010-08-11 Thread Richard O'Keefe

On Aug 11, 2010, at 7:30 PM, Ketil Malde wrote:
 Sure, if the premise is that investment banks (or the military) are evil,
 then it is morally questionable to support them.  If these are the
 major consumers of functional programming, one might question the ethics
 of working on FP in general as well.
 
 But as I interpreted this thread, the premise was not about the morality
 of specific sectors, but rather that finance takes away too much of
 the FP talent.

One (but only one, and I do not say the major one)
of the aspects of the global financial crisis is that
bankers created a number of advanced financial instruments
which nobody really knew how to value.
Advanced computational models were developed for the purpose.
People were warning about this 10 years ago or more; I bought a
couple of books about it from a remainder shop.

If functional programming gets associated in the profession's
eyes with *that* kind of programming, it will not do FP any good.

In any case, what with lambda expressions already in Apple's C
(of all languages!), it's clear that FP ideas are becoming mainstream
_without_ any need of help from the financial community.  (Actually,
that particular one is probably due to Objective C with its Smalltalk
influence, so the functional origin here is ultimately Lisp.)

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


Re: [Haskell-cafe] Re: Haskell in Industry

2010-08-11 Thread A Smith
New technologies are usually introduced by smart people who have the vision,
and drive to communicate  the benefits of doing it differently and usually
better to their peers, and seniors.
Few senior IT people will have any FP knowledge,  or maybe exposure  to  the
mathematical or CS  fundamentals  of FP over imperative programming.
New technologies need an environment where  spending can afford a degree of
risk.
I the UK, few graduates outside a limited set will have experienced Haskell,
OCAML, or Erlang. The talented will dabble  for the fun of it. Once MS push
F#, the situation will change. Look at the history and acceptance of C++ in
the 1990's.
--
Andrew in Edinburgh,Scotland.
A Haskell convert

On 11 August 2010 08:30, Ketil Malde ke...@malde.org wrote:

 Henning Thielemann schlepp...@henning-thielemann.de writes:

  about functional programming jobs in investment banking ...

  I don't think this is bad: having talented people recruited to work
  on functional programming will improve the technology for all of us.

  I'm not sure I follow this opinion in general. Analogously I could say:
  Supporting military is a good idea, since they invest in new
  technologies.

 Sure, if the premise is that investment banks (or the military) are evil,
 then it is morally questionable to support them.  If these are the
 major consumers of functional programming, one might question the ethics
 of working on FP in general as well.

 But as I interpreted this thread, the premise was not about the morality
 of specific sectors, but rather that finance takes away too much of
 the FP talent.  My opinion is that we should rather appreciate business
 or organizations willing to fund FP - perhaps especially for evil
 organizations, where funds would otherwise go to more nefarious
 purposes.

 -k
 --
 If I haven't seen further, it is by standing in the footprints of giants
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


[Haskell-cafe] WGP Call for Participation

2010-08-11 Thread Bruno Oliveira
==
   CALL FOR PARTICIPATION

   WGP 2010

   6th ACM SIGPLAN Workshop on Generic Programming
   Baltimore, Maryland, US
 Sunday, September 26th, 2010

  http://osl.iu.edu/wgp2010

Collocated with the International Conference on Functional Programming
 (ICFP 2010)
==


Goals of the workshop
-

Generic programming is about making programs more adaptable by making
them more general. Generic programs often embody non-traditional kinds
of polymorphism; ordinary programs are obtained from them by suitably
instantiating their parameters. In contrast with normal programs, the
parameters of a generic program are often quite rich in structure; for
example they may be other programs, types or type constructors, class
hierarchies, or even programming paradigms.

Generic programming techniques have always been of interest, both to
practitioners and to theoreticians, and, for at least 20 years,
generic programming techniques have been a specific focus of research
in the functional and object-oriented programming communities. Generic
programming has gradually spread to more and more mainstream
languages, and today is widely used in industry. This workshop brings
together leading researchers and practitioners in generic programming
from around the world, and features papers capturing the state of the
art in this important area.

Program
---

  * 09.00-10.00: Session 1 Chair: Marcin Zalewski 
* Welcome + PC chair report
  Bruno C. d. S. Oliveira and Marcin Zalewski
* Outrageous but Meaningful Coincidences (Dependent type-safe 
  syntax and evaluation)
  Conor McBride

  * 10.00-10.30: Tea/coffee

  * 10.30-12.30: Session 2 Chair: Shin-Cheng Mu 
* Scrap Your Zippers: A Generic Zipper for Heterogeneous Types 
  Michael D. Adams
* Generic Storage in Haskell
  Sebastiaan Visser and Andres Loeh
* Generic Selections of Subexpressions
  Martijn van Steenbergen, José Pedro Magalhães and Johan Jeuring

  * 12.30-14.00: Lunch

  * 14.00-16.00: Session 3 Chair: Bruno C. d. S. Oliveira 
* Generic Multiset Programming for Language-Integrated Querying 
  Fritz Henglein and Ken Friis Larsen
* Algorithms for Traversal-Based Generic Programming
  Bryan Chadwick and Karl Lieberherr
* Ad-hoc Polymorphism and Dynamic Typing in a Statically Typed 
  Functional Language
  Thomas van Noort, Peter Achten and Rinus Plasmeijer

  * 16.00-16.30: Tea/coffee

  * 16.30-18.00: Session 4 Chair: Conor McBride 
* Reason Isomorphically!
  Ralf Hinze and Daniel James
* Constructing Datatype-Generic Fully Polynomial-Time 
  Approximation Schemes Using Generalised Thinning
  Shin-Cheng Mu, Yu-Han Lyu and Akimasa Morihata


Workshop homepage:
  http://osl.iu.edu/wgp2010/
Registration link:
  https://regmaster3.com/2010conf/ICFP10/register.php
Local arrangements:
  http://www.icfpconference.org/icfp2010/local.html

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