Re: [Haskell-cafe] Greetings! 2D Graphics?

2009-12-04 Thread Luke Palmer
On Fri, Dec 4, 2009 at 12:13 AM, M Xyz functionallyharmoni...@yahoo.comwrote:

 Greetings, my name is M. This is my first time posting to a mailing list so
 forgive me if I've done something wrong. I just finished Real World
 Haskell and am currently working through School of Expression. I am new
 to Haskell but I already love it. My question is this...

 I am interested in doing graphics work in Haskell, but I am lost trying to
 pick a library. I've been designing engineering apps in Java for 6 years and
 I'll admit I've been coddled by its standard library, lol. I am looking for
 something very lightweight with the basic capabilities of Java's Graphics2D
 class (antialias, composite, clipping, transformation, simple drawing
 primitives, gradients). I want something simple and lightweight because my
 interest is to play with building higher level abstractions myself.

 I use XP and Ubuntu so I'd prefer not to use the Graphics-Win32 library
 used by School of Expression if there is a platform independent library.
 I've read through
 http://www.haskell.org/haskellwiki/Applications_and_libraries/Graphics and
 the pertinent libraries seem to be Haven, HGL or Cairo via Gtk2Hs right?
 Which is the most popular/active and appropriate for a beginner to start
 working with?


I admit author's bias, but I suggest graphics-drawingcombinators.  It is a
2D drawing library based on OpenGL with a pure interface (no IO, except to
finally render your drawing), and supports all the stuff you want except
clipping.

It uses the SDL bindings, which I have heard are not easy to install on
windows, but go smooth as a baby's bottom on ubuntu.

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


Re: [Haskell-cafe] Optimization with Strings ?

2009-12-04 Thread Jason Dagit
On Thu, Dec 3, 2009 at 8:25 AM, John D. Earle johndea...@cox.net wrote:

 Haskell has a problem with its type system and is not rigorous. Haskell is
 not a suitable language for proof assistants and so I would advise you to
 stay clear of Haskell. Standard ML was engineered with the needs of proof
 assistants in mind and so you may want to look into Standard ML, but you
 should be very happy with Objective CAML. It has an excellent reputation.
 The Coq proof assistant which is another French product is based on
 Objective CAML.


If I understand you correctly, SML was engineered with the needs of a proof
assistant in mind, but OCaml is a very different language.  And it seems you
are pushing F#/OCaml not SML.  Do F# and OCaml have full formal semantics
for their type systems that have been verified?  Or are they merely based
on Hindley-Milner type systems?  If it is the latter, then could you help me
understand why Haskell is so much worse?  If it's the former could you
please point me to the appropriate research so I can educate myself? If the
objection is primarily String performance based then I would recommend that
you take a look at ByteString or uvector.

Please help me understand the holes in Haskell's type system.  Have you
published some research on the flaws of Haskell's design?  If Haskell is
unsound I'd certainly like to know where and why so that I can improve my
programs.  Please help.

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


RE: [Haskell-cafe] Monomorphic local let bindings and GHCi

2009-12-04 Thread Simon Peyton-Jones
| So I think that if local let generalisation is abandoned, let bindings in GHCi
| would somehow have to be modified to remain polymorphic.

I agree.  They are like top-level bindings in a Haskell module, and should be 
generalised.  They don't suffer from the problems of generalising nested 
bindings.

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


Re: [Haskell-cafe] Finding HP

2009-12-04 Thread Roel van Dijk
 The suggestion was to have a single Download button, leading to a *page* of
 suitably described links, allowing the user to choose whether they only
 wanted the basics (a choice of compiler/interpreter + cabal), or the whole
 Platform, or something else.  It would be the ideal place to explain what
 cabal is and how to use hackage to get more libraries than are contained in
 the platform.  It would perhaps reduce the clutter on the front page that
 some people complained of (although I don't personally think it cluttered).

Thank you. That was exactly what I meant.

Now we need to make a prototype of that page.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] happstack homepage

2009-12-04 Thread Roel van Dijk
2009/12/3 Jeremy Shaw jer...@n-heptane.com:
 See this thread,
 http://groups.google.com/group/happs/browse_thread/thread/6e4d6af0109cc649

Ah, thank you. I somehow missed that.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] Second Call for Copy: Monad.Reader Issue 15

2009-12-04 Thread Ketil Malde
Brent Yorgey byor...@seas.upenn.edu writes:

 It's not too late to write something for Issue 15 of the Monad.Reader!

 Whether you're an established academic or have only just started
 learning Haskell, if you have something to say, please consider
 writing an article for The Monad.Reader!

One thing that'd make a *very* useful contribution, would be reviews
comparing different libraries that overlap in scope.  We have a large
selection of libraries now, but it's hard for users to know which ones
provide industry-grade usability, and which ones are merely proofs of
concept.

So, if you're wondering what library to use for some particular purpose,
why not try a set of them and mail the results to Brent?  GtkHs vs
wxWidgets vs ..., diagram vs graphics-drawingcombinators vs Chart vs...,
database libraries, XML parsing libraries, and so on and so on.

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


Re: [Haskell-cafe] Optimization with Strings ?

2009-12-04 Thread Colin Adams
 Please help me understand the holes in Haskell's type system.

Not really wanting to support the troll, but ...

unsafePerformIO?

Can't it be removed?
-- 
Colin Adams
Preston,
Lancashire,
ENGLAND
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Optimization with Strings ?

2009-12-04 Thread Neil Davies

Or maybe it should be renamed

  
proofObligationsOnUseNeedToBeSupliedBySuitablyQualifiedIndividualPerformIO


which is what it really is - unsafe in the wrong hands

Nei

On 4 Dec 2009, at 08:57, Colin Adams wrote:


Please help me understand the holes in Haskell's type system.


Not really wanting to support the troll, but ...

unsafePerformIO?

Can't it be removed?
--
Colin Adams
Preston,
Lancashire,
ENGLAND
___
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] Optimization with Strings ?

2009-12-04 Thread Colin Adams
But the type system doesn't insist on such a proof - so is it not a hole?

2009/12/4 Neil Davies semanticphilosop...@googlemail.com:
 Or maybe it should be renamed

  proofObligationsOnUseNeedToBeSupliedBySuitablyQualifiedIndividualPerformIO

 which is what it really is - unsafe in the wrong hands

 Nei

 On 4 Dec 2009, at 08:57, Colin Adams wrote:

 Please help me understand the holes in Haskell's type system.

 Not really wanting to support the troll, but ...

 unsafePerformIO?

 Can't it be removed?
 --
 Colin Adams
 Preston,
 Lancashire,
 ENGLAND
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe





-- 
Colin Adams
Preston,
Lancashire,
ENGLAND
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Wikipedia article

2009-12-04 Thread Simon Marlow

On 04/12/2009 01:30, Gwern Branwen wrote:


The changes look fine to me, although I'm a little surprised at all
the {{fact}} tags. (Some of them look very easy to fix, like why
typeclasses were introduced in the first place.)


Yes, they're just placeholders to fill in later.  (I'm new to wikipedia, 
should they be {{citation needed}} or something?)



There's no need to do any page moving or anything; the new version can
just be pasted in. The main concern is maintaining a complete
correct copyright history, and if Simon made all the edits modifying
the original text, and he also makes the big update, then there's no
issue: the holder of the copyright will appear aright in the history
with all his changes.


Ok, done!

http://en.wikipedia.org/wiki/Haskell_%28programming_language%29

edit away.  I'll try to have a go at the Parallelism/Concurrency section 
when I have time.


Cheers,
Simon


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


Re: [Haskell-cafe] Optimization with Strings ?

2009-12-04 Thread Neil Davies

Ah

but the type system is the proof - it doesn't permit you to construct  
things that are 'unsafe' - the whole way the language (and its  
implementation) is constructed is to do that for you.


The issue is that, very occasionally, you the programmer (usually for  
reasons of performance - runtime or code lines) want something  
slightly out of the ordinary. This is the escape mechanism.


To quote the late, great DNA - it is all about rigidly defined areas  
of doubt and uncertainty - one of the arts of programming is to push  
all the nasty doubt and uncertainty into a small corner where you can  
beat it to death with a large dose of logic, proof and (occasional)  
handwaving...


Now before you start talking about 'surely the type system should be  
complete' - I refer you to http://en.wikipedia.org/wiki/Gödel%27s_incompleteness_theorem


Take comfort in that, I do, it means that us humans still have a  
role...


Neil

On 4 Dec 2009, at 09:16, Colin Adams wrote:

But the type system doesn't insist on such a proof - so is it not a  
hole?


2009/12/4 Neil Davies semanticphilosop...@googlemail.com:

Or maybe it should be renamed

  
proofObligationsOnUseNeedToBeSupliedBySuitablyQualifiedIndividualPerformIO


which is what it really is - unsafe in the wrong hands

Nei

On 4 Dec 2009, at 08:57, Colin Adams wrote:


Please help me understand the holes in Haskell's type system.


Not really wanting to support the troll, but ...

unsafePerformIO?

Can't it be removed?
--
Colin Adams
Preston,
Lancashire,
ENGLAND
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe







--
Colin Adams
Preston,
Lancashire,
ENGLAND


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


RE: [Haskell-cafe] Is Haskell a Fanatic?

2009-12-04 Thread Simon Peyton-Jones
Friends

One of the absolutely best things about the Haskell community is that it is 
almost invariably respectful and usually friendly.  People often remark on this 
when they join the community.  Beginner questions are greeted with polite and 
helpful replies.  Category theory and elementary type errors show up in 
successive messages.  Etc.

But thread is an exception.

If you think someone is talking nonsense, I think the best policy is to ignore 
it or reply privately (not to the list); then the thread dies.  I find 
derogatory discussion of a particular person quite discouraging.  It is likely 
to be unjust, and it encourages more of the same.  It's like littering your own 
house.

Respect, guys, please.

Simon

|  This troll was, apparently, invited by one of the Simons
|  onto the Haskell' list, then asked to move his spiels here.
| 
| I am informed that the invitation I was referring to was actually
| about his being invited *out*, not in, so his origin is still a
| mystery and troll is likely appropriate.  (I can't say he's
| demonstrated much of a mathematical basis for his trollery; only a
| propensity for pompous declarations, and deflection when challenged on
| them.  Put up or shut up, troll.)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Is Haskell a Fanatic?

2009-12-04 Thread David Virebayre
On Fri, Dec 4, 2009 at 10:34 AM, Simon Peyton-Jones
simo...@microsoft.com wrote:
 Friends

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


Re: [Haskell-cafe] GHC magic optimization ?

2009-12-04 Thread Neil Brown

Emmanuel CHANTREAU wrote:

I will take an example:

f x y= x+y

The program ask the user to enter two numbers and print the sum. If the
user enter 1 2 f 1 2=3 is stored and a gargage collector is used to
remove this dandling expression later ?
If the user enter again 1 2, ghc search in dandling results to
try to find the result without computing it again ?
  

Hi,

I think what you're asking is how Haskell knows at run-time for which 
expressions it can re-use the results.  The answer is: it doesn't, it 
works it out at compile-time.  So if you have:


f x y = x + y

