Re: [Haskell-cafe] Filesystem access

2007-06-22 Thread Bulat Ziganshin
Hello Andrew,

Friday, June 22, 2007, 12:19:51 AM, you wrote:
 1. Is there *any* way to determine how large a file is *without* opening
 it? The only library function I can find to do with file sizes is 
 hFileSize; obviously this only works for files that you have permission
 to open!

std library doesn't contain such function, although it is easily
modeled after getModificationTime. note that on windows this will
return only lower 32 bits of file size due to using lstat() internally

another way around this is to look at getFileAttributes implementation
and build the same wrapper around win32 getfilesize function

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re[4]: [Haskell-cafe] haskell crypto is reaaaaaaaaaally slow

2007-06-22 Thread Bulat Ziganshin
Hello Duncan,

Thursday, June 21, 2007, 8:48:53 AM, you wrote:

  The smallest possible would be 2 words overhead by just using a
  ByteArray#,
 
 i tried it once and found that ByteArray# size is returned rounded to 4 -
 there is no way in GHC runtime to alloc, say, exactly 37 bytes. and
 don't forget to add 2 unused bytes at average

 Right, GHC heap object are always aligned to the natural alignment of
 the architecture, be that 4 or 8 bytes.

 Try the same experiment with C's malloc. I'd be very surprised if you
 can allocate 37 bytes and not end up using 40 (plus some extra for
 remembering the allocation length).

that i'm trying to say is that one need to store exact string size
because value returned by getSizeOfByteArray is aligned to 4

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Collections

2007-06-22 Thread Lennart Augustsson

It's not that broken,  It was designed by people from the FP community. :)

On 6/21/07, Andrew Coppin [EMAIL PROTECTED] wrote:


Brent Yorgey wrote:

 OK, I don't even understand that syntax. Have they changed the Java
 language spec or something?


 Yes.  As of version 5 (or 1.5, or whatever you want to call it), Java
 has parametric polymorphism.  Do a Google search for Java generics.

OMG - they actually added a language feature to Java... o_O

I bet it's broken though! ;-)

___
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: Type classes vs C++ overloading Re: [Haskell-cafe] Messing around with types [newbie]

2007-06-22 Thread Cristiano Paris

I sent this message yesterday to Bulat but it was intended for the haskel
cafe, so I'm resending it here today.

Thank to everyone who answered me privately. Today I'll keep on
experimenting and read the reference you gave me.

Cristiano

-- Forwarded message --
From: Cristiano Paris [EMAIL PROTECTED]
Date: Jun 21, 2007 6:20 PM
Subject: Re: Type classes vs C++ overloading Re: [Haskell-cafe] Messing
around with types [newbie]
To: Bulat Ziganshin [EMAIL PROTECTED]


On 6/21/07, Bulat Ziganshin [EMAIL PROTECTED] wrote:


Hello Cristiano,

Thursday, June 21, 2007, 4:46:27 PM, you wrote:

 class FooOp a b where
 foo :: a - b - IO ()

 instance FooOp Int Double where
 foo x y = putStrLn $ (show x) ++  Double  ++ (show y)

this is rather typical question :)



I knew it was... :D

unlike C++ which resolves any

overloading at COMPILE TIME, selecting among CURRENTLY available
overloaded definitions and complaining only when when this overloading
is ambiguous, type classes are the RUN-TIME overloading mechanism

your definition of partialFoo compiled into code which may be used
with any instance of foo, not only defined in this module. so, it
cannot rely on that first argument of foo is always Int because you may
define other instance of FooOp in other module. 10 is really
constant function of type:

10 :: (Num t) =  t

i.e. this function should receive dictionary of class Num in order to
return value of type t (this dictionary contains fromInteger::Integer-t
method which used to convert Integer representation of 10 into type
actually required at this place)

this means that partialFoo should have a method to deduce type of 10
in order to pass it into foo call. Let's consider its type:

partialFoo :: (FooOp t y) =  y - IO ()

when partialFoo is called with *any* argument, there is no way to
deduce type of t from type of y which means that GHC has no way to
determine which type 10 in your example should have. for example, if
you will define

instance FooOp Int32 Double where

anywhere, then call partialFoo (5.0::Double) will become ambiguous

shortly speaking, overloading resolved based on global class
properties, not on the few instances present in current module. OTOH,
you build POLYMORPHIC functions this way while C++ just selects
best-suited variant of overloaded function and hard-code its call

further reading:
http://homepages.inf.ed.ac.uk/wadler/papers/class/class.ps.gz
http://haskell.org/haskellwiki/OOP_vs_type_classes
chapter 7 of GHC user's guide, functional dependencies



M... your point is hard to understand for me.

In his message, I can understand Bryan Burgers' point better (thanks Bryan)
and I think it's somewhat right even if I don't fully understand the type
machinery occuring during ghc compilation (yet).

Quoting Bryan:

*From this you can see that 10 is not necessarily an Int, and 5.0 is
*not necessarily a Double. So the typechecker does not know, given just
10 and 5.0, which instance of 'foo' to use. But when you explicitly
told the typechecker that 10 is an Int and 5.0 is a Double, then the
type checker was able to choose which instance of 'foo' it should use.

So, let's see if I've understood how ghc works:

1 - It sees 5.0, which belongs to the Fractional class, and so for 10
belonging to the Num class.
2 - It only does have a (FooOp x y) instance of foo where x = Int and y =
Double but it can't tell whether 5.0 and 10.0 would fit in the Int and
Double types (there's some some of uncertainty here).
3 - Thus, ghci complains.

So far so good. Now consider the following snippet:

module Main where

foo :: Double - Double
foo = (+2.0)

bar = foo 5.0

I specified intentionally the type signature of foo. Using the same argument
as above, ghci should get stuck in evaluating foo 5.0 as it may not be a
Double, but only a Fractional. Surprisingly (at least to me) it works!

So, it seems as if the type of 5.0 was induced by the type system to be
Double as foo accepts only Double's.

If I understand well, there's some sort of asymmetry when typechecking a
function application (the case of foo 5.0), where the type signature of a
function is dominant, and where typechecking an overloaded function
application (the original case) since there type inference can't take place
as someone could add a new overloading later as Bulat says.

So, I tried to fix my code and I came up with this (partial) solution:

module Main where

class FooOp a b where
 foo :: a - b - IO ()

instance (Num t) = FooOp t Double where
 foo x y = putStrLn $ (show x) ++  Double  ++ (show y)

partialFoo :: Double - IO ()
partialFoo = foo 10

bar = partialFoo 5.0

As you can see, I specified that partialFoo does accept Double so the type
of 5.0 if induced to be Double by that type signature and the ambiguity
disappear (along with relaxing the type of a to be simply a member of the
Num class so 10 can fit in anyway).

Problems arise if I add another instance of FooOp where b is Int (i.e. FooOp
Int Int):

module 

Re: Type classes vs C++ overloading Re: [Haskell-cafe] Messing around with types [newbie]

2007-06-22 Thread Tomasz Zielonka
On Fri, Jun 22, 2007 at 10:57:58AM +0200, Cristiano Paris wrote:
 Quoting Bryan:
 
 *From this you can see that 10 is not necessarily an Int, and 5.0 is
 *not necessarily a Double. So the typechecker does not know, given just
 10 and 5.0, which instance of 'foo' to use. But when you explicitly
 told the typechecker that 10 is an Int and 5.0 is a Double, then the
 type checker was able to choose which instance of 'foo' it should use.

I would stress typechecker does not know, given just 10 and 5.0, which
instance of 'foo' to use. The statement 10 is not necessarily an Int
may be misleading. I would rather say 10 can be not only Int, but also
any other type in the Num type class.

 So, let's see if I've understood how ghc works:
 
 1 - It sees 5.0, which belongs to the Fractional class, and so for 10
 belonging to the Num class.
 2 - It only does have a (FooOp x y) instance of foo where x = Int and y =
 Double but it can't tell whether 5.0 and 10.0 would fit in the Int and
 Double types (there's some some of uncertainty here).

The problem is not that it can't tell whether 5.0 and 10 would fit Int
and Double (actually, they do fit), it's that it can't tell if they
won't fit another instance of FooOp.

 3 - Thus, ghci complains.
 
 So far so good. Now consider the following snippet:
 
 module Main where
 
 foo :: Double - Double
 foo = (+2.0)
 
 bar = foo 5.0
 
 I specified intentionally the type signature of foo. Using the same argument
 as above, ghci should get stuck in evaluating foo 5.0 as it may not be a
 Double, but only a Fractional. Surprisingly (at least to me) it works!

See above.

 So, it seems as if the type of 5.0 was induced by the type system to be
 Double as foo accepts only Double's.

I think that's correct.

 If I understand well, there's some sort of asymmetry when typechecking a
 function application (the case of foo 5.0), where the type signature of a
 function is dominant, and where typechecking an overloaded function
 application (the original case) since there type inference can't take place
 as someone could add a new overloading later as Bulat says.

There is no asymmetry. The key word here is *ambiguity*. In the
(Double - Double) example there is no ambiguity - foo is not
overloaded, in other words it's a single function, so it suffices
to check if the parameters have the right types.

In your earlier example, both 5.0 and foo are overloaded. If you had
more instances for FooOp, the ambiguity could be resolved in many ways,
possibly giving different behaviour. Haskell doesn't try to be smart
and waits for you to decide. And it pretends it doesn't see that there
is only one instance, because taking advantage of this situation could
give surprising results later.

 but it didn't work. Here's ghci's complaint:
 
 example.hs:7:0:
Duplicate instance declarations:
  instance (Num t1, Fractional t2) = FooOp t1 t2
-- Defined at example.hs:7:0
  instance (Num t1, Num t2) = FooOp t1 t2
-- Defined at example.hs:10:0
 Failed, modules loaded: none.

Instances are duplicate if they have the same (or overlapping) instance
heads. An instance head is the thing after =. What's before = doesn't
count.

 It seems that Num and Fractional are somewhat related. Any hint?

It's not important here, but indeed they are:
class (Num a) = Fractional a where

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


Re: [Haskell-cafe] Graphical Haskell

2007-06-22 Thread Pasqualino 'Titto' Assini
This might be of interest:

http://pipes.yahoo.com/pipes/

Best,

titto

On Friday 22 June 2007 11:15:49 peterv wrote:
 Hi,

 Since nobody gave an answer on this topic, I guess it is insane to do it in
 Haskell (at least for a newbie)? :)

 Thanks for any info,
 Peter

 -Original Message-
 From: [EMAIL PROTECTED]
 [mailto:[EMAIL PROTECTED] On Behalf Of peterv
 Sent: Wednesday, June 20, 2007 21:48
 To: haskell-cafe@haskell.org
 Subject: [Haskell-cafe] Graphical Haskell

 In the book Haskell School of Expression, streams are nicely explained
 using a graphical flow graph.

 This is also done more or less in
 http://research.microsoft.com/~simonpj/papers/marktoberdorf/Marktoberdorf.p
p t to explain monads and other concepts.

 I would like to create a program that allows you to create such flow
 graphs, and then let GHC generate the code and do type inference.

 I found a paper where Haskell is used to create a GUI application with
 undo/redo etc for creating graphical Basian networks
 (http://www.cs.uu.nl/dazzle/f08-schrage.pdf), so this gave me confidence
 that I could it do all in Haskell.

 Now, instead of generating Haskell code (which I could do first, would be
 easier to debug), I would like to directly create an AST, and use an
 Haskell API to communicate with GHC.

 I already found out that GHC indeed has such an API, but how possible is
 this idea? Has this been done before? I only found a very old attempt at
 this, confusingly also called Visual Haskell, see
 http://ptolemy.eecs.berkeley.edu/%7Ejohnr/papers/visual.html, but I can't
 find any source code for that project.

 I did a similar project in C# that generated C++ code, so I've done it
 before, just not in Haskell.

 Thanks a lot,
 Peter


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

 No virus found in this incoming message.
 Checked by AVG Free Edition.
 Version: 7.5.472 / Virus Database: 269.9.1/857 - Release Date: 20/06/2007
 14:18


 No virus found in this outgoing message.
 Checked by AVG Free Edition.
 Version: 7.5.472 / Virus Database: 269.9.1/857 - Release Date: 20/06/2007
 14:18


 ___
 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] Graphical Haskell

2007-06-22 Thread peterv
Hi,

Since nobody gave an answer on this topic, I guess it is insane to do it in
Haskell (at least for a newbie)? :)

Thanks for any info,
Peter

-Original Message-
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of peterv
Sent: Wednesday, June 20, 2007 21:48
To: haskell-cafe@haskell.org
Subject: [Haskell-cafe] Graphical Haskell

In the book Haskell School of Expression, streams are nicely explained
using a graphical flow graph.

This is also done more or less in
http://research.microsoft.com/~simonpj/papers/marktoberdorf/Marktoberdorf.pp
t to explain monads and other concepts.

I would like to create a program that allows you to create such flow graphs,
and then let GHC generate the code and do type inference. 

I found a paper where Haskell is used to create a GUI application with
undo/redo etc for creating graphical Basian networks
(http://www.cs.uu.nl/dazzle/f08-schrage.pdf), so this gave me confidence
that I could it do all in Haskell.

Now, instead of generating Haskell code (which I could do first, would be
easier to debug), I would like to directly create an AST, and use an Haskell
API to communicate with GHC. 

I already found out that GHC indeed has such an API, but how possible is
this idea? Has this been done before? I only found a very old attempt at
this, confusingly also called Visual Haskell, see
http://ptolemy.eecs.berkeley.edu/%7Ejohnr/papers/visual.html, but I can't
find any source code for that project.

I did a similar project in C# that generated C++ code, so I've done it
before, just not in Haskell.

Thanks a lot,
Peter


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

No virus found in this incoming message.
Checked by AVG Free Edition. 
Version: 7.5.472 / Virus Database: 269.9.1/857 - Release Date: 20/06/2007
14:18
 

No virus found in this outgoing message.
Checked by AVG Free Edition. 
Version: 7.5.472 / Virus Database: 269.9.1/857 - Release Date: 20/06/2007
14:18
 

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


Re: [Haskell-cafe] Re: Orthogonal Persistence in Haskell

2007-06-22 Thread Pasqualino 'Titto' Assini
Many thanks Claus for the extended explanation, it makes perfect sense.

For more info I will now turn to the papers :-)

Talking about serialisation, an interesting paper has just appeared on 
lambda-the-ultimate:

HOT Pickles
http://lambda-the-ultimate.org/node/2305

Regards,

 titto



On Friday 22 June 2007 00:28:53 Claus Reinke wrote:
  with orthogonal persistence, everything a program touches might
  persist, but usually, programs talk about the data being persistet (?),
  not about whether that data is currently temporary or in long-term
  storage. if you want to move such data between processes or storage
  areas, you move the reference, and the system handles serialisation/
  communication/deserialisation behind the scenes.
 
  This is interesting, could you elaborate on it?
  How would you get data to move around by moving its reference?

 more elaboration than the various papers, surveys, and phd theses
 listed in the references i provided?-) the idea is that i give you the
 reference, and you take care of looking at the data behind it,
 without me having to serialise the contents;-)

 but ok, lets see whether i can get the idea accross by example:

 a) suppose you want to move some x from list a to list b

 do you get the type of x, devise a type-specific traversal to
 serialise x from the source, move the flattened data from a to b,
 and deserialise x in the target?

 or do you just write:

 test = move ([1..4],[3..5])
 move (x:as) b = (as,x:bs)

 b) suppose you want to move some x from concurrent haskell
 process a to concurrent haskell process b

 do you get the type of x, devise a type-specific traversal to
 serialise x from the source, move the flattened data from a to b,
 and deserialise x in the target?

 or do you write something like:

 test = do { av-newEmptyMVar;
  bv-newEmptyMVar;
  forkIO (putMVar av [1..]);
  forkIO (takeMVar bv = print . take 10);
  move av bv }
 move av bv = takeMVar av = putMVar bv

 c) suppose you want to move some x from os process a to
 os process b

 do you get the type of x, devise a type-specific traversal to
 serialise x from the source, move the flattened data from a to b,
 and deserialise x in the target?

 yes. and if the type is not serialisable, you're stuck.

 d) suppose you want to move some x from os process a to
 an os file, for later retrieval in process b

 do you get the type of x, devise a type-specific traversal to
 serialise x from the source, move the flattened data from a to b,
 and deserialise x in the target?

 yes. and if the type is not serialisable, you're stuck.

 now, why are c/d so much more troublesome than a/b? i don't
 care whether the x to be moved is an integer, a matrix, a function,
 or the list of primes - i just want it to be moved from a to b. or
 rather, i move the reference to x, and the runtime system moves
 whatever representation is behind that, if a move is necessary,
 and without ever exposing that internal representation. and if i
 happen to move x into a long-term storage area, it will persist
 there for future reference, without further ado.

 much more about that idea in the papers i mentioned. or, if you
 prefer something more recent, have a look at the Clean papers:

 http://www.st.cs.ru.nl/Onderzoek/Publicaties/publicaties.html

 a selection of entries related to dynamics and first-class i/o:

 1997: 4. Pil, Marco, First Class File I/O
 2003: 7. Arjen van Weelden and Rinus Plasmeijer.
  Towards a Strongly Typed Functional Operating System.
 2003: 6. Martijn Vervoort and Rinus Plasmeijer.
  Lazy Dynamic Input/Output in the lazy functional language
 Clean 2004: 21. Arjen van Weelden, Rinus Plasmeijer.
 A Functional Shell that Dynamically Combines Compiled Code.

 hth,
 claus

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


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


