Re: [Haskell-cafe] Why Not Haskell?

2006-08-08 Thread Antti-Juhani Kaijanaho

Albert Lai wrote:

Let's have a fun quiz!  Guess the mainstream languages in question:


Spoilers for the quiz




































0. What language would allow

  4["hello world"]

   when a normal person would just write

  "hello world"[4]


This is a classic C misfeature.


1. What language, supporting a kind of both parametric polymorphism
   and subclass polymorphism, allows and actually features such a class
   declaration as

 class Enum> { ... }


I have to guess here. Java.


2. What language allows you to test primality in constant runtime?
   That is, move all the work to compile time, using its polymorphism.


C++, also a classic feature. There are even books that discuss this 
technique, and I believe a SPJ paper referring to it.

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


Re: [Haskell-cafe] Re: Why Not Haskell?

2006-08-08 Thread Reilly Hayes
On Aug 8, 2006, at 1:42 AM, Immanuel Litzroth wrote:"Reilly Hayes" <[EMAIL PROTECTED]> writes:  I don't understand your argument. How exactly does the GPL get in theway of selling software as an instantiation of business expertise?Are you saying that you have the business expertise but customersstill prefer not to buy your software? Doesn't that just mean thatyour expertise isn't worth much (economic evaluation :-). Or that youridea that they were buying expertise was not correct, they were justbuying the software after all, and now they have an alternative?I failed to communicate my case clearly.  The software *is* what is being sold.  The *reason* it is valuable is the business expertise required to build it.  There are markets with very small populations of people who both understand the business thoroughly and can implement solutions.  It makes software valuable and makes licensing the most effective way to monetize that value.Yes I know the business model. Sell them some overpriced softwarecharge them through the nose for support, features, training,installation, updates Your resentment against the GPL stems from the fact that it makessqueezing the last buck out of your clients somewhat harder (in somemarkets). It probably annoys you that you are not dealing with acompetitor who is making shitloads of money, making some price fixingor secret agreements not feasable. Your problem is that just as yourbusiness practice is not illegal, neither is the GPL.This paragraph is way out of line.  You have taken a discussion of the merits of using GPL software and turned it into a personal attack.  Attack the argument, not the arguer.  It would be both polite and reasonable to tone down the hostility if you actually want a discussion.Certainly, some firms use restrictive software licensing to maximize short term revenue from their clients in the way you describe.  But I was referring to the marketing value of having the IP.  It's easier to sell services when you have some unique core IP, even to clients that aren't going to buy your product.  It gives your credibility a boost.I don't have a problem with the GPL.  In my professional life,  I am careful to avoid GPL software in those cases where the GPL would interfere with the firm's commercial interests.  I certainly don't resent the GPL or those who choose to release software under the GPL.  In fact, I can imagine wanting to release some kinds of software under the GPL.The point I was making was that the GPL *does* get in the way of *some* optimal mechanisms of making money.  Which is *fine*.  That is one of the *intents* of the GPL.  The argument that I am trying to counter is the one that says open source is *always* better for everybody.  Sometimes, the best thing for the owner of the intellectual property is to keep it closed.  There *are* markets where monetization of IP is a zero sum game, or worse (if the IP is public, nobody makes any money).I'm not making (or getting involved in) the moral argument about free or opensoftware.  I will point out that the current good health of Haskell owes agreat deal to Microsoft through the computer scientists they employ.  I'm sureHaskell has benefitted from the largesse of other companies as well. That is definitely wrong. Haskell would be in even greater shape ifsome people who shall remain unnamed had not gone over to Microsoft. Iforesee an interesting discussion here.I don't see how you can say Haskell would be better OR worse off if people hadn't gone to work for Microsoft.  It's an entirely hypothetical case and it's just not knowable.  My point is much simpler.  Haskell & GHC do benefit from the efforts of people being paid by Microsoft.  Microsoft is planning to hire a full-time contractor to work on GHC.The snarky comment about "people who shall remain unnamed" is rude.-R Hayes ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] beginner's haskell question

