Re: [Haskell-cafe] Composing functions with runST

2007-01-04 Thread Paul Moore

On 1/3/07, Seth Gordon [EMAIL PROTECTED] wrote:

David House wrote:

 So I can't just tell someone who's just starting to learn Haskell that
 f $ g y is equivalent to f (g y); I have to say those two are
 *almost always* equivalent, but if you use $ and the compiler complains
 about not being able to match the expected and the inferred type and a
 type signature in the error message has the word 'forall', try rewriting
 that expression without the $ and see if it compiles.  Eeeww.

 Why would someone just starting to learn Haskell be using ST? The
 canonical tutorial structure is to start with the pure stuff and only
 introduce the (more complicated!) impure stuff (ST, IORefs, etc.) in
 an 'advanced techniques' or similar section.

I (and one other person on this list) ran into this issue when I was
trying to use takusen to make Haskell talk to a RDBMS.  You obviously
need to learn advanced techniques to *implement* such a thing, but you
shouldn't need advanced knowledge to *use a library* that happens to use
higher-rank polymorphic types in its API.


That other person was me, and I agree entirely. I have a little sample
project, using databases and concurrency, which I wanted to rewrite in
Haskell, as a learning exercise. I hit exactly this issue when simply
trying out some sample code, and my reaction was very much one of
irritation, frustration and confusion.

One of the nice things about Haskell, coming to it from an imperative
POV, is that monads can be thought of a little like first-class
composable statement blocks. When I understood that, I had a real
hey, that's neat! reaction.

One of the nasty things about Haskell (at my level of experience) is
that your nice helpful intuitions about monads can break down into
real confusion when you hit complex monads, monad transformers and the
like - *and you hit them quite early in the APIs of some libraries*!

It's not a big deal, but it's a bit offputting for a newcomer.
Paul.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Composing functions with runST

2007-01-04 Thread Paul Moore

On 1/3/07, Neil Mitchell [EMAIL PROTECTED] wrote:

As for beginner issues with rank-2 types, I've been learning Haskell
for years now, and have never felt the need for a rank-2 type. If the
interface for some feature requires rank-2 types I'd call that an
abstraction leak in most cases. It certainly means that you can't
properly Hoogle for it, can't compile it with Yhc, can't do full type
inference etc.


That may well be true. Something I forgot to mention in my previous
posting was that I'm not 100% convinced that the issue I hit with
Takusen isn't a problem with the library - I find it very hard to read
or understand some parts of the library documentation, basically
because the types seem so complex. My intuition says that reading a
database is logically similar to reading a file, so types like

doQuery :: (Statement stmt sess q, QueryIteratee (DBM mark sess) q i
seed b, IQuery q sess b) = stmt - i - seed - DBM mark sess seed

look pretty baffling to me - and don't match my intuition that

main = do
  withSession (connect user password server) $ do
-- simple query, returning reversed list of rows.
r - doQuery (sql select a, b, c from x) query1Iteratee []
liftIO $ putStrLn $ show r
otherActions session

is basically I/O. (Oh, by the way - that $ on the withSession line
is the one that caused the error which started this thread...)

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


Re: [Haskell-cafe] Composing functions with runST

2007-01-04 Thread Yitzchak Gale

Seth Gordon wrote:

From a friendliness-to-newbies point of view,
these error messages are a tremendous wart...
Eeeww.


Neil Mitchell wrote:

If the interface for some feature requires rank-2
types I'd call that an abstraction leak in most cases.


As the original poster of this thread, the one who was
bitten this time, let me point out that the use of
rank-2 polymorphism here is actually really nice.
It provides a strong safety guarantee for the ST monad
at *compile time*.

But the protection is a bit heavy-handed, so there are some
painful side effects that need to be addressed.

One is the confusion caused by the strange semantics
to those not familiar with the theory. That should be fixed
by simple, prominant, task-oriented documentation.
(You must always provide runST with an argument. So,
for example, you cannot write runST $ or runST ..)

And yes, perhaps the error messages in GHC could be
improved for newbies, but that was never intended to be the
strong point of GHC. I think Hugs is fine here.

The other is awkwardness in extending the capabilites
of ST. For that, I would propose that the function unsafeRunST
be added to the library.

Of course, if there is some way to improve both of these
situations by compilers relaxing the restrictions on rank-2
types somewhat, that would be great. But that is probably for
the future.

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


Re: [Haskell-cafe] Composing functions with runST

2007-01-04 Thread Yitzchak Gale

Paul Moore wrote:

...your nice helpful intuitions about monads can break down into
real confusion when you hit complex monads, monad transformers and the
like - *and you hit them quite early in the APIs of some libraries*!


I don't think that is a problem with the design of the
libraries. It is a problem with the documentation.

Almost all library documentation could be written so that
any user could easily use the library in a simple, practical,
straightforward way.

I am not saying that it would be easy, but it could be
done.

Nowadays, that type of documentation is taken for
granted for every popular programming language.

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


[Haskell-cafe] Re: Composing functions with runST

2007-01-04 Thread apfelmus
Neil Mitchell wrote:
 As for beginner issues with rank-2 types, I've been learning Haskell
 for years now, and have never felt the need for a rank-2 type. If the
 interface for some feature requires rank-2 types I'd call that an
 abstraction leak in most cases. It certainly means that you can't
 properly Hoogle for it, can't compile it with Yhc, can't do full type
 inference etc.

I think that the term abstraction leak is too harsh. In some sense,
you may as well call strong typing an abstraction leak because one
can do the stuff as well in a dynamic typed language and adding strong
typing means that you can't compile it with current compilers, you need
to implement type checking/inference etc. Of course, this analogy has
flaws as higher rank types go to the edge of computability whereas
strong typing can be implemented.