And at some point in your program you call f 1 2, and later on from a 
totally separate function you call f 1 2, the function will be evaluated 
twice (assuming 1 and 2 weren't known constants at compile-time).  But 
let's say you have:


g x y = f x y * f x y

Now the compiler (i.e. at compile-time) can do some magic.  It can spot 
the common expression and know the result of f x y must be the same both 
times, so it can convert to:


g x y = let z = f x y in z * z

Now, the Haskell run-time will evaluate f x y once, store the result in 
z, and use it twice.  That's how it can use commonalities in your code 
and avoid multiple evaluations of the same function call, which I 
*think* was your question.


Thanks,

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


Re: [Haskell-cafe] Re: Implicit newtype unwrapping

2009-12-04 Thread Joachim Breitner
Hi,

Am Freitag, den 04.12.2009, 01:00 +0100 schrieb Joachim Breitner:
 And just now, after writing half the code, I find out that $( fun
 [d|...|] ) runs the type checker on the declarations before passing them
 to fun, which of course kills my whole approach here, as only having the
 declarations pass through openNewType will make them type check.
 
 Is there any way to pass declarations to a TH function so that their
 names are resolved, but their type is not checked (or, alternatively,
 type errors are ignored).
 
 If not, what would be a sane work-around? 

I found one. openNewType now expects a type synonym declaration as the
very first declaration. It will then replace the type synonym by the
given type name in every type signature (which is simple, thanks to
Data.Generics), and change the function definition to wrap and unwarp
the types as needed. So the following actually works now:

$(openNewtype ''Foo [d|
type Foo' = Int

nullFoo :: Foo'
nullFoo = 0

toFoo :: Int - Foo'
toFoo = id

fromFoo :: Foo' - Int
fromFoo = id

succFoo :: Foo' - Foo'
succFoo = succ

addFoo :: Foo' - Foo' - Foo'
addFoo a b = a + b
|] )

Given this OpenNewType module:


{-# LANGUAGE PatternGuards #-}
module OpenNewtype where

import Debug.Trace
import Language.Haskell.TH
import Data.Monoid
import qualified Data.Map as M
import Data.Generics.Schemes
import Data.Generics.Aliases


openNewtype newTypeName declsQ = do
info - reify newTypeName
(taDecl:decls) - declsQ
tmpName1 - newName x
tmpName2 - newName x
-- Check if the given type is really a simple newtype
typeAlias - case taDecl of
TySynD typeAlias [] concreteType  -- Could check concrete Type 
against newtype
- return typeAlias
_   - error $ openNewType needs a type synosym 
declaration as the first declaration\nFirst declaration was:  ++ pprint taDecl
case info of
TyConI (NewtypeD _ _ _ (NormalC constr [(NotStrict,ConT _)]) _)
- let types = getTypeMap decls
   in  return $ map
 (go constr tmpName1 tmpName2 typeAlias types)
 decls
_   - error $ openNewType can only handle siple newtype 
defined types\nArgument was:  ++ pprint info
  where go constr tmpName1 tmpName2 typeAlias types d = case d of
(ValD (VarP name) _ _) - FunD name [Clause [] (NormalB (wrap 
name types)) [d]]
(FunD name _)  - FunD name [Clause [] (NormalB (wrap 
name types)) [d]]
(SigD _ _) - everywhere (mkT (\tn -
if tn == typeAlias
then newTypeName
else tn)) d
_  - d
  where wrap name types | Just t - M.lookup name types = wrapCo (VarE 
name) t 
| otherwise = (VarE name)

-- Short-Circuit if type to be replaced does not occur
wrapCo exp t | not (doesTypeNameOccur typeAlias t)
= exp
wrapCo exp (ConT t)
= inject exp
wrapCo exp (ForallT _ _ t)
= wrapCo exp t
wrapCo exp (VarT _)
= exp
wrapCo exp (TupleT _)
= exp
wrapCo exp (ArrowT)
= exp
wrapCo exp (ListT)
= exp
wrapCo exp (AppT (AppT ArrowT t1) t2)
= LamE [VarP tmpName1] (wrapCo (AppE exp (wrapCon (VarE 
tmpName1) t1)) t2)

-- Short-Circuit if type to be replaced does not occur
wrapCon exp t | not (doesTypeNameOccur typeAlias t)
= exp
wrapCon exp (ConT t) 
= unwrap exp
wrapCon exp (ForallT _ _ t)
= wrapCo exp t
wrapCon exp (VarT _)
= exp
wrapCon exp (TupleT _)
= exp
wrapCon exp (ArrowT)
= exp
wrapCon exp (ListT)
= exp
wrapCon exp (AppT (AppT ArrowT t1) t2)
= LamE [VarP tmpName1] (wrapCon (AppE exp (wrapCo (VarE 
tmpName1) t1)) t2)

inject :: Exp - Exp
inject e = AppE (ConE constr) e
unwrap :: Exp - Exp
unwrap e = LetE [ValD (ConP constr [VarP tmpName2]) (NormalB e) 
[]] (VarE tmpName2)

getTypeMap :: [Dec] - M.Map Name Type
getTypeMap = 

Re: [Haskell-cafe] GHC magic optimization ?

2009-12-04 Thread Luke Palmer
On Fri, Dec 4, 2009 at 3:36 AM, Neil Brown nc...@kent.ac.uk wrote:
 But let's say you have:

 g x y = f x y * f x y

 Now the compiler (i.e. at compile-time) can do some magic.  It can spot the
 common expression and know the result of f x y must be the same both times,
 so it can convert to:

 g x y = let z = f x y in z * z

GHC does *not* do this by default, quite intentionally, even when
optimizations are enabled.  The reason is because it can cause major
changes in the space complexity of a program.  Eg.

x = sum [1..10^6] + product [1..10^6]
x' = let l = [1..10^6] in sum l + product l

x runs in constant space, but x' keeps the whole list in memory.  The
CSE here has actually wasted both time and space, since it is harder
to save [1..10^6] than to recompute it!  (Memory vs. arithmetic ops)

So GHC leaves it to the user to specify sharing.  If you want an
expression shared, let bind it and reuse.

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


Re: [Haskell-cafe] GHC magic optimization ?

2009-12-04 Thread Joachim Breitner
Hi,

Am Freitag, den 04.12.2009, 10:36 + schrieb Neil Brown:
 But let's say you have:
 
 g x y = f x y * f x y
 
 Now the compiler (i.e. at compile-time) can do some magic.  It can
 spot the common expression and know the result of f x y must be the
 same both times, so it can convert to:
 
 g x y = let z = f x y in z * z
 
 Now, the Haskell run-time will evaluate f x y once, store the result
 in z, and use it twice.  That's how it can use commonalities in your
 code and avoid multiple evaluations of the same function call, which I
 *think* was your question. 

Note that although the compiler _could_ do this transformation, it does
not actually do it because of some unwanted subtleties:
http://www.haskell.org/haskellwiki/GHC:FAQ#Does_GHC_do_common_subexpression_elimination.3F

(I was a bit disappointed when I found out about this, after first
hearing how much great optimization a haskell compiler _could_ do, but
that’s reality.)

Greetings,
Joachim

-- 
Joachim nomeata Breitner
  mail: m...@joachim-breitner.de | ICQ# 74513189 | GPG-Key: 4743206C
  JID: nome...@joachim-breitner.de | http://www.joachim-breitner.de/
  Debian Developer: nome...@debian.org


signature.asc
Description: Dies ist ein digital signierter Nachrichtenteil
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Finding HP

2009-12-04 Thread Martijn van Steenbergen

Don Stewart wrote:

vandijk.roel:

On Wed, Dec 2, 2009 at 11:44 PM, Gregory Crosswhite
gcr...@phys.washington.edu wrote:

On a more serious note, Download Haskell /= Download Haskell Platform, so if I were glancing 
down the sidebar looking for a link to download the Haskell Platform then the first link wouldn't have 
registered for me.  And putting a X has been released link! in the news does not count as a prominent 
download link.

If I wanted to know something *about* the *Haskell Platform* I would
click the link The Haskell Platform under the section About. So it is
actually mentioned 3 times on the front page. What could be improved
are the 2 download links: Download Haskell and Download GHC. It
would perhaps be better to have one nice big Download button that
takes you to a separate download page.


Having a single download link that only points to the Haskell Platform
would be a bit of a policy shift. Is the community ready to accept that
users looking for Haskell should be given the HP binaries?


Although as others pointed out this wasn't the suggestion, I do think 
that it is a good idea to eventually have a single big download button à 
la firefox.com: Haskell Platform OS-specific (based on best effort 
guess) button linking directly to download, with less prominent options 
to download for other OS'es, or other implementations.


Groetjes,

Martijn.

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


[Haskell-cafe] Re: Optimization with Strings ?

2009-12-04 Thread Heinrich Apfelmus
Emmanuel CHANTREAU wrote:
 In my futur program, it use a lot of binary trees with strings (words)
 as leaf. There is just arround 1000 words and they will appear a lot of
 times. The program will possibly consume a lot of process and memory
 (it is a mathematics proover).

If your strings are indeed leaves, then chances are that you share them
a lot and there's nothing much to worry about. For instance, the
following complete binary tree

   data Tree a = Leaf a | Branch (Tree a) (Tree a)

   example a = tree 100
  where
  tree 0 = Leaf a
  tree n = let t = tree (n-1) in Branch t t

uses only linear space and the argument  a  is stored exactly once.


I'm not sure whether this answers your question, though, also because it
depends on what exactly you want. I suggest writing a tiny prototype of
your idea and asking on the mailing list again when there are any
performance problems.

Also, knowing Haskell's evaluation model helps a lot

  http://en.wikibooks.org/wiki/Haskell/Graph_reduction


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


Re: [Haskell-cafe] Wikipedia article

2009-12-04 Thread Sean Leather
On Fri, Dec 4, 2009 at 00:30, Simon Marlow wrote:

 As noted before, the Wikipedia article for Haskell is a disorganised mess.

 http://en.wikipedia.org/wiki/Haskell_%28programming_language%29


I'm confused. When I'm logged in to Wikipedia, I see a page that is vastly
different from when I'm not logged in. I haven't played with Wikipedia in a
long time, so perhaps there is some reason for this, of which I am not
aware.

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


Re: [Haskell-cafe] Wikipedia article

2009-12-04 Thread Simon Marlow

On 04/12/2009 11:18, Sean Leather wrote:


On Fri, Dec 4, 2009 at 00:30, Simon Marlow wrote:

As noted before, the Wikipedia article for Haskell is a disorganised
mess.

http://en.wikipedia.org/wiki/Haskell_%28programming_language%29


I'm confused. When I'm logged in to Wikipedia, I see a page that is
vastly different from when I'm not logged in. I haven't played with
Wikipedia in a long time, so perhaps there is some reason for this, of
which I am not aware.


Doesn't do that for me.  Strange.

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


[Haskell-cafe] language-dot usage

2009-12-04 Thread minh thu
Hi,

I'm using the language-dot package to generate some .dot file.

I'm wondering how to make edges. I was expecting to generate something like

1 - {2 ; 3}

but get in fact

1
- 2 - 3

I used the (pseudo) statements

[NodeStatement $ NodeID 1, EdgeStatement  [NodeId 2, NodeId 3]]

What is the proper way to do that ?

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


Re: [Haskell-cafe] Wikipedia article

2009-12-04 Thread Sean Leather
On Fri, Dec 4, 2009 at 12:20, Simon Marlow wrote:

 On 04/12/2009 11:18, Sean Leather wrote:

 On Fri, Dec 4, 2009 at 00:30, Simon Marlow wrote:
As noted before, the Wikipedia article for Haskell is a disorganised
mess.

http://en.wikipedia.org/wiki/Haskell_%28programming_language%29


 I'm confused. When I'm logged in to Wikipedia, I see a page that is
 vastly different from when I'm not logged in. I haven't played with
 Wikipedia in a long time, so perhaps there is some reason for this, of
 which I am not aware.


 Doesn't do that for me.  Strange.


Well, it seems to be resolved now. I tried it in two different browsers
though, so I swear it wasn't me!

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


[Haskell-cafe] Re: I miss OO

2009-12-04 Thread Heinrich Apfelmus
Peter Verswyvelen wrote:
 It would be fantastic to have a little practical real-world challenge
 (like building a simple music system, or a simple multi-channel sound
 mixer), and work this out in an imperative language, an
 object-oriented language, a functional language, and maybe other
 languages too, like logic languages or constraint languages (does the
 latter exist?)

Related:

   Paul Hudak, Mark P. Jones.
   Haskell vs. Ada vs. C++ vs. Awk vs. ...
 An Experiment in Software Prototyping Productivity
   http://www.haskell.org/papers/NSWC/jfp.ps


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


Re: [Haskell-cafe] language-dot usage

2009-12-04 Thread Ivan Lazar Miljenovic

*Shameless plug* use my graphviz package!

OK, relevant answer:

minh thu not...@gmail.com writes:
 I'm wondering how to make edges. I was expecting to generate something like

 1 - {2 ; 3}


 but get in fact

 1
 - 2 - 3

 I used the (pseudo) statements

 [NodeStatement $ NodeID 1, EdgeStatement  [NodeId 2, NodeId 3]]

So you're wanting an edge from 1 to 2 and from 1 to 3, but getting from
1 to 2 and from 2 to 3 instead?

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] You are in a twisty maze of concurrency libraries, all different ...

2009-12-04 Thread Patrick Caldon


I'm looking for the right concurrency library/semantics for what 
should be a reasonably simple problem.


I have a little simulator:

runWorldSim :: MTGen - SimState - IO SimState

it takes about a second to run on a PC. It's functional except it whacks 
the rng, which needs IO. I run 5-10 of these jobs, and then use:


mergeWorld :: [SimState] - SimState

to pick the best features of the runs and build another possible world 
(state).  Then I use this new world to run another 5-10 jobs and so on.  
I run this through ~2 iterations.


It's an obvious place for parallelism.

I'm looking for a concurrency library with something like:

forkSequence :: Int - [IO a] - IO [a]

which I could call with something like this:

forkSequence 4 (take 10 (repeat  (runWorldSim g ss)))

this would construct 4 threads, then dispatch the 10 jobs onto the 
threads, and pack up the

results into a list I could run through my merger.

It strikes me as something someone would already have done, but I can't 
find anything in hackage.  Probably I've missed something obvious?  Any 
pointers?


If not, what would be the best/easiest existing package to write an 
extension to?


Thanks,
Patrick.


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


Re: [Haskell-cafe] You are in a twisty maze of concurrency libraries, all different ...

2009-12-04 Thread Ivan Lazar Miljenovic
Patrick Caldon p...@pessce.net writes:
 it takes about a second to run on a PC. It's functional except it
 whacks the rng, which needs IO. I run 5-10 of these jobs, and then
 use:

Which RNG are you using that it needs so much IO?


 mergeWorld :: [SimState] - SimState

 to pick the best features of the runs and build another possible world
 (state).  Then I use this new world to run another 5-10 jobs and so
 on.  I run this through ~2 iterations.

 It's an obvious place for parallelism.

 I'm looking for a concurrency library with something like:

 forkSequence :: Int - [IO a] - IO [a]

 which I could call with something like this:

 forkSequence 4 (take 10 (repeat  (runWorldSim g ss)))

 this would construct 4 threads, then dispatch the 10 jobs onto the
 threads, and pack up the
 results into a list I could run through my merger.

 It strikes me as something someone would already have done, but I
 can't find anything in hackage.  Probably I've missed something
 obvious?  Any pointers?

 If not, what would be the best/easiest existing package to write an
 extension to?

 Thanks,
 Patrick.


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

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] You are in a twisty maze of concurrency libraries, all different ...

2009-12-04 Thread Patrick Caldon

Ivan Lazar Miljenovic wrote:

Patrick Caldon p...@pessce.net writes:
  

it takes about a second to run on a PC. It's functional except it
whacks the rng, which needs IO. I run 5-10 of these jobs, and then
use:


Which RNG are you using that it needs so much IO?
Mersenne Twister, System.Random.Mersenne.  The ordinary rng kills 
performance.


Patrick.

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


Re: [Haskell-cafe] You are in a twisty maze of concurrency libraries, all different ...

2009-12-04 Thread Neil Brown

Patrick Caldon wrote:


I'm looking for the right concurrency library/semantics for what 
should be a reasonably simple problem.


I have a little simulator:

runWorldSim :: MTGen - SimState - IO SimState

it takes about a second to run on a PC. It's functional except it 
whacks the rng, which needs IO. I run 5-10 of these jobs, and then use:


mergeWorld :: [SimState] - SimState

to pick the best features of the runs and build another possible world 
(state).  Then I use this new world to run another 5-10 jobs and so 
on.  I run this through ~2 iterations.


It's an obvious place for parallelism.

I'm looking for a concurrency library with something like:

forkSequence :: Int - [IO a] - IO [a]

which I could call with something like this:

forkSequence 4 (take 10 (repeat  (runWorldSim g ss)))

this would construct 4 threads, then dispatch the 10 jobs onto the 
threads, and pack up the

results into a list I could run through my merger.
Why particularly do you want to run the 10 jobs on 4 threads?  Haskell's 
run-time is quite good at spreading out the lightweight threads onto all 
your cores, so the easiest thing to do is run the 10 jobs on 10 
(light-weight) threads and let the run-time sort out the rest.  So if 
what you want is a function:


runPar :: [IO a] - IO [a]

you can easily construct this.  Shameless plug: my CHP library 
effectively has this function already, runParallel :: [CHP a] - CHP [a] 
(CHP being a slight layer on top of IO).  But you can do it just as 
easily with, say, STM.  Here is a version where order doesn't matter 
(apologies for the point-free style):


import Control.Concurrent
import Control.Concurrent.STM
import Control.Monad

modifyTVar :: TVar a - (a - a) - STM ()
modifyTVar tv f = readTVar tv = writeTVar tv . f

runPar :: [IO a] - IO [a]
runPar ps
 = do resVar - newTVarIO []
  mapM_ (forkIO . (= atomically . modifyTVar resVar . (:))) ps
  atomically $ do res - readTVar resVar
  when (length res  length ps) retry
  return res

If order does matter, you can zip the results with an index, and sort by 
the index afterwards.  If efficiency matters, you can perform other 
tweaks.  But the principle is quite straightforward.  Or you can 
refactor your code to take the IO dependency out of your random number 
generation, and run the sets of pure code in parallel using the parallel 
library.  If all you are using IO for is random numbers, that's probably 
the nicest approach.


Thanks,

Neil.

P.S. take 10 . repeat is the same as replicate 10
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell for Physicists

2009-12-04 Thread Roman Salmin
On Tue, Oct 13, 2009 at 9:44 PM, Don Stewart d...@galois.com wrote:



 http://www.galois.com/blog/2009/10/13/domain-specific-languages-for-domain-specific-problems/

 It advocates for Haskell + EDSLs, much as we have been discussing in
 this thread.


 I am think that use of EDSLs for Physics (and similar science) are very
arguable:
 To use EDSL domain expert need to know language in which DSL embedded,
which is more difficult than learn just DSL.
 Not better, if EDSL use only subset of base language:
 1. because you  need to teach this subset (probably rewrite of write new
tutorials, books etc..)
 2. and if someone use few EDSL with different subsets of base language it
can  (and probably will) became mess.
_So easiness in implementation results in burden for users_

 I see such situation in Particle Physics where I am working.
All basic software: ROOT, Geant4 are actually EDSLs based on C++
(and crippled C++: CINT). In my opinion this slowdown progress
tremendously! I am know many physicists who don't know ever necessary basic
of C++, although they use ROOT and Geant4.
 I am sure that what prevent them from learning C++ will prevent them from
learning
any other general purpose language.
 _So my strong opinion that solution is only DSL not EDSL_

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


[Haskell-cafe] Re: Are there standard idioms for lazy, pure error handling?

2009-12-04 Thread Heinrich Apfelmus
Ketil Malde wrote:
 Although I don't care for the cutesy naming suggested in the 'Train'
 datatype [...]
 
   data TerminatedList a e = Then a (TerminatedList a e)
   | Finally e
 
 (So you could do e.g:  4 `Then` 5 `Then` 1 `Finally` success!. Of
 course, you might prefer symbols instead.) 

I don't mind  Then  and  Finally  as constructors. The thing about the
Train  is not so much the suggestive constructor names  Wagon/Loco  or
Cabin/Caboose  but that the concept itself has an evocative and short
name,  Train .

In contrast,  TerminatedList  feels too much like an agglomeration of
technical terms to me (weak head normal form) where the names are
fairly unrelated to the actual definition. (This particularly applies to
weak, one could as well have dubbed the whole thing blue head normal
form without any loss of meaning.) Unfortunately,  TerminatedList is
also too long for extended use in type signatures. Something more
evocative and short, similar to the good old queue or stack would be
great.

How about trail or track, like in

   data Trail a b = Then a (Trail a b)
  | End b

the idea being that the trail of say a dog eventually leads to the dog
itself.


Another, not entirely serious, suggestion: ;)

   data Life a b = Work a (Life a b)
 | TheEnd b



Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


Re: [Haskell-cafe] Wikipedia article

2009-12-04 Thread Sean Leather
On Fri, Dec 4, 2009 at 13:11, Max Rabkin wrote:

 On Fri, Dec 4, 2009 at 1:18 PM, Sean Leather leat...@cs.uu.nl wrote:
  I'm confused. When I'm logged in to Wikipedia, I see a page that is
 vastly
  different from when I'm not logged in. I haven't played with Wikipedia in
 a
  long time, so perhaps there is some reason for this, of which I am not
  aware.

 Wikipedia uses a caching proxy for non-logged-in users.


Ah, thanks. I talked to somebody else who had the same problem, so now we
know.

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


Re: [Haskell-cafe] You are in a twisty maze of concurrency libraries, all different ...

2009-12-04 Thread Patrick Caldon

Neil Brown wrote:

Patrick Caldon wrote:


I'm looking for the right concurrency library/semantics for what 
should be a reasonably simple problem.


I have a little simulator:

runWorldSim :: MTGen - SimState - IO SimState

it takes about a second to run on a PC. It's functional except it 
whacks the rng, which needs IO. I run 5-10 of these jobs, and then use:


mergeWorld :: [SimState] - SimState