2006-08-08 Thread Donald Bruce Stewart
jens-theisen-tmp01:
> Hello,
> 
> as a haskell newbie I'm wondering about the following question.
> 
> Are there options to popular haskell implementations or other means 
> (haskell lint?) to check for incomplete patterns at compile time for 
> some? I can't see a reason why this shouldn't be possible or even a 
> relatively simple thing to implement.
> 
> Cheers,
> 
> Jens

You might just want to always use:
-Wall -Werror

to get the full range of extended warnings and checks.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] beginner's haskell question

2006-08-08 Thread J. Garrett Morris

The ghc flag -fwarn-incomplete-patterns might be what you're looking for.

/g

On 8/8/06, Jens Theisen <[EMAIL PROTECTED]> wrote:

Hello,

as a haskell newbie I'm wondering about the following question.

Are there options to popular haskell implementations or other means
(haskell lint?) to check for incomplete patterns at compile time for
some? I can't see a reason why this shouldn't be possible or even a
relatively simple thing to implement.

Cheers,

Jens

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




--
We have lingered in the chambers of the sea 
By sea-girls wreathed with seaweed red and brown
Till human voices wake us, and we drown.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] beginner's haskell question

2006-08-08 Thread Jens Theisen

Hello,

as a haskell newbie I'm wondering about the following question.

Are there options to popular haskell implementations or other means 
(haskell lint?) to check for incomplete patterns at compile time for 
some? I can't see a reason why this shouldn't be possible or even a 
relatively simple thing to implement.


Cheers,

Jens

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


Re: [Haskell-cafe] Why Not Haskell?

2006-08-08 Thread Albert Lai
"Brian Hulley" <[EMAIL PROTECTED]> writes:

> Also, the bottom line imho is that Haskell is a difficult language to
> understand, and this is compounded by the apparent cleverness of
> unreadable code like:
> 
>  c = (.) . (.)
> 
> when a normal person would just write:
> 
>  c f g a b = f (g a b)

All mainstream languages are also difficult to understand, with
similarly clever, unreadable code.  Let's have a fun quiz!  Guess the
mainstream languages in question:

0. What language would allow

  4["hello world"]

   when a normal person would just write

  "hello world"[4]

   I first saw this in Dr. Dobb's Journal a decade ago; the author
   said that someone actually used it in interviews!

1. What language, supporting a kind of both parametric polymorphism
   and subclass polymorphism, allows and actually features such a class
   declaration as

 class Enum> { ... }

2. What language allows you to test primality in constant runtime?
   That is, move all the work to compile time, using its polymorphism.

*   *   *