Concerning interfaces, higher rank types offer crucial static checking
that cannot be achieved without them. The prominent example is ST. The
next example is the parsing library frisby. In both cases, it would be
easy to wrack havoc in case the interface would not use higher rank
types. The same analogy as above applies: one uses strong typing because
one does not want to wreak havoc. I would not call this an abstraction
leak.

Concerning implementation, higher rank types are even more widespread:
almost everything involving continuations needs them: ReadP, Exceptions
(as opposed to Either), deforestation etc. In fact, it is quite possible
to throw away algebraic data types altogether and build everything you
need with higher rank types. A prominent example is

   [a] ~= (forall b . (a - b - b) - b - b)
   ~= (forall b . (Maybe (a,b) - b) - b)

The denotational semantics do not change, but the time and space
behavior is much different.

Perhaps the above remarks misinterpret your statement and you meant
abstraction leak in the sense that, because higher rank types are
available, the interface author used them without thinking whether the
same effect can be achieved in ordinary Haskell. Alas, such problems are
not tied to higher rank types: proper interface design is an art and
does not come for free, not to mention interface documentation[1]. One
could easily berserk: why does this library use String and doesn't
abstract it with a type class? Why does that interface only provide IO,
why isn't this available as a library of pure functions? What do these
obviously crappy semantics mean? In this case, higher rank types are a
symptom, not the problem. If one wants to cure the problem by
disallowing the symptom, then I suggest to also erase the symptom IO.
Thoroughly.

Of course, the drawbacks of higher rank types you mentioned remain. In
the case of hoogleability, I'm confident that it is possible to
implement them, it's only that someone has to think hard about it.
Implementing higher rank types in YHC is even harder but not impossible.
Sure, type inference is the most difficult thing, and one has to accept
glitches and drawbacks to make it work. Compared to these difficulties,
I think that the remark

 So I can't just tell someone who's just starting to learn Haskell that
 f $ g y is equivalent to f (g y); I have to say those two are
 *almost always* equivalent, but if you use $ and the compiler complains
 about not being able to match the expected and the inferred type and a
 type signature in the error message has the word 'forall', try rewriting
 that expression without the $ and see if it compiles.  Eeeww.

posted in this tread is too harsh. That's life, every language has its
flaws and glitches: parts of the layout rule, pattern guards, I want a
better records system, views, generic programming, etc. But, when code
has to be finished, those glitches or annoying things are best countered
with a shrug: they are not life-threatening. A programming language with
nonexistent type system and ugly semantics is. And much to our joy,
Haskell is far from this.

In that sense, dear reader of this post, just rewrite that expression
without $ and see if it compiles. The complier authors don't want to
annoy you, it's just that the exact reasons why this cannot yet be put
to work are damn hard. You are encouraged to learn about System F to get
a grasp of what is going on, but spending this one $ will be much cheaper.


Regards,
apfelmus

[1] Concerning library documentation, I think that literate Haskell
sources have the drawback that they are either tied to TeX
(\begin{code}..\end{code}) or that every line has to start with a ''.
I'd suggest to add a code../code or something else. The point is
that while (La)TeX can be cranked up to a publishing system, it is not
suited for many tasks such as media-dependent processing. TeX is a macro
language, not a structured document type. And for the strongly typed
Haskell programmer used to referential transparency, macros are a nightmare.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Composing functions with runST

2007-01-04 Thread Yitzchak Gale

I wrote:

Combining ST and MTL can be messy, even in this simple
case. You will probably write something with a type like
RandomGen g = [a] - g - ST s ([a], g)


Udo Stenzel wrote:

But why would you even want to do this?  It's ugly and cumbersome.


Yes indeed.


You'd plug a runST in there and get
shuffle :: RandomGen g = [a] - g - ([a], g)


Yes. In fact, that is what I did in practice.

As you say, the overall effect is ugly and cumbersome.
And this is with only the simplest of stateful calculations.
I shudder to think about what happens when things are more
complex. That is why I am thinking that -


Wouldn't it be nice if instead you could just write:

shuffle :: (RandomGen g, MonadState g m) = [a] - m [a]
shuffle = stToState . shuffleST


and then just use that directly inside a calculation that
is otherwise purely non-ST?


It seems, what you really want is
shuffleST :: RandomGen g = [a] - StateT g ST [a]


Actually, I tried that. It didn't help - it was just one more
layer I had to peel away to get at the ST inside.

There seems to be no way to avoid the fact that you
think about state in two very different ways in these
two monads. Every program is written in either one style
or the other. Occasionally, you require an isolated use
of the opposite style, and I am looking for ways of simplifying
the resulting mess. StateT st ST and MonadST look like
ways of combining the two, but in practice I find that they
just seem to get in the way.

I am starting to be convinced that the only way to
write the function I want is by using unsafeRunST.

Or type it as

stToState :: MonadState st m = (st - ST s (a, st)) - m a

and then write in the documentation that the
user is require to write

do
 r - newSTRef x
 ...
 y - readSTRef r
 return (z, y)

by hand every time. Yuck.

Am I missing something?

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


[Haskell-cafe] Re: Composing functions with runST

2007-01-04 Thread apfelmus
Yitzchak Gale wrote:
 Well, it turns out that using Data.Sequence or Data.IntMap
 to shuffle a list becomes prohibitive if you might have
 more than about 10^5 elements in your list. So in that
 case you will need to use a mutable array, and you now
 need ST.
 [..]

 Wouldn't it be nice if instead you could just write:

 shuffle :: (RandomGen g, MonadState g m) = [a] - m [a]
 shuffle = stToState . shuffleST
 
 and then just use that directly inside a calculation that
 is otherwise purely non-ST?
 
 It seems, what you really want is
 shuffleST :: RandomGen g = [a] - StateT g ST [a]
 
 Actually, I tried that. It didn't help - it was just one more
 layer I had to peel away to get at the ST inside.
 
 There seems to be no way to avoid the fact that you
 think about state in two very different ways in these
 two monads. Every program is written in either one style
 or the other. Occasionally, you require an isolated use
 of the opposite style, and I am looking for ways of simplifying
 the resulting mess. StateT st ST and MonadST look like
 ways of combining the two, but in practice I find that they
 just seem to get in the way.