to pick the best features of the runs and build another possible 
world (state).  Then I use this new world to run another 5-10 jobs 
and so on.  I run this through ~2 iterations.


It's an obvious place for parallelism.

I'm looking for a concurrency library with something like:

forkSequence :: Int - [IO a] - IO [a]

which I could call with something like this:

forkSequence 4 (take 10 (repeat  (runWorldSim g ss)))

this would construct 4 threads, then dispatch the 10 jobs onto the 
threads, and pack up the

results into a list I could run through my merger.
Why particularly do you want to run the 10 jobs on 4 threads?  
Haskell's run-time is quite good at spreading out the lightweight 
threads onto all your cores, so the easiest thing to do is run the 10 
jobs on 10 (light-weight) threads and let the run-time sort out the 
rest.  


Thanks so much for that! I'll give it a go.

Different threads is just because some of the jobs are memory hogs, and 
I want to minimize the number running simultaneously.  I'll see what 
happens with a runPar-like approach, and use a queue-based approach if 
it becomes a problem.

So if what you want is a function:

runPar :: [IO a] - IO [a]

you can easily construct this.  Shameless plug: my CHP library 
effectively has this function already, runParallel :: [CHP a] - CHP 
[a] (CHP being a slight layer on top of IO).  But you can do it just 
as easily with, say, STM.  Here is a version where order doesn't 
matter (apologies for the point-free style):


import Control.Concurrent
import Control.Concurrent.STM
import Control.Monad

modifyTVar :: TVar a - (a - a) - STM ()
modifyTVar tv f = readTVar tv = writeTVar tv . f

runPar :: [IO a] - IO [a]
runPar ps
 = do resVar - newTVarIO []
  mapM_ (forkIO . (= atomically . modifyTVar resVar . (:))) ps
  atomically $ do res - readTVar resVar
  when (length res  length ps) retry
  return res

If order does matter, you can zip the results with an index, and sort 
by the index afterwards.  If efficiency matters, you can perform other 
tweaks.  But the principle is quite straightforward.  Or you can 
refactor your code to take the IO dependency out of your random number 
generation, and run the sets of pure code in parallel using the 
parallel library.  If all you are using IO for is random numbers, 
that's probably the nicest approach.


Good, fast random numbers are unfortunately necessary - I had a nice 
implementation using System.Random, but had to rewrite it because 
performance was poor :( .



P.S. take 10 . repeat is the same as replicate 10


Thanks again!

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


Re: [Haskell-cafe] Is Haskell a Fanatic?

2009-12-04 Thread Ketil Malde
Simon Peyton-Jones simo...@microsoft.com writes:

 Respect, guys, please.

Yes.  Much as I enjoy the mangling of Shakespeare (finally some use out
of that Eng.Lit. class all those years ago), I worry that this will
finally be the thread that launched a thousand replies and burned the
bottomless archives of the Haskell Café.  Thus I humbly submit the
following proposal for the FAQ:

Q: Somebody made an obviously counterfactual statement implying Haskell is
   inferior to some lesser language (one that only a moron would use
   anyway). Although I know we try to keep things civil around here,
   this person is obviously doing this on purpose to provoke us, and as
   a responsible citizen of this forum, I shall be forced to go against
   the normal comme-il-faut (and my better judgement) and publicly
   humiliate him or her, just like he or she wants me to.  How should I
   best go about it?

A: Words are like sunrays, and each word or ray
   burns hotter when focused and terse
   And if you have nothing at all nice nice to say
   make sure that you say it in verse

   If somebody argues in endless recursion
   you'll find that it irks you at times
   So either give helpful advice for conversion
   or produce your harassment in rhymes

   Trees are more lovely than poems, it's true
   and words can burn hotter than wood
   Do you really have nothing else better to do?
   Then at least try to make it /sound/ good.

-k 
(Who has lots of better things to do, unfortunately)
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] language-dot usage

2009-12-04 Thread minh thu
2009/12/4 Ivan Lazar Miljenovic ivan.miljeno...@gmail.com:

 *Shameless plug* use my graphviz package!

Ok. I see your DotEdge has explicit from/to nodes but not
language-dot. I've not a lot of code, so using your package should be
easy. But still I wonder what the intended usage of languge-dot is.

 OK, relevant answer:

 minh thu not...@gmail.com writes:
 I'm wondering how to make edges. I was expecting to generate something like

 1 - {2 ; 3}


 but get in fact

 1
 - 2 - 3

 I used the (pseudo) statements

 [NodeStatement $ NodeID 1, EdgeStatement  [NodeId 2, NodeId 3]]

 So you're wanting an edge from 1 to 2 and from 1 to 3, but getting from
 1 to 2 and from 2 to 3 instead?

Exactly. Also, if I write only [EdgeStatement  [NodeId 2, NodeId 3]],
it will produce
- 2 - 3 (i.e. no 1, but sill the arc to 2).

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


Re: [Haskell-cafe] Is Haskell a Fanatic?

2009-12-04 Thread Dougal Stanton
On Fri, Dec 4, 2009 at 6:36 AM, Evan Laforge qdun...@gmail.com wrote:
 I'd just like to point out or reiterate the odd rise in trolling and the
 recent announcements of haskell-2010...

 Just wait until haskell-2012 is announced with nonexistential aka
 eschatological types spelled notany a. World.

 It evaluates to a new form of bottom that blackholes the entire world...

I hear prototypes are already being used at the LHC for this very
purpose. Well-typed doomsday machines can't go wrong ;-)


D

-- 
Dougal Stanton
dou...@dougalstanton.net // http://www.dougalstanton.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: computing lists of pairs

2009-12-04 Thread Christian Maeder
Daniel Fischer schrieb:
 Am Mittwoch 02 Dezember 2009 18:54:51 schrieb Christian Maeder:
 Daniel Fischer schrieb:
 However, according to a couple of tests, the funkyName version is
 somewhat faster and allocates less.
 My timing tests showed that your fpairs version is fastest.

Interesting. Using a faster version of sequence:

http://www.haskell.org/pipermail/haskell-cafe/2009-November/069491.html

\begin{code}
allPossibilities :: [[a]] - [[a]]
allPossibilities [] = [[]]
allPossibilities (l:ls) = [ x : xs | x - l, xs - allPossibilities ls]

funkyName :: (a - b - Bool) - [a] - [b] - [[(a, b)]]
funkyName p s l = case s of
  h : t - [(h, a) : ys | a - filter (p h) l, ys - funkyName p t l]
  [] - [[]]

fpairs :: (a - b - Bool) - [a] - [b] - [[(a, b)]]
fpairs p s l =
  allPossibilities [[(a, b) | b - filter (p a) l] | a - s]
\end{code}

fpairs and funkyName are about equally fast.

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


Re: [Haskell-cafe] Haskell for Physicists

2009-12-04 Thread Matthias Görgens
  _So my strong opinion that solution is only DSL not EDSL_

Why do you think they will learn your DSL, if they don't learn any
other language?  And if your DSL includes general purpose stuff, like
functions, control structures, data structures, you'll re-invent the
wheel.  Probably porly.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Are there standard idioms for lazy, pure error handling?

2009-12-04 Thread wren ng thornton

wren ng thornton wrote:
One of the nice things about not having a Nil is that it lets you easily 
be polymorphic over things ending in () ---a normal list---, (Maybe a) 
---a fallible list---, (Either a b) ---your progress type---, etc. 
Whereas the version that has both Nil and End forces us into the (Maybe 
a) scenario. A side effect of this is that the (Either a b) option isn't 
available because we can only construct t=Mx.(x*t)+(1+a+b) not 
t=Mx.(x*t)+(a+b).


Er, I meant t=Mx.(c*x)+(1+a+b) vs t=Mx.(c*x)+(a+b). This is what I get 
for posting without coffee.


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: computing lists of pairs

2009-12-04 Thread Luke Palmer
On Fri, Dec 4, 2009 at 6:42 AM, Christian Maeder
christian.mae...@dfki.de wrote:
 Daniel Fischer schrieb:
 Am Mittwoch 02 Dezember 2009 18:54:51 schrieb Christian Maeder:
 Daniel Fischer schrieb:
 However, according to a couple of tests, the funkyName version is
 somewhat faster and allocates less.
 My timing tests showed that your fpairs version is fastest.

 Interesting. Using a faster version of sequence:

 http://www.haskell.org/pipermail/haskell-cafe/2009-November/069491.html

 \begin{code}
 allPossibilities :: [[a]] - [[a]]
 allPossibilities [] = [[]]
 allPossibilities (l:ls) = [ x : xs | x - l, xs - allPossibilities ls]

I am confused.  This is exactly sequence.  How is this a faster
version?  Other than maybe avoiding some dictionary-passing?

Incidentally there is a better version of sequence for finding
products of lists:

allPossibilities :: [[a]] - [[a]]
allPossibilities [] = [[]]
allPossibilities (l:ls) = [ x : xs | xs - allPossibilites ls, x - l ]

Or, the general form (I don't know of a use other than for lists, however):

sequence' :: Applicative f = [f a] - f [a]
sequence' [] = pure []
sequence' (x:xs) = liftA2 (flip (:)) xs x

The difference is that it binds the tail of the list first, so the
generated tails are shared.  This means less consing, less GC strain,
and a lot less memory usage if you store them.

Mind, the answers come out in a different order.

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


Re: [Haskell-cafe] You are in a twisty maze of concurrency libraries, all different ...

2009-12-04 Thread Duncan Coutts
On Fri, 2009-12-04 at 22:51 +1100, Patrick Caldon wrote:
 I'm looking for the right concurrency library/semantics for what 
 should be a reasonably simple problem.
 
 I have a little simulator:
 
 runWorldSim :: MTGen - SimState - IO SimState
 
 it takes about a second to run on a PC. It's functional except it whacks 
 the rng, which needs IO.

Wait! This is not going to work!

You cannot use the MTGen from the mersenne-random in a concurrent IO
program because the C code uses a single global mutable RNG state. Your
independent simulations would not be independent and you would not get
reproducible results. Indeed you could get incorrect results or
segfaults because the C code does not expect to be called from multiple
threads simultaneously (there is no locking).

Personally I would attack this by eliminating the IO. There's no
justification for a random number generator being in IO. And look at the
problems it causes!

There are other MT implementations that do not use C code which assumes
it's ok to use one single global mutable RNG state for an entire
process. There are pure-Haskell MT impls that use mutable variables in
ST but give an overall pure lazy list of random numbers. If you don't
need MT specifically then there are other fast RNGs too.

Duncan

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


[Haskell-cafe] Re: computing lists of pairs

2009-12-04 Thread Christian Maeder
Luke Palmer schrieb:
 \begin{code}
 allPossibilities :: [[a]] - [[a]]
 allPossibilities [] = [[]]
 allPossibilities (l:ls) = [ x : xs | x - l, xs - allPossibilities ls]
 
 I am confused.  This is exactly sequence.  How is this a faster
 version?  Other than maybe avoiding some dictionary-passing?

I suppose, dictionary-passing is really the reason for slower code.

 Incidentally there is a better version of sequence for finding
 products of lists:
 
 allPossibilities :: [[a]] - [[a]]
 allPossibilities [] = [[]]
 allPossibilities (l:ls) = [ x : xs | xs - allPossibilites ls, x - l ]

I cannot really observe a speed up, with this version, but there are
probably examples where any version is faster than the other.

 Or, the general form (I don't know of a use other than for lists, however):

Maybe should be another useful instance.

 sequence' :: Applicative f = [f a] - f [a]
 sequence' [] = pure []
 sequence' (x:xs) = liftA2 (flip (:)) xs x
 
 The difference is that it binds the tail of the list first, so the
 generated tails are shared.  This means less consing, less GC strain,
 and a lot less memory usage if you store them.

This argument it too complicated for me.

 Mind, the answers come out in a different order.

Yes, thanks.

Christian

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


Re: [Haskell-cafe] ANNOUNCE: error-message

2009-12-04 Thread Henning Thielemann
Gregory Crosswhite schrieb:
 If there is one thing that we really don't have enough of in Haskell, it is 
 *ways to handle errors*!  Thus, I am pleased to announce the release of the 
 error-message package to help in filling this, erm, gap.
 
 This philosophy behind this package is that it is often better to find out 
 all of the errors that have occured in a computation and report them 
 simultaneously, rather than aborting as soon as the first error is 
 encountered.  Towards this end, this package supplies a type of /combinable 
 error messages/ (ErrorMessage in the Data.ErrorMessage module) so that all of 
 the errors from subcomputations can be gathered and presented together.

I would call such non-serious errors 'warnings'. Warnings can be
collected using Writer monad.

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


Re: [Haskell-cafe] New Hackage category: Error Handling

2009-12-04 Thread Henning Thielemann
Gregory Crosswhite schrieb:

 When I uploaded my new package, error-message, I also went ahead and 
 created a new category:  Error Handling.

Error handling is the same as debugging for you? I hope it is not
intended for generating further confusion about exception handling and
debugging (= help programmers to analyse errors).

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


Re: [Haskell-cafe] Is Haskell a Fanatic?

2009-12-04 Thread David Leimbach
Hi Simon and others,

Personally I don't see anything wrong with this guy's line of questioning.
 He wants some proof that Haskell can live up to some of the claims made
about it.  There's a lot of selling of languages like Clojure, Scala, and
Haskell going on that have real world examples showing how code compares
from one language to the next (sometimes unfairly I'll add, in that the code
that one person writes in one language, does not illustrate the best of that
language).

I will admit I missed out on the optimization thread that people refer to.
 I guess I could read the archives, but the tone of this thread makes me
think it's not worthwhile.

I think what it boils down to is Haskell use is a choice that every person
gets to make for their spare time projects and if you're lucky enough to
have such a choice at your job, why not check it out and see for yourself?

If one disagrees with the claims of the salesmen, perhaps a trial period
will convince one otherwise, it's not like it costs anything but time.
 There's not even a 90 day money back guarantee to worry about.

As for trolls on the mailing list, I personally do not have time to read
every message that comes through haskell-cafe because the level of activity
is higher than my available bandwidth for reading emails.  As such, I often
press this lovely button the people who made my computer and operating
system so thoughtfully designed called delete.  Man does that thing ever
work wonders...

Then people can refrain from increasing the magnitude of the denominator in
the signal to noise ratio that has a nice value at the moment here in this
community.  Sadly I think I just did the opposite, but since this is a cafe,
and I had something to say, and I said it, I don't feel so badly about it,
and won't comment on it again.

Just my 2 cents, which might be all I have left these days :-)

Dave

On Fri, Dec 4, 2009 at 1:34 AM, Simon Peyton-Jones simo...@microsoft.comwrote:

 Friends

 One of the absolutely best things about the Haskell community is that it is
 almost invariably respectful and usually friendly.  People often remark on
 this when they join the community.  Beginner questions are greeted with
 polite and helpful replies.  Category theory and elementary type errors show
 up in successive messages.  Etc.

 But thread is an exception.

 If you think someone is talking nonsense, I think the best policy is to
 ignore it or reply privately (not to the list); then the thread dies.  I
 find derogatory discussion of a particular person quite discouraging.  It is
 likely to be unjust, and it encourages more of the same.  It's like
 littering your own house.

 Respect, guys, please.

 Simon

 |  This troll was, apparently, invited by one of the Simons
 |  onto the Haskell' list, then asked to move his spiels here.
 |
 | I am informed that the invitation I was referring to was actually
 | about his being invited *out*, not in, so his origin is still a
 | mystery and troll is likely appropriate.  (I can't say he's
 | demonstrated much of a mathematical basis for his trollery; only a
 | propensity for pompous declarations, and deflection when challenged on
 | them.  Put up or shut up, troll.)
 ___
 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] inotify-alike for mac os x?

2009-12-04 Thread David Leimbach
d

On Thu, Dec 3, 2009 at 7:55 PM, Gregory Collins g...@gregorycollins.netwrote:

 Conal Elliott co...@conal.net writes:

  I'd like to make some FRPish toys that keep files updated to have
  functional relationships with other files.  hinotify looks like just
  the sort of underlying magic I could use for efficient implementation
  on linux.  Is there any support for mac os x?  Could support be either
  added to hinotify or maybe inotify and a mac-friendly library be
  abstracted into a common Haskell interface?  I'm fine with an
  imperative interface, since I can abstract into a functional library,
  which I guess would be a sort of persistent simplified FRP.

 On Mac  BSD you have to use kqueue, and on Windows it's
 ReadDirectoryChangesW. A platform-agnostic Haskell library for detecting
 filesystem change notifications is something that I would really
 appreciate!


launchd does everything on mac os x, like literally everything.  My mother
said if I can't say something good about someone or something then don't say
anything at all, and in this case, I'm taking her advice on what I think
about launchd, however if you click the link below you might get an idea of
how that works on Mac OS X.