I have programmed and watched programming for more than two decades.
I have observed that the rise and fall of popularity is, of course,
driven by many factors: cultural, social, economical, religious,
political, propagandic, ... but superiority is never one of them.
(Library abundance is, I say, less of a cause and more of an effect.
You have some popularity and then you have more contributors;
conversely you lose popularity and then you lose authors.  Yes there
is some feeding back, but the bootstrapping is more significant.  Perl
has a large library, but that's because it has got an impressive
following.  And where did that following come from?  Mostly economic
(there was a demand, a niche) and religious ("it's like natural
languages").)

Recall that some decent technology that once attained as much as 49%
market share could still decline and vanish in less than a decade.  I
am referring to Betamax video tapes.  It lost to VHS video tapes, of
lesser picture quality and 51% market share.  What did Betamax miss?
Apparently, nothing.  It seems that the only difference you can put
your finger at - and even this is elusive - is price.  VHS was
slightly cheaper, and apparently that did it.

If you were born after Betamax had vanished, I congratulate you, on
two counts.  First, you skipped the dark age during which there was no
Haskell, no Gofer, not even Scheme; there was Lisp but even then not
all functions were first-class.  Second, don't feel bad about missing
the video war, as you will soon see an even better one, this time
between Blu-Ray and HD-DVD.  Any bet?

I am trying to say this, with much foregoing digression: we could
equip Haskell with the perfect library, the perfect IDEs and tools,
the perfect tutorials and examples, the license that pleases
everyone... every nice thing mentioned in this thread, and it may
still not become popular.  Betamax had everything and 49% market share
(if Haskell had 49% mind share, we would be really thrilled, right?),
and it could still vanish.

How to make Haskell more popular?  How to make anything at all more
popular?  I am inclined to think it's a purely social question.
Nothing short of a rigorous social science can answer it.  All the nice
things mentioned in this thread, we should strive to build for our own
sake of course, but they don't answer the question.

I have long stopped asking that question.  Once again, I say we should
strive to build all the missing things mentioned.  What impact will
they make to the grand scheme of things, we don't know.  If there will
be none, don't be surprised; it's life.  One day we may have a
rigorous social science that can explain it.  Until then, I share with
you a line a Greek friend puts in his .plan file:

  Man plans and God laughs.

*   *   *

Answers to quiz:
0. http://c-faq.com/aryptr/joke.html
1. http://weblogs.java.net/blog/arnold/archive/2005/06/generics_consid_1.html
2. http://homepage.mac.com/sigfpe/Computing/peano.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] HWS - With Plugins

2006-08-08 Thread Johan Tibell

The HWS - With Plugins tarball is unavailable at the author's website
(http://www.mdstud.chalmers.se/~md9ms/hws-wp/) and his email address
doesn't work so this is desperate attempt to reach him. So, Martin
Sjögren, are you here somewhere?

P.S. If someone else knows where I could get hold of the source or at
least the source of the original HWS I would be greatful.

Cheers,

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


Re: [Haskell-cafe] creating tree with level subnodes and incrementing number?

2006-08-08 Thread Marc Weber
Thanks to you all!
I think I've learned a lot.

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


Re: [Haskell-cafe] creating tree with level subnodes and incrementing number?

2006-08-08 Thread Tomasz Zielonka
On Tue, Aug 08, 2006 at 02:30:39PM +0200, Marc Weber wrote:
> Is there a better way to do this?

In this case it is quite easy to separate the task into two smaller
ones:
- creating the tree with a desired shape
- numbering the nodes in post-order

The first task is naturally expressed without monads.

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


[Haskell-cafe] Re: [Haskell] thread-local variables

2006-08-08 Thread Frederik Eaton
> Furthermore, can we move this thread from the Haskell mailing list
> (which should not have heavy traffic) to either Haskell-Café, or
> the libraries list?

Sure, moving to haskell-cafe.

Frederik

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


[Haskell-cafe] RE: [Haskell] thread-local variables

2006-08-08 Thread Simon Peyton-Jones
| I have initialized a wiki page:
| 
| http://haskell.org/haskellwiki/Thread_local_storage

Great

| I have put a page on the wiki summarizing the thread. However, I want
| to say that I think that email is a better medium for most ongoing
| discussions. 

I agree.  
Discussion by email
Outcomes on Wiki (including outcomes recording differences of viewpoint)

The goal is that the outcome is a comprehensible summary of the outcome of the 
discussion, for the benefit of the many who will not follow the evolving 
debate.  


Furthermore, can we move this thread from the Haskell mailing list (which 
should not have heavy traffic) to either Haskell-Café, or the libraries list?

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


Re: [Haskell-cafe] creating tree with level subnodes and incrementing number?

2006-08-08 Thread Udo Stenzel
Marc Weber wrote:
> I've tried as an exercise to learn how to use the state monad to create
> a tree this way:
> 
> createTree :: Int -> Int -> (Tree Int, Int)
> createTree 4 = runState $ State $ \s -> (Node s [] , s+1) -- stop at level 4
> createTree level = runState (do item <- State $ (\s -> (s,s+1))
>   forest <- State $ (\s -> foldr (\_ (for, n) -> 
> let (l, n') = (createTree (level + 1) n) in (l:for,n')) 
>  ([], s) 
>  (replicate level 
> ()) )
>   return $ Node item (reverse forest) )

Isn't the whole point of the State Monad *not* to thread the state
through every function explicitly?  It should probably look like this
(untested code):

createTree :: Int -> Int -> (Tree Int, Int)
createTree = runState . createTree'

bump :: State Int Int
bump = do s <- get ; put $! s+1 ; return s

createTree' :: Int -> State (Tree Int)
createTree' 4 = do s <- bump ; return $ Node s []
createTree' level = do item <- bump
   forest <- replicateM (createTree' $ level+1) level
   return $ Node item forest

or even

createTree' level = liftM2 Node bump
   (replicateM (createTree' $ level+1) level)



Udo.
-- 
Two rules get you through life: If it's stuck and it's not supposed to
be, WD-40 it. If it's not stuck and it's supposed to be, duct tape it.
-- The Duct Tape Guys' book "WD-40"


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


Re: [Haskell-cafe] How can we detect and fix memory leak due to lazyness?

2006-08-08 Thread Udo Stenzel
Ahn, Ki Yung wrote:
> Recently, I'm facing the dark side of laziness
> -- the memory leak because of laziness.
> 
> Are there standardized approaches for detecting and fixing
> these kind of problems?

Not really.  As Don S. already said, try heap profiling.  The function
that is too lazy will show up as producer.  Other than that, you'll just
have to learn to look for the typical patterns.  Understanding Haskell's
evaluation model and being able to simulate it in your head also helps.

> sctAnal gs = null cgs || all (not . null) dcs
> where
>   gs' = fixSize compose $ Set.fromList [TT (x,y,cs) [] | To _ x y
> cs<-Set.toList gs]
>   cgs = [z | z@(TT (x,y,cs) _)<-Set.toList gs', x==y]
>   dcs = [[c| c@(a,D,b)<-Set.toList cs , a==b] | TT (_,_,cs) _<-cgs]
>   compose gs = trace ("## "++show (Set.size gs)) $ foldr checkInsert gs $ do
 ^ point 1
> TT (x1,y1,cs1) l1 <- Set.toList gs
> TT (_,y2,cs2) l2 <- takeWhileTTfrom y1 . Set.toList $ setGT (TT
> (y1,Al""(-1),Set.empty) []) gs
> return $ TT (x1,y2,cs1 `comp` cs2) (l1++y1:l2)
 ^^^ point 2
>   takeWhileTTfrom y = takeWhile (\(TT (y',_,_) _) -> y==y')
>   checkInsert x s
>   | Set.member x s = s
>   | otherwise  = Set.insert x s

I can see two sources of problems.  Point 2 seems to be the cause of
your immediate problem:  this builds nested applications of (++) and
never evaluates them.  If the result is demanded, (++) calls itself
recursively, and if the list is too long, the stack gets exhausted.
'seq' doesn't help, that would only let the (++) accumulate in the
list's tail, but 'foldr seq' should help, and so would deepSeq.  I
wonder why

> instance (Ord a, Ord b) => Ord (TT a b) where
>  (TT x lx) < (TT y ly) = lx==lx && ly==ly && x < y

doesn't.  Does the (lx == lx) get optimized away?  The easiest solution
would be to use a data structure that directly supports concatenation.
Any implementation of a deque is good (FingerTrees?  Having them around
can never hurt...) and so is a function.  Replace the list [a] by a
function ([a] -> [a]), replace [] by id and replace (l1++y1:l2) by
(l1.(y1:).l2).  Also helps with the quadratic runtime, btw.

At point 1i, there lurks another problem.  You may find that some graphs
will blow your stack or even your heap.  That's because the repeated
application of checkInsert is not evaluated and this thunk may get too
deep or need more space than the Set it would buils.  I think, you want
foldl' (note the prime) here.


Udo.
-- 
F:  Was ist ansteckend und kommutiert?
A:  Eine Abelsche Grippe.


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


Re: [Haskell-cafe] creating tree with level subnodes and incrementing number?

2006-08-08 Thread Chris Kuklewicz

Is there a better way to do this?
This problem is similar to adding numbers to each tree item

Marc


Yes.  The feature you wanted is "replicateM".

The point of a State monad is you probably never have to touch the State data 
constructor:



module Main where

import Control.Monad.State
import Data.Tree

type Supply = State Int
unique :: Supply Int
unique = do
  value <- get
  put (succ value)
  return value

createTree :: Int -> Supply (Tree Int)
createTree 4 = do
  me <- unique
  return (Node me [])
createTree level = do
  me <- unique
  children <- replicateM level (createTree (succ level))
  return (Node me children)

main = do
  putStrLn $ drawTree $ fmap show $ evalState (createTree 2) 0


Or even more tersely:

> import Control.Monad
>

createTree :: Int -> Supply (Tree Int)
createTree 4 = liftM (`Node` []) unique
createTree level = liftM2 Node unique (replicateM level (createTree (succ 
level)))

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


[Haskell-cafe] creating tree with level subnodes and incrementing number?

2006-08-08 Thread Marc Weber
Hi

I've tried as an exercise to learn how to use the state monad to create
a tree this way:

module Main where
import Control.Monad.State
import Data.Tree
import Random

createTree :: Int -> Int -> (Tree Int, Int)
createTree 4 = runState $ State $ \s -> (Node s [] , s+1) -- stop at level 4
createTree level = runState (do item <- State $ (\s -> (s,s+1))
forest <- State $ (\s -> foldr (\_ (for, n) -> 
let (l, n') = (createTree (level + 1) n) in (l:for,n')) 
   ([], s) 
   (replicate level 
()) )
return $ Node item (reverse forest) )


main = do
  putStrLn $ drawTree $ fmap show $ fst $ createTree 2 0

 output --
0
|
+- 1-- features: auto numbering and level n exists of n Nodes
|  |
|  +- 2
|  |
|  +- 3
|  |
|  `- 4
|
`- 5
   |
   +- 6
   |
   +- 7
   |
   `- 8

   |  |
   2  3  ... Nodes per level

I think this line is not very easy to understand.. the (replecate part is just 
a dummy to count the iterations)
forest <- State $ (\s -> foldr (\_ (for, n) -> let (l, n') = (createTree (level 
+ 1) n) in (l:for,n')) 
   ([], s) 
   (replicate level ()) )

Is there a better way to do this?
This problem is similar to adding numbers to each tree item

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


Re: [Haskell-cafe] How can we detect and fix memory leak due to lazyness?

2006-08-08 Thread Chris Kuklewicz

Ahn, Ki Yung wrote:

Recently, I'm facing the dark side of laziness
-- the memory leak because of laziness.

Typical pattern that I encounter the problem is like this.

My code was working fine and I was happy.
I just wanted to inspect some properties of my code so
I made a slight chage go the code such as adding counter
argument or attaching auxiliary data filed to original data for
tracing how the data has been constructed.
All of a sudden the program runs out of memory or overflows
the stack.

One problem is that it comes up unexpectedly. Another even
worse problem is that sometimes I get no idea for the exact
location causing the leak!

It really panics facing such darkness of lazy evaluation.
Just a small innocent looking fix for inspection or tracing
blow things up, sometime with no clue for its reason.

When we implement a debugging or tracing option in the
software and let the user toggle those features, how could
we be sure that turning on those features won't crash the
software written in Haskell?

Are there standardized approaches for detecting and fixing
these kind of problems?

Haskell may be type safe but not safe at all from unexpanded
diversion, which is not because of the programmers' mistake
but just because of the laziness.


I have posted an wiki article including one example of adding
a counter to count the number of basic operations in sorting algorithm.

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

This was a rather simple situation and we figured out how to
cure this by self equality check ( x==x ) forcing evaluation.



There are worse cases not being able to figure out the cure.
I wrote a function for analyzing some property of a graph,
which worked fine.

fixOnBy t p f x = if t x' `p` t x then x else fixOnBy t p f x' where x' 
= f x


fixSize f x = fixOnBy Set.size (==) f x

sctAnal gs = null cgs || all (not . null) dcs
where
  gs' = fixSize compose $ Set.fromList [(x,y,cs) | To _ x y 
cs<-Set.toList gs]

  cgs = [z | z@(x,y,cs)<-Set.toList gs', x==y]
  dcs = [ [c| c@(a,D,b)<-Set.toList cs , a==b] | (_,_,cs)<-cgs]
  compose gs = trace ("## "++show (Set.size gs)) $ foldr Set.insert gs $ do
(x1,y1,cs1) <- Set.toList gs
(_,y2,cs2)  <-  takeWhileFst y1 $ Set.toList $ setGT
(y1,Al""(-1),Set.empty) gs
return (x1,y2,cs1 `comp` cs2)
  takeWhileFst y = takeWhile (\(y',_,_) -> y==y')

This function makes a transitive closure of the given set of relations
by fixpoint iteration on the size of the set of weighted edges.

Sample output is like this.

*Main> main
## 170
## 400
## 1167
## 2249
## 2314
False


When I add an extra data field for tracing how the new relation was
constructed, (e.g. tag [a,b,c] on a->c if it came from a->b and b->c)
it suddenly overflows the stack even before printing out the trace.


I find that overflow a bit odd.  What is the ghc command line?  Are you using 
optimization flags?



The following is the code that leaks memory.

sctAnal gs = null cgs || all (not . null) dcs
where
  gs' = fixSize compose $ Set.fromList [TT (x,y,cs) [] | To _ x y
cs<-Set.toList gs]
  cgs = [z | z@(TT (x,y,cs) _)<-Set.toList gs', x==y]
  dcs = [[c| c@(a,D,b)<-Set.toList cs , a==b] | TT (_,_,cs) _<-cgs]
  compose gs = trace ("## "++show (Set.size gs)) $ foldr checkInsert gs 
$ do

TT (x1,y1,cs1) l1 <- Set.toList gs
TT (_,y2,cs2) l2 <- takeWhileTTfrom y1 . Set.toList $ setGT (TT
(y1,Al""(-1),Set.empty) []) gs
return $ TT (x1,y2,cs1 `comp` cs2) (l1++y1:l2)
  takeWhileTTfrom y = takeWhile (\(TT (y',_,_) _) -> y==y')
  checkInsert x s
  | Set.member x s = s
  | otherwise  = Set.insert x s

data TT a b = TT a b deriving (Show)
instance (Eq a, Eq b) => Eq (TT a b) where
 (TT x lx) == (TT y ly) = lx==lx && ly==ly && x == y
instance (Ord a, Ord b) => Ord (TT a b) where
 (TT x lx) < (TT y ly) = lx==lx && ly==ly && x < y



Tracing by eye:

sctAnal gc => null cgs => Set.toList gs' =>

let long = (Set.fromList [TT (x,y,cs) [] | To _ x y cs<-Set.toList gs])
in fixOnBy Set.size (==) compose (long) =>

if (Set.size (compose long)) == (Set.size long) then long else (compose long) =>

Set.size (compose long) => compose long =>

trace ("##"++show (Set.size long))  => Set.size long => long =>

Set.fromList [TT (x,y,cs) [] | To _ x y cs<-Set.toList gs] => Set.toList gs

Which does not look like it will blow stack space.  So I cannot see why the 
tracing function does not get to print the size.


I would try to simplify the string the trace function prints into a literal 
instead of a calculation on the size.  Then I would add many many more (trace 
"literal" $) functions to the code until I get some that print before it 
crashes.  But I suspect you have done most of that.

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


Re: [Haskell-cafe] Re: Why Not Haskell?

2006-08-08 Thread Immanuel Litzroth
"Reilly Hayes" <[EMAIL PROTECTED]> writes:

> On Aug 7, 2006, at 10:00 AM, Stefan Monnier wrote:
> In any case, making a living by selling a program (as opposed to services
> around that program) is a difficult business.  
>
>
> Making a living writing and selling programs for use by a wide audience is one
> thing. But there is a lot of money to be made by developers who really
> understand a complex niche market (assuming the niche is actually populated by
> customers who need and can pay for the product).  And the GPL absolutely gets
> in the way of that.  Because what you're really selling in that kind of market
> is software as an instantiation of business expertise.

I don't understand your argument. How exactly does the GPL get in the
way of selling software as an instantiation of business expertise?
Are you saying that you have the business expertise but customers
still prefer not to buy your software? Doesn't that just mean that 
your expertise isn't worth much (economic evaluation :-). Or that your 
idea that they were buying expertise was not correct, they were just 
buying the software after all, and now they have an alternative?

> Maybe you should thank the FSF for making you doubt: you should really
> think
> very hard about how you're going to make a living off of selling a 
> program,
> even if that program hasn't been anywhere near any GPL'd code.  In all
> likelihood it'll be much easier to earn your money by selling services
> around your program than just the program itself.
>
>
> Selling services is much easier if you can tie the services to IP that you own
> exclusively.  It can also double your firm's daily rate on related
> services.  And the economics of selling product (the program) can be  MUCH
> better, assuming people want to use the program.  If they don't, then you 
> don't
> have a service business either.

Yes I know the business model. Sell them some overpriced software
charge them through the nose for support, features, training,
installation, updates 
Your resentment against the GPL stems from the fact that it makes 
squeezing the last buck out of your clients somewhat harder (in some
markets). It probably annoys you that you are not dealing with a
competitor who is making shitloads of money, making some price fixing
or secret agreements not feasable. Your problem is that just as your
business practice is not illegal, neither is the GPL.  

> I'm not making (or getting involved in) the moral argument about free or open
> software.  I will point out that the current good health of Haskell owes a
> great deal to Microsoft through the computer scientists they employ.  I'm sure
> Haskell has benefitted from the largesse of other companies as well.
>
That is definitely wrong. Haskell would be in even greater shape if
some people who shall remain unnamed had not gone over to Microsoft. I
foresee an interesting discussion here.
Immanuel
-- 
***
I can, I can't.
Tubbs Tattsyrup

--
Immanuel Litzroth
Software Development Engineer
Enfocus Software
Antwerpsesteenweg 41-45
9000 Gent
Belgium
Voice: +32 9 269 23 90
Fax : +32 9 269 16 91
Email: [EMAIL PROTECTED]
web : www.enfocus.be
***
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] IO Monad/ haskelldb strange error?

2006-08-08 Thread Marc Weber
line << 39 works fine
line 56 doesn't. Why?
Isn't  both a IO monad (because of the print statements)
After commenting out 56 it compiles fine

Any suggestion appreciated.. I'm struggling for some hours now..

module Modules.ObjectTree where
import Debug.Trace
import Data.FunctorM
import DBUtils
import qualified DB.VT.Ezcontentobject_tree as EOT
import qualified DB.VT.Ezcontentobject as CO
import Database.HaskellDB.HDBRec
import Database.HaskellDB
import Database.HaskellDB.Query as Q
import Data.Tree
import Monad
import Control.Monad.Trans
import Maybe
import qualified List
 
instance FunctorM Tree where
  fmapM f (Node a forest) = do
a' <- f a
forest' <- mapM (fmapM f) forest
return $ Node a' forest'
 
 
type ObjectTree a = Tree  (Record a)
 
truncTree 1 (Node a _) = Node a []
truncTree x (Node a forest) = Node a $ map (truncTree (x-1)) forest
 
oT con = do
  print "blah" -- because of this we  should  have a simple IO Monad ?
  lookupField con (CO.name) (CO.ezcontentobject)  (CO.xid) (constant (1 :: 
Int)) >>= print :: IO () -- < 39
  return "blah"
 
-- printObjectsAsTree :: MonadIO m => ((Database -> m a) -> m a) -> Int -> IO ()
printObjectsAsTree con startid= do
  print "test"
  root <- liftM head  $ lRS (EOT.parent_node_id) (constant (startid :: Int))
  print root
  --showRS root >>= putStrLn
  node <- po root
  node_show <- fmapM showRS node
  return  $ drawTree node_show
  -- return "end"
  where lRS = lookupFieldRS con (EOT.ezcontentobject_tree)
po root = let root_id = (root!(EOT.node_id) :: Int)
  in do  print "dumm" -- IO Monad too ?
 print (root!(EOT.node_id))
 lookupField con (CO.name) (CO.ezcontentobject)  
(CO.xid) (constant (1 :: Int)) >>= print --  <<56
 return $ Node root []
 --childs <- lRS (EOT.parent_node_id) (constant root_id)
 --mapM_ (\r -> r!(EOT.node_id)) childs >>= print
showRS r = do -- name <- lookupField con (CO.name) (CO.ezcontentobject) 
(CO.xid) (constant 1) >>= print
  return "ab" :: IO String
  --return $ (show $ r!node_id) ++ " (" ++ (fromJust name) 
++ " )"
 
---
|| Preprocessing executables for dbez-0.0...
|| Building dbez-0.0...
|| Chasing modules from: db_ez.hs
|| [1 of 6] Skipping  DBUtils  ( DBUtils.hs, 
dist/build/db_ez/db_ez-tmp/DBUtils.o )
|| [2 of 6] Skipping  DB.VT.Ezcontentobject_tree ( 
DB/VT/Ezcontentobject_tree.hs, 
dist/build/db_ez/db_ez-tmp/DB/VT/Ezcontentobject_tree.o )
|| [3 of 6] Skipping  DB.VT.Ezcontentobject ( DB/VT/Ezcontentobject.hs, 
dist/build/db_ez/db_ez-tmp/DB/VT/Ezcontentobject.o )
|| [4 of 6] Compiling Modules.ObjectTree ( Modules/ObjectTree.hs, 
dist/build/db_ez/db_ez-tmp/Modules/ObjectTree.o )
|| 
Modules/ObjectTree.hs|43| 0:
|| Couldn't match `DB.VT.Ezcontentobject_tree.Contentobject_id'
|| against `DB.VT.Ezcontentobject.Contentclass_id'
||   Expected type: RecCons DB.VT.Ezcontentobject_tree.Contentobject_id
||   (Maybe Int)
||   vr
||   Inferred type: RecCons DB.VT.Ezcontentobject.Contentclass_id
||   Int
||   vr1
|| When using functional dependencies to combine
||   Database.HaskellDB.Database.GetRec (RecCons f (Expr a) er)
||   (RecCons f a vr),
||  arising from the instance declaration at Imported from 
Database.HaskellDB.Database
||   Database.HaskellDB.Database.GetRec (RecCons 
DB.VT.Ezcontentobject_tree.Contentobject_id
||(Expr (Maybe Int))

[...]
||  

(RecCons DB.VT.Ezcontentobject_tree.Sort_order
||  

 (Expr (Maybe Int))
||  

 RecNil
||   (RecCons 
DB.VT.Ezcontentobject.Contentclass_id Int vr),
arising from use of `lookupFieldRS' at Modules/ObjectTree.hs|52| 14-26
|| When generalising the type(s) for `printObjectsAsTree'
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


deriving DeepSeq and deep strict fields proposals (Re[2]: [Haskell-cafe] How can we detect and fix memory leak due to lazyness?)

2006-08-08 Thread Bulat Ziganshin
Hello Ki,

Tuesday, August 8, 2006, 6:34:51 AM, you wrote:

> Unfortunately seq and the strict data declaration is not helpful in general.
> They are only helpful on base values such as Int or Bool.
> What they do is just making sure that it is not a thunk.
> That is if it was a list it would just evaluate to see the cons cell
> but no further.

> Someone wrote a deepSeq module for forcing deep evaluation, which is

it was a proposal to add deepSeq to the language itself (just allow to
automatically derive it by compiler, for example). we can add another
proposal of implementing deep strict fields:

data T = C !![Int]

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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