I don't get what exactly you want.

If you want to carry your state named MyState (f.i. type MyState =
[Cards,Players]) around in a monad, you use Control.Monad.State MyState.

If (and only if) you have an algorithm (like depth-first search) that
carries an array as state around (nodes already visited) and you know
that this array is used in a single threaded fashion, it might be worth
to update the array in place. For that, you use Control.Monad.ST and
Data.Array.ST and you can be confident that the state carrying has been
strictness analyzed and fine tuned to match the machine. In short, you
get updates in place without selling your soul to IO, runST is your
protection from evil and will keep you pure. ST does not really have
more uses than this one (besides being the foundation for IO). For more
info on ST, see
   http://research.microsoft.com/Users/simonpj/Papers/state-lasc.ps.gz

Note that the you can now achieve the array thing as well with
Data.Array.Diff. This is a purely functional interface to an array type
that uses destructible updates internally and keeps a history to become
persistent. However, I doubt that an array makes a difference over
Data.IntMap for all but the most special cases.


 I am starting to be convinced that the only way to
 write the function I want is by using unsafeRunST. 
 Or type it as
 
 stToState :: MonadState st m = (st - ST s (a, st)) - m a
 
 and then write in the documentation that the
 user is require to write
 
 do
  r - newSTRef x
  ...
  y - readSTRef r
  return (z, y)
 
 by hand every time. Yuck.

If the programmer needs to adhere to a policy, the type system may well
enforce it for him. No unsafeRunST. It's far better to struggle with the
safety device than to discover the hard way that running without it will
directly lead into the debugging hell.


Regards,
apfelmus

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


Re[2]: [Haskell-cafe] Composing functions with runST

2007-01-04 Thread Bulat Ziganshin
Hello Yitzchak,

Thursday, January 4, 2007, 12:25:41 PM, you wrote:

 The other is awkwardness in extending the capabilites
 of ST. For that, I would propose that the function unsafeRunST
 be added to the library.

this function exists, but named unsafeIOtoST. IO and ST is exactly the same
things, the only difference that foreign imports may be marked as IO
operations but both ST ones. as a result, ST is restricted to a few
standard operations that guarantees to bo be mutually transparent for
consumers of runST.

when one goes to extend ST functionality, unsafeIOtoST is used. for
3xample, in Hugs it is used to convert peek/poke IO operations into
STUArray implementation. except for compile-time type sugar, there is no
difference between those two type constructors. unsafeIOtoST is like liftIO:

unsafeIOtoST :: IO a - ST s a


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Composing functions with runST

2007-01-04 Thread Yitzchak Gale

I wrote:

Am I missing something?


Yes! In reality, I do not need unsafeSTRef for this
at all, using a type suggested earlier by Udo:

stToState :: MonadState st m = (forall s. STRef s st - ST s a) - m a
stToState f = do
   s - get
   let (y, s') = runST (stm f s)
   put s'
   return y
 where
   stm f s = do
 r - newSTRef s
 y - f r
 s' - readSTRef r
 return (y, s')

This works! Thanks, Udo!

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


Re: Re[2]: [Haskell-cafe] Composing functions with runST

2007-01-04 Thread Yitzchak Gale

Hi Bulat,

I wrote:

One is the confusion caused by the strange semantics
to those not familiar with the theory...


Like me, of course.


The other is awkwardness in extending the capabilites
of ST. For that, I would propose that the function unsafeRunST
be added to the library.


Bulat Ziganshin wrote:

this function exists, but named unsafeIOtoST.


That wasn't what I had in mind, because it forces the
thread parameter to take the specific value RealWorld.

But I am not sure anymore that it is needed. It turned out
that my case was just another instance of the first
kind of awkwardness. So I no longer have any evidence
that the second kind of awkwardness exists. So
I withdraw my proposal.

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


Re: [Haskell-cafe] Arrays performance

2007-01-04 Thread Paolo Veronelli
Quoting Paolo Veronelli [EMAIL PROTECTED]:
 I paste new version in case you care give me some moe suggestion.



import Data.Maybe
import Data.List
import Data.Array.Diff

import System.Environment
import Control.Arrow 
import Control.Monad

import Random


inc l i = l // [(i,l!i + 1)]
switch l i = l // [(i,not (l!i))]
constArray n v = listArray (0,n-1) (repeat v)

data Folding = Folding 
  {clusters :: [(Int,Int)], remi :: Int, colsCount :: DiffArray Int Int 
,rowsCheck :: DiffArray Int Bool}

result (Folding cs _ _ _) = cs

rcluster ls d s = let 
  devil s@(Folding cs r hs fs) l@(row,col) = let 
ns = s { clusters = (l:cs), rowsCheck = switch fs row, colsCount = inc hs 
col } 
rowtest  | c  d   = ns 
   
 | (c == d)  (r  0) = ns { remi = r - 1 }
 
 | otherwise   = s
  where c = hs ! col
in if (not (fs ! row)) then rowtest else s  
  
  in foldl devil s ls
 
mcluster :: (Int,Int) - [(Int,Int)] -  [(Int,[Int])]
mcluster (lr,lc) ls = let 
  (k,r) = divMod lr lc
  start = Folding{clusters = [],remi = r,colsCount = constArray lc 0,rowsCheck 
= constArray lr False } 
  cs = result $ rcluster ls k start
  in map collapse . groupBy (comp fst (==)) . sort . map swap $ cs 
  where 
comp f g x y = (f x) `g` (f y) 
swap = snd  fst 
collapse = (head  unzip)  (fst *** snd)


cluster :: (Ord b) = (a - a - b) - [a] - [a] - [(a,[a])]
cluster fxy xs ys =  let 
  mkArray (l,xs) = (listArray :: (Int,Int) - [e] - DiffArray Int e)  (0,l-1)  
xs 
  xls = mkArray (lc,xs)
  yls = mkArray (rc,ys)
  (lc,rc) =  (length xs,length ys)
  in
  map ((yls !) *** map (xls !)) (mcluster (lc,rc) (snd.unzip.sort $ delta))
where
  delta  = [(fxy x y,(n,m))|(n,x) - zip [0..] xs, (m,y) - zip [0..] ys]

 
-- call it with 2 args, the number ov values and the number of clusters
-- prog 101 10   will cluster 101 values in 10 clusters

points m n = do gen - getStdGen
return $ splitAt n (take (m + n) (randomRs (0,100::Int) gen))

test1 = do args - getArgs
   return $ map read args :: IO [Int] 

main = do 
[m,n] - test1
--let [m,n] = [10,3200]
(ps,bs) - points m n
print $ cluster (\x y - abs (x - y)) ps bs

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


Re: [Haskell-cafe] Announce: Package rdtsc for reading IA-32 time stamp counters

2007-01-04 Thread Andy Georges

Hi,


version 1.0 of package rdtsc has just been released.

This small package contains one module called 'Rdtsc.Rdtsc'.


I am wondering what it would take to get rdpmc in there as well. Of  
course, you'd need some way to set the pmcs before running, but that  
can be done using e.g. perfctr. I'd like to take a swing at  
implementing this, unless somebody else volunteers or thinks it's  
basically useless.


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


Re: [Haskell-cafe] Arrays performance

2007-01-04 Thread Chris Kuklewicz
Paolo Veronelli wrote:
 Quoting Paolo Veronelli [EMAIL PROTECTED]:
 I paste new version in case you care give me some moe suggestion.
 
 
 
 import Data.Maybe
 import Data.List
 import Data.Array.Diff
 
 import System.Environment
 import Control.Arrow 
 import Control.Monad
 
 import Random
 
 
 inc l i = l // [(i,l!i + 1)]
 switch l i = l // [(i,not (l!i))]
 constArray n v = listArray (0,n-1) (repeat v)

I don't know about performance differences, but I write constArray using the
default value I can give to accumArray:

constArray n v = accumArray (const) v (0,n-1) []

where (const) might as well be (undefined) or (error unused)

 data Folding = Folding 
   {clusters :: [(Int,Int)], remi :: Int, colsCount :: DiffArray Int Int 
 ,rowsCheck :: DiffArray Int Bool}
 

 result (Folding cs _ _ _) = cs

 
 rcluster ls d s = let 
   devil s@(Folding cs r hs fs) l@(row,col) = let 
 ns = s { clusters = (l:cs), rowsCheck = switch fs row, colsCount = inc hs 
 col } 
 rowtest  | c  d   = ns   
  
  | (c == d)  (r  0) = ns { remi = r - 1 }  

  | otherwise   = s
   where c = hs ! col
 in if (not (fs ! row)) then rowtest else s
 
   in foldl devil s ls

I cannot tell by a quick glance, but you may want foldl' instead of foldl here.

  
 mcluster :: (Int,Int) - [(Int,Int)] -  [(Int,[Int])]
 mcluster (lr,lc) ls = let 
   (k,r) = divMod lr lc
   start = Folding{clusters = [],remi = r,colsCount = constArray lc 
 0,rowsCheck = constArray lr False } 
   cs = result $ rcluster ls k start
   in map collapse . groupBy (comp fst (==)) . sort . map swap $ cs 
   where 
 comp f g x y = (f x) `g` (f y) 
 swap = snd  fst 
 collapse = (head  unzip)  (fst *** snd)

snd.unzip is better written as map snd so this is
  collapse = (fst.head  map snd)
which is identical to the pointful
  collapse x@((a,_):_) = (a,map snd x)

 
 cluster :: (Ord b) = (a - a - b) - [a] - [a] - [(a,[a])]
 cluster fxy xs ys =  let 
   mkArray (l,xs) = (listArray :: (Int,Int) - [e] - DiffArray Int e)  
 (0,l-1)  xs 
   xls = mkArray (lc,xs)
   yls = mkArray (rc,ys)
   (lc,rc) =  (length xs,length ys)
   in
   map ((yls !) *** map (xls !)) (mcluster (lc,rc) (snd.unzip.sort $ delta))

snd.unzip is better written as map snd

Do you need the sort $ delta to sort the snd field as well as the fst?  If not
then using sortBy (comp fst compare) might be clearer (and may be faster or
slower).

 where
   delta  = [(fxy x y,(n,m))|(n,x) - zip [0..] xs, (m,y) - zip [0..] ys]

I don't know if it matters, but zip [0..] xs is the same as assocs xls and
the same for ys/yls.

And now something slightly bizarre occurs to me.  The list map swap delta
looks perfect to initialize a two dimensional Array to cache the fxy x y values
you pre-compute for the sorting.  Rather than form (n*m) pairs you could form a
single unboxed n by m Array:

deltaArray :: UArray (Int,Int) Int -- Unboxed for efficiency
deltaArray = listArray ((0,0),(lc,rc)) [fxy x y | x - xs, y - ys]

delta :: [(Int,Int)]
delta = sortBy (comp (deltaArray!) compare) deltaArray.indices

If you only need to sort by the fst field, i.e. the (fxy x y), then this is
sufficient and you can call (mcluster (lc,rc) delta).  If you needed delta
sorted by both fields, then a more complicated function to sortBy is needed:

delta = sortBy (\nm1 nm2 - compare (deltaArray!nm1) (deltaArray!nm2) `mappend`
compare nm1 nm2) deltaArray.indices

The `mappend` depends on the instance Monoid Ordering and import Data.Monoid
and is a great way to chain comparisons.

 -- call it with 2 args, the number ov values and the number of clusters
 -- prog 101 10   will cluster 101 values in 10 clusters
 
 points m n = do gen - getStdGen
 return $ splitAt n (take (m + n) (randomRs (0,100::Int) gen))
 
 test1 = do args - getArgs
return $ map read args :: IO [Int] 
 
 main = do 
 [m,n] - test1
 --let [m,n] = [10,3200]
 (ps,bs) - points m n
 print $ cluster (\x y - abs (x - y)) ps bs
 
 ___
 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 Weekly News: January 02, 2007

2007-01-04 Thread Henning Thielemann

On Tue, 2 Jan 2007, Donald Bruce Stewart wrote:

Dimensional: Statically checked physical dimensions. Björn Buckwalter
[4]announced version 0.1 of [5]Dimensional, a module for statically
checked physical dimensions. The module facilitates calculations with
physical quantities while statically preventing e.g. addition of
quantities with differing physical dimensions.

4. http://article.gmane.org/gmane.comp.lang.haskell.general/14691
5. http://code.google.com/p/dimensional/

How is it related to this one:
  http://www.haskell.org/haskellwiki/Dimensionalized_numbers
?

It should certainly be mentioned on
  http://www.haskell.org/haskellwiki/Physical_units
  
http://www.haskell.org/haskellwiki/Libraries_and_tools/Mathematics#Physical_units
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Announce: Package rdtsc for reading IA-32 time stamp counters

2007-01-04 Thread Martin Grabmueller
Andy Georges schrieb:
 Hi,
 
 version 1.0 of package rdtsc has just been released.

 This small package contains one module called 'Rdtsc.Rdtsc'.
 
 I am wondering what it would take to get rdpmc in there as well. Of
 course, you'd need some way to set the pmcs before running, but that can
 be done using e.g. perfctr. I'd like to take a swing at implementing
 this, unless somebody else volunteers or thinks it's basically useless.

I welcome any patches.  Currently, I do not plan to support other performance
counters or measurement schemes.

BTW, version 1.1 of rdtsc is now available from

  http://uebb.cs.tu-berlin.de/~magr/projects/rdtsc/doc/

or

  darcs get --partial http://uebb.cs.tu-berlin.de/~magr/projects/rdtsc/

(thanks to Bjorn Bringert for the hask-home tool used to generate the homepage 
for rdtsc).

Bye,
  Martin





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


[Haskell-cafe] MVar style question

2007-01-04 Thread Chad Scherrer

When using MVars, is there a reason to prefer using MVar (a,b) over
(MVar a, MVar b), or vice versa? I'm not sure if this is really a
question of style, or if there are practial implications I'm missing
one way or another. Thanks!

--

Chad Scherrer

Time flies like an arrow; fruit flies like a banana -- Groucho Marx
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Redefining superclass default methods in a subclass

2007-01-04 Thread Brian Hulley

Hi,
Looking at some of the ideas in 
http://www.haskell.org/haskellwiki/The_Other_Prelude , it struck me that the 
class system at the moment suffers from the problem that as hierarchies get 
deeper, the programmer is burdened more and more by the need to 
cut-and-paste method definitions between instances because Haskell doesn't 
allow a superclass (or ancestor class) method default to be redefined in a 
subclass.


For example, consider this part of a proposal for Functor = Applicative = 
Monad:


   -- I've just used 'm' so it's easy to see what parts are relevant to 
Monad

   class Functor m where
   fmap :: (a - b) - m a - m b

   class Functor m = Applicative m where
   return :: a - m a

   (*) :: m (a - b) - m a - m b

   () :: m a - m b - m b
   ma  mb = -- left as exercise for a rainy day!

   class Applicative m = Monad m where
   (=) :: m a - (a - m b) - m b

The problem with this is that whereas someone defining a Monad at the moment 
only needs to define (return) and (=), with the above, though it gives 
obvious advantages in flexibility, generality etc, defining a new Monad 
involves providing methods (in instance decls) for fmap and (*) as well, 
and the default method for () is


   ma  mb = (fmap (const id) ma) * mb

(from that page above) which I'm sure everyone will agree is a *lot* more 
complicated than:


   ma  mb = ma = (\_ - mb)

Not only is the first definition for () more complicated, it obscures the 
simple fact that for monads it's just a trivial special-use case of = 
where the bound argument is ignored.


Therefore I'm wondering if it would be possible to allow default methods for 
a superclass to be defined, or redefined, in a subclass, so we could write:


   class Applicative m = Monad m where
   (=) :: m a - (a - m b) - m b

   mf * ma = mf = \f - ma = \a - return (f a)

   ma  mb = ma = \_ = - mb

   fmap f ma = ma = \a - return (f a)

(I know the above can be written in a more point-free style but I wrote it 
like that to make it easy to understand what's happening.)


The essential point here (excuse the pun :-) ) is that it is impossible to 
write the default methods in the class in which the operation is defined, 
because the implementation depends on methods of the relevant subclass (and 
will therefore be different for different subclasses though not for each 
particular instance of a given ancestor class of a  particular subclass). As 
Haskell stands at the moment, we are forced to cut and paste identical 
methods for each individual instance of each ancestor class of a particular 
subclass because we can't override an ancestor class method in the *class* 
decl for a subclass.


The type class system at present is based on the idea that you can define 
related methods together and in terms of each other, at one level of the 
hierarchy. However as the above example shows, related methods sometimes 
need to be spread over the hierarchy but we still want to be able to define 
default implementations of them in terms of each other.


Perhaps there is some reason this can't be done?

Brian.
--
http://www.metamilk.com 


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


Re: [Haskell-cafe] Re: Seeking advice on a style question

2007-01-04 Thread Steve Schafer
[Apologies for the long delay in replying; I've been traveling, etc.]

On Sun, 31 Dec 2006 20:11:47 +0100, you wrote:

The other extreme is the one I favor: the whole pipeline is expressible
as a chain of function compositions via (.). One should be able to write

  process = rectangles2pages . questions2rectangles

This means that (rectangles2pages) comes from a (self written) layout
library and that (questions2rectangles) comes from a question formatting
library and both concern are completely separated from each other. If
such a factorization can be achieved, you get clear semantics, bug
reduction and code reuse for free.

I favor that approach, too. ;) The problem is that when there is a
multi-step process, and various bits of information get propagated
throughout, as required by the various steps in the process, the overall
decomposition into a series of steps a . b . c . ... can become brittle
in the face of changing requirements.

Let's say, for example, a change request comes in that now requires step
13 to access information that had previously been discarded back at step
3. The simple approach is to propagate that information in the data
structures that are passed among the intervening steps. But that means
that all of the steps are touched by the change--because the relevant
data structures are redefined--even though they're just passing the new
data along.

The less simple (and not always feasible) approach is to essentially
start over again and re-jigger all of the data structures and
subprocesses to handle the new requirement. But this can obviously
become quite a task.

If there are only the cases of some single question or a full
questionnaire, you could always do

blowup :: SingleQuestion - FullQuestionaire
preview = process (blowup a_question) ...

In general, I think that it's the task of (process) to inspect (Item)
and to plug together the right steps. For instance, a single question
does not need page breaks or similar. I would avoid overloading the
(load*) functions and (paginate) on (Item).

A single question can be several pages long, so it does need to be
paginated. The reason for the decomposition as it now stands is that any
item (and there are more kinds of items than just questions and
questionnaires) can be decomposed into a pagemaster and a list of
questions. Once that has occurred, all items acquire essentially the
same shape. That's why loading the pagemaster and loading the
questions are the first two steps in the process.

Btw, the special place end suggests that the question markup
language does not incorporate all of: conditional questions,
question groups, group templates? Otherwise, I'd just let the user
insert

   if media=print
  template-instance ref=endquestions.xml /
   /if

at the end of every questionnaire. If you use such a tiny macro language
(preferably with sane and simple semantics), you can actually merge
(stripUndisplayedQuestions) and (appendEndQuestions) into a function
(evalMacros) without much fuss.

If only I had the power to impose those kinds of changes

Unfortunately, I have little control over the logical organization of
questions, questionnaires and all of the other little bits and pieces.
(I assure you I would have done it quite differently if I could.)
Instead, I have to deal with an ad hoc pseudo-hierarchical
quasi-relational database structure, and to settle for occasional extra
columns to be added to the tables in order to specify information that I
can't synthesize any other way.

Uh, that doesn't sound good. I assume that the post-processing is not
implemented in Haskell?

Not even remotely so. ;) In the paper world, post-processing consists of
semi-automated collation and stapling of the actual printed pages. In
the electronic world, during previous survey periods, an analogous
process was used (a front questionnaire and a back questionnaire
would be figuratively stapled together); we're looking to make the
merging a bit smoother and more automatic this time around.

As is often the case, the motivation for the rather arcane
post-processing is human, rather than technical. Let's say I have ten
different questionnaires, where the first five pages of each
questionnaire are identical, and these are followed by six additional
pages that differ from one questionnaire to another. That's a total of
10 * 11 = 110 pages, but only 5 + 10 * 6 = 65 _distinct_ pages.

As hard as it may be to believe, the people who are responsible for
approving the questionnaires see it like this: If the system produces
one 5-page front questionnaire and ten 6-page back questionnaires,
then that's 65 pages that they have to inspect. But if the system were
to produce ten 11-page questionnaires, even though the first five pages
of each questionnaire are generated from exactly the same data using
exactly the same software, that's 110 pages that they have to inspect.

Fine, though I don't see exactly why this isn't done before after the
questions have 

Re: [Haskell-cafe] MVar style question

2007-01-04 Thread Roberto Zunino

Chad Scherrer wrote:

When using MVars, is there a reason to prefer using MVar (a,b) over
(MVar a, MVar b), or vice versa?


No one is strictly better than the other. But there are practical 
implications of choosing between them.


For instance, MVar (A,B) is less prone to deadlock issues than (MVar A, 
MVar B). Consider


   (a,b) :: (MVar A, MVar B)

   alice = do takeMVar a ; takeMVar b ; foo ; putMVar a x ; putMVar b y
   bob   = do takeMVar b ; takeMVar a ; bar ; putMVar b w ; putMVar a z

If alice and bob run concurrently, it might happen that alice takes a, 
bob takes b, and no one can proceed further. So, you must be very 
careful about the ordering of the takeMVar's (e.g. if you need both, 
always take a before taking b). There is no such issue using MVar (A,B), 
since only a single takeMVar is needed.