http://stackoverflow.com/questions/1515730/is-there-a-command-like-watch-or-inotifywait-on-the-mac

Dave


 G
 --
 Gregory Collins g...@gregorycollins.net
 ___
 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] inotify-alike for mac os x?

2009-12-04 Thread Ross Mellgren
kqueue is the low level interface, but requires that you handle all  
file system events as they happen, and fast. There is a higher level  
interface called fsevents (with accompanying daemon fseventsd) which  
allows you a more calm way to read the file system events.


http://developer.apple.com/mac/library/documentation/Darwin/Conceptual/FSEvents_ProgGuide/Introduction/Introduction.html

I think launchd just happens to have an integration to kqueue or  
fseventsd, I'm not sure launching a program every time a file changes  
would be the best thing :-)


-Ross


On Dec 4, 2009, at 11:08 AM, David Leimbach wrote:


d

On Thu, Dec 3, 2009 at 7:55 PM, Gregory Collins g...@gregorycollins.net 
 wrote:

Conal Elliott co...@conal.net writes:

 I'd like to make some FRPish toys that keep files updated to have
 functional relationships with other files.  hinotify looks like just
 the sort of underlying magic I could use for efficient  
implementation
 on linux.  Is there any support for mac os x?  Could support be  
either

 added to hinotify or maybe inotify and a mac-friendly library be
 abstracted into a common Haskell interface?  I'm fine with an
 imperative interface, since I can abstract into a functional  
library,

 which I guess would be a sort of persistent simplified FRP.

On Mac  BSD you have to use kqueue, and on Windows it's
ReadDirectoryChangesW. A platform-agnostic Haskell library for  
detecting

filesystem change notifications is something that I would really
appreciate!

launchd does everything on mac os x, like literally everything.  My  
mother said if I can't say something good about someone or something  
then don't say anything at all, and in this case, I'm taking her  
advice on what I think about launchd, however if you click the link  
below you might get an idea of how that works on Mac OS X.


http://stackoverflow.com/questions/1515730/is-there-a-command-like-watch-or-inotifywait-on-the-mac

Dave

G
--
Gregory Collins g...@gregorycollins.net
___
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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Is Haskell a Fanatic?

2009-12-04 Thread Keith Sheppard
There is nothing wrong with constructive criticism and debate. We
should welcome it and I think that the initial response did. But the
OP's follow up of:

It will be better for all of you to figure it out for yourselves and
gain more experience about what is out there. Haskell isn't the world.
Haskell would be the cutting edge if it didn't have competition.

tells me that the post was not intended to be constructive

Best
-Keith

On Fri, Dec 4, 2009 at 10:58 AM, David Leimbach leim...@gmail.com wrote:
 Hi Simon and others,
 Personally I don't see anything wrong with this guy's line of questioning.
  He wants some proof that Haskell can live up to some of the claims made
 about it.  There's a lot of selling of languages like Clojure, Scala, and
 Haskell going on that have real world examples showing how code compares
 from one language to the next (sometimes unfairly I'll add, in that the code
 that one person writes in one language, does not illustrate the best of that
 language).
 I will admit I missed out on the optimization thread that people refer to.
  I guess I could read the archives, but the tone of this thread makes me
 think it's not worthwhile.
 I think what it boils down to is Haskell use is a choice that every person
 gets to make for their spare time projects and if you're lucky enough to
 have such a choice at your job, why not check it out and see for yourself?
 If one disagrees with the claims of the salesmen, perhaps a trial period
 will convince one otherwise, it's not like it costs anything but time.
  There's not even a 90 day money back guarantee to worry about.
 As for trolls on the mailing list, I personally do not have time to read
 every message that comes through haskell-cafe because the level of activity
 is higher than my available bandwidth for reading emails.  As such, I often
 press this lovely button the people who made my computer and operating
 system so thoughtfully designed called delete.  Man does that thing ever
 work wonders...
 Then people can refrain from increasing the magnitude of the denominator in
 the signal to noise ratio that has a nice value at the moment here in this
 community.  Sadly I think I just did the opposite, but since this is a cafe,
 and I had something to say, and I said it, I don't feel so badly about it,
 and won't comment on it again.
 Just my 2 cents, which might be all I have left these days :-)
 Dave

 On Fri, Dec 4, 2009 at 1:34 AM, Simon Peyton-Jones simo...@microsoft.com
 wrote:

 Friends

 One of the absolutely best things about the Haskell community is that it
 is almost invariably respectful and usually friendly.  People often remark
 on this when they join the community.  Beginner questions are greeted with
 polite and helpful replies.  Category theory and elementary type errors show
 up in successive messages.  Etc.

 But thread is an exception.

 If you think someone is talking nonsense, I think the best policy is to
 ignore it or reply privately (not to the list); then the thread dies.  I
 find derogatory discussion of a particular person quite discouraging.  It is
 likely to be unjust, and it encourages more of the same.  It's like
 littering your own house.

 Respect, guys, please.

 Simon

 |  This troll was, apparently, invited by one of the Simons
 |  onto the Haskell' list, then asked to move his spiels here.
 |
 | I am informed that the invitation I was referring to was actually
 | about his being invited *out*, not in, so his origin is still a
 | mystery and troll is likely appropriate.  (I can't say he's
 | demonstrated much of a mathematical basis for his trollery; only a
 | propensity for pompous declarations, and deflection when challenged on
 | them.  Put up or shut up, troll.)
 ___
 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





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


Re: [Haskell-cafe] inotify-alike for mac os x?

2009-12-04 Thread Svein Ove Aas
On Fri, Dec 4, 2009 at 5:31 PM, Ross Mellgren rmm-hask...@z.odi.ac wrote:
 kqueue is the low level interface, but requires that you handle all file
 system events as they happen, and fast.

For the purposes of creating a binding in haskell, my preferred way
would be to use the low-level interface and build saner abstractions
on top of that; it would be trivial to buffer them haskell-side.

That said.. you say you have to handle the events fast. What happens
if you don't?

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


Re: [Haskell-cafe] GHC magic optimization ?

2009-12-04 Thread Mark Lentczner

On Dec 4, 2009, at 2:43 AM, Luke Palmer wrote:

 So GHC leaves it to the user to specify sharing.  If you want an
 expression shared, let bind it and reuse.

Does GHC treat where and let the same in this regard? Or in code, are these 
treated the same?

 x'' = sum l + product l where l = [1..10^6]

 x' = let l = [1..10^6] in sum l + product l


I couldn't tell if the report implies that or not.

- Mark




Mark Lentczner
http://www.ozonehouse.com/mark/
m...@glyphic.com



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


Re: [Haskell-cafe] Is Haskell a Fanatic?

2009-12-04 Thread gladstein
I thought we were supposed to be civil on this list? 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell for Physicists

2009-12-04 Thread Roman Salmin
On Fri, Dec 04, 2009 at 01:43:42PM +, Matthias Görgens wrote:
   _So my strong opinion that solution is only DSL not EDSL_

 Why do you think they will learn your DSL, if they don't learn any
 other language?
 I didn't said that they didn't learn any language. They learn languages,
but
 only part that is necessary to do particular task.
  f.e. ROOT CINT(C++ interpreter) didn't distinguish object from pointer to
object, i.e.
  statement h.ls(); works as well as h-ls(); independently of either h has
type TH1F or TH1F*,
  so beginning ROOT user didn't need know what is pointer, memory management
helps him.
 But early or latter one need to write more complicated code,
 then one need to spend months to reading big C++ books, and struggling with
compilers errors, segfaults etc..^(1) (instead of doing assigned task!) or,
what is more usually, trying Ad hoc methods for writing software.
 So people will learn DSL because:
  1. DSL is simpler than general purpose language
  2. DSL describe already known domain for user, (one probably don't need
monads, continuations, virtual methods, template instantiation etc...etc...)
so learning is easy, and didn't consume much time.

  And if your DSL includes general purpose stuff, like
 functions, control structures, data structures, you'll re-invent the
 wheel.  Probably porly.
 You didn't need to reinvent the wheel, because you DSL compiler can
produce Haskell code:
   DSL - General Purpose Language - Executable
 And ever if you do, it saves allot of time of experts.

 Roman.

(1) In Haskell this probably will sound like: reading allot of small
tutorials and articles, grokking monads,
   struggling with type-check errors, infinite loops, laziness, etc...
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: computing lists of pairs

2009-12-04 Thread Daniel Fischer
Am Freitag 04 Dezember 2009 16:48:25 schrieb Christian Maeder:
 Luke Palmer schrieb:
  \begin{code}
  allPossibilities :: [[a]] - [[a]]
  allPossibilities [] = [[]]
  allPossibilities (l:ls) = [ x : xs | x - l, xs - allPossibilities ls]
 
  I am confused.  This is exactly sequence.  How is this a faster
  version?  Other than maybe avoiding some dictionary-passing?

 I suppose, dictionary-passing is really the reason for slower code.

I don't think so. With the code of sequence specialised to lists, I get the 
same 
performance as with Control.Monad.sequence (at least, the difference is too 
small to be 
reliably measured), while allPossibilities is significantly faster.
Perhaps the code generator can handle list comprehensions better than folds?


  Incidentally there is a better version of sequence for finding
  products of lists:
 
  allPossibilities :: [[a]] - [[a]]
  allPossibilities [] = [[]]
  allPossibilities (l:ls) = [ x : xs | xs - allPossibilites ls, x - l ]

 I cannot really observe a speed up, with this version, but there are
 probably examples where any version is faster than the other.

I can,

da...@linux-mkk1:~/Haskell/CafeTesting time ./pairs 7 9 20
5529600
0.18user 0.00system 0:00.18elapsed 102%CPU (0avgtext+0avgdata 0maxresident)k
0inputs+0outputs (0major+521minor)pagefaults 0swaps
da...@linux-mkk1:~/Haskell/CafeTesting time ./pairs +RTS -A200M -RTS 6 9 20
5529600
0.45user 0.26system 0:00.71elapsed 100%CPU (0avgtext+0avgdata 0maxresident)k
0inputs+0outputs (0major+56604minor)pagefaults 0swaps


  Or, the general form (I don't know of a use other than for lists,
  however):

 Maybe should be another useful instance.

  sequence' :: Applicative f = [f a] - f [a]
  sequence' [] = pure []
  sequence' (x:xs) = liftA2 (flip (:)) xs x
 
  The difference is that it binds the tail of the list first, so the
  generated tails are shared.  This means less consing, less GC strain,
  and a lot less memory usage if you store them.

 This argument it too complicated for me.

aP1 [] = [[]]
aP1 (h:t) = do
x - h
xs - aP1 t
return (x:xs)

for every x in h, we calculate the combinations of t anew.

aP2 [] = [[]]
aP2 (h:t) = do
xs - aP2 t
x - h
return (x:xs)

now we first calculate the combinations of t, for each of those, we cons the 
elements of h 
to it in turn and never reuse it afterwards.


  Mind, the answers come out in a different order.

 Yes, thanks.

 Christian


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


Re: [Haskell-cafe] Are there standard idioms for lazy, pure error handling?

2009-12-04 Thread Duncan Coutts
On Thu, 2009-12-03 at 19:49 -0500, wren ng thornton wrote:
 Duncan Coutts wrote:
  I've got an open mind on the suggestion to amalgamate the two ways the
  list could end. I'm not especially in favour of generalising for the
  sake of generalising, especially if it looses the connection to the
  notion of annotating your ordinary data structure with extra errors.
  If I effectively always have to use an Either for the final value then
  perhaps it does not buy anything and just makes the folds uglier (since
  it might loose the connection with the ordinary fold). But it could make
  even that use case simpler so it's worth looking at in a few examples
  (eg the tar package).
 
 These days I view folds as automatically defined by the data type, so I 
 don't see any reason (on those grounds) to want to compare it to lists' 
 foldr as opposed to any other arbitrary catamorphism.

Sure the fold is defined by the data type, except when we are pretending
that one data type is another. This type is intended as a list that is
annotated with errors. So I want to be able to switch between list
versions and this version just by adding an extra error-handling
parameter to the ordinary list fold.

As another example of this, consider the VersionRange type in Cabal. It
provides two different folds depending on what view you want. Neither
matches the underlying constructors exactly.

Duncan

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


Re: [Haskell-cafe] inotify-alike for mac os x?

2009-12-04 Thread Ross Mellgren
Well, I don't think anything bad will happen, but I think I remember  
there being no/little buffering, so your program had to be responsive  
if you wanted to get the events. fseventsd is a daemon on top that  
keeps logs, so you can read them at leisure.


I'm sorry I can't find the original article I had read to learn this,  
otherwise I'd link you directly so you could make your own judgements.


I think the decision between the two is primarily based on your use  
case. If you are intended to run continuously and handling each event  
will probably not use that many resources (as to not bog down the  
system as you receive many file system events), and you need real-time  
tracking, kqueue is for you.


Conversely, if you need to know things changed soon after, but not  
immediately, and especially if you don't want to be running  
continuously, then fseventsd is for you.


This is my understanding, not having used either directly (I've only  
used inotify on linux).


-Ross

On Dec 4, 2009, at 11:39 AM, Svein Ove Aas wrote:

On Fri, Dec 4, 2009 at 5:31 PM, Ross Mellgren rmm-hask...@z.odi.ac  
wrote:
kqueue is the low level interface, but requires that you handle  
all file

system events as they happen, and fast.


For the purposes of creating a binding in haskell, my preferred way
would be to use the low-level interface and build saner abstractions
on top of that; it would be trivial to buffer them haskell-side.

That said.. you say you have to handle the events fast. What happens
if you don't?

--
Svein Ove Aas


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


Re: [Haskell-cafe] ANNOUNCE: error-message

2009-12-04 Thread Gregory Crosswhite
On Dec 4, 2009, at 7:55 AM, Henning Thielemann wrote:

 Gregory Crosswhite schrieb:
 If there is one thing that we really don't have enough of in Haskell, it is 
 *ways to handle errors*!  Thus, I am pleased to announce the release of the 
 error-message package to help in filling this, erm, gap.
 
 This philosophy behind this package is that it is often better to find out 
 all of the errors that have occured in a computation and report them 
 simultaneously, rather than aborting as soon as the first error is 
 encountered.  Towards this end, this package supplies a type of /combinable 
 error messages/ (ErrorMessage in the Data.ErrorMessage module) so that all 
 of the errors from subcomputations can be gathered and presented together.
 
 I would call such non-serious errors 'warnings'. Warnings can be
 collected using Writer monad.
 

The errors are indeed serious because they prevent the computation from being 
finished;  it's just that errors are often not fatal in the sense that you 
have to stop when you encounter the first one rather than seeing if anything 
else also went wrong.  For example, consider compilation errors:  any error 
causes the compilation to fail, but the compiler tries to uncover as many 
errors as it can at once so that it can show you the whole list rather than 
just the first one.

On Dec 4, 2009, at 7:57 AM, Henning Thielemann wrote:

 Gregory Crosswhite schrieb:
 
 When I uploaded my new package, error-message, I also went ahead and 
 created a new category:  Error Handling.
 
 Error handling is the same as debugging for you? I hope it is not
 intended for generating further confusion about exception handling and
 debugging (= help programmers to analyse errors).


No, but I can see how you would have gotten that impression since the examples 
I supply in my documentation are all programmer errors.  The real purpose of 
this is to collect together errors that ultimately came from bad program 
inputs, i.e. user errors.  In particular, the motivation for this package was 
that I have written a build system, and I wanted to collect as many errors in 
the build as possible and show them all to the user at once.

Cheers,
Greg

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


Re: [Haskell-cafe] Optimization with Strings ?

2009-12-04 Thread Duncan Coutts
On Thu, 2009-12-03 at 13:03 +0100, Emmanuel CHANTREAU wrote:
 Hello
 
 In my futur program, it use a lot of binary trees with strings (words)
 as leaf. There is just arround 1000 words and they will appear a lot of
 times. The program will possibly consume a lot of process and memory
 (it is a mathematics proover).
 
 I began this program in C++ but haskell has a prety good speed and
 memory footprint and is easier. But I don't know if it worth to do this
 optimization: having a dictionary to translate string words in Int.
 
 The answer depends on the automatic optimizations in GHC, because GHC
 could compare quickely two strings if it is the same object, so it
 depends if program generated by GHC have a dictionary (tree) of strings
 internaly. Someone knows this ?

There's nothing automatic about it. It depends on the implementation of
the type of string you are using. For the String type there is no
equality short-cut, for ByteString there is.

Duncan

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


Re: [Haskell-cafe] GHC magic optimization ?