[Haskell-cafe] Re: Collections

2007-06-22 Thread apfelmus
Thomas Conway wrote:
 On 6/22/07, Duncan Coutts [EMAIL PROTECTED] wrote:
 You might find that lazy IO is helpful in this case. The primitive that
 implements lazy IO is unsafeInterleaveIO :: IO a - IO a
 
 Personally, unsafeInterleaveIO is so horribly evil, that even just
 having typed the name, I'll have to put the keyboard through the
 dishwasher (see http://www.coudal.com/keywasher.php).

:D :D
Finally someone who fully understands the true meaning of the prefix
unsafe  ;)

 Note that using a Map will probably not help since it needs to
 read all the keys to be able to construct it so that'd pull
 in all the data from disk.

 Well, in the case I'm dealing with, the map can contain the current
 key from each postings vector, and the closure for reading the
 remainder of the vector. E.g. Map Key ([IO (Maybe Key)]).

In any case, you have to store as many keys as you have lists to sort,
but lazy mergesort will not hold on more than (length xs + 1) keys in
memory at a single moment in time and only force one new key per
retrieval. No lingering intermediate lists :)

In this situation, unsafeInterleaveIO is an easy way to carry this
behavior over to the IO-case:

 type Reader t = IO (Maybe t)
 type Writer t = t - IO ()

 readList :: Reader t - IO [t]
 readList m = unsafeInterleaveIO $ do
mx - m
case mx of
   Just x  - liftM (x:) $ readList m
   Nothing - return []

 mergesortIO :: Ord t = [Reader t] - Writer t - IO ()
 mergesortIO xs f = do
ys - mapM readList xs
mapM_ f $ mergesort ys

Here, readList creates only as many list elements as you demand,
similarly to getContents. Of course, it has the same problem as
getContents, namely that you can accidentally close the file before
having read all data. But this is applies to any on-demand approach be
it with IO or without.

Also, you can make the heap in mergesort explicit and obtain something
similar to your current approach with Data.Map. The observation is that
while mergesort does create a heap, its shape does not change and is
determined solely by (length xs).

-- convenient invariant:
--   the smaller element comes from the left child
  data Ord b = Heap m b = Leaf m b | Branch b (Tree a b) (Tree a b)

-- smart constructor
  branch :: Ord b = Tree m b - Tree m b - Tree m b
  branch x y
  | gx = gy  = Branch gx x y
  | otherwise = Branch gy y x
  where
  (gx,gy) = (getMin x, getMin y)

-- fromList is the only way to insert elements into a heap
  fromList :: Ord b = [(m,b)] - Heap m b
  fromList = foldtree1 branch . map (uncurry Leaf)

  getMin :: Heap m b - b
  getMin (Leaf _ b)  = b
  getMin (Branch b _ _ ) = b

  deleteMin :: Heap (Reader b) b - IO (Maybe (Heap (Reader b) b))
  deleteMin (Leaf m _) = m = return . fmap (Leaf m)
  deleteMin (Branch _ x y) = do
mx' - deleteMin x
return . Just $ case mx' of
   Just x' - branch x' y
   Nothing - y

  mergesortIO :: Ord t = [Reader t] - Writer t - IO ()
  mergesortIO xs f = ...

 Also, I need to support concurrent querying and updates,
 and trying to manage the locking is quite hard enough as it is,
 without trying to keep track of which postings vectors have closures
 pointing to them!

I guess you have considered Software Transactional Memory for atomic
operations?
   http://research.microsoft.com/~simonpj/papers/stm/index.htm

Also, write-once-read-many data structures (like lazy evaluation uses
them all the time) are probably very easy to get locked correctly.


Regards,
apfelmus

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


Re: Type classes vs C++ overloading Re: [Haskell-cafe] Messing around with types [newbie]

2007-06-22 Thread Cristiano Paris

On 6/22/07, Tomasz Zielonka [EMAIL PROTECTED] wrote:
...


The problem is not that it can't tell whether 5.0 and 10 would fit Int
and Double (actually, they do fit), it's that it can't tell if they
won't fit another instance of FooOp.



You expressed the concept in more correct terms but I intended the same...
I'm starting to understand now.



Instances are duplicate if they have the same (or overlapping) instance
heads. An instance head is the thing after =. What's before = doesn't
count.



So, the context is irrelevant to distinguishing instances?


It seems that Num and Fractional are somewhat related. Any hint?

It's not important here, but indeed they are:
   class (Num a) = Fractional a where



I see. Thank you Tomasz.

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


Re: [Haskell-cafe] Haskell version of ray tracer code is much slower than the original ML

2007-06-22 Thread Philip Armstrong

On Thu, Jun 21, 2007 at 08:42:57PM +0100, Philip Armstrong wrote:

On Thu, Jun 21, 2007 at 03:29:17PM -0400, Mark T.B. Carroll wrote:

Philip Armstrong [EMAIL PROTECTED] writes:
(snip)

Why on earth would you use -fexcess-precision if you're using Floats?
The excess precision only apples to Doubles held in registers on x86
IIRC. (If you spill a Double from a register to memory, then you lose
the extra precision bits in the process).


Some googling suggests that point 2 on
http://www.haskell.org/hawiki/FasterFloatingPointWithGhc
might have been what I was thinking of.


That's the old wiki. The new one gives the opposite advice! (As does
the ghc manual):

 http://www.haskell.org/ghc/docs/latest/html/users_guide/faster.html
 http://www.haskell.org/haskellwiki/Performance/Floating_Point


Incidentally, the latter page implies that ghc is being overly
pessimistic when compilling FP code without -fexcess-precision:

On x86 (and other platforms with GHC prior to version 6.4.2), use
 the -fexcess-precision flag to improve performance of floating-point
 intensive code (up to 2x speedups have been seen). This will keep
 more intermediates in registers instead of memory, at the expense of
 occasional differences in results due to unpredictable rounding.

IIRC, it is possible to issue an instruction to the x86 FP unit which
makes all operations work on 64-bit Doubles, even though there are
80-bits available internally. Which then means there's no requirement
to spill intermediate results to memory in order to get the rounding
correct.

Ideally, -fexcess-precision should just affect whether the FP unit
uses 80 or 64 bit Doubles. It shouldn't make any performance
difference, although obviously the generated results may be different.

As an aside, if you use the -optc-mfpmath=sse option, then you only
get 64-bit Doubles anyway (on x86).

cheers, Phil

--
http://www.kantaka.co.uk/ .oOo. public key: http://www.kantaka.co.uk/gpg.txt
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Graphical Haskell

2007-06-22 Thread Henning Thielemann

On Fri, 22 Jun 2007, peterv wrote:

 Since nobody gave an answer on this topic, I guess it is insane to do it in
 Haskell (at least for a newbie)? :)

It's certainly an interesting project. Since signal processing is much
like functional programming, a graphical Haskell editor could also serve
as a nice signal processing graph editor.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Graphical Haskell

2007-06-22 Thread Pasqualino 'Titto' Assini

On Friday 22 June 2007 11:21:31 Henning Thielemann wrote:
 On Fri, 22 Jun 2007, peterv wrote:
  Since nobody gave an answer on this topic, I guess it is insane to do it
  in Haskell (at least for a newbie)? :)

 It's certainly an interesting project. Since signal processing is much
 like functional programming, a graphical Haskell editor could also serve
 as a nice signal processing graph editor.

An existing example of which is CAL's Gem Cutter:

http://resources.businessobjects.com/labs/cal/gemcutter-techpaper.pdf 

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


Re: [Haskell-cafe] To yi or not to yi, is this really the question? A plea for a cooperative, ubiquitous, distributed integrated development system.

2007-06-22 Thread Claus Reinke

Most languages, even Java, have a reflection capability to dynamically
inspect an object.

_Even_ Java? That's a strange point of view considering how much money
went into this technology.


they didn't take reflection seriously at first, initially providing only a 
half-baked feature set; that state, and the transition period when they 
finally noticed that they actually needed better reflection support for 
their own tools was somewhat painful (was it around/before jdk 1.2? 
partially coevolving with jni, debuggers, beans, etc.?).



I also find it hard to believe that most languages have reflection,
especially those which are traditionally focused on efficiency and
compilation to native code, like C, C++, Fortran, Pascal, etc.


c did have something like 'thing', providing you with the address of
'thing's representation, and in more innocent times, with the ability to
read and rewrite that representation:-) c++ had templates, overloading

if you doubt the expressive power of even such restricted reflection
support, think of buffer overflow exploits or, in the scripting world,
of string injection attacks. these are negative examples, but they
demonstrate the potential of reflection support: to enable the 
unexpected, to support evolution of uses not originally planned for.



How many languages with reflection can you list?


you're kidding, right? 


lisp, prolog, smalltalk, clos' mop, java, javascript, sh, perl, ..
well, most shellsscripting languages, and to a (sometimes very)
limited extent, most languages

however, that's a bit vague, and i always mix up the directions, so 
let me try to pin down some terms, so that we're at least mixed up

the same way:-)

   - reification: from program/data to representation (reify, quote)
   - reflection: from representation to program/data (eval, splice)
   - meta-programming: programs operating on program representations
   - reflective programming: programs operating on their own representations

unless i'm talking about specific operations/instances of the scheme,
i tend to refer to the last item, encompassing all others, when i talk
about reflection in programming languages.

now, if you consider the old game of quines (programs printing their 
own representation), most turing-complete languages provide some
reflection, the only question is, is it well supported or so awkward 
that its only uses are limited to theory papers and obfuscated code 
competitions?



I think the reasons are mostly insufficient resources and not enough
interest to justify the effort. 


the former, yes. the latter, no. the lisp/smalltalk folks have known
all along, the java folks have found out the hard way, and some of
us haskellers are still trying to pretend we do not know, even though
we've been bitten often enough:

-   good reflection support makes it easy to develop tools
   and to experiment with language extensions

-   lack of good reflection support causes mutually inconsistent
   complex workarounds trying to reinvent reflection support
   the hard way while seriously hampering tool development

anyone who tried to develop tools for haskell before the haskell
implementations started to provide haskell apis to their inner
workings can attest to the difficulties. whereas, the better these
apis get, the less current developers are even aware that there
used to be problems of that kind.

and at the language level, we still use preprocessors, including
the c one:-( btw, languages with adequate reflection support tend 
not to have separate preprocessors), we do have partial efforts 
like template haskell, data/typeable (and the generic techniques 
based on them, including scrap your boilerplate), in fact the 
whole type-class-level programming area could be said to be
about type-based meta-programming generating functional 
programs from type-level proofs, then there are pragmas and 
implicit insertion of program markers for profiling/coverage 
analysis/debugging, complete program transformations for 
profiling/tracing/debugging, multiple separate frontends and 
ast types, language.haskell, hsx, programatica, poor man's 
versions of type dynamic, dynamic loading and runtime code 
generation, data.dynamic, hs-plugins, ghc api, yhc api, hugs 
server api, .. ah, well, you get the idea?-)


perhaps the most important aspect of reflection support is to
notice that there is a common theme in all these separate
efforts, and a common support base that could help to make
all of those efforts and similar tools/extensions/applications
easier to develop, with the base designed to be consistent
and maintained continuosly, in a single place, instead of 
developed and forgotten again and again.


claus

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


[Haskell-cafe] Re: Haskell version of ray tracer code is much slower than the original ML

2007-06-22 Thread Simon Marlow

Philip Armstrong wrote:

On Thu, Jun 21, 2007 at 08:42:57PM +0100, Philip Armstrong wrote:

On Thu, Jun 21, 2007 at 03:29:17PM -0400, Mark T.B. Carroll wrote:



That's the old wiki. The new one gives the opposite advice! (As does
the ghc manual):

 http://www.haskell.org/ghc/docs/latest/html/users_guide/faster.html
 http://www.haskell.org/haskellwiki/Performance/Floating_Point


Incidentally, the latter page implies that ghc is being overly
pessimistic when compilling FP code without -fexcess-precision:

On x86 (and other platforms with GHC prior to version 6.4.2), use
 the -fexcess-precision flag to improve performance of floating-point
 intensive code (up to 2x speedups have been seen). This will keep
 more intermediates in registers instead of memory, at the expense of
 occasional differences in results due to unpredictable rounding.

IIRC, it is possible to issue an instruction to the x86 FP unit which
makes all operations work on 64-bit Doubles, even though there are
80-bits available internally. Which then means there's no requirement
to spill intermediate results to memory in order to get the rounding
correct.


For some background on why GHC doesn't do this, see the comment MORE FLOATING 
POINT MUSINGS... in


  http://darcs.haskell.org/ghc/compiler/nativeGen/MachInstrs.hs

The main problem is floats: even if you put the FPU into 64-bit mode, your float 
operations will be done at 64-bit precision.  There are other technical problems 
that we found with doing this, the comment above elaborates.


GHC passes -ffloat-store to GCC, unless you give the flag -fexcess-precision. 
The idea is to try to get reproducible floating-point results.  The native code 
generator is unaffected by -fexcess-precision, but it produces rubbish 
floating-point code on x86 anyway.



Ideally, -fexcess-precision should just affect whether the FP unit
uses 80 or 64 bit Doubles. It shouldn't make any performance
difference, although obviously the generated results may be different.



As an aside, if you use the -optc-mfpmath=sse option, then you only
get 64-bit Doubles anyway (on x86).


You probably want SSE2.  If I ever get around to finishing it, the GHC native 
code generator will be able to generate SSE2 code on x86 someday, like it 
currently does for x86-64.  For now, to get good FP performance on x86, you 
probably want


  -fvia-C -fexcess-precision -optc-mfpmath=sse2

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


[Haskell-cafe] Re: Haskell version of ray tracer code is much slower than the original ML

2007-06-22 Thread Simon Marlow

Philip Armstrong wrote:

On Thu, Jun 21, 2007 at 08:15:36PM +0200, peterv wrote:
So float math in *slower* than double math in Haskell? That is 
interesting.
Why is that?   

BTW, does Haskell support 80-bit long doubles? The Intel CPU seems 
to use

that format internally.


As I understand things, that is the effect of using -fexcess-precision.

Obviously this means that the behaviour of your program can change
with seemingly trivial code rearrangements,


Not just code rearrangements: your program will give different results depending 
on the optimisation settings, whether you compile with -fvia-C or -fasm, and the 
results will be different from those on a machine using fixed 32-bit or 64-bit 
precision floating point operations.


Cheers,
Simon

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


Re: [Haskell-cafe] Re: Collections

2007-06-22 Thread Thomas Conway

On 6/22/07, apfelmus [EMAIL PROTECTED] wrote:

I guess you have considered Software Transactional Memory for atomic
operations?
   http://research.microsoft.com/~simonpj/papers/stm/index.htm