On the other hand using MVar (A,B) may reduce concurrency, imposing 
unnecessary locks. If alice2 only needs a, why should she be blocked 
from bob2 using only b? This issue gets worse once one starts using MVar 
(A,B,C,...), or MVar [A].


So, the solution is: choose wisely! ;-)

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


[Haskell-cafe] trivial function application question

2007-01-04 Thread brad clawsie
greetings to this helpful and informative list

i have a small problem that will be certainly trivial for almost
everyone reading this, i would appreciate a little help

lets say i have a string

s = abcdefg

now i have two lists of strings, one a list of patterns to match, and
a list of replacement strings:

patterns = [a,b]
replace = [Z,Y]

from which my intent is that a be replaced by Z, b by Y etc

now using the replace function from MissingH.Str (which i know is now 
renamed), i wish to apply replace to s using (pattern[0], replace[0]), 
(pattern[1], replace[1])...(pattern[N], replace[N]).

i am sure there is an elegant way to apply replace to s for all of
these argument pairs without composing replace N times myself, but the
solution escapes me.

thanks in advance for any help you can provide for this trivial issue
brad

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


Re: [Haskell-cafe] trivial function application question

2007-01-04 Thread Neil Mitchell

Hi Brad,


i have a small problem that will be certainly trivial for almost
everyone reading this, i would appreciate a little help