2009-12-04 Thread Luke Palmer
On Fri, Dec 4, 2009 at 9:44 AM, Mark Lentczner ma...@glyphic.com wrote:

 On Dec 4, 2009, at 2:43 AM, Luke Palmer wrote:

 So GHC leaves it to the user to specify sharing.  If you want an
 expression shared, let bind it and reuse.

 Does GHC treat where and let the same in this regard? Or in code, are these 
 treated the same?

where is just sugar for let.


 x'' = sum l + product l where l = [1..10^6]

 x' = let l = [1..10^6] in sum l + product l


 I couldn't tell if the report implies that or not.

        - Mark




 Mark Lentczner
 http://www.ozonehouse.com/mark/
 m...@glyphic.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


Re: [Haskell-cafe] Is Haskell a Fanatic?

2009-12-04 Thread Luke Palmer
On Fri, Dec 4, 2009 at 9:34 AM, Keith Sheppard keiths...@gmail.com wrote:
 There is nothing wrong with constructive criticism and debate. We
 should welcome it and I think that the initial response did. But the
 OP's follow up of:

 It will be better for all of you to figure it out for yourselves and
 gain more experience about what is out there. Haskell isn't the world.
 Haskell would be the cutting edge if it didn't have competition.

 tells me that the post was not intended to be constructive

In which case -- I believe David was arguing -- we ignore it and
continue reading the constructive threads.

Luke

 Best
 -Keith

 On Fri, Dec 4, 2009 at 10:58 AM, David Leimbach leim...@gmail.com wrote:
 Hi Simon and others,
 Personally I don't see anything wrong with this guy's line of questioning.
  He wants some proof that Haskell can live up to some of the claims made
 about it.  There's a lot of selling of languages like Clojure, Scala, and
 Haskell going on that have real world examples showing how code compares
 from one language to the next (sometimes unfairly I'll add, in that the code
 that one person writes in one language, does not illustrate the best of that
 language).
 I will admit I missed out on the optimization thread that people refer to.
  I guess I could read the archives, but the tone of this thread makes me
 think it's not worthwhile.
 I think what it boils down to is Haskell use is a choice that every person
 gets to make for their spare time projects and if you're lucky enough to
 have such a choice at your job, why not check it out and see for yourself?
 If one disagrees with the claims of the salesmen, perhaps a trial period
 will convince one otherwise, it's not like it costs anything but time.
  There's not even a 90 day money back guarantee to worry about.
 As for trolls on the mailing list, I personally do not have time to read
 every message that comes through haskell-cafe because the level of activity
 is higher than my available bandwidth for reading emails.  As such, I often
 press this lovely button the people who made my computer and operating
 system so thoughtfully designed called delete.  Man does that thing ever
 work wonders...
 Then people can refrain from increasing the magnitude of the denominator in
 the signal to noise ratio that has a nice value at the moment here in this
 community.  Sadly I think I just did the opposite, but since this is a cafe,
 and I had something to say, and I said it, I don't feel so badly about it,
 and won't comment on it again.
 Just my 2 cents, which might be all I have left these days :-)
 Dave

 On Fri, Dec 4, 2009 at 1:34 AM, Simon Peyton-Jones simo...@microsoft.com
 wrote:

 Friends

 One of the absolutely best things about the Haskell community is that it
 is almost invariably respectful and usually friendly.  People often remark
 on this when they join the community.  Beginner questions are greeted with
 polite and helpful replies.  Category theory and elementary type errors show
 up in successive messages.  Etc.

 But thread is an exception.

 If you think someone is talking nonsense, I think the best policy is to
 ignore it or reply privately (not to the list); then the thread dies.  I
 find derogatory discussion of a particular person quite discouraging.  It is
 likely to be unjust, and it encourages more of the same.  It's like
 littering your own house.

 Respect, guys, please.

 Simon

 |  This troll was, apparently, invited by one of the Simons
 |  onto the Haskell' list, then asked to move his spiels here.
 |
 | I am informed that the invitation I was referring to was actually
 | about his being invited *out*, not in, so his origin is still a
 | mystery and troll is likely appropriate.  (I can't say he's
 | demonstrated much of a mathematical basis for his trollery; only a
 | propensity for pompous declarations, and deflection when challenged on
 | them.  Put up or shut up, troll.)
 ___
 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





 --
 keithsheppard.name
 ___
 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] From function over expression (+, *) derive function over expression (+)

2009-12-04 Thread Radek Micek
Hello.

I have two types for expression:

data Expr = Add Expr Expr | Mul Expr Expr | Const Int

data AExpr = AAdd AExpr AExpr | AConst Int

The first one supports addition and multiplication and the second
only addition.

I can write a function to simplify the first expression:

simplify :: Expr - Expr
simplify = {- replaces:
a*1 and 1*a by a,
a+0 and 0+a by a -}

And I would like to use the function simplify for the second type
AExpr. What can I do is to convert AExpr to Expr, simplify it and
convert it back. But I don't like this solution because
conversions take some time.

I would prefer following: I say to the compiler that AAdd is like Add
and AConst is like Const and the compiler derives function
asimplify for AExpr.

Is it possible to do this? In fact I want to have two distinct types
where one is extension of the second (Expr is extension of AExpr)
and I want to define a function for the extended type (Expr) and
use it for the original type (AExpr). I assume that the function won't
introduce Mul to the expression which had no Mul.

Thanks in advance

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


Re: [Haskell-cafe] From function over expression (+, *) derive function over expression (+)

2009-12-04 Thread Eugene Kirpichov
It is possible to do this automatically, but you'll have to program
the automation yourself with Template Haskell.

2009/12/4 Radek Micek radek.mi...@gmail.com:
 Hello.

 I have two types for expression:

 data Expr = Add Expr Expr | Mul Expr Expr | Const Int

 data AExpr = AAdd AExpr AExpr | AConst Int

 The first one supports addition and multiplication and the second
 only addition.

 I can write a function to simplify the first expression:

 simplify :: Expr - Expr
 simplify = {- replaces:
 a*1 and 1*a by a,
 a+0 and 0+a by a -}

 And I would like to use the function simplify for the second type
 AExpr. What can I do is to convert AExpr to Expr, simplify it and
 convert it back. But I don't like this solution because
 conversions take some time.

 I would prefer following: I say to the compiler that AAdd is like Add
 and AConst is like Const and the compiler derives function
 asimplify for AExpr.

 Is it possible to do this? In fact I want to have two distinct types
 where one is extension of the second (Expr is extension of AExpr)
 and I want to define a function for the extended type (Expr) and
 use it for the original type (AExpr). I assume that the function won't
 introduce Mul to the expression which had no Mul.

 Thanks in advance

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




-- 
Eugene Kirpichov
Web IR developer, market.yandex.ru
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] From function over expression (+, *) derive function over expression (+)

2009-12-04 Thread Luke Palmer
On Fri, Dec 4, 2009 at 10:26 AM, Radek Micek radek.mi...@gmail.com wrote:
 Hello.

 I have two types for expression:

 data Expr = Add Expr Expr | Mul Expr Expr | Const Int

 data AExpr = AAdd AExpr AExpr | AConst Int

 The first one supports addition and multiplication and the second
 only addition.

 I can write a function to simplify the first expression:

 simplify :: Expr - Expr
 simplify = {- replaces:
 a*1 and 1*a by a,
 a+0 and 0+a by a -}

 And I would like to use the function simplify for the second type
 AExpr. What can I do is to convert AExpr to Expr, simplify it and
 convert it back. But I don't like this solution because
 conversions take some time.

Well there are more involved reasons than simply the conversion taking
time.  If you would like the type system on your side, you have a
decent modeling problem on your hands.  How can you guarantee that
simplify will return a type that will fit in AExpr?  Simplify might
turn a+a into 2*a, and then your trick no longer works.  It would
seem that you need to typecheck the function twice.

You could attempt to go the other way, i.e. define a simplify on AExpr
and map to and from Expr, but that will have trouble with expressions
like 0+(2*a), because 2*a has no representation in AExpr.

My hunch is that to do this properly, you need to use some of the
fixed point modeling that I can't find the paper about (!)  (It's
popular, someone please chime in :-).  I.e. define a data type which,
directed by type classes, may or may not support multiplication.  Then
define separately an additive simplifier and a multiplicative
simplifier on that.

There is some ugly bookkeeping involved, so that the code *locally* is
not that pretty, but it has good large-scale engineering properties.

And in the grand scheme of things, the conversions will not take that
much time.  The equivalent of a pointer indirection per node (+ some
GC).  And there is no difference in memory usage because of laziness.
This is not the level at which you worry about speed in Haskell -- at
least in my experience.

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


Re: [Haskell-cafe] From function over expression (+, *) derive function over expression (+)

2009-12-04 Thread Derek Elkins
On Fri, Dec 4, 2009 at 11:26 AM, Radek Micek radek.mi...@gmail.com wrote:
 Hello.

 I have two types for expression:

 data Expr = Add Expr Expr | Mul Expr Expr | Const Int

 data AExpr = AAdd AExpr AExpr | AConst Int

 The first one supports addition and multiplication and the second
 only addition.

 I can write a function to simplify the first expression:

 simplify :: Expr - Expr
 simplify = {- replaces:
 a*1 and 1*a by a,
 a+0 and 0+a by a -}

 And I would like to use the function simplify for the second type
 AExpr. What can I do is to convert AExpr to Expr, simplify it and
 convert it back. But I don't like this solution because
 conversions take some time.

 I would prefer following: I say to the compiler that AAdd is like Add
 and AConst is like Const and the compiler derives function
 asimplify for AExpr.

 Is it possible to do this? In fact I want to have two distinct types
 where one is extension of the second (Expr is extension of AExpr)
 and I want to define a function for the extended type (Expr) and
 use it for the original type (AExpr). I assume that the function won't
 introduce Mul to the expression which had no Mul.

What you'd ideally want is called refinement types which Haskell, and
as far as I know, no practical language has.  There is a paper about a
way to encode these, but it is fairly heavy-weight.  You could use
phantom type trickery to combine the data types into one type but
still statically check that only additive expressions are passed to
certain functions, but that too is also probably more trouble than
it's worth.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: computing lists of pairs

2009-12-04 Thread Christian Maeder
Daniel Fischer schrieb:
 allPossibilities :: [[a]] - [[a]]
 allPossibilities [] = [[]]
 allPossibilities (l:ls) = [ x : xs | xs - allPossibilites ls, x - l ]
 I cannot really observe a speed up, with this version, but there are
 probably examples where any version is faster than the other.
 
 I can,

Oh yes, I can too.

 aP1 [] = [[]]
 aP1 (h:t) = do
 x - h
 xs - aP1 t
 return (x:xs)
 
 for every x in h, we calculate the combinations of t anew.

Do we? Isn't aP1 t one closure that's being evaluated only once?

 aP2 [] = [[]]
 aP2 (h:t) = do
 xs - aP2 t
 x - h
 return (x:xs)
 
 now we first calculate the combinations of t, for each of those, we cons the 
 elements of h 
 to it in turn and never reuse it afterwards.

Thanks for explaining.

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


Re: [Haskell-cafe] Is Haskell a Fanatic?

2009-12-04 Thread Sebastian Sylvan
On Thu, Dec 3, 2009 at 5:09 PM, John D. Earle johndea...@cox.net wrote:

 See [Haskell-cafe] Optimization with Strings ? for background.

 Don Stewart wrote, the guarantees of purity the type system provides are
 extremely
 useful for verification purposes. My response to this is in theory. This
 is what caught my attention initially, but the language lacks polish and
 does not appear to be going in a direction where it shows signs where it
 will self-correct. It may even be beyond repair. I care about others and I
 don't want people to be misled.

 I am already well aware of the numbers. They do not impress me. I have
 written on this already. I have given Haskell the benefit of the doubt and
 said, What's wrong with being uncompromising? There is something wrong with
 it, if it has taken you off the path of truth. This is not uncompromising.
 This is something else. It is called fanaticism and this is the opinion that
 I have come to after due consideration.

 If you are going to argue your case, be constructive. Tell me how the type
 system is not flawed and how the Haskell language is rigorous. What proof do
 you have of this? Explain to me how Haskell has been merely uncompromising
 in its pursuit of perfection and did not manage to step over the threshold
 into fanaticism. Please remain on topic and on point.


I honestly don't understand what your beef is. Could you explain what you
mean with some specifics? In what way does Haskell lack polish? What makes
you think it's not going in a direction where it will self correct?
What's the path of truth and in what way is Haskell not on it?

I would very much appreciate if you could try to explain what you mean using
specific examples. I read the other thread and the post of yours didn't
really seem to make much sense to me there either.

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


Re: [Haskell-cafe] From function over expression (+, *) derive function over expression (+)

2009-12-04 Thread Reid Barton
On Fri, Dec 04, 2009 at 11:52:35AM -0600, Derek Elkins wrote:
 On Fri, Dec 4, 2009 at 11:26 AM, Radek Micek radek.mi...@gmail.com wrote:
  Hello.
 
  I have two types for expression:
 
  data Expr = Add Expr Expr | Mul Expr Expr | Const Int
 
  data AExpr = AAdd AExpr AExpr | AConst Int
 
  The first one supports addition and multiplication and the second
  only addition.
 
  I can write a function to simplify the first expression:
 
  simplify :: Expr - Expr
  simplify = {- replaces:
  a*1 and 1*a by a,
  a+0 and 0+a by a -}
 
  And I would like to use the function simplify for the second type
  AExpr. What can I do is to convert AExpr to Expr, simplify it and
  convert it back. But I don't like this solution because
  conversions take some time.
 
  I would prefer following: I say to the compiler that AAdd is like Add
  and AConst is like Const and the compiler derives function
  asimplify for AExpr.
 
  Is it possible to do this? In fact I want to have two distinct types
  where one is extension of the second (Expr is extension of AExpr)
  and I want to define a function for the extended type (Expr) and
  use it for the original type (AExpr). I assume that the function won't
  introduce Mul to the expression which had no Mul.
 
 What you'd ideally want is called refinement types which Haskell, and
 as far as I know, no practical language has.  There is a paper about a
 way to encode these, but it is fairly heavy-weight.  You could use
 phantom type trickery to combine the data types into one type but
 still statically check that only additive expressions are passed to
 certain functions, but that too is also probably more trouble than
 it's worth.

In this particular case, with only two types Expr and AExpr, the
encoding is not particularly onerous.

{-# LANGUAGE GADTs, EmptyDataDecls, ViewPatterns #-}

data M
data Blah

-- A value of type 'E a' can only involve multiplication when a is M
data E a where
  Const :: Int - E a
  Add :: E a - E a - E a
  Mul :: E M - E M - E M

type Expr = E M
type AExpr = E Blah

-- The same simplify function we would write for the original Expr,
-- with a different type
simplify :: E a - E a
simplify (Const x) = Const x
simplify (Add (simplify - a) (simplify - b)) = case (a, b) of
  (Const 0, _) - b
  (_, Const 0) - a
  _ - Add a b
simplify (Mul (simplify - a) (simplify - b)) = case (a, b) of
  (Const 1, _) - b
  (_, Const 1) - a
  _ - Mul a b

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


Re: [Haskell-cafe] Are there standard idioms for lazy, pure error handling?

2009-12-04 Thread Jason McCarty
wren ng thornton wrote:

 concat1 :: T a b - (b - T a b) - T a b

This could just as easily be

  concat :: T a b - (b - T a c) - T a c

right? It's a little weird to call this concatenation, but I bet it
could come in handy.

-- 
Jason McCarty jmcca...@sent.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Is Haskell a Fanatic?

2009-12-04 Thread Gregory Crosswhite
Sebastian,

It helps if you think of John as having already won in this discussion, since 
he succeeded in getting a lengthy high-noise emotional reaction from us.  :-)

Cheers,
Greg


On Dec 4, 2009, at 10:00 AM, Sebastian Sylvan wrote:

 
 
 On Thu, Dec 3, 2009 at 5:09 PM, John D. Earle johndea...@cox.net wrote:
 See [Haskell-cafe] Optimization with Strings ? for background.
 
 Don Stewart wrote, the guarantees of purity the type system provides are 
 extremely
 useful for verification purposes. My response to this is in theory. This is 
 what caught my attention initially, but the language lacks polish and does 
 not appear to be going in a direction where it shows signs where it will 
 self-correct. It may even be beyond repair. I care about others and I don't 
 want people to be misled.
 
 I am already well aware of the numbers. They do not impress me. I have 
 written on this already. I have given Haskell the benefit of the doubt and 
 said, What's wrong with being uncompromising? There is something wrong with 
 it, if it has taken you off the path of truth. This is not uncompromising. 
 This is something else. It is called fanaticism and this is the opinion that 
 I have come to after due consideration.
 
 If you are going to argue your case, be constructive. Tell me how the type 
 system is not flawed and how the Haskell language is rigorous. What proof do 
 you have of this? Explain to me how Haskell has been merely uncompromising in 
 its pursuit of perfection and did not manage to step over the threshold into 
 fanaticism. Please remain on topic and on point. 
 
 I honestly don't understand what your beef is. Could you explain what you 
 mean with some specifics? In what way does Haskell lack polish? What makes 
 you think it's not going in a direction where it will self correct?
 What's the path of truth and in what way is Haskell not on it? 
 
 I would very much appreciate if you could try to explain what you mean using 
 specific examples. I read the other thread and the post of yours didn't 
 really seem to make much sense to me there either.
 
 -- 
 Sebastian Sylvan
 ___
 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] SYB looping very, very mysteriously