Also, write-once-read-many data structures (like lazy evaluation uses
them all the time) are probably very easy to get locked correctly.


STM was *the* justification to the mgt for letting me use Haskell
rather than C++. :-)

However, you do need to take care, because in this context it would be
easy to end up creating great big transactions which conflict with one
another, which quite aside from wasting CPU on retries, can in extreme
cases lead to starvation. A bit like laziness, STM is fantastic for
correctness, but can be a bit obtuse for performance. With that
proviso, I think STM is better than sliced bread.[*]

Incidentally, I read Herlihy's papers on lock free data structures
early on in my work on parallelism and concurrency for Mercury in the
mid 90's. What a shame I didn't have the wit to understand them
properly at the time, or Mercury might have had STM 10 years ago. :-)

T.
[*] People who know me well, would realize that since I bake my own
bread and slice it with a bread-knife myself, comparison to sliced
bread may be faint praise. It isn't.
--
Dr Thomas Conway
[EMAIL PROTECTED]

Silence is the perfectest herald of joy:
I were but little happy, if I could say how much.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Graphical Haskell

2007-06-22 Thread Claus Reinke

Since nobody gave an answer on this topic, I guess it is insane to do it in
Haskell (at least for a newbie)? :)


not necessarily; we're all waiting for your first release?-)


I would like to create a program that allows you to create such flow graphs,
and then let GHC generate the code and do type inference. 


spun off from dazzle, which you've found, there's also blobs:

   http://www.cs.york.ac.uk/fp/darcs/Blobs/


Now, instead of generating Haskell code (which I could do first, would be
easier to debug), I would like to directly create an AST, and use an Haskell
API to communicate with GHC. 


one thing to consider: things get a little more tricky when the generated
haskell and dynamically loaded code is meant to do graphics (such as 
updating the original diagram with the state of the simulation). in particular, 
check that the gui framework actually works via that more circuituous route 
(similar problems to running in ghci instead of ghc).



I already found out that GHC indeed has such an API, but how possible is
this idea? Has this been done before? 


the ghc api is meant to support this kind of endeavours, and it isn't frozen
yet, either: the ghc team is happy to receive feedback about things that work 
or things that could work better.


before the ghc api, before blobs (after dazzle, though;), i did an embedding
of haskell-coloured petri nets in haskell, with a very simplistic graphical
net editor on top of wxhaskell, which generated haskell code for the net,
then called ghci to type-check and run the resulting code with a copy of
the original net graphics to update during simulation (poor man's reflection:):

   http://www.cs.kent.ac.uk/people/staff/cr3/HCPN/

it worked, but some things were annoying: 


- no high-level support for writing graph editors in wxhaskell;
   blobs aims to fix that

- awkward meta-programming and runtime reflection;
   ghc api should help a lot (but i can't see anything wrong with
   letting it work on generated source code first; optimization can
   come latter)

- wxhaskell encourages low-level dependencies, at least when
   you're writing your first wxhaskell programs, because it can
   be rather difficult just to find the function you need, you're
   tempted to use it right there, just to see if it works, and leave
   cleaning up for later, which never comes; 

   gui frameworks are worse than the io monad; try to abstract 
   and limit your uses of gui lib features to as few modules as 
   possible; nicer code, easier to switch to different framework


- abi incompatibility!!^*L$W%*^%*! 


   sorry,-) but that has become the deal breaker for me; it is
   bad enough that there are two major haskell gui libs out
   there, as it means that your clients may have the wrong one
   or none at all, and need to install the one you need; but,
   worse than that, whenever there's a new ghc release, 
   everybody needs to rebuild their gui libs, and if you

   have the latest ghc release and a recent ghc head installed,
   you even need separate copies of the gui lib, etc, etc. 


   so you use a nice high-level language to get a lot done
   in very little very portable code, but instead of distributing
   a few pages of haskell, with build as simple as ghc --make,
   you have to worry about rather huge gui lib installations,
   and you have to worry anew for each ghc release..

btw, i am thinking about reviving my hcpn project, to make 
use of the ghc api, but i'd like to get rid of the binary gui lib 
dependency first. my current take on this is gui lib? no, 
thanks, i'm just  browsing, if you know what i mean?-)


hth,
claus


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


Re: [Haskell-cafe] Collections

2007-06-22 Thread ajb
G'day.

Quoting Andrew Coppin [EMAIL PROTECTED]:

 True enough - but that's a rather specific task.

There are a lot of rather specific tasks out there.

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


[Haskell-cafe] Re: Haskell version of ray tracer code is much slower than the original ML

2007-06-22 Thread Philip Armstrong

On Fri, Jun 22, 2007 at 01:16:54PM +0100, Simon Marlow wrote:

Philip Armstrong wrote:

IIRC, it is possible to issue an instruction to the x86 FP unit which
makes all operations work on 64-bit Doubles, even though there are
80-bits available internally. Which then means there's no requirement
to spill intermediate results to memory in order to get the rounding
correct.


For some background on why GHC doesn't do this, see the comment MORE 
FLOATING POINT MUSINGS... in


  http://darcs.haskell.org/ghc/compiler/nativeGen/MachInstrs.hs


Twisty. I guess 'slow, but correct, with switches to go faster at the
price of correctness' is about the best option.

You probably want SSE2.  If I ever get around to finishing it, the GHC 
native code generator will be able to generate SSE2 code on x86 someday, 
like it currently does for x86-64.  For now, to get good FP performance on 
x86, you probably want


  -fvia-C -fexcess-precision -optc-mfpmath=sse2


Reading the gcc manpage, I think you mean -optc-msse2
-optc-mfpmath=sse. -mfpmath=sse2 doesn't appear to be an option.

(I note in passing that the ghc darcs head produces binaries from
ray.hs which are about 15% slower than ghc 6.6.1 ones btw. Same
optimisation options used both times.)

cheers, Phil

--
http://www.kantaka.co.uk/ .oOo. public key: http://www.kantaka.co.uk/gpg.txt
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Haskell version of ray tracer code is much slower than the original ML

2007-06-22 Thread Dougal Stanton

On 22/06/07, Claus Reinke [EMAIL PROTECTED] wrote:


perhaps this should be generalised to ghc flag profiles, to cover
things like '-fno-monomorphism-restriction -fno-mono-pat-binds'
or '-fglasgow-exts -fallow-undecidable-instances; and the like?


You just *know* someone's gonna abuse that to make a genuine
-funroll-loops, right? ;-)

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


Re: [Haskell-cafe] Re: Haskell version of ray tracer code is much slower than the original ML

2007-06-22 Thread Claus Reinke

  -fvia-C -fexcess-precision -optc-mfpmath=sse2


is there, or should there be a way to define -O profiles for ghc?
so that -O would refer to the standard profile, -Ofp would refer
to the combination above as a floating point optiimisation profile,
other profiles might include things like -funbox-strict-fields, and
-Omy42 would refer to my own favourite combination of flags..

perhaps this should be generalised to ghc flag profiles, to cover
things like '-fno-monomorphism-restriction -fno-mono-pat-binds'
or '-fglasgow-exts -fallow-undecidable-instances; and the like?

just a thought,
claus

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


Re: [Haskell-cafe] Re: Haskell version of ray tracer code is muchslower than the original ML

2007-06-22 Thread Claus Reinke

on second thought, user-defined profiles are a two-edged sword,
negating the documentation advantages of in-source flags. better to
handle that in the editor/ide. but predefined flag profiles would still
seem to make sense?

there is something wrong about this wealth of options. it is great 
that one has all that control over details, but it also makes it more 
difficult to get things right (eg, i was surprised that -O doesn't 
unbox strict fields by default). even a formula one driver doesn't 
control every lever himself, that's up to the team.


for optimisations, i used to have a simple picture in mind (from
my c days, i guess?), when ghci is no longer fast enough, that is:

no -O: standard executables are fast enough, thank you

-O: standard executables aren't fast enough, do something
   about it, but don't bother me with the details

-O2: i need your best _safe_ optimisation efforts, and i'm 
   prepared to pay for that with longer compilation times


-O3: i need your absolute best optimisation efforts, and i'm 
   prepared to verify myself that optimisations that cannot 
   automatically be checked for safety have no serious negative 
   effect on the results (it would be nice if you told me which

   potentially unsafe optimisations you used in compilation)

on top of that, as an alternative to -O3, specific tradeoffs would
be useful, where i specify whether i want to optimize for space
or for time, or which kinds of optimization opportunities the
compiler should pay attention to, such as strictness, unboxing,
floating point ops, etc.. but even here i wouldn't want to give
platform-specific options, i'd want the compiler to choose the
most appropriate options, given my specified tradeoffs and
emphasis, taking into account platform and self-knowledge.

so, i'd say -Ofp, and the compiler might pick:


  -fvia-C -fexcess-precision -optc-mfpmath=sse2


if i'm on a platform and compiler version where that is an 
appropriate selection of flags to get the best floating point

performance. and it might pick a different selection of flags
on a different platform, or with a different compiler version.


perhaps this should be generalised to ghc flag profiles, to cover
things like '-fno-monomorphism-restriction -fno-mono-pat-binds'
or '-fglasgow-exts -fallow-undecidable-instances; and the like?


that is a slightly different story, and it might be useful (a) to 
provide flag groups (-fno-mono*) and (b) to specify implication

(just about every language extension flag implies -fglasgow-exts,
so there's no need to specify that again, and there might be
other opportunities for reducing groups of options with a
single maximum in the implication order; one might even 
introduce pseudo-flags for grouping, such as -fhaskell2;-).


claus

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


[Haskell-cafe] Shouldn't this be lazy???

2007-06-22 Thread Olivier Boudry

Hi all,

I'm playing with the TagSoup library trying to extract links to
original pictures from my Flickr Sets page. This programs first loads
the Sets page, open links to each set, get links to pictures and then
search for original picture link (see steps in main function).

It does the job, but for the tests I just wanted to take 10 links to
reduce the time the program runs. Just hoping that haskell laziness
would magically take the minimum amount of data required to get the
first 10 links out of this set of pages.

I did this replacing:
  (putStrLn . unlines . concat) origLinks
with
  (putStrLn . unlines . take 10 . concat) origLinks
in the main function.

With the last version of that line, I effectively only get 10 links
but the runtime is exactly the same for both main functions.

As I'm a newbie haskell programmer I certainly missing something.

By the way I know Flickr has an api I could use, but the purpose was
playing with TagSoup.

Thanks for any advice.

Olivier.

Here's the code:

module Main where

import Data.Html.TagSoup
import Control.Monad (liftM)
import Data.List (isPrefixOf, groupBy)
import Data.Maybe (mapMaybe)
import System (getArgs)
import System.Time
import IO (hPutStrLn, stderr)

base= http://www.flickr.com;
setsUrl name = /photos/ ++ name ++ /sets/

main :: IO ()
main = do
   args  - getArgs
   tStart- getClockTime
   setLinks  - getLinksByAttr (class, Seta) (base ++ setsUrl (args !! 0))
   picLinks  - mapM (getLinksByAttr (class, image_link)) setLinks
   origLinks - mapM (getLinksAfterImgByAttr (src,
http://l.yimg.com/www.flickr.com/images/icon_download.gif;)) $
(mapMaybe linkToOrigSize . concat) picLinks
   (putStrLn . unlines . concat) origLinks
   tEnd  - getClockTime
   hPutStrLn stderr ( timeDiffToString $ diffClockTimes tEnd tStart )

-- | extract all links from a tag types having given attribute
getLinksByAttr :: (String, String) - String - IO [String]
getLinksByAttr attr url = do
   sects - getSectionsByTypeAndAttr a attr url
   return $ hrefs sects

-- | get a tags following a img having a specific attribute
getLinksAfterImgByAttr :: (String, String) - String - IO [String]
getLinksAfterImgByAttr attr url = do
   sects - getSectionsByTypeAndAttr img attr url
   return $ hrefs $ map (dropWhile (not . isTagOpen) . drop 1) sects

-- | create sections from tag type and attribute
getSectionsByTypeAndAttr :: String - (String, String) - String - IO [[Tag]]
getSectionsByTypeAndAttr tagType attr url = do
   tags - liftM parseTags $ openURL $ url
   (return . filterByTypeAndAttr tagType attr) tags
 where
   filterByTypeAndAttr :: String - (String, String) - [Tag] - [[Tag]]
   filterByTypeAndAttr t a = sections (~== TagOpen t [a])

-- | extract href values from sections of a tags
hrefs :: [[Tag]] - [String]
hrefs = map (addBase . fromAttrib href . head)
 where
   addBase :: String - String
   addBase s | http://; `isPrefixOf` s = s
   addBase s | otherwise= base ++ s

-- | transform a link to a picture into a link to the original size picture
linkToOrigSize :: String - Maybe String
linkToOrigSize link =
   if parts !! 3 == photos then
   Just $ newUrl parts
   else
   Nothing
 where
   parts = map tail $ groupBy (const(/='/')) link
   newUrl p = http://www.flickr.com/photo_zoom.gne?id=; ++ p !! 5 ++
size=ocontext= ++ p !! 7
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Graphical Haskell

2007-06-22 Thread peterv
Wow thanks for all the info! This certainly can get me started.

And yet I have some more questions (sorry!):

- Unfortunately this project won't be open source; if my first tests are
successful, I will try to convince my employer (who wants to develop such a
graphical language) to use Haskell for building a prototype instead of
C#/F#/Java. Can Haskell be used for creating commercial projects? When the
product is released, it *will* be downloadable for free, but the source code
won't be (most likely). 

- If my employer agrees on Haskell, and when our first round of investment
is completed, we will be looking for a couple of good Haskell developers.
What would be the best place to look for good Haskell developers? This
mailing list? Ideally development will have to take place in
Antwerp/Belgium, although we might work with remotely located freelancers.
We prefer agile development (SCRUM, and maybe we will be doing extreme
programming, to be decided) with a small group of capable people. To get an
idea of what my employer is doing, visit http://www.nazooka.com. My
colleagues and I wrote most of the software for doing this back in the
1990s, and of course the real work is done by 3D graphics artists.

- Regarding GUIs, does a real FP-style GUI exist instead of those wrappers
around OO GUIs? I did some searches but besides some research papers about
FranTk and wxFruit I only found wrappers such as Gtk2Hs and wxHaskell that
use a lot of monadic IO. It's very hard for an old school OO style
programmer like myself to switch my mind into lazy functional programming
(although I think I've seen the light yesterday when digging deep into the
FRP of the SOE book, LOL ;-).
 
- Functional reactive programming like looks cool (I only looked at the SOE
book, must still look at Yampa), but somehow I feel this is still an active
area of research. What is the latest work on FRP (for GUIs / games /
animation / simulations...)? What are the major open issues? 

- Regarding performance (for real-time simulations, not GUIs), I think the
garbage collector will get really stressed using FRP because of all those
infinite lazy streams; my gut feeling says a generational garbage collector
like Microsoft's .NET could help here (but the gut is often wrong, see
http://www.youtube.com/watch?v=RF3m3f9iMRc for an laugh ;). Regarding the
GC, is http://hackage.haskell.org/trac/ghc/wiki/GarbageCollectorNotes still
up-to-date?  

Okay, that's enough for now. More is less...

- Peter

-Original Message-
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Claus Reinke
Sent: Friday, June 22, 2007 14:02
To: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Graphical Haskell

 Since nobody gave an answer on this topic, I guess it is insane to do it
in
 Haskell (at least for a newbie)? :)

not necessarily; we're all waiting for your first release?-)

 I would like to create a program that allows you to create such flow
graphs,
 and then let GHC generate the code and do type inference. 

spun off from dazzle, which you've found, there's also blobs:

http://www.cs.york.ac.uk/fp/darcs/Blobs/
 
 Now, instead of generating Haskell code (which I could do first, would be
 easier to debug), I would like to directly create an AST, and use an
Haskell
 API to communicate with GHC. 

one thing to consider: things get a little more tricky when the generated
haskell and dynamically loaded code is meant to do graphics (such as 
updating the original diagram with the state of the simulation). in
particular, 
check that the gui framework actually works via that more circuituous route 
(similar problems to running in ghci instead of ghc).
 
 I already found out that GHC indeed has such an API, but how possible is
 this idea? Has this been done before? 

the ghc api is meant to support this kind of endeavours, and it isn't frozen
yet, either: the ghc team is happy to receive feedback about things that
work 
or things that could work better.

before the ghc api, before blobs (after dazzle, though;), i did an embedding
of haskell-coloured petri nets in haskell, with a very simplistic graphical
net editor on top of wxhaskell, which generated haskell code for the net,
then called ghci to type-check and run the resulting code with a copy of
the original net graphics to update during simulation (poor man's
reflection:):

http://www.cs.kent.ac.uk/people/staff/cr3/HCPN/

it worked, but some things were annoying: 

- no high-level support for writing graph editors in wxhaskell;
blobs aims to fix that

- awkward meta-programming and runtime reflection;
ghc api should help a lot (but i can't see anything wrong with
letting it work on generated source code first; optimization can
come latter)

- wxhaskell encourages low-level dependencies, at least when
you're writing your first wxhaskell programs, because it can
be rather difficult just to find the function you need, you're
tempted to use it right there, just to see if 

Re: [Haskell-cafe] A probably-stupid question about a Prelude implementation.

2007-06-22 Thread Neil Mitchell

Hi Michael,

You're wrong :)


foldr (||) False (repeat True)


Gives:


True


Remember that in Haskell everything is lazy, which means that the ||
short-circuits as soon as it can.

Thanks

Neil


On 6/22/07, Michael T. Richter [EMAIL PROTECTED] wrote:


 So, I'm now going over the code in the 'Report with a fine-toothed comb
because a) I'm actually able to read it now pretty fluently and b) I want to
know what's there in detail for a project I'm starting.  I stumbled across
this code:

 any :: (a - Bool) - [a] - Bool