If you have trivial problems, its often useful to ask on Haskell IRC
(http://www.haskell.org/haskellwiki/IRC_channel)


from which my intent is that a be replaced by Z, b by Y etc

i am sure there is an elegant way to apply replace to s for all of
these argument pairs without composing replace N times myself, but the
solution escapes me.


In your example all strings are one letter long, is that how this
works? If so, then you can simplify the problem significantly to use
Char's, and use the following library functions:

First off, if you want to apply the same transformation to each item
of a list, namely to either replace it or leave it the same. This
calls out for map.

Secondly you want to do lookups in some sort of table. The lookup
function can be very handy here. The lookup function works on
associative lists, so you'd need to zip patterns and replace into an
associative list.

If you really want to operate on strings, rather than characters, then
you have to be more clever. Also replace called multiple times
probably won't be enough, consider replacing 1 with 2, 2 with 3. If
you just call replace multiple times, 1 may well end up at 3, when 2
is more likely to be the right answer.

Thanks

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


Re: [Haskell-cafe] trivial function application question

2007-01-04 Thread J. Garrett Morris

On 1/4/07, brad clawsie [EMAIL PROTECTED] wrote:

lets say i have a string

s = abcdefg

now i have two lists of strings, one a list of patterns to match, and
a list of replacement strings:

patterns = [a,b]
replace = [Z,Y]

from which my intent is that a be replaced by Z, b by Y etc

now using the replace function from MissingH.Str (which i know is now
renamed), i wish to apply replace to s using (pattern[0], replace[0]),
(pattern[1], replace[1])...(pattern[N], replace[N]).


You can create the replacing functions using zipWith :: (a - b - c)
- [a] - [b] - [c] (from the Prelude) as follows:

replacers = zipWith patterns replace

You then need to apply these functions to your starting string s.  I
would probably use foldr for that, something like this:

foldr ($) s replacers

Where ($) performs function application.

As Neil points out, if your replacements overlap, this could cause
replacement text to itself be replaced.

/g

--
It is myself I have never met, whose face is pasted on the underside of my mind.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Redefining superclass default methods in a subclass

2007-01-04 Thread Roberto Zunino

Brian Hulley wrote:

Hi,
Looking at some of the ideas in 
http://www.haskell.org/haskellwiki/The_Other_Prelude , it struck me that 
the class system at the moment suffers from the problem that as 
hierarchies get deeper, the programmer is burdened more and more by the 
need to cut-and-paste method definitions between instances because 
Haskell doesn't allow a superclass (or ancestor class) method default to 
be redefined in a subclass.


The class aliases proposal lists several similar shortcomings of the 
current class system.


http://repetae.net/john/recent/out/classalias.html


Perhaps there is some reason this can't be done?


Some random thoughts:

How one would write instances? Using your Monad class, does
   instance Monad F where
  return = ...
  (=) = ...
automatically define an instance for Applicative?

If it does: What if there already is such an instance? Which one gets 
used for ()? The user-defined one or the Monad default? Is separate 
compilation still possible? (If there is no instance right now, one 
might pop out in another module...)


If it does not: How can one define it, without copy-and-pasting the default?

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


Re: [Haskell-cafe] MVar style question

2007-01-04 Thread Mike Gunter

Do you need to maintain invariants that span the two?  Put
operationally, do you want different threads to be able to access a
and b concurrently?

-m

Chad Scherrer [EMAIL PROTECTED] writes:

 When using MVars, is there a reason to prefer using MVar (a,b) over
 (MVar a, MVar b), or vice versa? I'm not sure if this is really a
 question of style, or if there are practial implications I'm missing
 one way or another. Thanks!

 -- 

 Chad Scherrer

 Time flies like an arrow; fruit flies like a banana -- Groucho Marx
 ___
 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] Redefining superclass default methods in a subclass