2009-12-04 Thread David Fox
I have created an entry in the syb-with-class issue database
here:http://code.google.com/p/syb-with-class/issues/detail?id=3

I attached a version of the code with the necessary bits of
Happstack.Data.Default included in-line.

On Thu, Dec 3, 2009 at 2:50 PM, Jeremy Shaw jer...@n-heptane.com wrote:
 I have the following program which loops under GHC 6.10.4:

 http://www.hpaste.org/fastcgi/hpaste.fcgi/view?id=13561#a13561

 {-# LANGUAGE DeriveDataTypeable, FlexibleInstances, MultiParamTypeClasses,
 UndecidableInstances #-}
 module Main where

 import qualified Data.Data as Data
 import Data.Typeable (Typeable)
 import Happstack.Data.Default
 import Data.Generics.SYB.WithClass.Basics
 import Data.Generics.SYB.WithClass.Instances ()

 data Proposition = Proposition Expression  deriving (Show, Data.Data,
 Typeable)
 data Expression = Conjunction (Maybe Expression) deriving (Show, Data.Data,
 Typeable)

 -- instance (Sat (ctx [Expression]), Sat (ctx Expression), Sat (ctx
 Proposition)) = Data ctx Proposition where
 instance Data DefaultD Proposition where
    gunfold _ k z c =
        case constrIndex c of
          1 - k (z Proposition)
 instance Default Proposition

 constrExpr :: Constr
 constrExpr = mkConstr dataTypeExpr Conjuction [] Prefix

 dataTypeExpr :: DataType
 dataTypeExpr = mkDataType Expression [constrExpr]

 instance ( Data ctx [Expression]
         , Sat  (ctx Expression)
         , Sat  (ctx (Maybe Expression))) = Data ctx Expression where
 {-
 instance Data DefaultD Expression where
 -}
    gunfold _ k z c =
        case constrIndex c of
          1 - k (z Conjunction)
    dataTypeOf _ _ = dataTypeExpr

 instance Default Expression

 e :: Expression
 e =  defaultValueD dict

 main = print e

 I wish to explain the *many* ways in which it is mysterious. If you load the
 program into GHCi and evaluate 'e' it will hang. If you compile the program
 and run it, it will output loop. This behavior seems annoying, but not
 very weird. But, here is where it gets fun:

 1. if you load the program into GHCi and eval 'e' it will hang. But, if you
 load the program and type, '(defaultValueD dict) :: Expression' at the
 prompt, it works fine!

 2. if you remove the (Data DefaultD Proposition) instance, it  works fine.
 (Even though Expression does not refer to Proposition in any way)

 3. if you simply change the definition of 'gunfold' in the 'Data ctx
 Proposition' instance to, error foo. The application works fine. That's
 right, if you change the body of a function that isn't even being called,
 evaluating 'e' starts working. (Even though Expression does not refer to
 Proposition in any way. And even though that gunfold instance is never
 actually called).

 4. if you change the constraint on, Data ctx Expression,  from (Data ctx
 [Expression]) to (Data ctx Expression) it works fine. (Or remove it all
 together).

 5. if you change 'instance (Data DefaultD Proposition) where' to the line
 above it which is commented out, it works fine.

 6. if you change the type of Proposition to, data Proposition = Proposition
 (Expression, Expression), then it works fine.

 So far I have only tested this in GHC 6.10.4.

 Any idea what is going on here? I can't imagine how changing the body of
 functions that aren't being called would fix things...

 - jeremy
 ___
 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] Is Haskell a Fanatic?

2009-12-04 Thread Jason Dusek
2009/12/04 Simon Peyton-Jones simo...@microsoft.com:
 If you think someone is talking nonsense, I think the best
 policy is to ignore it or reply privately (not to the list);
 then the thread dies.  I find derogatory discussion of a
 particular person quite discouraging.  It is likely to be
 unjust, and it encourages more of the same.  It's like
 littering your own house.

  +1

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


[Haskell-cafe] Low Level Audio - Writing bytes to the sound card?

2009-12-04 Thread M Xyz

What is the most minimal (preferably platform independent) library available 
for writing bytes to the sound card? I see 60 wonderful libraries on Hackage, 
but I really just need the Haskell equivalent of an audio.write(byte[]) method. 
What sound api are these 60 libraries using?

I think the portaudio library is the only contender but when I try to install 
it I get:

cabal install portaudio
Resolving dependencies...
Downloading portaudio-0.0.1...
Configuring portaudio-0.0.1...
cabal: Missing dependency on a foreign library:
* Missing C library: portaudio
This problem can usually be solved by installing the system package that
provides this library (you may need the -dev version). If the library is
already installed but in a non-standard location then you can use the flags
--extra-include-dirs= and --extra-lib-dirs= to specify where it is.
cabal: Error: some packages failed to install:
portaudio-0.0.1 failed during the configure step. The exception was:
exit: ExitFailure 1





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


[Haskell-cafe] Re: ANNOUNCE: Blueprint 0.1 -- PREVIEW

2009-12-04 Thread Ben Franksen
Gregory Crosswhite wrote:
 I have posted Blueprint to Hackage so that people can see what I have done
 and possibly play with it.

Very interesting, this. However, I could not build it. I get

b...@sarun[2]: ~/tmp  cabal install blueprint
Resolving dependencies...
cabal: There is no installed version of base

Needless to say this is wrong:

b...@sarun[2]: ~/tmp  ghc-pkg list base  
/usr/local/lib/ghc-6.10.4/./package.conf:
base-3.0.3.1, base-4.1.0.0
/home/ben/.ghc/i386-linux-6.10.4/package.conf:

This has not happened to me with any other packages from hackage.

Cheers
Ben

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


Re: [Haskell-cafe] Low Level Audio - Writing bytes to the sound card?

2009-12-04 Thread John Van Enk
Hi,

portaudio is my embarrassing fault, but it does work most of the time.
(Community, some one remind me to revisit this package after Christmas.)

Are you running in Windows? Linux? If Linux, which flavor?

/jve

On Fri, Dec 4, 2009 at 1:51 PM, M Xyz functionallyharmoni...@yahoo.comwrote:


 What is the most minimal (preferably platform independent) library
 available for writing bytes to the sound card? I see 60 wonderful libraries
 on Hackage, but I really just need the Haskell equivalent of an
 audio.write(byte[]) method. What sound api are these 60 libraries using?

 I think the portaudio library is the only contender but when I try to
 install it I get:

 cabal install portaudio
 Resolving dependencies...
 Downloading portaudio-0.0.1...
 Configuring portaudio-0.0.1...
 cabal: Missing dependency on a foreign library:
 * Missing C library: portaudio
 This problem can usually be solved by installing the system package that
 provides this library (you may need the -dev version). If the library is
 already installed but in a non-standard location then you can use the flags
 --extra-include-dirs= and --extra-lib-dirs= to specify where it is.
 cabal: Error: some packages failed to install:
 portaudio-0.0.1 failed during the configure step. The exception was:
 exit: ExitFailure 1




 ___
 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] FFI and ghci

2009-12-04 Thread Patrick LeBoutillier
Hi all,

I have a small FFI-based library that I like to test like this:

  $ ghci -I../c -L../c/.libs -lmlp t.hs
  GHCi, version 6.10.1: http://www.haskell.org/ghc/  :? for help
  Loading package ghc-prim ... linking ... done.
  Loading package integer ... linking ... done.
  Loading package base ... linking ... done.
  Loading object (dynamic) mlp ... done
  final link ... done
  [1 of 9] Compiling MLP  ( MLP.hs, interpreted )
  [2 of 9] Compiling MLP.Error( MLP/Error.hs, interpreted )
  [3 of 9] Compiling MLP.Context  ( MLP/Context.hs, interpreted )
  [4 of 9] Compiling MLP.Runtime  ( MLP/Runtime.hs, interpreted )
  [5 of 9] Compiling MLP.Object   ( MLP/Object.hs, interpreted )
  [6 of 9] Compiling MLP.Type ( MLP/Type.hs, interpreted )
  [7 of 9] Compiling MLP.Value( MLP/Value.hs, interpreted )
  [8 of 9] Compiling MLP.Language ( MLP/Language.hs, interpreted )
  [9 of 9] Compiling Main ( t.hs, interpreted )
  Ok, modules loaded: MLP, MLP.Object, Main, MLP.Runtime, MLP.Context,
MLP.Error, MLP.Value, MLP.Type, MLP.Language.
  *Main main

Note: Inside libmlp.so, another shared object is loaded using dlopen().

When running this test program I get some sporadic segmentation
faults, which seem to always occur at entrypoint to the
shared object that is loaded with dlopen().


But when I compile it with ghc, i.e.

$ ghc --make -I../c -L../c/.libs -lmlp t.hs

I can't reproduce crash.

Can anyone see why this could be happening? It's quite possible that
there is really a bug in the C code,
but if someone knows about a bug or something in ghci that can cause
this behaviour I can stop looking...


Thanks a lot,

Patrick

-- 
=
Patrick LeBoutillier
Rosemère, Québec, Canada
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: computing lists of pairs

2009-12-04 Thread Daniel Fischer
Am Freitag 04 Dezember 2009 19:00:33 schrieb Christian Maeder:

  aP1 [] = [[]]
  aP1 (h:t) = do
  x - h
  xs - aP1 t
  return (x:xs)
 
  for every x in h, we calculate the combinations of t anew.

 Do we? Isn't aP1 t one closure that's being evaluated only once?

That depends. Firstly, it depends on the optimisation level.
--
module AllPossibilities where

import Debug.Trace

aP1 :: [[Int]] - [[Int]]
aP1 [] = [[]]
aP1 l@(h:t) = trace (aP1  ++ show l) [x:xs | x - h, xs - aP1 t]

aP2 :: [[Int]] - [[Int]]
aP2 [] = [[]]
aP2 l@(h:t) = trace (aP2  ++ show l) [x:xs | xs - aP2 t, x - h]
--

Compiled without optimisations (or interpreted):

Prelude AllPossibilities aP1 [[1,2,3],[4,5,6],[7,8,9]]
aP1 [[1,2,3],[4,5,6],[7,8,9]]
aP1 [[4,5,6],[7,8,9]]
aP1 [[7,8,9]]
[[1,4,7],[1,4,8],[1,4,9]aP1 [[7,8,9]]
,[1,5,7],[1,5,8],[1,5,9]aP1 [[7,8,9]]
,[1,6,7],[1,6,8],[1,6,9]aP1 [[4,5,6],[7,8,9]]
aP1 [[7,8,9]]
,[2,4,7],[2,4,8],[2,4,9]aP1 [[7,8,9]]
,[2,5,7],[2,5,8],[2,5,9]aP1 [[7,8,9]]
,[2,6,7],[2,6,8],[2,6,9]aP1 [[4,5,6],[7,8,9]]
aP1 [[7,8,9]]
,[3,4,7],[3,4,8],[3,4,9]aP1 [[7,8,9]]
,[3,5,7],[3,5,8],[3,5,9]aP1 [[7,8,9]]
,[3,6,7],[3,6,8],[3,6,9]]
Prelude AllPossibilities aP2 [[1,2,3],[4,5,6],[7,8,9]]
aP2 [[1,2,3],[4,5,6],[7,8,9]]
aP2 [[4,5,6],[7,8,9]]
aP2 [[7,8,9]]
[[1,4,7],[2,4,7],[3,4,7],[1,5,7],[2,5,7],[3,5,7],[1,6,7],[2,6,7],[3,6,7],[1,4,8],[2,4,8],
[3,4,8],[1,5,8],[2,5,8],[3,5,8],[1,6,8],[2,6,8],[3,6,8],[1,4,9],[2,4,9],[3,4,9],[1,5,9],
[2,5,9],[3,5,9],[1,6,9],[2,6,9],[3,6,9]]

it's evaluated multiple times. Compiled with optimisation (-O or -O2),

Prelude AllPossibilities aP1 [[1,2,3],[4,5,6],[7,8,9]]
aP1 [[1,2,3],[4,5,6],[7,8,9]]
aP1 [[4,5,6],[7,8,9]]
aP1 [[7,8,9]]
[[1,4,7],[1,4,8],[1,4,9],[1,5,7],[1,5,8],[1,5,9],[1,6,7],[1,6,8],[1,6,9],[2,4,7],[2,4,8],
[2,4,9],[2,5,7],[2,5,8],[2,5,9],[2,6,7],[2,6,8],[2,6,9],[3,4,7],[3,4,8],[3,4,9],[3,5,7],
[3,5,8],[3,5,9],[3,6,7],[3,6,8],[3,6,9]]
Prelude AllPossibilities aP2 [[1,2,3],[4,5,6],[7,8,9]]
aP2 [[1,2,3],[4,5,6],[7,8,9]]
aP2 [[4,5,6],[7,8,9]]
aP2 [[7,8,9]]
[[1,4,7],[2,4,7],[3,4,7],[1,5,7],[2,5,7],[3,5,7],[1,6,7],[2,6,7],[3,6,7],[1,4,8],[2,4,8],
[3,4,8],[1,5,8],[2,5,8],[3,5,8],[1,6,8],[2,6,8],[3,6,8],[1,4,9],[2,4,9],[3,4,9],[1,5,9],
[2,5,9],[3,5,9],[1,6,9],[2,6,9],[3,6,9]]

it's only evaluated once.

But if we think about what happens when we have n lists of lengths l1, ..., ln, 
there are 
l2*...*ln combinations of the tail. Each of these combinations is used l1 
times, once for 
each element of the first list. However, between two uses of a particular 
combination, all 
the other (l2*...*ln-1) combinations are used once. If l2*...*ln is large, only 
a tiny 
fraction of the combinations of the tail fit in the memory at once, so they 
simply can't 
be reused and have to be recalculated each time (theoretically, a handful could 
be kept in 
memory for reuse).

On the other hand, in aP2, each combination of the tail is of course also used 
l1 times, 
but these are in direct succession, and the combination has been bound to a 
name for the 
entire scope, it's practically guaranteed to be calculated only once and 
garbage collected 
once.

By the way, if the order in which the combinations are generated matters:

aP1 === map reverse . aP2 . reverse


  aP2 [] = [[]]
  aP2 (h:t) = do
  xs - aP2 t
  x - h
  return (x:xs)
 
  now we first calculate the combinations of t, for each of those, we cons
  the elements of h to it in turn and never reuse it afterwards.

 Thanks for explaining.

 C.

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


Re: [Haskell-cafe] Is Haskell a Fanatic?

2009-12-04 Thread Miguel Mitrofanov
Well, since he thinks we're fanatics, getting a strong emotional  
reaction from us is something one certainly wouldn't desire.


On 4 Dec 2009, at 21:14, Gregory Crosswhite wrote:


Sebastian,

It helps if you think of John as having already won in this  
discussion, since he succeeded in getting a lengthy high-noise  
emotional reaction from us.  :-)


Cheers,
Greg


On Dec 4, 2009, at 10:00 AM, Sebastian Sylvan wrote:




On Thu, Dec 3, 2009 at 5:09 PM, John D. Earle johndea...@cox.net  
wrote:

See [Haskell-cafe] Optimization with Strings ? for background.

Don Stewart wrote, the guarantees of purity the type system  
provides are extremely
useful for verification purposes. My response to this is in  
theory. This is what caught my attention initially, but the  
language lacks polish and does not appear to be going in a  
direction where it shows signs where it will self-correct. It may  
even be beyond repair. I care about others and I don't want people  
to be misled.


I am already well aware of the numbers. They do not impress me. I  
have written on this already. I have given Haskell the benefit of  
the doubt and said, What's wrong with being uncompromising? There  
is something wrong with it, if it has taken you off the path of  
truth. This is not uncompromising. This is something else. It is  
called fanaticism and this is the opinion that I have come to after  
due consideration.


If you are going to argue your case, be constructive. Tell me how  
the type system is not flawed and how the Haskell language is  
rigorous. What proof do you have of this? Explain to me how Haskell  
has been merely uncompromising in its pursuit of perfection and did  
not manage to step over the threshold into fanaticism. Please  
remain on topic and on point.