any p = or . map p

or :: [Bool] - Bool
or = foldr (||) False


Now I see how this works and it's all elegant and clear and all that.  But
I have two nagging problems with it (that are likely related):

   1. Using foldr means I'll be traversing the whole list no matter
   what.  This implies (perhaps for a good reason) that it can only work on a
   finite list.
   2. I don't see any early bale-out semantics.  The way I read this
   it's going to expand a whole list of n and perform n comparisons (including
   the one with the provided False).


Considering that I only need a single True result to make the whole
expression true, I'd have expected there to be some clever semantics to
allow exactly this.  But what I'm seeing, unless I'm really misreading the
code, is that if I give it a list of a million boolean expressions, it will
cheerfully evaluate these million boolean expressions and perform a million
calls to (||) before giving me a result.

Please tell me I'm wrong and that I'm missing something?

  --
*Michael T. Richter* [EMAIL PROTECTED] (*GoogleTalk:*
[EMAIL PROTECTED])
*There are two ways of constructing a software design. One way is to make
it so simple that there are obviously no deficiencies. And the other way is
to make it so complicated that there are no obvious deficiencies. (Charles
Hoare)*

___
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] A probably-stupid question about a Prelude implementation.

2007-06-22 Thread Philip Armstrong

On Fri, Jun 22, 2007 at 11:31:17PM +0800, Michael T. Richter wrote:

   1. Using foldr means I'll be traversing the whole list no matter what.
  This implies (perhaps for a good reason) that it can only work on a
  finite list.


foldr is lazy.


  Please tell me I'm wrong and that I'm missing something?


You are wrong and you're missing something :)

compare: 
 any ((==) 2) [1,2,3]

and
 any ((==) 2) [1..]

any ((==) 0) [1..] will go _|_ of course.

Phil

--
http://www.kantaka.co.uk/ .oOo. public key: http://www.kantaka.co.uk/gpg.txt
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] A probably-stupid question about a Prelude implementation.

2007-06-22 Thread Dougal Stanton

On 22/06/07, Michael T. Richter [EMAIL PROTECTED] wrote:


 So, I'm now going over the code in the 'Report with a fine-toothed comb 
because a) I'm actually able to read it now pretty fluently and b) I want to 
know what's there in detail for a project I'm starting.  I stumbled across this 
code:


 any :: (a - Bool) - [a] - Bool
 any p = or . map p

 or :: [Bool] - Bool
 or = foldr (||) False

 Now I see how this works and it's all elegant and clear and all that.  But I 
have two nagging problems with it (that are likely related):

Using foldr means I'll be traversing the whole list no matter what.  This 
implies (perhaps for a good reason) that it can only work on a finite list.
I don't see any early bale-out semantics.  The way I read this it's going to 
expand a whole list of n and perform n comparisons (including the one with the 
provided False).



Well, try it:

Prelude any (10) [1..]
True

By way of contrast, this (doesn't) work as you expected:

Prelude let any' p = foldl (||) False . map p
Prelude any' (10) [1..]
^C
Interrupted.

A left fold will keep on going with an infinite list in this case.

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


Re: [Haskell-cafe] A probably-stupid question about a Prelude implementation.

2007-06-22 Thread Chris Kuklewicz

Neil Mitchell wrote:

Hi Michael,

You're wrong :)

  foldr (||) False (repeat True)

Gives:

  True

Remember that in Haskell everything is lazy, which means that the || 
short-circuits as soon as it can.


Thanks

Neil



Specifically it is graph reduced like this:

or [F,T,F,F...]

foldr (||) F [F,T,F,F...]

F || foldr (||) F [T,F,F...]

foldr (||) F [T,F,F...]

T || foldr (||) F [F,F...]

T

The last line is because (T || _ = T) and lazyness

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


Re: [Haskell-cafe] Haskell version of ray tracer code is much slower than the original ML

2007-06-22 Thread Philip Armstrong

On Thu, Jun 21, 2007 at 01:45:04PM +0100, Philip Armstrong wrote:

As I said, I've tried the obvious things  they didn't make any
difference. Now I could go sprinkling $!, ! and seq around like
confetti but that seems like giving up really.


OK. Looks like I was mistaken. Strictness annotations *do* make a
difference! Humph. Wonder what I was doing wrong yesterday?

Anyway timings follow, with all strict datatypes in the Haskell
version:

Langauge File Time in seconds
Haskell  ray.hs   38.2
OCamlray.ml   23.8 
g++-4.1  ray.cpp  12.6


(ML  C++ Code from
http://www.ffconsultancy.com/languages/ray_tracer/comparison.html)

Gcc seems to have got quite a bit better since Jon last benchmarked
this code.

Phil

--
http://www.kantaka.co.uk/ .oOo. public key: http://www.kantaka.co.uk/gpg.txt
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] A probably-stupid question about a Prelude implementation.

2007-06-22 Thread Michael T. Richter
So, I'm now going over the code in the 'Report with a fine-toothed comb
because a) I'm actually able to read it now pretty fluently and b) I
want to know what's there in detail for a project I'm starting.  I
stumbled across this code:


any :: (a - Bool) - [a] - Bool
any p = or . map p

or :: [Bool] - Bool
or = foldr (||) False


Now I see how this works and it's all elegant and clear and all that.
But I have two nagging problems with it (that are likely related):

 1. Using foldr means I'll be traversing the whole list no matter
what.  This implies (perhaps for a good reason) that it can only
work on a finite list.
 2. I don't see any early bale-out semantics.  The way I read this
it's going to expand a whole list of n and perform n comparisons
(including the one with the provided False).


Considering that I only need a single True result to make the whole
expression true, I'd have expected there to be some clever semantics to
allow exactly this.  But what I'm seeing, unless I'm really misreading
the code, is that if I give it a list of a million boolean expressions,
it will cheerfully evaluate these million boolean expressions and
perform a million calls to (||) before giving me a result.

Please tell me I'm wrong and that I'm missing something?

-- 
Michael T. Richter [EMAIL PROTECTED] (GoogleTalk:
[EMAIL PROTECTED])
There are two ways of constructing a software design. One way is to make
it so simple that there are obviously no deficiencies. And the other way
is to make it so complicated that there are no obvious deficiencies.
(Charles Hoare)


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


Re: [Haskell-cafe] Shouldn't this be lazy???

2007-06-22 Thread Malcolm Wallace
Olivier Boudry [EMAIL PROTECTED] wrote:

 I did this replacing:
(putStrLn . unlines . concat) origLinks
 with
(putStrLn . unlines . take 10 . concat) origLinks

Unfortunately, 'origLinks' has already been computed in full, before the
'take 10' applies to it.  Why?  Because 'origLinks' is the result of an
I/O action, which forces it:

 main = do ...
   origLinks - mapM (getLinksAfterImgByAttr ...) picLinks

What you really want to do is to trim the picLinks before you download
them. e.g.

 main = do ...
   origLinks - mapM (getLinksAfterImgByAttr ...) (take 10 picLinks)

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


Re: [Haskell-cafe] Shouldn't this be lazy???

2007-06-22 Thread Marc Weber
 It does the job, but for the tests I just wanted to take 10 links to
 reduce the time the program runs. Just hoping that haskell laziness
 would magically take the minimum amount of data required to get the
 first 10 links out of this set of pages.

I haven't read the details of the post. But I think its due to lazy
operations not beeing lazy by default.

Have a look at this thread it might help
http://groups.google.com/group/fa.haskell/browse_thread/thread/5deaee07a8398d07/d5b3c85aa8c2860c?lnk=stq=Marc+Weber+lazyIOrnum=1hl=en#d5b3c85aa8c2860c

All which is done is throwing in a unsafeInterleaveIO at some locations.
Because I didn't want to implement all list functions again I had the
idea of inventing the LazyIO monad (which calls unsafeInterleaveIO
automatically) But doing this to often resulted in no list processing at
all ;)
I hope that this gives you a hint to look more stuff up on the wiki
using the search etc.
If this didn't help post again and I'll have a closer look.

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


[Haskell-cafe] Type-level Programming

2007-06-22 Thread Vincenz Syntactically

Dear all,

Recently I was playing around with encoding matrices in the type-level
system.  Thereby one can enable the multiplication of matrices.  The general
idea (which can be read about at (
http://notvincenz.blogspot.com/2007/06/generalized-matrix-multiplication.html)
is that there is more than one way to multiplly a matrix.

Given two matrices A and B, with M and N dimensions:

a_1*...*a_m and b_1*...*b_n  then whenever the last L dimensions of A match
the first L dimensions of B, they can be multiplied to have a matrix of
dimension:

a_1*..*a_(m-l)*b_(l+1)*...*b_n

What one does is a dot-product on those middle L dimensions.  This is what I
tried to do in the code in the blogpost.  However, I was unable to formulate
the constraints for the final multiplication class that does the actual
proper cross-multiplication.

Is this at all possible, or was I chasing ghosts?

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


Re: [Haskell-cafe] Shouldn't this be lazy???

2007-06-22 Thread Olivier Boudry

Reading code like the following:

main = do
 s - getContents
 let r = map processIt (lines s)
 putStr (unlines r)

I was thinking all IO operations were lazy. But in fact it looks like
getContents is lazy by design but not the whole IO stuff.

Thank you all for your helpful answers,

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


Re: [Haskell-cafe] Shouldn't this be lazy???

2007-06-22 Thread Olivier Boudry

Marc,

Thanks for the link. Your LazyIO monad is really interesting. Do you
know if this construct exists in GHC? (this question was left open in
this thread)

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


Re: [Haskell-cafe] Shouldn't this be lazy???

2007-06-22 Thread Olivier Boudry

On 6/22/07, David Roundy [EMAIL PROTECTED] wrote:

Or make this lazy with:

 main = do ...
   origLinks - mapM (unsafeInterleaveIO . getLinksAfterImgByAttr ...) 
picLinks
--
David Roundy
Department of Physics
Oregon State University


Just for info I used your tip to bring laziness into the function that
fetches the URLs. Work great and lazy now!

-- | create sections from tag type and attribute
getSectionsByTypeAndAttr :: String - (String, String) - String - IO [[Tag]]
getSectionsByTypeAndAttr tagType attr url = do
   tags - unsafeInterleaveIO $ liftM parseTags $ openURL $ url
   (return . filterByTypeAndAttr tagType attr) tags
 where
   filterByTypeAndAttr :: String - (String, String) - [Tag] - [[Tag]]
   filterByTypeAndAttr t a = sections (~== TagOpen t [a])

Thanks,

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


Re: [Haskell-cafe] Plugin Problem - Weirder

2007-06-22 Thread Daniel Fischer
Am Freitag, 22. Juni 2007 04:29 schrieb Donald Bruce Stewart:

 The file system was down here, sorry.  Should be up now.

Ah, just unlucky timing.
darcs got, installed, all well.

 -- Don

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


Re: [Haskell-cafe] Telling the time

2007-06-22 Thread Andrew Coppin

Marc Weber wrote:

On Thu, Jun 21, 2007 at 09:15:12PM +0100, Andrew Coppin wrote:
  

Greetings.

Is there a standard library function anywhere which will parse a string 
into some kind of date/time representation? And, further, is there some 
function that will tell me how many seconds elapsed between two such times?


I know about Data.Time.*
and System.Time ( tdSec . diffClockTimes )

For parsing there is the library written by bringert:
http://www.cs.chalmers.se/~bringert/darcs/parsedate/

I don't know wether it is in the library index on the haskell.org.
If not we should add it. I was'nt able to find it there.
  


OK, I'll try a deeper look...

(I see there's a giant pile of modules to do with dates and times, but I 
can't make much sense out of them - and in at least one place, the 



The trouble is that time processing can be complicated if you want to
pay attention to leap seconds/ years etc. leap seconds can't be known in
advance etc.
  


I don't care about leap seconds - and neither does the hardware clock on 
the server that generates these logs. ;-) I just want to find out how 
long each step took...


documentation on the Haskell website doesn't actually match what's 
installed on my computer!)


That's why I'm reading the source all the time ;)
  


Oh... goodie...

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


Re: [Haskell-cafe] Odd lack of laziness

2007-06-22 Thread Andrew Coppin

Chaddaï Fouché wrote:

You should be using BS.null f rather than BS.length f  0.

While we're on the subject... anybody know a neat way to check, say, 
whether a list contains exactly 1 element? (Obviously pattern matching 
can do it, but that requires big case-expressions...)


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


Re: [Haskell-cafe] Collections

2007-06-22 Thread Andrew Coppin

Dan Piponi wrote:

Andrew said:


True enough - but that's a rather specific task. I'm still not seeing
vast numbers of other uses for this...


Graphs are one of the most ubiquitous structures in the whole of
computer science. Whether you're representing dataflows, or decoding
error-correcting codes, or decomposing an almost block matrix into
independent parts for multiprocessing, or figuring out which registers
to spill in a compiler, or programming neural networks, or finding the
shortest path between two cities, or trying to find dependencies in a
sequence of tasks, or constructing experimental designs, or using an
expert system to diagnose disease symptoms, or trying to find optimal
arrangements of marriage partners, or a million other tasks, graphs
appear everywhere!


I see *trees* around the place a lot, but not general graphs.

Maybe it's just the type of problems I attempt to solve?

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


Re: [Haskell-cafe] Collections

2007-06-22 Thread Andrew Coppin

Lennart Augustsson wrote:

It's not that broken,  It was designed by people from the FP community. :)


OMG... A Java feature designed by people who know stuff about stuff?

Next thing they'll implement real multiple inheritance or something... ;-)

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


Re: [Haskell-cafe] Re: Collections

2007-06-22 Thread Andrew Coppin

apfelmus wrote:

:D :D
Finally someone who fully understands the true meaning of the prefix
unsafe  ;)
  


Personally, I'm loving the whole concept of this puppy:

 GHC.Prim.*reallyUnsafePtrEquality#

I have absolutely no idea what it does, but it must be something really 
unsafe! ;-)


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


Re: [Haskell-cafe] Odd lack of laziness

2007-06-22 Thread Stefan O'Rear
On Fri, Jun 22, 2007 at 07:14:39PM +0100, Andrew Coppin wrote:
 Chaddaï Fouché wrote:
 You should be using BS.null f rather than BS.length f  0.
 
 While we're on the subject... anybody know a neat way to check, say, 
 whether a list contains exactly 1 element? (Obviously pattern matching 
 can do it, but that requires big case-expressions...)