2007-01-04 Thread Brian Hulley

Roberto Zunino wrote:

Brian Hulley wrote:

because Haskell doesn't allow a superclass (or ancestor class)
method default to be redefined in a subclass.


How one would write instances? Using your Monad class, does
   instance Monad F where
  return = ...
  (=) = ...
automatically define an instance for Applicative?


Yes, but I'd make the method names be call-site-bound so the actual method 
that is called is determined by the set of instance decls and class decls 
visible at each particular call site, and any instances that are 
automatically created would be hidden by any explicitly defined instances 
that are visible.




If it does: What if there already is such an instance? Which one gets
used for ()? The user-defined one or the Monad default?


A possible proposal could be:
1) Class and instance decls would allow method implementations to be given 
for any methods in the class or any ancestor class.


2) Whenever an instance decl is visible there would always be a full set of 
instance decls for all ancestor classes, by supplementing the set of 
explicitly given instance decls that are visible by automatically generated 
implicit instance decls.


3) The most specific method implementation would always be chosen (ie prefer 
an explicit instance method over a class method and prefer a subclass method 
to a superclass method)


In particular rule 2) would mean that the actual method used depends on 
what's available at the call site which means that a Haskell program could 
no longer be thought of as being re-written into a single module before 
compilation, since the meaning of overloaded names would be determined by 
(CalledFromModule, Type) not just Type.