I honestly don't understand what your beef is. Could you explain  
what you mean with some specifics? In what way does Haskell lack  
polish? What makes you think it's not going in a direction where it  
will self correct?

What's the path of truth and in what way is Haskell not on it?

I would very much appreciate if you could try to explain what you  
mean using specific examples. I read the other thread and the post  
of yours didn't really seem to make much sense to me there either.


--
Sebastian Sylvan
___
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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Low Level Audio - Writing bytes to the sound card?

2009-12-04 Thread M Xyz


Hi,
portaudio is my embarrassing fault, but it does work most of the time. 
(Community, some one remind me to revisit this package after Christmas.)
Are you running in Windows? Linux? If Linux, which flavor?

/jve


I'm using Haskell on XP but I dual boot with Ubuntu 9 and I'd prefer not to 
break compatibility. I'm new to this, was I supposed to install portaudio for 
my OS before downloading the Haskell package? Are there other similar simple 
sound apis?



On Fri, Dec 4, 2009 at 1:51 PM, M Xyz functionallyharmoni...@yahoo.com wrote:


What is the most minimal (preferably platform independent) library available 
for writing bytes to the sound card? I see 60 wonderful libraries on Hackage, 
but I really just need the Haskell equivalent of an audio.write(byte[]) method. 
What sound api are these 60 libraries using?


I think the portaudio library is the only contender but when I try to install 
it I get:

cabal install portaudio
Resolving dependencies...
Downloading portaudio-0.0.1...
Configuring portaudio-0.0.1...

cabal: Missing dependency on a foreign library:
* Missing C library: portaudio
This problem can usually be solved by installing the system package that
provides this library (you may need the -dev version). If the library is

already installed but in a non-standard location then you can use the flags
--extra-include-dirs= and
 --extra-lib-dirs= to specify where it is.
cabal: Error: some packages failed to install:
portaudio-0.0.1 failed during the configure step. The exception was:
exit: ExitFailure 1






  
___

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] Low Level Audio - Writing bytes to the sound card?

2009-12-04 Thread John Van Enk
You'll have to install the portaudio C libraries and header files before
continuing. I never actually tested the package on XP, if you get it to
work, I'd love to hear your experience.

/jve

On Fri, Dec 4, 2009 at 2:20 PM, M Xyz functionallyharmoni...@yahoo.comwrote:



 Hi,

 portaudio is my embarrassing fault, but it does work most of the time.
 (Community, some one remind me to revisit this package after Christmas.)

 Are you running in Windows? Linux? If Linux, which flavor?

 /jve


 I'm using Haskell on XP but I dual boot with Ubuntu 9 and I'd prefer not to
 break compatibility. I'm new to this, was I supposed to install portaudio
 for my OS before downloading the Haskell package? Are there other similar
 simple sound apis?




 On Fri, Dec 4, 2009 at 1:51 PM, M Xyz 
 functionallyharmoni...@yahoo.comhttp://mc/compose?to=functionallyharmoni...@yahoo.com
  wrote:


 What is the most minimal (preferably platform independent) library
 available for writing bytes to the sound card? I see 60 wonderful libraries
 on Hackage, but I really just need the Haskell equivalent of an
 audio.write(byte[]) method. What sound api are these 60 libraries using?

 I think the portaudio library is the only contender but when I try to
 install it I get:

 cabal install portaudio
 Resolving dependencies...
 Downloading portaudio-0.0.1...
 Configuring portaudio-0.0.1...
 cabal: Missing dependency on a foreign library:
 * Missing C library: portaudio
 This problem can usually be solved by installing the system package that
 provides this library (you may need the -dev version). If the library is
 already installed but in a non-standard location then you can use the
 flags
 --extra-include-dirs= and --extra-lib-dirs= to specify where it is.
 cabal: Error: some packages failed to install:
 portaudio-0.0.1 failed during the configure step. The exception was:
 exit: ExitFailure 1




 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org http://mc/compose?to=haskell-c...@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] You are in a twisty maze of concurrency libraries, all different ...

2009-12-04 Thread Paul Johnson

On 04/12/09 11:51, Patrick Caldon wrote:


I'm looking for the right concurrency library/semantics for what 
should be a reasonably simple problem.


I have a little simulator:

runWorldSim :: MTGen - SimState - IO SimState

it takes about a second to run on a PC. It's functional except it 
whacks the rng, which needs IO. I run 5-10 of these jobs, and then use:


mergeWorld :: [SimState] - SimState

to pick the best features of the runs and build another possible world 
(state).  Then I use this new world to run another 5-10 jobs and so 
on.  I run this through ~2 iterations.


It's an obvious place for parallelism.

If you can get rid of the need for IO then you can use Control.Parallel 
to evaluate pure functions instead.  If you only use IO for the random 
numbers then you can either keep a StdGen in your SimState or else use a 
State StdGen monad.  Since your random number use is presumably 
already in monadic IO you could probably switch to a state monad fairly 
trivially.


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


Re: [Haskell-cafe] Re: ANNOUNCE: Blueprint 0.1 -- PREVIEW

2009-12-04 Thread Gregory Crosswhite
Yes, that is because at this time Blueprint is presently of a lower quality 
than other packages on Hackage.  ;-)  At the moment you need to execute the 
setup script manually:

runhaskell Setup.hs bootstrap
./Setup configure
./Setup build +RTS -N4 -RTS
./Setup install

(The +RTS -N4 -RTS part is optional;  it just tells Setup to use up to 4 
threads to do building in parallel where possible.)

I have known about the problem that you just mentioned --- that is, although 
running cabal configure and cabal build in the build directory works just 
fine, cabal install does not work ---  but because my .cabal file looked fine 
I assumed until now that it was just a quirk of the cabal program.  I only 
just now figured out that to make cabal install work I need to make sure that 
the build dependencies are listed in the Library section rather than only in 
the main section, as otherwise cabal refuses to simply run Setup install even 
though that actually takes care of everything for it!

Anyway, thank you for checking out Blueprint!  At this point it might be better 
to pull the sources directly from github (the Home Page link) since I have 
made many improvements since that release (though I haven't fixed the cabal 
install problem yet).  And I do plan on thoroughly polishing and documenting 
Blueprint one of these days.  :-)

Cheers,
Greg


On Dec 4, 2009, at 11:02 AM, Ben Franksen wrote:

 Gregory Crosswhite wrote:
 I have posted Blueprint to Hackage so that people can see what I have done
 and possibly play with it.
 
 Very interesting, this. However, I could not build it. I get
 
 b...@sarun[2]: ~/tmp  cabal install blueprint
 Resolving dependencies...
 cabal: There is no installed version of base
 
 Needless to say this is wrong:
 
 b...@sarun[2]: ~/tmp  ghc-pkg list base  
 /usr/local/lib/ghc-6.10.4/./package.conf:
base-3.0.3.1, base-4.1.0.0
 /home/ben/.ghc/i386-linux-6.10.4/package.conf:
 
 This has not happened to me with any other packages from hackage.
 
 Cheers
 Ben
 
 ___
 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] Are there standard idioms for lazy, pure error handling?

2009-12-04 Thread David Menendez
On Fri, Dec 4, 2009 at 1:14 PM, Jason McCarty jmcca...@sent.com wrote:
 wren ng thornton wrote:

     concat1 :: T a b - (b - T a b) - T a b

 This could just as easily be

  concat :: T a b - (b - T a c) - T a c

 right? It's a little weird to call this concatenation, but I bet it
 could come in handy.

T a is, among other things, the free monad for the functor (,) a. The
concat you describe is the monadic bind.

data T a b = D b | W a (T a b)

instance Monad (T a) where
return = D

D b = f = f b
W a t = f = W a (t = f)

-- 
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] seems like I'm on the wrong track

2009-12-04 Thread Paul Johnson

On 02/12/09 01:55, Michael Mossey wrote:
 I have a quite messy problem which is describable as a big state 
machine, at least in the way I think of it. An input event can 
trigger a cascade of changes to the state. Channel numbers must be 
assigned and tracked, table numbers as well, decisions about whether 
to create a new table or re-use an old one, global variables and 
commands added and/or modified, etc. So I am hoping for a comment from 
that perspective.


First, I wonder if some of the ideas in Functional Reactive Programming 
might help; its a very clean and declarative way of dealing with messy 
event-based stuff like this.



Second, more generally, for Haskell design you need to take a step back 
and think about the mathematical relations between things in your domain 
that an application programmer cares about.  Then you can think about 
how to map from your domain model to an implementation like CSound.


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


Re: [Haskell-cafe] Low Level Audio - Writing bytes to the sound card?

2009-12-04 Thread M Xyz

 if you get it to work

As a spoiled Java programmer, this new role as pioneer is a bit intimidating, 
but I will give it a shot. :) 

I downloaded the portaudio v19 source and I'm attempting to build it. 
Apparently I have to register my Visual Studio Express with Microsoft. Deeper 
down the rabbit hole... (Interesting aside, on the registration form under 
What programming language topics are you interested in? neither F# or Haskell 
are listed)

I wish there was a multimedia standard library for beginners like me. Writing 
audio to the speakers shouldn't be such a journey.


You'll have to install the portaudio C libraries and header files before 
continuing. I never actually tested the package on XP, if you get it to work, 
I'd love to hear your experience.
/jve


On Fri, Dec 4, 2009 at 2:20 PM, M Xyz functionallyharmoni...@yahoo.com wrote:



Hi,

portaudio is my embarrassing fault, but it does work most of the time. 
(Community, some one remind me to revisit this package after Christmas.)
Are you running in Windows? Linux? If Linux, which flavor?


/jve


I'm using Haskell on XP but I dual boot with Ubuntu 9 and I'd prefer not to 
break compatibility. I'm new to this, was I supposed to install portaudio for 
my OS before downloading the Haskell package? Are there other similar simple 
sound apis?




On Fri, Dec 4, 2009 at 1:51 PM, M Xyz functionallyharmoni...@yahoo.com wrote:




What is the most minimal (preferably platform independent) library available 
for writing bytes to the sound card? I see 60 wonderful libraries on Hackage, 
but I really just need the Haskell equivalent of an audio.write(byte[]) method. 
What sound api are these 60 libraries using?



I think the portaudio library is the only contender but when I try to install 
it I get:

cabal install portaudio
Resolving dependencies...
Downloading portaudio-0.0.1...
Configuring portaudio-0.0.1...


cabal: Missing dependency on a foreign library:
* Missing C library: portaudio
This problem can usually be solved by installing the system package that
provides this library (you may need the -dev version). If the library is


already installed but in a non-standard location then you can use the flags
--extra-include-dirs= and
 --extra-lib-dirs= to specify where it is.
cabal: Error: some packages failed to install:
portaudio-0.0.1 failed during the configure step. The exception was:
exit: ExitFailure 1







  
___

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] SYB looping very, very mysteriously

2009-12-04 Thread Jeremy Shaw
I have stripped things down to the bare minimum, and test under GHC  
6.10, GHC 6.12, Linux, and Mac OS X. Results are consistent.


In the following code,

 1. if you load the code into ghci and evaluate e it will hang, but  
(defaultValueD dict) :: Expression returns fine
 2. if you change the gunfold instance for Proposition to, error  