data LazyNat = Zero | Succ LazyNat  deriving(Eq,Ord)

instance Enum LazyNat where
succ = Succ
pred (Succ x) = x

toEnum 0 = Zero
toEnum (x+1) = succ (toEnum x)

fromEnum Zero = 0
fromEnum (Succ x) = fromEnum x + 1

instance Num LazyNat where -- this is a lie, the lifted naturals only
   -- form a *semi*ring.  Sigh.
fromIntegral = toEnum

Zero + y = y
Succ x + y = Succ (x + y)

Zero * y = 0
Succ x * y = y + x * y

abs = id
signum 0 = 0
signum _ = 1

x - Zero = x
Succ x - Succ y = x - y


length' [] = Zero
length' (x:xs) = Succ (length xs)

null x = length' x == 0

one x = length' x == 1

atLeastFive x = length' x = 5

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


Re: [Haskell-cafe] Collections

2007-06-22 Thread Andrew Coppin

Calvin Smith wrote:

Andrew Coppin wrote:
True enough - but that's a rather specific task. I'm still not seeing 
vast numbers of other uses for this...


You can see lots of applications for graphs at the following page:

http://www.graph-magics.com/practic_use.php


I see a pattern here - these are all the kinds of programs that I'm 
never likely to ever write. Maybe that's the cause? ;-)


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


Re: [Haskell-cafe] Collections

2007-06-22 Thread Dan Piponi

Andrew said:


I see *trees* around the place a lot, but not general graphs.


A link discussing the application of graph theory for each of the
examples I gave. In each case the structure used is not a tree.

http://citeseer.ist.psu.edu/wiberg96codes.html
http://citeseer.ist.psu.edu/context/22137/0
http://en.wikipedia.org/wiki/Bayesian_network
http://www.scl.ameslab.gov/ctpsm07/
http://en.wikipedia.org/wiki/Neural_network
http://en.wikipedia.org/wiki/Dijkstra's_algorithm
http://links.jstor.org/sici?sici=0025-5572(198612)2%3A70%3A454%3C273%3ASBGPAG%3E2.0.CO%3B2-U
http://links.jstor.org/sici?sici=0025-570X(200106)74%3A3%3C234%3AAAOTML%3E2.0.CO%3B2-P
http://bears.ece.ucsb.edu/research-info/DP/dfg.html
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] A probably-stupid question about a Prelude implementation.

2007-06-22 Thread Dan Weston

This is how I think of it:

lazyIntMult :: Int - Int - Int
lazyIntMult 0 _ = 0
lazyIntMult _ 0 = 0
lazyIntMult a b = a * b

*Q 0 * (5 `div` 0)
*** Exception: divide by zero
*Q 0 `lazyIntMult` (5 `div` 0)
0

foldr evaluates a `f` (b `f` (c `f` ...))

Only f knows which arguments are strict and in which order to evaluate 
them. foldr knows nothing about evaluation order.


Dan

Michael T. Richter wrote:
So, I'm now going over the code in the 'Report with a fine-toothed comb 
because a) I'm actually able to read it now pretty fluently and b) I 
want to know what's there in detail for a project I'm starting.  I 
stumbled across this code:


any :: (a - Bool) - [a] - Bool
any p = or . map p

or :: [Bool] - Bool
or = foldr (||) False


Now I see how this works and it's all elegant and clear and all that.  
But I have two nagging problems with it (that are likely related):


   1. Using foldr means I'll be traversing the whole list no matter
  what.  This implies (perhaps for a good reason) that it can only
  work on a finite list.
   2. I don't see any early bale-out semantics.  The way I read this
  it's going to expand a whole list of n and perform n comparisons
  (including the one with the provided False). 



Considering that I only need a single True result to make the whole 
expression true, I'd have expected there to be some clever semantics to 
allow exactly this.  But what I'm seeing, unless I'm really misreading 
the code, is that if I give it a list of a million boolean expressions, 
it will cheerfully evaluate these million boolean expressions and 
perform a million calls to (||) before giving me a result.


Please tell me I'm wrong and that I'm missing something?

--
*Michael T. Richter* [EMAIL PROTECTED] 
mailto:[EMAIL PROTECTED] (*GoogleTalk:* [EMAIL PROTECTED])
/There are two ways of constructing a software design. One way is to 
make it so simple that there are obviously no deficiencies. And the 
other way is to make it so complicated that there are no obvious 
deficiencies. (Charles Hoare)/





___
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[2]: [Haskell-cafe] Haskell version of ray tracer code is much slower than the original ML

2007-06-22 Thread Bulat Ziganshin
Hello Philip,

Friday, June 22, 2007, 7:36:51 PM, you wrote:
 Langauge File Time in seconds
 Haskell  ray.hs   38.2
 OCamlray.ml   23.8 
 g++-4.1  ray.cpp  12.6

can you share sourcecode of this variant? i'm interested to see how
much it is obfuscated

btw, *their* measurement said that ocaml is 7% faster :)

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] A probably-stupid question about a Prelude implementation.

2007-06-22 Thread Bulat Ziganshin
Hello Michael,

Friday, June 22, 2007, 7:31:17 PM, you wrote:

no surprise - you got a lot of answers :)  it is the best part of
Haskell, after all :)

the secret Haskell weapon is lazy evaluation which makes *everything*
short-circuited. just consider standard () definition:

() False _ = False
() True  x = x

this means that as far as first argument of () is False, we don't
even examine second one. and because everything is lazy evaluated,
this second argument passed as non-evaluated *expression*. if we never
examined it, it will be never evaluated:

Prelude True  (0 `div` 00)
*** Exception: divide by zero
Prelude False  (0 `div` 00)
False

in particular, this allows to create your own control structures. and
another example is that you found: infinite list may be processed as
far as you may calculate result using only finite part of list:

Prelude take 10 [1..]
[1,2,3,4,5,6,7,8,9,10]
Prelude and (cycle [True, False])
False

in particular, last example calculated as

True  False  ...

where ... remains uncalculated because we find final answer after
examining second list element. i suggest you to use textual
substitution to see how the last and call are translated into this
sequence of  applications. this substitution is real process of
evaluating haskell code, it is called graph reduction by scientists :)

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


[Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-22 Thread Dave Bayer

Hi all,

I've been going over my code trying to get it all to compile with  
ghc -Wall -Werror, without introducing constructs that would make  
my code the laughing stock of the dynamic typing community. They  
already think we're nuts; my daydreams are of a more computer  
literate society where Jessie Helms stands up in the U.S. Senate to  
read aloud my type declarations to the derisive laughter of the Ruby  
and Lisp parties.


There's a fine line between my opinion as to how GHC should issue  
warnings, and a legitimate bug report. I've already submitted a bug  
report for the need to declare the type of the wildcard pattern,  
because I believe that the case is clear. Here, I'm seeking guidance.  
Perhaps I just don't know the most elegant construct to use?


My sample code is this:



{-# OPTIONS_GHC -Wall -Werror #-}

module Main where

import Prelude hiding ((^))
import qualified Prelude ((^))

default (Int)

infixr 8 ^
(^) :: Num a = a - Int - a
x ^ n = x Prelude.^ n

main :: IO ()
main =
   let r = pi :: Double
   x = r ^ (3 :: Int)
   y = r ^ 3
   z = r Prelude.^ 3
   in  putStrLn $ show (x,y,z)



GHC issues a Warning: Defaulting the following constraint(s) to type  
`Int' for the definition of z.


The definition of y glides through, so a qualified import and  
redefinition of each ambiguous operator does provide a work-around,  
but the code is lame. (I could always encapsulate it in a module  
Qualude.)


If I import a module that I don't use, then ghc -Wall -Werror  
rightly complains. By analogy, if I use default (Int) to ask GHC to  
default to Int but the situation never arises, then GHC should  
rightly complain. Instead, if I use default (Int), GHC complains  
about defaulting anyways. In my opinion, this is a bug, but I'd like  
guidance before reporting it. Is there a more elegant way to handle  
the numeric type classes with ghc -Wall -Werror ?


No one is forced to use ghc -Wall -Werror, but it should be a  
practical choice.


I've enjoyed the recent typing discussions here. On one hand, there's  
little difference between using dynamic typing, and writing  
incomplete patterns in a strongly typed language. On the other hand,  
how is an incomplete pattern any different from code that potentially  
divides by zero? One quickly gets into decidability issues, dependent  
types, Turing-complete type systems.


My personal compromise is to use ghc -Wall -Werror, live with the  
consequences, and get back to work. Perhaps I'll get over it, but  
that's a slippery slope back to Lisp.


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


Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-22 Thread David Roundy
On Fri, Jun 22, 2007 at 11:37:15AM -0700, Dave Bayer wrote:
 GHC issues a Warning: Defaulting the following constraint(s) to type  
 `Int' for the definition of z.

Why don't you just use -fno-warn-type-defaults? Warnings are just that:
warnings.  If you believe the defaulting matches what you want to do, then
you don't need the warning.

ghc -Werr -Wall is a often good idea, but if you prefer a different
programming style (e.g. no top-level type declarations required), ghc gives
you the flexibility to do that.
-- 
David Roundy
Department of Physics
Oregon State University
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell version of ray tracer code is much slower than the original ML

2007-06-22 Thread Philip Armstrong

On Fri, Jun 22, 2007 at 10:11:27PM +0400, Bulat Ziganshin wrote:

Friday, June 22, 2007, 7:36:51 PM, you wrote:

Langauge File Time in seconds
Haskell  ray.hs   38.2
OCamlray.ml   23.8 
g++-4.1  ray.cpp  12.6


can you share sourcecode of this variant? i'm interested to see how
much it is obfuscated


http://www.kantaka.co.uk/darcs/ray

The cpp  ml versions are precisely those available from the download
links on http://www.ffconsultancy.com/languages/ray_tracer/comparison.html

The optimisation options I used can be seen in the makefile.


btw, *their* measurement said that ocaml is 7% faster :)


Indeed. The gcc-4.0 compilied binary runs at about 15s IIRC, but it's
still much better than 7% faster than the ocaml binary.

cheers, Phil

--
http://www.kantaka.co.uk/ .oOo. public key: http://www.kantaka.co.uk/gpg.txt
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] A probably-stupid question about a Prelude implementation.

2007-06-22 Thread Andrew Coppin

Chris Kuklewicz wrote:

Specifically it is graph reduced like this:

or [F,T,F,F...]

foldr (||) F [F,T,F,F...]

F || foldr (||) F [T,F,F...]

foldr (||) F [T,F,F...]

T || foldr (||) F [F,F...]

T

The last line is because (T || _ = T) and lazyness


I must sheepishly confess that I mistakenly throught that foldr would 
construct a chaint chain of ORs, which would then only be evaluated when 
it's returned.


Now I see why there's a strict version of foldl but *not* foldr... ;-)

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


Re: [Haskell-cafe] Re: Collections