(The desire to hide instance decls or have different instance decls for the 
same type within the same program has come up before on the list but 
unfortunately I can't remember who posted something along these lines or 
when.)



Is separate
compilation still possible? (If there is no instance right now, one
might pop out in another module...)



I think it should still be possible because within a module, the 
overloadings would be determined by the set of explicitly defined instances 
in scope in that module. Various optimizations might be more tricky because 
the call site module associated with each overloaded name would need to be 
taken into account when inlining across module boundaries (ie a name used 
inside an inlined function needs to be resolved as if it had been used in 
the module where the function was defined not the module where the function 
is inlined).


For example:

   module A where
   import Proposed.Control.Monad

   data T a = T a
   instance Monad T

   [-# INLINE foo #-}
   foo :: a - T a
   foo = return  -- uses Monad class default
   -- which is inherited from the Applicative
   -- class default

   module B where
   import A
   import Proposed.Control.Monad

   instance Applicative T where
   return x = retB x

   bar :: T a
   bar = return 'q'-- would use (retB)

   zap :: T a
   zap = foo 'q'-- would use (return) from A

A question is whether the extra difficulty in resolving overloadings (for 
human reader as well as complier) is worth the advantages of being able to 
get generated definitions for () for Applicative and (fmap) for Functor 
from a single instance decl for (Monad.=) etc.


[Rearranged]

The class aliases proposal lists several similar shortcomings of the
current class system.
http://repetae.net/john/recent/out/classalias.html


IIUC the class alias proposal is about being able to group classes together 
and deal with them as a whole so similar issues of resolving overloadings 
arising from overlapping aliases/ explicit instance decls etc would arise 
(and I imagine the solutions would lie in similar directions).


Brian.
--
http://www.metamilk.com 


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


[Haskell-cafe] Re: [Haskell] Re: state of HaXml?

2007-01-04 Thread Donald Bruce Stewart
nr:
   Sure, you can replace the openFile/hGetContents pair by readFile, but the
   real problem is the presence of the hClose.  Removing that will solve your
   problem (but note that you now have no control over when the file is
   actually closed).
 
 Can I just leave it hanging and rely on the garbage collector to close
 it in the fullness of time?

Yeah, once your program has demanded the entire file, it'll close the
Handle.
  
 Because of laziness, I believe there's no point in my writing the
 following:
 
  load fn = do handle - IO.openFile fn IO.ReadMode
   contents - IO.hGetContents handle
   let xml = XP.xmlParse fn contents
   IO.hClose handle
   return xml
 
 Is that correct?

Yep.  Its not neccessary in the usual programming cases to explicitly
close the handle.

IF you start really hammering the filesystem do you start to care about
ensuring files are closed (so you don't hang on to too many FDs). Or if
you start mutating files on disk. For these situations there are strict
readFiles, or Data.ByteString.readFile

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


Re: [Haskell-cafe] trivial function application question

2007-01-04 Thread tphyahoo

So the core question (speaking as a perler) is how do you write

  my $s= 'abcdefg';
  $s =~ s/a/z/g;
  $s =~ s/b/y/g;
  print $s\n;

 in haskell? There are various haskell regex libraries out there,
 including ones that advertise they are PCRE (Perl Compatible Reg Ex).

 But which one to use? How hard to install? With the libs mentioned
 above, the PCRE-ness seems only to be for matching, not for
 substitutions.

 http://www.cs.chalmers.se/~d00nibro/harp/
 http://repetae.net/john/computer/haskell/JRegex/

 So, I would like to know a good answer to this as well.

 thomas.




brad clawsie-2 wrote:
 
 greetings to this helpful and informative list
 
 i have a small problem that will be certainly trivial for almost
 everyone reading this, i would appreciate a little help
 
 lets say i have a string
 
 s = abcdefg
 
 now i have two lists of strings, one a list of patterns to match, and
 a list of replacement strings:
 
 patterns = [a,b]
 replace = [Z,Y]
 
 from which my intent is that a be replaced by Z, b by Y etc
 
 now using the replace function from MissingH.Str (which i know is now 
 renamed), i wish to apply replace to s using (pattern[0], replace[0]), 
 (pattern[1], replace[1])...(pattern[N], replace[N]).
 
 i am sure there is an elegant way to apply replace to s for all of
 these argument pairs without composing replace N times myself, but the
 solution escapes me.
 
 thanks in advance for any help you can provide for this trivial issue
 brad
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 

-- 
View this message in context: 
http://www.nabble.com/trivial-function-application-question-tf2922232.html#a8173692
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] trivial function application question

2007-01-04 Thread J. Garrett Morris

Oops, I seem not to have proofread my message.

On 1/4/07, J. Garrett Morris [EMAIL PROTECTED] wrote:

On 1/4/07, brad clawsie [EMAIL PROTECTED] wrote:
 s = abcdefg
 patterns = [a,b]
 replacements = [Z,Y]


I changed the name here so as not to conflict with the replace function.

snip


You can create the replacing functions using zipWith :: (a - b - c)
- [a] - [b] - [c] (from the Prelude) as follows:

replacers = zipWith replace patterns replacements


This line was previously incorrect.

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