gunfold it stops hanging -- even though this code is never called.
 3. if you change, ( Data ctx [Expression], Sat (ctx Expression) =  
Data ctx Expression, to (Data ctx Expression, ) = ... it stops  
hanging.


If someone could explain why each of these cases perform as they do,  
that would be awesome! Right now it is a big mystery to me.. e calls  
dict .. and there is only one instance of dict available, which should  
call error right away. I can't see how something could get in the way  
there...


- jeremy

{-# LANGUAGE DeriveDataTypeable, FlexibleContexts, FlexibleInstances,  
MultiParamTypeClasses, UndecidableInstances, RankNTypes,  
ScopedTypeVariables, KindSignatures, EmptyDataDecls,  
NoMonomorphismRestriction #-}

module Main where

import qualified Data.Data as Data
import Data.Typeable

--- syb-with-class

data Constr = Constr deriving (Eq, Show)

data Proxy (a :: * - *)

class Sat a where
dict :: a

class (Typeable a, Sat (ctx a)) = Data ctx a where
 gunfold :: Proxy ctx
 - (forall b r. Data ctx b = c (b - r) - c r)
 - (forall r. r - c r)
 - Constr
 - c a

instance (Sat (ctx [a]),Data ctx a) = Data ctx [a]

--- Default

class (Data DefaultD a) = Default a where
defaultValue :: a

data DefaultD a = DefaultD { defaultValueD :: a }

instance Default t = Sat (DefaultD t) where
dict = error Sat (DefaultD t) not implemented

instance Default a = Default [a] where
defaultValue = error Default [a] not implemented

--- Trouble

data Proposition = Proposition Expression  deriving (Show, Data.Data,  
Typeable)
data Expression = Conjunction Expression deriving (Show, Data.Data,  
Typeable)


-- instance (Sat (ctx [Expression]), Sat (ctx Expression), Sat (ctx  
Proposition)) = Data ctx Proposition where

instance Data DefaultD Proposition  where
gunfold _ k z c = k (z Proposition)
--gunfold _ k z c = error gunfold

instance Default Proposition

-- Change Data ctx [Expression] to Data ctx Expression and main works.
instance ( Data ctx [Expression]
 , Sat (ctx Expression)
 ) = Data ctx Expression

instance Default Expression

e :: Expression
e = defaultValueD (dict :: DefaultD Expression)

main = print e

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


Re: [Haskell-cafe] Low Level Audio - Writing bytes to the sound card?

2009-12-04 Thread minh thu
2009/12/4 M Xyz functionallyharmoni...@yahoo.com

  if you get it to work

 As a spoiled Java programmer, this new role as pioneer is a bit intimidating, 
 but I will give it a shot. :)

 I downloaded the portaudio v19 source and I'm attempting to build it. 
 Apparently I have to register my Visual Studio Express with Microsoft. Deeper 
 down the rabbit hole... (Interesting aside, on the registration form under 
 What programming language topics are you interested in? neither F# or 
 Haskell are listed)

 I wish there was a multimedia standard library for beginners like me. Writing 
 audio to the speakers shouldn't be such a journey.

Hi,

Did you look at synthesizer ? There is a short introductory file [1].
Be sure to look at the source (there is a link next to each function
definition). Outputting list of values is easy, for instance

Play.monoToInt16 (44100::Double) (map sin [0::Double,0.1..])

It uses SoX [2], which should be installed.

Cheers,
Thu

[1] 
http://hackage.haskell.org/packages/archive/synthesizer-core/0.2.1/doc/html/Synthesizer-Plain-Tutorial.html
[2] http://sox.sourceforge.net/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: From function over expression (+, *) derive function over expression (+)

2009-12-04 Thread Radek Micek
Thank you for your reply. If I understand this correctly
I can use your solution to have functions which work on any
subsets of constructors like in this example:

{-# LANGUAGE GADTs, EmptyDataDecls #-}

data Yes
data No

data AnyType a b c where
  A :: AnyType Yes b c
  B :: AnyType a Yes c
  C :: AnyType a b Yes

func :: AnyType a b No - String
func A = A
func B = B

func2 :: AnyType No No c - String
func2 C = C

On Dec 4, 7:14 pm, Reid Barton rwbar...@math.harvard.edu wrote:
 On Fri, Dec 04, 2009 at 11:52:35AM -0600, Derek Elkins wrote:
  On Fri, Dec 4, 2009 at 11:26 AM, Radek Micek radek.mi...@gmail.com wrote:
   Hello.

   I have two types for expression:

   data Expr = Add Expr Expr | Mul Expr Expr | Const Int

   data AExpr = AAdd AExpr AExpr | AConst Int

   The first one supports addition and multiplication and the second
   only addition.

   I can write a function to simplify the first expression:

   simplify :: Expr - Expr
   simplify = {- replaces:
   a*1 and 1*a by a,
   a+0 and 0+a by a -}

   And I would like to use the function simplify for the second type
   AExpr. What can I do is to convert AExpr to Expr, simplify it and
   convert it back. But I don't like this solution because
   conversions take some time.

   I would prefer following: I say to the compiler that AAdd is like Add
   and AConst is like Const and the compiler derives function
   asimplify for AExpr.

   Is it possible to do this? In fact I want to have two distinct types
   where one is extension of the second (Expr is extension of AExpr)
   and I want to define a function for the extended type (Expr) and
   use it for the original type (AExpr). I assume that the function won't
   introduce Mul to the expression which had no Mul.

  What you'd ideally want is called refinement types which Haskell, and
  as far as I know, no practical language has.  There is a paper about a
  way to encode these, but it is fairly heavy-weight.  You could use
  phantom type trickery to combine the data types into one type but
  still statically check that only additive expressions are passed to
  certain functions, but that too is also probably more trouble than
  it's worth.

 In this particular case, with only two types Expr and AExpr, the
 encoding is not particularly onerous.

 {-# LANGUAGE GADTs, EmptyDataDecls, ViewPatterns #-}

 data M
 data Blah

 -- A value of type 'E a' can only involve multiplication when a is M
 data E a where
   Const :: Int - E a
   Add :: E a - E a - E a
   Mul :: E M - E M - E M

 type Expr = E M
 type AExpr = E Blah

 -- The same simplify function we would write for the original Expr,
 -- with a different type
 simplify :: E a - E a
 simplify (Const x) = Const x
 simplify (Add (simplify - a) (simplify - b)) = case (a, b) of
   (Const 0, _) - b
   (_, Const 0) - a
   _ - Add a b
 simplify (Mul (simplify - a) (simplify - b)) = case (a, b) of
   (Const 1, _) - b
   (_, Const 1) - a
   _ - Mul a b

 Regards,
 Reid Barton
 ___
 Haskell-Cafe mailing list
 haskell-c...@haskell.orghttp://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: Optimizing Parsec 3 -- was: Wiki software?

2009-12-04 Thread John MacFarlane
 On Mon, Nov 23, 2009 at 12:29 PM, Antoine Latter aslat...@gmail.com wrote:
 
 I finally had some time to test it.  After running it multiple times
 (of course, it would be nice to use criterion here), I'm getting
 numbers in this neighborhood:
 

I used criterion to compare pandoc compiled with parsec2 to
pandoc compiled with your version of parsec3.  (The benchmark
is converting testsuite.txt from markdown to HTML.) The difference was
minor:

parsec2:
mean: 67.66576 ms, lb 67.56722 ms, ub 67.88983 ms, ci 0.950
std dev: 722.3878 us, lb 323.0343 us, ub 1.356013 ms, ci 0.950

parsec3:
mean: 68.20847 ms, lb 68.16387 ms, ub 68.26284 ms, ci 0.950
std dev: 252.7773 us, lb 204.5512 us, ub 325.2424 us, ci 0.950

So, once you release the new parsec3, I am prepared to remove the
parsec  3 restriction from the libraries I maintain: pandoc,
highlighting-kate, filestore, gitit, and yst.

John

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


[Haskell-cafe] Are there major inefficiencies in Haskell compared to OCaml?

2009-12-04 Thread Casey Hawthorne
Are there major inefficiencies in Haskell compared to OCaml?
If so, can something be done about them?
--
Regards,
Casey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Are there major inefficiencies in Haskell compared to OCaml?

2009-12-04 Thread Don Stewart
caseyh:
 Are there major inefficiencies in Haskell compared to OCaml?
 If so, can something be done about them?

Can you be more specific?

Looking at the u64q shootout:


http://shootout.alioth.debian.org/u64q/benchmark.php?test=alllang=ghclang2=ocamlbox=1

Shows the two implementations tied for memory, and code size, but
Haskell winning the speed tests more often.

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


Re: [Haskell-cafe] GHC magic optimization ?

2009-12-04 Thread Matt Morrow
Although, in Luke's example,

 x = sum [1..10^6] + product [1..10^6]
 x' = let l = [1..10^6] in sum l + product l

We can do much much better, if we're sufficiently smart.

-- Define:
bar m n = foo (enumFromTo m n)
foo xs  = sum xs + prod xs

-- We're given:
sum = foldl (+) 0
product = foldl (*) 1
foldl f z xs =
  case xs of
[] - []
x:xs - foldl f (f z x) xs
enumFromTo m n =
  case m  n of
True - []
False - m : enumFromTo (m+1) n

-- The fused loop becomes:
foo xs = go0 0 1 xs
  where go0 a b xs =
  case xs of
[] - a+b
x:xs - go0 (a+x) (b*x) xs

-- Now inline foo in bar:
bar m n = go2 0 1 m n
  where go2 = go0 a b (go1 m n)
go0 a b xs =
  case xs of
[] - a+b
x:xs - go0 (a+x) (b*x) xs
go1 m n =
  case m  n of
True - []
False - m : go1 (m+1) n

-- considering go2
go2 = go0 a b (go1 m n)

== case (go1 m n) of
  [] - a+b
   x:xs - go0 (a+x) (b*x) xs

== case (case m  n of
   True - []
   False - m : go1 (m+1) n) of
  [] - a+b
  x:xs - go0 (a+x) (b*x) xs

== case m  n of
  True - case [] of
[] - a+b
x:xs - go0 (a+x) (b*x) xs

  False - case (m : go1 (m+1) n) of
 [] - a+b
 x:xs - go0 (a+x) (b*x) xs

== case m  n of
  True - a+b
  False - go0 (a+m) (b*m) (go1 (m+1) n)

-- So,
go2 = case m  n of
True - a+b
False - go0 (a+m) (b*m) (go1 (m+1) n)

-- And by the original def of go2
go2 = go0 a b (go1 m n)

-- We get
go2 = case m  n of
True - a+b
False - go2 (a+m) (b*m) (m+1) n

-- go0 and go1 and now dead in bar
bar m n = go2 0 1 m n
  where go2 = case m  n of
True - a+b
False - go2 (a+m) (b*m) (m+1) n

-- (furthermore, if (+) here is for Int/Double etc,
-- we can reduce go2 further to operate on machine
-- ints/doubles and be a register-only non-allocating loop)

-- So now finally returning to our original code:
 x = sum [1..10^6] + product [1..10^6]
 x' = let l = [1..10^6] in sum l + product l

-- We get:
x' = bar 1 (10^6)

And the intermediate list never exists at all.

Matt




On 12/4/09, Luke Palmer lrpal...@gmail.com wrote:
 On Fri, Dec 4, 2009 at 3:36 AM, Neil Brown nc...@kent.ac.uk wrote:
 But let's say you have:

 g x y = f x y * f x y

 Now the compiler (i.e. at compile-time) can do some magic.  It can spot
 the
 common expression and know the result of f x y must be the same both
 times,
 so it can convert to:

 g x y = let z = f x y in z * z

 GHC does *not* do this by default, quite intentionally, even when
 optimizations are enabled.  The reason is because it can cause major
 changes in the space complexity of a program.  Eg.

 x = sum [1..10^6] + product [1..10^6]
 x' = let l = [1..10^6] in sum l + product l

 x runs in constant space, but x' keeps the whole list in memory.  The
 CSE here has actually wasted both time and space, since it is harder
 to save [1..10^6] than to recompute it!  (Memory vs. arithmetic ops)

 So GHC leaves it to the user to specify sharing.  If you want an
 expression shared, let bind it and reuse.

 Luke
 ___
 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] Are there major inefficiencies in Haskell compared to OCaml?

2009-12-04 Thread Rick R
On Fri, Dec 4, 2009 at 4:25 PM, Casey Hawthorne cas...@istar.ca wrote:

 Are there major inefficiencies in Haskell compared to OCaml?
 If so, can something be done about them?



There are definitely some gotchas when it comes to performance, mostly in
the realm of inadvertent space leaks and such.
But that's just it, they are gotchas. A new haskeller will no doubt
encounter them, but they are generally simple to fix.

When Haskell and Ocaml are coded by their respective experts, I would, in
general, trust Haskell to be faster.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] GHC magic optimization ?

2009-12-04 Thread George Pollard
2009/12/4 Evan Laforge qdun...@gmail.com:
 The interesting thing is CAFs, which at the top level will never be
 out of scope and hence live forever.

Untrue! CAFs can be garbage collected as well. See:

http://www.haskell.org/pipermail/glasgow-haskell-users/2005-September/009051.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Are there major inefficiencies in Haskell compared to OCaml?

2009-12-04 Thread Erik de Castro Lopo
Casey Hawthorne wrote:

 Are there major inefficiencies in Haskell compared to OCaml?

As a five plus year veteran of Ocaml and a one year user of Haskell
I would say in general no.

However, Ocaml's strict evaluation makes it easy for someone new to
the language to have a pretty accurate guess about its run time and 
memory usage something which can be difficult in the face of Haskell's
lazy evaluation (not that I have experienced any obvious manifestations
of this myself).

Erik
-- 
--
Erik de Castro Lopo
http://www.mega-nerd.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Low Level Audio - Writing bytes to the sound card?

2009-12-04 Thread M Xyz

Did you look at synthesizer ? There is a short introductory file [1].
Cheers,
Thu

[1] 
http://hackage.haskell.org/packages/archive/synthesizer-core/0.2.1/doc/html/Synthesizer-Plain-Tutorial.html

Thanks for the tutorial link. As I'm new to Haskell, these 2 lines got me 
thinking: Using plain lists is not very fast and Getting real-time 
performance is mostly an issue of the right signal data structure. What do you 
use as an efficient byte buffer in a value-oriented language? 

The array tutorial says Obviously, a naive implementation of such an array 
semantics would be
intolerably inefficient, either requiring a new copy of an array for each
incremental redefinition, or taking linear time for array lookup; thus, serious 
attempts at using this
approach employ sophisticated static analysis and clever run-time
devices to avoid excessive copying.



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


Re: [Haskell-cafe] Greetings! 2D Graphics?

2009-12-04 Thread Michael Steele
 I admit author's bias, but I suggest graphics-drawingcombinators.  It is a
 2D drawing library based on OpenGL with a pure interface (no IO, except to
 finally render your drawing), and supports all the stuff you want except
 clipping.

 It uses the SDL bindings, which I have heard are not easy to
 install on windows, but go smooth as a baby's bottom on ubuntu.

 Luke

I'll second this.  I started using graphics-drawingcombinators about a month
ago so I could easily convert SDL Surfaces into 2D sprites within OpenGL.  The
entire haddock synopsis fits on a single browser page, making it extremely
easily to start using and build off of.

You might also want to take a look at Conrad Barski's picnic tutorial at
http://www.lisperati.com/haskell/, where he does some work with 2D graphics by
generating .svg files.

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


Re: [Haskell-cafe] inotify-alike for mac os x?

2009-12-04 Thread Bryan O'Sullivan
On Fri, Dec 4, 2009 at 8:39 AM, Svein Ove Aas svein@aas.no wrote:


 That said.. you say you have to handle the events fast. What happens
 if you don't?


If you don't handle events quickly, they're typically thrown away by the
kernel without you ever getting to read them. That is, for instance, what
happens on Linux with inotify. Throwing away events means that your app's
internal mirror of the filesystem state becomes wrong, which is Very Bad for
most applications that care. (i.e. Ross's assertion than nothing bad will
happen is generally not true.)

*However*, with inotify you *also* can't afford to perform a single read
system call per event, because that will cause your watch the filesystem
event to soak up most of the system's CPU time. So what you have to do is
select to listen for there's an event ready to be read, then sleep a
little while, *then* read in the hope that many (but not too many!) events
will have been queued that you can all read at once.

And at that point, you'll be getting a stale notification about a file or
directory that may no longer even exist, or may have changed type. Consider:
I create a file f, write data into it, rename it to g, then create a
directory named f. You wake up 10 milliseconds later, and the first event
you hear about is that a file named f was created.

This is all by way of saying that working with filesystem change
notification interfaces is extremely subtle and tricky, enormously more so
than you'd think on casual inspection. It's very easy to write a program
that uses these interfaces in ways that will make it either generate garbage
or consume huge amounts of CPU, and in fact the common case is to write a
program that does both.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] inotify-alike for mac os x?

2009-12-04 Thread Ross Mellgren


On Dec 4, 2009, at 5:30 PM, Bryan O'Sullivan wrote:

On Fri, Dec 4, 2009 at 8:39 AM, Svein Ove Aas svein@aas.no  
wrote:


That said.. you say you have to handle the events fast. What happens
if you don't?

If you don't handle events quickly, they're typically thrown away by  
the kernel without you ever getting to read them. That is, for  
instance, what happens on Linux with inotify. Throwing away events  
means that your app's internal mirror of the filesystem state  
becomes wrong, which is Very Bad for most applications that care.  
(i.e. Ross's assertion than nothing bad will happen is generally not  
true.)


Ah hah yeah, I meant in the context of it won't block the kernel or  
cause your computer to melt. It varies between applications whether  
dropping events is bad or not so I wasn't commenting there.


However, with inotify you also can't afford to perform a single read  
system call per event, because that will cause your watch the  
filesystem event to soak up most of the system's CPU time. So what  
you have to do is select to listen for there's an event ready to be  
read, then sleep a little while, then read in the hope that many  
(but not too many!) events will have been queued that you can all  
read at once.


And at that point, you'll be getting a stale notification about a  
file or directory that may no longer even exist, or may have changed  
type. Consider: I create a file f, write data into it, rename it to  
g, then create a directory named f. You wake up 10 milliseconds  
later, and the first event you hear about is that a file named f was  
created.


This is all by way of saying that working with filesystem change  
notification interfaces is extremely subtle and tricky, enormously  
more so than you'd think on casual inspection. It's very easy to  
write a program that uses these interfaces in ways that will make it  
either generate garbage or consume huge amounts of CPU, and in fact  
the common case is to write a program that does both.


Amen. I've written an application that does this kind of work using  
inotify and it was a nightmare. I think this is why fseventsd was  
invented for OS X, and I'm not sure if there's any linux equivalent.


However, if someone were to write a library that uses kqueue /  
inotify / win32-call-I-forget-the-name-of-from-earlier-post in a way  
that is both efficient and correct, that would be totally awesome.


-Ross


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


Re: [Haskell-cafe] Are there major inefficiencies in Haskell compared to OCaml?

2009-12-04 Thread M Xyz


However, Ocaml's strict evaluation makes it easy for someone new to
the language to have a pretty accurate guess about its run time and 
memory usage something which can be difficult in the face of Haskell's
lazy evaluation (not that I have experienced any obvious manifestations
of this myself).

Erik

Speaking as someone new to the language, this is one subject that confused me 
while reading RWH. They kept using the phrase space leak and I would think 
Well, I understand that with laziness one simple call could trigger an 
explosion of calculations but how is that a 'leak'?

I had to go back and reread that section before I realized that the laziness 
was implemented as *runtime thunks* and I finally understood why they called it 
a leak. Looking back I think they did a good job explaining it after all, I 
just totally missed it the first time through. 




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


Re: [Haskell-cafe] From function over expression (+, *) derive function over expression (+)

2009-12-04 Thread Martijn van Steenbergen

Luke Palmer wrote:

On Fri, Dec 4, 2009 at 10:26 AM, Radek Micek radek.mi...@gmail.com wrote:

Hello.

I have two types for expression:

data Expr = Add Expr Expr | Mul Expr Expr | Const Int

data AExpr = AAdd AExpr AExpr | AConst Int

The first one supports addition and multiplication and the second
only addition.

I can write a function to simplify the first expression:

simplify :: Expr - Expr
simplify = {- replaces:
a*1 and 1*a by a,
a+0 and 0+a by a -}

And I would like to use the function simplify for the second type
AExpr. What can I do is to convert AExpr to Expr, simplify it and
convert it back. But I don't like this solution because
conversions take some time.


Well there are more involved reasons than simply the conversion taking
time.  If you would like the type system on your side, you have a
decent modeling problem on your hands.  How can you guarantee that
simplify will return a type that will fit in AExpr?  Simplify might
turn a+a into 2*a, and then your trick no longer works.  It would
seem that you need to typecheck the function twice.

You could attempt to go the other way, i.e. define a simplify on AExpr
and map to and from Expr, but that will have trouble with expressions
like 0+(2*a), because 2*a has no representation in AExpr.

My hunch is that to do this properly, you need to use some of the
fixed point modeling that I can't find the paper about (!)  (It's
popular, someone please chime in :-).  I.e. define a data type which,
directed by type classes, may or may not support multiplication.  Then
define separately an additive simplifier and a multiplicative
simplifier on that.


Perhaps you're looking for:

Wouter Swierstra
Data types à la carte
http://www.cse.chalmers.se/~wouter/Publications/DataTypesALaCarte.pdf

Groetjes,

Martijn.

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


Re: [Haskell-cafe] inotify-alike for mac os x?

2009-12-04 Thread Matt Morrow
Conal,

If I were looking to do this, I'd read the relevant parts of the libev code.

Matt


On 12/3/09, Conal Elliott co...@conal.net wrote:
 I'd like to make some FRPish toys that keep files updated to have functional
 relationships with other files.  hinotify looks like just the sort of
 underlying magic I could use for efficient implementation on linux.  Is
 there any support for mac os x?  Could support be either added to hinotify
 or maybe inotify and a mac-friendly library be abstracted into a common
 Haskell interface?  I'm fine with an imperative interface, since I can
 abstract into a functional library, which I guess would be a sort of
 persistent simplified FRP.

- Conal

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


  1   2   >