2007-06-22 Thread Duncan Coutts
On Fri, 2007-06-22 at 15:34 +1000, Thomas Conway wrote:
 On 6/22/07, Duncan Coutts [EMAIL PROTECTED] wrote:
  You might find that lazy IO is helpful in this case. The primitive that
  implements lazy IO is unsafeInterleaveIO :: IO a - IO a
 
 Personally, unsafeInterleaveIO is so horribly evil, that even just
 having typed the name, I'll have to put the keyboard through the
 dishwasher (see http://www.coudal.com/keywasher.php). Also, I need to
 support concurrent querying and updates, and trying to manage the
 locking is quite hard enough as it is, without trying to keep track of
 which postings vectors have closures pointing to them!

Ah yes, fair enough. If you're doing updates at the same time then lazy
IO isn't appropriate as you need control over when the IO happens.

Duncan

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


Re: Re[4]: [Haskell-cafe] haskell crypto is reaaaaaaaaaally slow

2007-06-22 Thread Duncan Coutts
On Fri, 2007-06-22 at 10:52 +0400, Bulat Ziganshin wrote:

  i tried it once and found that ByteArray# size is returned rounded to 4 -
  there is no way in GHC runtime to alloc, say, exactly 37 bytes. and
  don't forget to add 2 unused bytes at average
 
  Right, GHC heap object are always aligned to the natural alignment of
  the architecture, be that 4 or 8 bytes.

 that i'm trying to say is that one need to store exact string size
 because value returned by getSizeOfByteArray is aligned to 4


Ah yes, you're quite right. To allow GHC's ByteArray# to be used to
implement a compact string type it'd have to be changed to store the
length in bytes rather than words.

Duncan

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


Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-22 Thread Dave Bayer

On Jun 22, 2007, at 11:42 AM, David Roundy wrote:


On Fri, Jun 22, 2007 at 11:37:15AM -0700, Dave Bayer wrote:

GHC issues a Warning: Defaulting the following constraint(s) to type
`Int' for the definition of z.


Why don't you just use -fno-warn-type-defaults?

...

ghc -Werr -Wall is a often good idea, but if you prefer a different
programming style (e.g. no top-level type declarations required),  
ghc gives

you the flexibility to do that.


To be precise, I __PREFER__ a ghc  -Wall -Werror programming style.  
In particular, I always want defaulting errors, because sometimes I  
miss the fact that numbers I can count on my fingers are defaulting  
to Integer.


Once I explicitly declare default (Int), I want ghc  -Wall - 
Werror to shut up, unless this defaulting rule never gets used.  
Instead, it complains anyways when the defaulting takes place that  
I've just declared I know about. In other words, I want warnings  
involving default to follow the same logic currently used for  
warnings involving import.


This is a bug. I want ghc  -Wall -Werror to be a practical choice,  
left on all the time, and in my example I had to work too hard to  
avoid the warning. Other people just wouldn't use ghc  -Wall - 
Werror, the way some people won't use seat belts, and the way some  
people view any strongly typed language as a cumbersome seat belt. If  
we tolerate ridiculously arcane syntax to handle these situations, we  
fully deserve to be marginalized while Ruby takes over the world.


In other words, I'm disputing that the top-level declarations are in  
fact required. GHC can be trivially modified to allow Haskell to  
handle this situation far more elegantly.


(It is amusing the sides we're taking on this, and the stereotype  
that physicists compute faster than mathematicians because they don't  
worry about convergence issues. Effectively, the stereotype holds  
that mathematicians think with -Wall -Werror on, and physicists  
don't. Perhaps it's true?)



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


Re: [Haskell-cafe] A probably-stupid question about a Prelude implementation.

2007-06-22 Thread Andrew Coppin

Bulat Ziganshin wrote:

no surprise - you got a lot of answers :)  it is the best part of
Haskell, after all :)
  


Only if you ask easy questions. ;-)


the secret Haskell weapon is lazy evaluation which makes *everything*
short-circuited. just consider standard () definition:
  


Again, only if you Do It Right(tm). But fortunately, that's not usually 
difficult... :-D


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


Re: [Haskell-cafe] Lambdabot

2007-06-22 Thread Derek Elkins
On Fri, 2007-06-22 at 20:10 +0200, Daniel Fischer wrote:

[blah blah blah]

 Finally, is there a tutorial/manual for using lambdabot?

Um... #haskell...

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


[Haskell-cafe] directory tree?

2007-06-22 Thread Chad Scherrer

Haskell is great at manipulating tree structures, but I can't seem to
find anything representing a directory tree. A simple representation
would be something like this:

data Dir = Dir {dirName :: String, subDirectories :: [Dir], files :: [File]}
data File = File {fileName :: String, fileSize :: Int}

Maybe these would need to be parametrized to allow a function
splitting files by extension or that kind of thing. Anyway, the whole
idea would be to abstract as much of the file stuff out of the IO
monad as possible.

I haven't used the Scrap Your Boilerplate stuff yet, but it seems
like that could fit in here naturally to traverse a Dir and make
changes at specified points.

The only problem I can see (so far) with the approach is that it might
make big changes to the directory tree too easy to make. I'm not
sure immediately how to deal with that, or if the answer is just to
post a be careful disclaimer.

So, what do you think? Do you know of any work in this direction? Is
there a way to make dangerous 1-liners safe? Is there a fundamental
flaw with the approach I'm missing?

Thanks much,

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


[Haskell-cafe] Need for speed: the Burrows-Wheeler Transform

2007-06-22 Thread Andrew Coppin
OK, so I *started* writing a request for help, but... well I answered my 
own question! See the bottom...





I was reading Wikipedia, and I found this:

 http://en.wikipedia.org/wiki/Burrows-Wheeler_transform

I decided to sit down and see what that looks like in Haskell. I came up 
with this:




module BWT where

import Data.List

rotate1 :: [x] - [x]
rotate1 [] = []
rotate1 xs = last xs : init xs

rotate :: [x] - [[x]]
rotate xs = take (length xs) (iterate rotate1 xs)

bwt :: (Ord x) = [x] - [x]
bwt = map last . sort . rotate


step :: (Ord x) = [x] - [[x]] - [[x]]
step xs = zipWith (:) xs . sort

inv_bwt :: (Ord x) = x - [x] - [x]
inv_bwt mark xs =
 head . filter (\xs - head xs == mark) .
 head . drop ((length xs) - 1) . iterate (step xs) .
 map (\x - [x]) $ xs



My my, isn't that SO much shorter? I love Haskell! :-D

Unfortunately, the resident C++ expert fails to grasp the concept of 
example code, and insists on comparing the efficiency of this program 
to the C one on the website.


Fact is, he's translated the presented C into C++, and it can apparently 
transform a 145 KB file in 8 seconds using only 3 MB of RAM. The code 
above, however, took about 11 seconds to transform 4 KB of text, and 
that required about 60 MB of RAM. (I tried larger, but the OS killed the 
process for comsuming too much RAM.)


Well anyway, the code was written for simplicity, not efficiency. I've 
tried to explain this, but apparently that is beyond his comprehension. 
So anyway, it looks like we have a race on. :-D


The first thing I did was the optimisation mentioned on Wikipedia: you 
don't *need* to build a list of lists. You can just throw pointers 
around. So I arrived at this:




module BWT2 (bwt) where

import Data.List

rotate :: Int - [x] - Int - [x]
rotate l xs n = (drop (l-n) xs) ++ (take (l-n) xs)

bwt xs =
 let l  = length xs
 ys = rotate l xs
 in  map (last . rotate l xs) $
 sortBy (\n m - compare (ys n) (ys m)) [0..(l-1)]


This is indeed *much* faster. With this, I can transform 52 KB of text 
in 9 minutes + 60 MB RAM. The previous version seemed to have quadratic 
memory usage, whereas this one seems to be linear. 52 KB would have 
taken many months with the first version!


Still, 9 minutes (for a file 3 times smaller) is nowhere near 8 seconds. 
So we must try harder... For my next trick, ByteStrings! (Never used 
them before BTW... this is my first try!)



module BWT3 (bwt) where

import Data.List
import qualified Data.ByteString as Raw

rotate :: Int - Raw.ByteString - Int - Raw.ByteString
rotate l xs n = (Raw.drop (l-n) xs) `Raw.append` (Raw.take (l-n) xs)

bwt xs =
 let l  = Raw.length xs
 ys = rotate l xs
 in  Raw.pack $
 map (Raw.last . rotate l xs) $
 sortBy (\n m - compare (ys n) (ys m)) [0..(l-1)]


Now I can transform 52 KB in 54 seconds + 30 MB RAM. Still nowhere near 
C++, but a big improvement none the less.


Woah... What the hell? I just switched to Data.ByteString.Lazy and WHAM! 
Vast speed increases... Jeepers, I can transform 52 KB so fast I can't 
even get to Task Manager fast enough to *check* the RAM usage! Blimey...


OK, just tried the 145 KB test file that Mr C++ used. That took 2 
seconds + 43 MB RAM. Ouch.


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


Re: [Haskell-cafe] A probably-stupid question about a Prelude implementation.

2007-06-22 Thread Jan-Willem Maessen


On Jun 22, 2007, at 2:30 PM, Dan Weston wrote:


This is how I think of it:

lazyIntMult :: Int - Int - Int
lazyIntMult 0 _ = 0
lazyIntMult _ 0 = 0
lazyIntMult a b = a * b

*Q 0 * (5 `div` 0)
*** Exception: divide by zero
*Q 0 `lazyIntMult` (5 `div` 0)
0

foldr evaluates a `f` (b `f` (c `f` ...))

Only f knows which arguments are strict and in which order to  
evaluate them. foldr knows nothing about evaluation order.


And, indeed, if you foldr a function with left zeroes, and you check  
for them explicitly as lazyIntMult and (||) do, then foldr is  
guaranteed to terminate early if it finds a zero.


z is a left zero of op if for all x, z `op` x = z.

This isn't the only time foldr will terminate early, but it is an  
important one.


-Jan-Willem Maessen



Dan




smime.p7s
Description: S/MIME cryptographic signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Lambdabot

2007-06-22 Thread Daniel Fischer
I can partially answer my questions.
Removing also Seen does away with the ByteString.index error.
Must check the code to see why.

Two more concrete questions
a) how do I gracefully leave lambdabot?
ctrl-C or killing it from another shell are the only ways out I found so far.
b) what does lambdabot expect in the fptools directory?

Cheers,
Daniel

Am Freitag, 22. Juni 2007 20:10 schrieb ich:
 Greetings,
 lambdabot segfaulted when installing
 Fact
 Haddock
 Quote
 Source
 Todo
 Where

 What's special about them?
 I.e., why did they cause a segfault and the others not?

 And, how could I build a lambdabot _with_ them (though I'm not sure, I'll
 actually want them, but I might).

 Without these, I now have an apparently working lambdabot, well, not
 properly working.
 First time I started it, all seemed well, but from then on:
 $ ./lambdabot
 Initialising plugins ..sending message to
 bogus server: IrcMessage {msgServer = freenode, msgLBName =
 urk!outputmessage, msgPrefix = , msgCommand = NAMES, msgParams =
 []}
 ... done.
 Main: caught (and ignoring) IRCRaised Data.ByteString.index: index too
 large: 0, length = 0
 lambdabot  3+7
 Main: caught (and ignoring) IRCRaised Data.ByteString.index: index too
 large: 0, length = 0
  10
 lambdabot

 The bogus message thing also appeared the first time, I hope this is meant
 to be so.
 But what about the ByteString.index exception?
 Where might that come from?
 How to get rid of it?

 Finally, is there a tutorial/manual for using lambdabot?

 Thanks for any help,
 Daniel

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


Re: [Haskell-cafe] Re: Lambdabot

2007-06-22 Thread Stefan O'Rear
On Fri, Jun 22, 2007 at 10:37:55PM +0200, Daniel Fischer wrote:
 I can partially answer my questions.
 Removing also Seen does away with the ByteString.index error.
 Must check the code to see why.
 
 Two more concrete questions
 a) how do I gracefully leave lambdabot?
 ctrl-C or killing it from another shell are the only ways out I found so far.

quit

 b) what does lambdabot expect in the fptools directory?

Absolutely nothing.  It's dead code.

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


Re: [Haskell-cafe] directory tree?

2007-06-22 Thread Jeremy Shaw
Hello,

Have you seen Tom Moertel's series on directory-tree printing in Haskell ?

http://blog.moertel.com/articles/2007/03/28/directory-tree-printing-in-haskell-part-three-lazy-i-o

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


Re: [Haskell-cafe] directory tree?

2007-06-22 Thread David Roundy
On Fri, Jun 22, 2007 at 01:19:01PM -0700, Chad Scherrer wrote:
 Haskell is great at manipulating tree structures, but I can't seem to
 find anything representing a directory tree. A simple representation
 would be something like this:
 
 data Dir = Dir {dirName :: String, subDirectories :: [Dir], files :: [File]}
 data File = File {fileName :: String, fileSize :: Int}
 
 Maybe these would need to be parametrized to allow a function
 splitting files by extension or that kind of thing. Anyway, the whole
 idea would be to abstract as much of the file stuff out of the IO
 monad as possible.
 
 I haven't used the Scrap Your Boilerplate stuff yet, but it seems
 like that could fit in here naturally to traverse a Dir and make
 changes at specified points.
 
 The only problem I can see (so far) with the approach is that it might
 make big changes to the directory tree too easy to make. I'm not
 sure immediately how to deal with that, or if the answer is just to
 post a be careful disclaimer.
 
 So, what do you think? Do you know of any work in this direction? Is
 there a way to make dangerous 1-liners safe? Is there a fundamental
 flaw with the approach I'm missing?

Darcs does this sort of thing (see SlurpDirectory.lhs in the source code),
which can be pretty nice, but you really only want to use it for read-only
purposes.  Early versions of darcs made modifications directly to Slurpies
(these directory tree data structures), which kept track of what changes
had been made, and then there was a write modifications IO functions that
actually made the changes.  But this was terribly fragile, since ordering
of changes had to be kept track of, etc.  The theory was nice, that we'd be
able to make the actual changes all at once (only write once to each file,
for example, each file had a dirty bit), but in practice we kept running
into trouble.  So now we just use this for read-only purposes, for which it
works fine, although it still can be scary, if users modify the directories
while we're looking at them (but this is scary regardless...).

Nowadays we've got a (moderately) nice little monad DarcsIO, which allows
us to do file/directory IO operations on either Slurpies or disk, or
various other sorts of virtualized objects.  Someday I'd like to write an
industrial strength version of this monad (which addresses more than just
darcs' needs).
-- 
David Roundy
Department of Physics
Oregon State University
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Need for speed: the Burrows-Wheeler Transform

2007-06-22 Thread Stefan O'Rear
On Fri, Jun 22, 2007 at 09:26:40PM +0100, Andrew Coppin wrote:
 OK, so I *started* writing a request for help, but... well I answered my 
 own question! See the bottom...
...
 Unfortunately, the resident C++ expert fails to grasp the concept of 
 example code, and insists on comparing the efficiency of this program 
 to the C one on the website.
...
 Fact is, he's translated the presented C into C++, and it can apparently 
 transform a 145 KB file in 8 seconds using only 3 MB of RAM. The code 
...
 Woah... What the hell? I just switched to Data.ByteString.Lazy and WHAM! 
 Vast speed increases... Jeepers, I can transform 52 KB so fast I can't 
 even get to Task Manager fast enough to *check* the RAM usage! Blimey...
 
 OK, just tried the 145 KB test file that Mr C++ used. That took 2 
 seconds + 43 MB RAM. Ouch.

Mr. C++ apparently isn't a very good C++ programmer, since his best
effort absolutely *pales* in comparison to Julian Seward's BWT:

[EMAIL PROTECTED]:/usr/local/src/hpaste$ head -c 135000 /usr/share/dict/words | 
(time bzip2 -vvv)  /dev/null
  (stdin): 
block 1: crc = 0x25a18961, combined CRC = 0x25a18961, size = 135000
  0 work, 135000 block, ratio  0.00
  135000 in block, 107256 after MTF  1-2 coding, 61+2 syms in use
  initial group 6, [0 .. 0], has 20930 syms (19.5%)
  initial group 5, [1 .. 1], has 4949 syms ( 4.6%)
  initial group 4, [2 .. 2], has 20579 syms (19.2%)
  initial group 3, [3 .. 4], has 17301 syms (16.1%)
  initial group 2, [5 .. 10], has 24247 syms (22.6%)
  initial group 1, [11 .. 62], has 19250 syms (17.9%)
  pass 1: size is 127140, grp uses are 339 550 192 440 12 613 
  pass 2: size is 51693, grp uses are 321 440 288 316 139 642 
  pass 3: size is 51358, grp uses are 329 387 376 304 122 628 
  pass 4: size is 51302, grp uses are 298 421 397 304 125 601 
  bytes: mapping 21, selectors 433, code lengths 110, codes 51297
final combined CRC = 0x25a18961
2.602:1,  3.075 bits/byte, 61.57% saved, 135000 in, 51887 out.

real0m0.165s
user0m0.044s
sys 0m0.012s


Yup, does slightly more work (huffman coding) in 1/200 the time :)

(Note, on my system .Lazy BWT3 takes 5.3s on the same input)

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


Re: [Haskell-cafe] Need for speed: the Burrows-Wheeler Transform

2007-06-22 Thread David Roundy
On Fri, Jun 22, 2007 at 09:26:40PM +0100, Andrew Coppin wrote:
 OK, so I *started* writing a request for help, but... well I answered my 
 own question! See the bottom...

...

 module BWT3 (bwt) where
 
 import Data.List
 import qualified Data.ByteString as Raw
 
 rotate :: Int - Raw.ByteString - Int - Raw.ByteString
 rotate l xs n = (Raw.drop (l-n) xs) `Raw.append` (Raw.take (l-n) xs)
 
 bwt xs =
  let l  = Raw.length xs
  ys = rotate l xs
  in  Raw.pack $
  map (Raw.last . rotate l xs) $
  sortBy (\n m - compare (ys n) (ys m)) [0..(l-1)]
 
 
 Now I can transform 52 KB in 54 seconds + 30 MB RAM. Still nowhere near 
 C++, but a big improvement none the less.

The trouble is that Raw.append is an O(N) operation, making the computation
O(N^2) where it ought to be O(NlogN).

 Woah... What the hell? I just switched to Data.ByteString.Lazy and WHAM! 
 Vast speed increases... Jeepers, I can transform 52 KB so fast I can't 
 even get to Task Manager fast enough to *check* the RAM usage! Blimey...
 
 OK, just tried the 145 KB test file that Mr C++ used. That took 2 
 seconds + 43 MB RAM. Ouch.

In this case append is an O(1) operation.  But you're still getting killed
on prefactors, because you're generating a list of size N and then sorting
it.  Lists are just not nice data structures to sort, nor are they nice to
have for large N.

To get better speed and memory use, I think you'd want to avoid the
intermediate list in favor of some sort of strict array, but that'd be
ugly.
-- 
David Roundy
Department of Physics
Oregon State University
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Compile-time here document facility

2007-06-22 Thread Dave Bayer
I couldn't find a compile-time here document facility, so I wrote one  
using Template Haskell:



module HereDocs(hereDocs) where

import Control.Exception
import Language.Haskell.TH.Syntax

getDoc :: String - [String] - (String,[String])
getDoc eof txt =
let (doc,rest) = break (== eof) txt
in  (unlines doc, drop 1 rest)

makeVal :: String - String - [Dec]
makeVal var doc = let name = mkName var in
[SigD name (ConT (mkName String)),
ValD (VarP name) (NormalB (LitE (StringL doc))) []]

scanSrc :: [Dec] - [String] - Q [Dec]
scanSrc vals [] = return vals
scanSrc vals (x:xs) = case words x of
[var, =, ('':'':eof)] -
let (doc,rest) = getDoc eof xs
val = makeVal var doc
in  scanSrc (vals ++ val) rest
_ - scanSrc vals xs

hereDocs :: FilePath - Q [Dec]
hereDocs src =
let fin = catchJust assertions (evaluate src) (return.takeWhile  
(/= ':'))

in  runIO (fin = readFile = return . lines) = scanSrc []


One binds here documents embedded in comments by writing


import HereDocs
$(hereDocs Main.hs)


As an idiom, one can refer to the current file as follows; the first  
thing hereDocs does is catch assert errors in order to learn the file  
name:



import HereDocs
$(hereDocs $ assert False )


Here is an example use:


{-# OPTIONS_GHC -fth -Wall -Werror #-}

module Main where

import System
import Control.Exception

import HereDocs
$(hereDocs $ assert False )

{-
ruby = RUBY
#!/usr/bin/env ruby
hello = EOF
Ruby is not
   an acceptable Lisp
EOF
puts hello
RUBY

lisp = LISP
#!/usr/bin/env mzscheme -qr
(display #EOF
Lisp is not
   an acceptable Haskell
EOF
)
(newline)
LISP
-}

exec :: FilePath - String - IO ExitCode
exec fout str = do
   writeFile fout str
   system (chmod +x  ++ fout ++ ; ./ ++ fout)

main :: IO ExitCode
main = do
   exec hello.rb ruby
   exec hello.scm lisp



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


Re: [Haskell-cafe] directory tree?

2007-06-22 Thread Chad Scherrer

On 6/22/07, Jeremy Shaw [EMAIL PROTECTED] wrote:

Hello,

Have you seen Tom Moertel's series on directory-tree printing in Haskell ?


No, I hadn't. Might be just the ticket. Thanks!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Need for speed: the Burrows-Wheeler Transform

2007-06-22 Thread Philippa Cowderoy
On Fri, 22 Jun 2007, Andrew Coppin wrote:

 Woah... What the hell? I just switched to Data.ByteString.Lazy and WHAM! Vast
 speed increases... Jeepers, I can transform 52 KB so fast I can't even get to
 Task Manager fast enough to *check* the RAM usage! Blimey...
 
 OK, just tried the 145 KB test file that Mr C++ used. That took 2 seconds + 43
 MB RAM. Ouch.
 

A note re RAM usage: it behaves differently in a GCed environment, you 
might want to see if it runs with a smaller max heap size. Obviously 
you'll spend more time GCing.

-- 
[EMAIL PROTECTED]

My religion says so explains your beliefs. But it doesn't explain
why I should hold them as well, let alone be restricted by them.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-22 Thread David Roundy
On Fri, Jun 22, 2007 at 12:34:09PM -0700, Dave Bayer wrote:
 On Jun 22, 2007, at 11:42 AM, David Roundy wrote:
 
 On Fri, Jun 22, 2007 at 11:37:15AM -0700, Dave Bayer wrote:
 GHC issues a Warning: Defaulting the following constraint(s) to type
 `Int' for the definition of z.
 
 Why don't you just use -fno-warn-type-defaults?
 ...
 ghc -Werr -Wall is a often good idea, but if you prefer a different
 programming style (e.g. no top-level type declarations required),  
 ghc gives
 you the flexibility to do that.
 
 To be precise, I __PREFER__ a ghc  -Wall -Werror programming style.  
 In particular, I always want defaulting errors, because sometimes I  
 miss the fact that numbers I can count on my fingers are defaulting  
 to Integer.
 
 Once I explicitly declare default (Int), I want ghc  -Wall - 
 Werror to shut up, unless this defaulting rule never gets used.  
 Instead, it complains anyways when the defaulting takes place that  
 I've just declared I know about. In other words, I want warnings  
 involving default to follow the same logic currently used for  
 warnings involving import.

I see, that makes sense.  And I have no idea that would help you.

 This is a bug. I want ghc  -Wall -Werror to be a practical choice,  
 left on all the time, and in my example I had to work too hard to  
 avoid the warning. Other people just wouldn't use ghc  -Wall - 
 Werror, the way some people won't use seat belts, and the way some  
 people view any strongly typed language as a cumbersome seat belt. If  
 we tolerate ridiculously arcane syntax to handle these situations, we  
 fully deserve to be marginalized while Ruby takes over the world.
 
 In other words, I'm disputing that the top-level declarations are in  
 fact required. GHC can be trivially modified to allow Haskell to  
 handle this situation far more elegantly.

I think of top-level type declarations as type-checked comments, rather
than a seat-belt.  It forces you to communicate to others what a function
does, if that function may be used elsewhere.  I like this.  Although it can
be cumbersome for quick and dirty code, developers trying to read your code
will thank you for it (unless you make *everything* top-level, which is
just poor coding style).

-Wall -Werror isn't a seat belt, it's a coding-style guideline.
-- 
David Roundy
Department of Physics
Oregon State University
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] directory tree?

2007-06-22 Thread Greg Fitzgerald

Chad,


I can't seem to find anything representing a directory tree


Here's my shot.  http://hpaste.org/370

Not much different than Tom Moertel's, but grabs the fileSize along the way.


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


Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-22 Thread Dave Bayer

On Jun 22, 2007, at 2:46 PM, David Roundy wrote:

I think of top-level type declarations as type-checked comments,  
rather
than a seat-belt.  It forces you to communicate to others what a  
function
does, if that function may be used elsewhere.  I like this.   
Although it can
be cumbersome for quick and dirty code, developers trying to read  
your code
will thank you for it (unless you make *everything* top-level,  
which is

just poor coding style).

-Wall -Werror isn't a seat belt, it's a coding-style guideline.


I don't think one can make blanket statements as to what type systems  
are for. I doubt that the people who've dedicated their lives to  
type theory are doing so to provide style guidelines.


I like the quick and open-ended definition that types are compile- 
time proxies for run-time values. It happens that current type  
systems are closely tied to propositional logic, because so many  
logicians are drawn to the work. This need not be the case.


From this point of view, one pays attention to type theory because  
one produces the best code by providing the best guidance to the  
compiler. -Wall -Werror is establishing a contract to do so.


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


Re: [Haskell-cafe] Shouldn't this be lazy???

2007-06-22 Thread Henning Thielemann

On Fri, 22 Jun 2007, Olivier Boudry wrote:

 -- | create sections from tag type and attribute
 getSectionsByTypeAndAttr :: String - (String, String) - String - IO [[Tag]]
 getSectionsByTypeAndAttr tagType attr url = do
 tags - unsafeInterleaveIO $ liftM parseTags $ openURL $ url
 (return . filterByTypeAndAttr tagType attr) tags
   where
 filterByTypeAndAttr :: String - (String, String) - [Tag] - [[Tag]]
 filterByTypeAndAttr t a = sections (~== TagOpen t [a])

I think if openURL is not lazy, then the unsafeInterleaveIO will not help
much because it only defers the whole computation until the first part of
the result is requested. One call to unsafeInterleaveIO cannot divide a
big IO action into small pieces of lazily triggered actions. I think
unsafeInterleaveIO is unnecessary here.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] copy-on-write monad?

2007-06-22 Thread Greg Meredith

Fellow Functionally-Caffeinated,

i have a few questions regarding copy-on-write semantics. i am working for a
client that is stuck with a legacy in-house language that chose
copy-on-write as a way to provide aliasing-issue-free semantics to a user
population they perceived as not sophisticated in programming. Despite the
fact that they are now realizing there are a lot of very sophisticated and
performant ways of providing ways to avoid aliasing problems, they are stuck
having to support copy-on-write for legacy codes.

So, i have two basic questions. First, has anyone worked out a monadic
approach to copy-on-write? (And, Is there any analysis of perf
characteristics of said monadic schemes?)

Second, i have worked out a scheme which is like a version control system.
The mutable collection is treated like a source tree. A reference to a
mutable collection is like a tag for a branch of the tree. Updates attach
deltas to a given branch of the tree. Accesses have to be matched to see if
they are impacted by any update-deltas. There is an
optimization/memo-ization strategy in which certain events (access or
update) trigger a copy to be made, finally, and the updates applied to the
copy. This shifts perf characteristics so that access becomes slower and
update considerably faster in the common case. Does anyone know if such a
scheme has been studied? i'd like to compare implementations, too, if
possible.

Best wishes,

--greg

--
L.G. Meredith
Managing Partner
Biosimilarity LLC
505 N 72nd St
Seattle, WA 98103

+1 206.650.3740

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


Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-22 Thread Brandon S. Allbery KF8NH


On Jun 22, 2007, at 17:46 , David Roundy wrote:


-Wall -Werror isn't a seat belt, it's a coding-style guideline.


So, as long as we're on this topic...

I have a program which I'm checking with -Wall but not -Werror,  
because it has several pattern matches which *I* know are fine but  
which ghc doesn't.  (I suspect, from its description, that Catch  
would also recognize it's fine.)  Which leads me to wonder:


(1) any way to flag a pattern match as I know this is okay, don't  
warn about it without shutting off pattern match warnings completely?


(2) any way that, given the need to roll a bunch of records into a  
single type, I can somehow declare things such that calling one of  
these functions that expects only a single component record type with  
a different record type raises a *compile-time* error?  (That is,  
roughly the opposite of the usual pattern match error behavior.)   
Unfortunately I can't split the records into independent types  
because the full record type controls a state machine and different  
states require different components, and I can't use a typeclass to  
do it because you can't declare a list of a typeclass (VRow r) =  
[r].  (Yes, this may become an array later, but it's only 25 or so  
entries.)


The special cases are where I'm asking the state machine to do  
lookups from files that are actually things like DNS lookups.  Some  
of these are passed file-based lookups in order to modify the DNS  
lookup's result (domain stripping, for example) and these will (a)  
never be invoked with a lookup type other than VDNS and (b) never be  
handed a VProcess-based VLookup or a VDNS as the modifier.


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


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


Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-22 Thread Stefan O'Rear
On Fri, Jun 22, 2007 at 06:11:24PM -0400, Brandon S. Allbery KF8NH wrote:
 (1) any way to flag a pattern match as I know this is okay, don't  
 warn about it without shutting off pattern match warnings completely?


case scrutinee of
  Pattern - alternative
  Pattern - alternative
  _ - error Can't happen in functionname

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


Re: [Haskell-cafe] directory tree?

2007-06-22 Thread Chad Scherrer

Nice, thanks! Certainly looks like a good start at this.

What got me thinking about this is I'd like to be able to do something
like this in just a couple lines of code:

gunzip -c ./2*/*.z

... and feed the result into a giant lazy ByteString. Now, the UNIX
command doesn't really cut it, because it complains there are too many
files, but its simplicity still makes the IO monad solution feel
clunky by comparison.

Chad

On 6/22/07, Greg Fitzgerald [EMAIL PROTECTED] wrote:

Here's my shot.  http://hpaste.org/370
Not much different than Tom Moertel's, but grabs the fileSize along the way.
-Greg

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


Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-22 Thread Dave Bayer

On Jun 22, 2007, at 12:34 PM, Dave Bayer wrote:

In particular, I always want defaulting errors, because sometimes I  
miss the fact that numbers I can count on my fingers are defaulting  
to Integer.


So no one took the bait to actually offer me a shorter idiom, but I  
thought about the above sentence, and had a big Homer Simpson Doh!  
revelation. In the acual code I was cleaning up, just write out the  
exponentiations, for example,



evalBezier :: R - Bezier - [R]
evalBezier t b = let s = 1-t in case b of
Line x y - s*.x .+. t*.y
Cubic w x y z - s*s*s*.w .+. 3*s*s*t*.x .+. 3*s*t*t*.y .+.  
t*t*t*.z


To my taste, that's much prettier than half a dozen lines of  
declarations to get ^ to behave with ghc -Wall -Werror, and after all  
I'm just hand-unrolling the code for ^.

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


Re: [Haskell-cafe] Odd lack of laziness

2007-06-22 Thread Henning Thielemann

On Fri, 22 Jun 2007, Stefan O'Rear wrote:

 length' [] = Zero
 length' (x:xs) = Succ (length xs)

also known as Data.List.genericLength. :-)

See also
  http://darcs.haskell.org/htam/src/Number/PeanoNumber.hs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-22 Thread Henning Thielemann

On Fri, 22 Jun 2007, Brandon S. Allbery KF8NH wrote:

 I have a program which I'm checking with -Wall but not -Werror,
 because it has several pattern matches which *I* know are fine but
 which ghc doesn't.  (I suspect, from its description, that Catch
 would also recognize it's fine.)  Which leads me to wonder:

 (1) any way to flag a pattern match as I know this is okay, don't
 warn about it without shutting off pattern match warnings completely?

Add the catch all case with '_':

f _ = error this case cannot occur, because this would violate the invariant X

If the error occurs anyway, you get a report that your believe was wrong.
(Or the user gets the report, and he doesn't know how to react.)

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


Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-22 Thread Henning Thielemann

On Fri, 22 Jun 2007, Dave Bayer wrote:

 If I import a module that I don't use, then ghc -Wall -Werror
 rightly complains. By analogy, if I use default (Int) to ask GHC to
 default to Int but the situation never arises, then GHC should
 rightly complain. Instead, if I use default (Int), GHC complains
 about defaulting anyways. In my opinion, this is a bug, but I'd like
 guidance before reporting it. Is there a more elegant way to handle
 the numeric type classes with ghc -Wall -Werror ?

My understanding of defaulting is that it is bad style to rely on it. It
is mostly needed for working in GHCi.

For the particular exponentiation issue, I found the following: The
overwhelming part of constant exponents of (^) in my modules is 2. The
defaulting is mostly relevant for number literals, whereas variables get
their types from somewhere else. So you may consider implementing a 'sqr'
function for squaring values.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-22 Thread Derek Elkins
On Sat, 2007-06-23 at 00:29 +0200, Henning Thielemann wrote:
 On Fri, 22 Jun 2007, Brandon S. Allbery KF8NH wrote:
 
  I have a program which I'm checking with -Wall but not -Werror,
  because it has several pattern matches which *I* know are fine but
  which ghc doesn't.  (I suspect, from its description, that Catch
  would also recognize it's fine.)  Which leads me to wonder:
 
  (1) any way to flag a pattern match as I know this is okay, don't
  warn about it without shutting off pattern match warnings completely?
 
 Add the catch all case with '_':
 
 f _ = error this case cannot occur, because this would violate the invariant 
 X
 
 If the error occurs anyway, you get a report that your believe was wrong.
 (Or the user gets the report, and he doesn't know how to react.)

Sure he does.  Irately tell you that your program doesn't work and then,
upon repeated prompting and guidance, provide you with said error
message. 

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


Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-22 Thread Brandon S. Allbery KF8NH


On Jun 22, 2007, at 18:29 , Henning Thielemann wrote:

If the error occurs anyway, you get a report that your believe was  
wrong.

(Or the user gets the report, and he doesn't know how to react.)


Well, that's why I included the other leg, where I'd like the  
compiler to catch me at compile time if I set up a situation where it  
might occur --- because ideally that case can't happen at run time,  
but if I set up the types that way then I can't build the state  
machine because it's a polymorphic list.  (And no, I don't think  
HList is the right answer here.)


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


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


Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-22 Thread David Roundy
On Fri, Jun 22, 2007 at 03:07:59PM -0700, Dave Bayer wrote:
 On Jun 22, 2007, at 2:46 PM, David Roundy wrote:
 I think of top-level type declarations as type-checked comments, rather
 than a seat-belt.  It forces you to communicate to others what a
 function does, if that function may be used elsewhere.  I like this.
 Although it can be cumbersome for quick and dirty code, developers
 trying to read your code will thank you for it (unless you make
 *everything* top-level, which is just poor coding style).
 
 -Wall -Werror isn't a seat belt, it's a coding-style guideline.
 
 I don't think one can make blanket statements as to what type systems  
 are for. I doubt that the people who've dedicated their lives to  
 type theory are doing so to provide style guidelines.

-Wall doesn't flag type errors, and really has little to do with type
systems.  It's a set of heuristics describing for what someone considers
poor programming practices.

I agree that type systems are much more than that, that wasn't what (I
thought) we were talking about.  You get strongly-typed code whether or not
you enable warnings.

And regarding my above statement about top-level type declarations, that's
about the declarations, not the type system.  They have no effect on the
code that's generated (except in occasional rare cases, where they allow
the compiler to do more optimizations), but they do allow you to get better
error messages, and they communicate your intent to code readers.  I see
the latter as the better reason to always include top-level type
declarations.
-- 
David Roundy
Department of Physics
Oregon State University
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell version of ray tracer code is much slowerthan the original ML

2007-06-22 Thread Claus Reinke

http://www.kantaka.co.uk/darcs/ray


try making ray_sphere and intersect' local to intersect,
then drop their constant ray parameter. saves me 25%.
claus
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-22 Thread Dave Bayer

On Jun 22, 2007, at 4:37 PM, David Roundy wrote:


You get strongly-typed code whether or not you enable warnings.


In my opinion it's delusional to think one is using strong typing if  
one doesn't enable warnings. All the puffing about the advantages of  
strong typing look pretty silly if code hangs up on an incomplete  
pattern. Let's remember that the other side of this debate is rather  
eloquent, be it Paul Graham or a Ruby enthusiast. People who don't  
worry so much about types believe that they get things done. Is using  
a strongly typed language like buying a hybrid car, it costs too much  
but you're helping with maybe someday...?


I refuse to drink the Kool-Aid and recite precisely what I'm told a  
type is in June, 2007; I'm hoping that types will evolve by the time  
I die. For types to evolves, we need to step back a few feet and  
think more loosely what a type really is.


If someone writes working code with incomplete patterns, they're  
effectively using a dependent type without being able to say so in  
Haskell. They're using a specialization of the type they claim to be  
using, in which the missing patterns are never needed. Filling in with


	_  - error I'm sweeping this under the rug so it's no longer the  
type system's problem


just highlights the inadequacy of the type system. The code hangs  
either way, if the belief that this case doesn't happen is wrong. I'm  
more of a Will the code hang or not? kind of guy than Will I be  
kicked out of the tree house if I use the wrong words for things?  
kind of guy. The missing pattern that shouldn't happen is abstractly  
a type issue, whether we can get the compiler to lay off or not.


Similarly, the whole defaulting debate is good form/bad form  
considerations for how best to use types to automatically write code  
for us.


It all comes back to what I said before, types are compile-time  
proxies for run-time values. I'm nudging at compile-time, therefore  
I'm messing with types, not values.


If I go away and write in Lisp or Ruby, then return to Haskell with  
ghc -Wall -Werror, it is glaringly obvious to me that the nudging I  
have to do to get things to work with warnings on has to do with  
types. I truly don't mind the nudging, it is very educational, but  
let's call a spade a spade?





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


Re: [Haskell-cafe] A probably-stupid question about a Prelude implementation.

2007-06-22 Thread Michael T. Richter
On Fri, 2007-22-06 at 22:28 +0400, Bulat Ziganshin wrote:

 no surprise - you got a lot of answers :)  it is the best part of
 Haskell, after all :)


Yes, that is one of the best parts of Haskell.  And I sometimes even
understand the answers which is better!


 the secret Haskell weapon is lazy evaluation which makes *everything*
 short-circuited. just consider standard () definition:



 () False _ = False
 () True  x = x


Dammit!  Teaches me to make assumptions.  Of course operators in
Haskell are going to be JAF (Just Another Function).  I didn't bother to
look one level lower than the foldr because I still have my C/C
++/practically-every-other-language-in-the-universe assumption that
operators are special syntactical constructs, not sugar for POBF
(Plain Old Boring Functions).  Had I read the definitions of  and ||
I'd never have asked the question I did.  I'd have got it right away.
(The irony is that even though the operators were being called as
functions in foldr, I have their use so ingrained in my head that I read
their use as functions in foldr and internally translated this to
imperative loops using operators!

I'd like to thank everybody for the various answers to this question.
It's been enlightening both on the front of remembering the subtleties
of Haskell's underlying assumptions and on the front of remembering what
a joy this community is.

-- 
Michael T. Richter [EMAIL PROTECTED] (GoogleTalk:
[EMAIL PROTECTED])
When debugging, novices insert corrective code; experts remove defective
code. (Richard Pattis)


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


Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-22 Thread Derek Elkins
On Fri, 2007-06-22 at 17:39 -0700, Dave Bayer wrote:
 On Jun 22, 2007, at 4:37 PM, David Roundy wrote:
 
  You get strongly-typed code whether or not you enable warnings.
 
 In my opinion it's delusional to think one is using strong typing if  
 one doesn't enable warnings. All the puffing about the advantages of  
 strong typing look pretty silly if code hangs up on an incomplete  
 pattern. Let's remember that the other side of this debate is rather  
 eloquent, be it Paul Graham or a Ruby enthusiast. People who don't  
 worry so much about types believe that they get things done. Is using  
 a strongly typed language like buying a hybrid car, it costs too much  
 but you're helping with maybe someday...?

Okay... people who don't worry so much about incomplete patterns believe
that they get things done.

There are trade offs in type systems about how much effort you want to
require of the user and how much the type system will catch.  Haskell's
type system is at a point that does a lot with very little.  You can do
ridiculously more if you don't mind requiring more from the user.

 
 I refuse to drink the Kool-Aid and recite precisely what I'm told a  
 type is in June, 2007; I'm hoping that types will evolve by the time  
 I die. For types to evolves, we need to step back a few feet and  
 think more loosely what a type really is.
 
 If someone writes working code with incomplete patterns, they're  
 effectively using a dependent type without being able to say so in  
 Haskell. They're using a specialization of the type they claim to be  
 using, in which the missing patterns are never needed. Filling in with
 
   _  - error I'm sweeping this under the rug so it's no longer the  
 type system's problem
 
 just highlights the inadequacy of the type system. 

It's not an inadequacy, it's a trade off, but if you want, Epigram is
right over there.


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


Re: [Haskell-cafe] Shouldn't this be lazy???

2007-06-22 Thread Marc Weber
On Fri, Jun 22, 2007 at 01:51:12PM -0400, Olivier Boudry wrote:
 Marc,
 
 Thanks for the link. Your LazyIO monad is really interesting. Do you
 know if this construct exists in GHC? (this question was left open in
 this thread)

I couldn't find it. That's why I've written it.
I think there is not much interest because the question was left open.

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


Re: [Haskell-cafe] Haskell version of ray tracer code is much slower than the original ML

2007-06-22 Thread Jon Harrop
On Friday 22 June 2007 19:54:16 Philip Armstrong wrote:
 On Fri, Jun 22, 2007 at 10:11:27PM +0400, Bulat Ziganshin wrote:
 btw, *their* measurement said that ocaml is 7% faster :)

 Indeed. The gcc-4.0 compilied binary runs at about 15s IIRC, but it's
 still much better than 7% faster than the ocaml binary.

What architecture, platform, compiler versions and compile lines are you 
using?

On my 2x 2.2GHz Athlon64 running x64 Debian I now get:

GHC 6.6.1:26.5sghc -funbox-strict-fields -O3 ray.hs -o ray
OCaml 3.10.0: 14.158s  ocamlopt -inline 1000 ray.ml -o ray
g++ 4.1.3: 8.056s  g++ -O3 -ffast-math ray.cpp -o ray

Also, the benchmarks and results that I cited before are more up to date than 
the ones you're using. In particular, you might be interested in these faster 
versions:

  http://www.ffconsultancy.com/languages/ray_tracer/code/5/ray.ml
  http://www.ffconsultancy.com/languages/ray_tracer/code/5/ray.cpp

For ./ray 6 512, I get:

OCaml: 3.140s  ocamlopt -inline 1000 ray.ml -o ray
C++:   2.970s  g++ -O3 -ffast-math ray.cpp -o ray

-- 
Dr Jon D Harrop, Flying Frog Consultancy Ltd.
The OCaml Journal
http://www.ffconsultancy.com/products/ocaml_journal/?e
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Compile-time here document facility

2007-06-22 Thread Donald Bruce Stewart
bayer:
 I couldn't find a compile-time here document facility, so I wrote one  
 using Template Haskell:

Very nice! You should wrap it in a little .cabal file, and upload it to
hackage.haskell.org, so we don't forget about it.

Details on cabalising and uploading here:

http://haskell.org/haskellwiki/How_to_write_a_Haskell_program
http://cgi.cse.unsw.edu.au/~dons/blog/2006/12/11

-- Don

 
 module HereDocs(hereDocs) where
 
 import Control.Exception
 import Language.Haskell.TH.Syntax
 
 getDoc :: String - [String] - (String,[String])
 getDoc eof txt =
 let (doc,rest) = break (== eof) txt
 in  (unlines doc, drop 1 rest)
 
 makeVal :: String - String - [Dec]
 makeVal var doc = let name = mkName var in
 [SigD name (ConT (mkName String)),
 ValD (VarP name) (NormalB (LitE (StringL doc))) []]
 
 scanSrc :: [Dec] - [String] - Q [Dec]
 scanSrc vals [] = return vals
 scanSrc vals (x:xs) = case words x of
 [var, =, ('':'':eof)] -
 let (doc,rest) = getDoc eof xs
 val = makeVal var doc
 in  scanSrc (vals ++ val) rest
 _ - scanSrc vals xs
 
 hereDocs :: FilePath - Q [Dec]
 hereDocs src =
 let fin = catchJust assertions (evaluate src) (return.takeWhile  
 (/= ':'))
 in  runIO (fin = readFile = return . lines) = scanSrc []
 
 One binds here documents embedded in comments by writing
 
 import HereDocs
 $(hereDocs Main.hs)
 
 As an idiom, one can refer to the current file as follows; the first  
 thing hereDocs does is catch assert errors in order to learn the file  
 name:
 
 import HereDocs
 $(hereDocs $ assert False )
 
 Here is an example use:
 
 {-# OPTIONS_GHC -fth -Wall -Werror #-}
 
 module Main where
 
 import System
 import Control.Exception
 
 import HereDocs
 $(hereDocs $ assert False )
 
 {-
 ruby = RUBY
 #!/usr/bin/env ruby
 hello = EOF
 Ruby is not
an acceptable Lisp
 EOF
 puts hello
 RUBY
 
 lisp = LISP
 #!/usr/bin/env mzscheme -qr
 (display #EOF
 Lisp is not
an acceptable Haskell
 EOF
 )
 (newline)
 LISP
 -}
 
 exec :: FilePath - String - IO ExitCode
 exec fout str = do
writeFile fout str
system (chmod +x  ++ fout ++ ; ./ ++ fout)
 
 main :: IO ExitCode
 main = do
exec hello.rb ruby
exec hello.scm lisp
 
 
 ___
 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] Haskell version of ray tracer code is much slower than the original ML

2007-06-22 Thread Donald Bruce Stewart
jon:
 On Friday 22 June 2007 19:54:16 Philip Armstrong wrote:
  On Fri, Jun 22, 2007 at 10:11:27PM +0400, Bulat Ziganshin wrote:
  btw, *their* measurement said that ocaml is 7% faster :)
 
  Indeed. The gcc-4.0 compilied binary runs at about 15s IIRC, but it's
  still much better than 7% faster than the ocaml binary.
 
 What architecture, platform, compiler versions and compile lines are you 
 using?
 
 On my 2x 2.2GHz Athlon64 running x64 Debian I now get:
 
 GHC 6.6.1:26.5sghc -funbox-strict-fields -O3 ray.hs -o ray

Don't use -O3 , its *worse* than -O2, and somewhere between -Onot and -O iirc,

ghc -O2 -funbox-strict-fields -fvia-C -optc-O2 -optc-ffast-math 
-fexcess-precision

Are usually fairly good.



 OCaml 3.10.0: 14.158s  ocamlopt -inline 1000 ray.ml -o ray
 g++ 4.1.3: 8.056s  g++ -O3 -ffast-math ray.cpp -o ray
 
 Also, the benchmarks and results that I cited before are more up to date than 
 the ones you're using. In particular, you might be interested in these faster 
 versions:
 
   http://www.ffconsultancy.com/languages/ray_tracer/code/5/ray.ml
   http://www.ffconsultancy.com/languages/ray_tracer/code/5/ray.cpp
 
 For ./ray 6 512, I get:
 
 OCaml: 3.140s  ocamlopt -inline 1000 ray.ml -o ray
 C++:   2.970s  g++ -O3 -ffast-math ray.cpp -o ray
 
 -- 
 Dr Jon D Harrop, Flying Frog Consultancy Ltd.
 The OCaml Journal
 http://www.ffconsultancy.com/products/ocaml_journal/?e
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Graphical Haskell

2007-06-22 Thread Donald Bruce Stewart
bf3:
 Wow thanks for all the info! This certainly can get me started.
 
 And yet I have some more questions (sorry!):
 
 - Unfortunately this project won't be open source; if my first tests are
 successful, I will try to convince my employer (who wants to develop such a
 graphical language) to use Haskell for building a prototype instead of
 C#/F#/Java. Can Haskell be used for creating commercial projects? When the
 product is released, it *will* be downloadable for free, but the source code
 won't be (most likely). 

It can, and is used. See the industry page, 

   http://haskell.org/haskellwiki/Haskell_in_industry 

they're the big players, there's numerous small groups that have maybe a
few in house Haskell tools.

 
 - If my employer agrees on Haskell, and when our first round of investment
 is completed, we will be looking for a couple of good Haskell developers.

Wonderful.

 What would be the best place to look for good Haskell developers? This
 mailing list? Ideally development will have to take place in
 Antwerp/Belgium, although we might work with remotely located freelancers.
 We prefer agile development (SCRUM, and maybe we will be doing extreme
 programming, to be decided) with a small group of capable people. To get an
 idea of what my employer is doing, visit http://www.nazooka.com. My
 colleagues and I wrote most of the software for doing this back in the
 1990s, and of course the real work is done by 3D graphics artists.

I suspect the best place to advertise is still [EMAIL PROTECTED]
Most jobs seems to be sent here, and its also cheap :-) You have access
to a few thousand competent Haskell people directly.

 - Regarding GUIs, does a real FP-style GUI exist instead of those wrappers
 around OO GUIs? I did some searches but besides some research papers about
 FranTk and wxFruit I only found wrappers such as Gtk2Hs and wxHaskell that
 use a lot of monadic IO. It's very hard for an old school OO style
 programmer like myself to switch my mind into lazy functional programming
 (although I think I've seen the light yesterday when digging deep into the
 FRP of the SOE book, LOL ;-).

gtk2hs is probably the most 'industrial' UI lib.

  
 - Functional reactive programming like looks cool (I only looked at the SOE
 book, must still look at Yampa), but somehow I feel this is still an active
 area of research. What is the latest work on FRP (for GUIs / games /
 animation / simulations...)? What are the major open issues? 
 
 - Regarding performance (for real-time simulations, not GUIs), I think the
 garbage collector will get really stressed using FRP because of all those
 infinite lazy streams; my gut feeling says a generational garbage collector
 like Microsoft's .NET could help here (but the gut is often wrong, see
 http://www.youtube.com/watch?v=RF3m3f9iMRc for an laugh ;). Regarding the
 GC, is http://hackage.haskell.org/trac/ghc/wiki/GarbageCollectorNotes still
 up-to-date?  

Well, best to find out. In practice i've not found GC to be an issue.
Premature optimisation and all that.

 
 Okay, that's enough for now. More is less...
 

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


Re: [Haskell-cafe] Graphical Haskell

2007-06-22 Thread Jon Harrop
On Friday 22 June 2007 16:38:18 peterv wrote:
 - Unfortunately this project won't be open source; if my first tests are
 successful, I will try to convince my employer (who wants to develop such a
 graphical language) to use Haskell for building a prototype instead of
 C#/F#/Java. Can Haskell be used for creating commercial projects? When the
 product is released, it *will* be downloadable for free, but the source
 code won't be (most likely).

We are developing both OCaml and F# into graphical platforms for technical 
computing:

  http://www.ffconsultancy.com/products/smoke_vector_graphics/
  http://www.ffconsultancy.com/products/fsharp_for_visualization/

and are also interested in doing this with Haskell. Our projects are also 
closed source but Smoke is freely available in platform-independent bytecode.

 ...
 - Regarding performance (for real-time simulations, not GUIs), I think the
 garbage collector will get really stressed using FRP because of all those
 infinite lazy streams; my gut feeling says a generational garbage collector
 like Microsoft's .NET could help here (but the gut is often wrong, see
 http://www.youtube.com/watch?v=RF3m3f9iMRc for an laugh ;). Regarding the
 GC, is http://hackage.haskell.org/trac/ghc/wiki/GarbageCollectorNotes still
 up-to-date?

To the best of my knowledge, OCaml is head and shoulders above the 
alternatives in this respect. It is certainly several times faster than F# 
for GC-intensive work. The main reason is that .NET imposes concurrent GC, 
which introduces locks around every allocation and cripples performance when 
value lifetime distributions are typical of a functional language. The Unix 
approach of forking processes seems to be far better suited to functional 
languages (this is not dissimilar to Erlang's GC-per-thread approach).

For example, the time taken to solve the 11 queens problem with the same 
program that filters out int pairs from a list of all board positions:

OCaml: 5s
F#: 30s

Also, the worst case performance of our visualization tools is 5x faster in 
OCaml than it was in C++. Assuming the same is true of Haskell, I think it is 
probably premature to be worrying about GC performance.

-- 
Dr Jon D Harrop, Flying Frog Consultancy Ltd.
The OCaml Journal
http://www.ffconsultancy.com/products/ocaml_journal/?e
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe