Re: [Haskell] Probably a trivial thing for people knowing Haskell

2008-10-20 Thread Udo Stenzel
 Friedrich wrote:
 Ok to  be more concrete is the laziness hidden here?
 
 check_line line sum count =  
 let match = matchRegex regexp line
 in case match of
Just strs - (sum + read (head strs) :: Integer, count + 1)
Nothing - (sum, count)

Yes, part of it.  To see why, put yourself into the role of an evaluator
for your program.  An application of check_line will not be evaluated
until necessary, and it becomes necessary only if the result is bound to
a pattern (and that binding is needed for some reason).  At that point,
enough has to be evaluated to determine whether the result is actually a
pair or bottom.

So what will you do?  The body of check_line is a case expression, so
you need to sufficiently evaluate its scrutinee.  You evaluate enough of
matchRegex to see whether the result is Nothing or Just.  Let's say it's
Just.  So you descent into the Just branch, and you see the result is a
pair (and not bottom).  The elements of the pair have not been
evaluated, there was no need to.  Also, the arguments to check_line have
not been evaluated, except for line.

You need to force the evaluation of the elements of the result pair
whenever the pair itself is demanded, for example:

 check_line line sum count =  
 let match = matchRegex regexp line
 in case match of
Just strs - ((,) $! (sum + read (head strs) :: Integer)) $! 
  count + 1
Nothing - ((,) $! sum) $! count)

(The associativity of ($!) is inconvenient here.  I want
left-associative ($!).  Actually, a strict pair type would be even more
convenient here.)

On recent GHC with bang-patterns, this short-cut works, too.  It's not
quite equivalent, because it will create unevaluated thunks, though they
won't pile up:

 check_line line !sum !count =  
 let match = matchRegex regexp line
 in case match of
Just strs - (sum + read (head strs) :: Integer, count + 1)
Nothing - (sum, count)


Paul Johnson wrote:
 Try putting turning the Just line into something like
 
   Just strs - (seq sum $ sum + read (head strs) :: Integer, seq count 
 $ count + 1)

This doesn't help.  First of all, you don't try putting anything
anywhere.  Without understanding what's going on, you'll only create
ugly code, bang your head against a wall and still end up with a space
leak (been there, done that, bought the t-shirt).  Instead, go through
the evaluation by hand and/or use a heap profiler to guide you.  Then
put strictness annotations where needed (and only there).

Putting seqs inside the pair is useless, because the problem is that
nobody will look there to begin with.  Applying seq to sum and count
helps, if done outside the pair constructor, but is not quite right.
You want the new sums to be evaluated strictly, and while making the
function strict in its arguments helps, it stops one step too early.


-Udo



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


Re: [Haskell] Probably a trivial thing for people knowing Haskell

2008-10-20 Thread Udo Stenzel
Friedrich wrote:
 Taral [EMAIL PROTECTED] writes:
  Wow, talk about doing everything by hand. :) There are a lot of
  utility functions that make your life easier. Try this:

Given a strict pair, it should work:

  import Control.Monad
  import Data.Char
  import Data.List
  import System.Directory
  import System.IO
  import Text.Regex
 

data Pair = Pair !Integer !Integer

  main = do
  allFiles - getDirectoryContents .
  let files = filter (isDigit . head) allFiles
  contents - mapM readFile files
  let (sum, count) = foldl' countDownloads (0,0) $ lines $ concat contents

let Pair sum count = foldl' countDownloads (Pair 0 0) $ lines $ concat contents

  putStr (Download =  ++ show sum ++  in  ++ show count ++  days are 
   ++
   show (fromIntegral sum / fromIntegral count) ++  downloads/day\n)
 
  match = matchRegex $ mkRegex ([0-9]+) Windows ex
 
  countDownloads (s, c) l =
  case match l of
  Just [n] - (s + read n, c + 1)
  Nothing - (s, c)

countDownloads p@(Pair s c) l =
case match l of
Just [n] - Pair (s + read n) (c + 1)
Nothing - p



-Udo


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


Re: [Haskell] Re: Trying to install binary-0.4

2007-10-21 Thread Udo Stenzel
Duncan Coutts wrote:
 New tarball releases of Cabal-1.2.1, bytestring-0.9, binary-0.4.1, tar
 and others (zlib, bzlib, iconv) will appear on hackage in the next few
 days.

I just tried one of them, iconv.  First it wants a recent cabal; that's
fine, I installed the darcs version.  Then I get this:

| Codec/Text/IConv.hs:64:17:
| Could not find module `Data.ByteString':
|   it is a member of package bytestring-0.9, which is hidden

Okay, it obviously tries to be smart, but doesn't know that I upgraded
to a separate ByteString library.  So I take out the gunk about
'flag(bytestring-in-base)' and try again:

| Setup: At least the following dependencies are missing:
| base 2.0||=2.2

Of course that was to be expected, since I have base-2.0 hacked to not
get in conflict with bytestring-0.9, and you (Duncan) couldn't possibly
anticipate this (or could you?).  Now what am I supposed to do?  Give my
messed up base a new version number?  (Which one?)  Rewrite every single
cabal file, hoping that they never become Turing complete turning the
exercise into a reverse engineering fest rivaling the ICFP contest?
Bite the bullet and install GHC from darcs?

For the time being, I'll go with 'ghc --make'.  And I think that cabal
configurations are an exceptionally bad idea carried to perfection.
They make things worse, not better.  (And that's just GHC 6.6... I don't
want to even think about what happens on Hugs, JHC and YHC.)

What would it take to talk you into giving up on supporting the broken
base-2.0 and incorporating a patch to unbreak it into the bytestring
setup?  Can I stop the insanity by simply writing that patch?


 So all will not be plain sailing for the first few weeks after
 ghc-6.8 comes out as maintainers update their packages. People will have
 to be patient and/or stick to ghc-6.6 for a bit.

Okay, so now we have *three* almost-stable versions of GHC in wide
circulation, all of them broken in different ways with respect to cabal
packages.  I feel tears welling up...


-Udo


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


Re: [Haskell] Re: Trying to install binary-0.4

2007-10-18 Thread Udo Stenzel
Don Stewart wrote:
 If I understand correctly, the main issue for Udo is simply that the
 MonadFix instance is required by his code, and isn't available in binary
 0.3 -- the version to be used on earlier GHCs. Is that right Udo?

No, the issue is that nothing works.  It turns out that I actually
wanted the MonadFix instance for something unrelated, only at about the
same time (and using runGetState, I can even work around that if I
want).  Here's the story of how not to intall tar-1.0 on GHC 6.4:

- I'm on a Ubuntu system, GHC 6.4 has been installen from .deb packages,
  my local GHC config is empty.

- I unpack tar-1.0 and try to run Setup configure on it

  = module Distribution.Simple does not export UserHooks(confHook)

- I need a more recent cabal, my choice is cabal-1.1.6.2, which install
  flawlessly.

- back to tar-1.0

  = base = 2.0 is required,
  = unix-1.0 is used for unix-any

  This is already messed up, tar wants unix-compat, not unix-any.  (Or
  is it?  See below.) Apparently, it is a fatal error to have a dash in
  any package name.  This explains why System.PosixCompat will never be
  found, no matter how often I install it.

- Since binary is also needed, I'll now install binary-0.3

  = could not find module Data.ByteString

- So I need ByteString.  It is not in Hackage.  Googling around leads me
  to http://www.cse.unsw.edu.au/~dons/fps.html, where I download
  fps-0.7, since fps is what binary.cabal mentions in a comment.

- fps-0.7 install flawlessly.

- back to building binary

  = constructor LPS is not found

- no newer fps is available, I get bytestring from darcs

- bytestring wants a newer cabal.  But my patience is already running
  out, so instead I edit the cabal file, and it installs.

- back to building binary

  = module Data.ByteString.Base not found


At this point I'm fed up, delete the whole setup and go back to the
one I already hacked up to work with binary-0.4.  Getting binary-0.4
and hammering it into shape to run on GHC 6.4 would have been the next
step anyway, and after that, tar-1.0 needs to be edited to refer to
System.Posix and then it would probably work.  I dimply remember that it
was also impossible to install unix-compat because the wrong cabal was
picked up and I ended up throwing out unix-compat completely.

Okay, summarizing, what did cabal do for me?  Well, it helped me install
a new version of cabal and an obsolete version of something else.
Sorry, but this whole experience is a huge turnoff.  With things going
that smoothly, I'm better off using ghc --make and distributing the
stuff I cannot rely on directly with my code.

Now here's the story for GHC 6.6:

- I'm on Debian testing, GHC 6.6.1 is installed, cabal is 1.1.6.2.  I'm
  in a fresh user account without local additions to GHC.

- download tar-1.0, unpack and configure.  Binary is needed.

- download binary-0.3, installs flawlessly.

- back to tar-1.0.  Now this is weird:

 = Dependency unix-any: using unix-2.1
 = cannot satisfy dependency unix-compat=0.1

 Why does it want *both* unix and unix-compat?  The .cabal file mentions
 only one of them, unix-compat.

- download unix-compat, installs flawlessly.

- tar works now


So things look a lot better on GHC 6.6, but only because I used
binary-0.3 instead of 0.4, and I did this only because Don recently
mentioned it.  Suppose I tried binary-0.4 (because I want 'instance
MonadFix Get' or because I don't know better):

- dependencies on split base cannot be fulfilled.  I have to edit the
  cabal file.

- bytestring needs to be updated

- a new cabal is needed

- the description of base has to be patched to remove the conflict with
  base

- binary-0.4 installs now

- try to configure tar-1.0

  = Could not find module `Distribution.Setup'


This is no fun at all.  Not only do I have to work around the
incompatible changes in base, the interface of Cabal also changed in an
incompatible way.


-Udo
-- 
My teachers could easily have ridden with Jesse James for all the time
they stole from me. -- Richard Brautigan


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


Re: [Haskell] Re: Trying to install binary-0.4

2007-10-14 Thread Udo Stenzel
Bjorn Bringert wrote:
 The tar package uses System.PosixCompat from the unix-compat package  
 to also work under non-posix systems (read Windows). This dependency  
 is listed in the tar.cabal file (see http://hackage.haskell.org/ 
 packages/archive/tar/0.1/tar.cabal). System.Posix was never renamed.
 [...]
 Why not just install unix-compat? It is listed as a dependency after  
 all.

Actually Windows claims to be a Posix system, too (not that I really
believe it or care much).  Iirc, unix-compat blew up on GHC 6.4, too,
again by picking up the wrong Cabal.  I'll check this again tomorrow
(don't have access to that machine right now).

Anyway, I don't see why something that provides the same functionality
as something else needs a different name.  With the mechanism of
something like apt (Provides, Conflicts, Replaces, ...) I'd have no
problem, but Cabal doesn't do that stuff.

Maybe it should, though.


 I seem to be able to build the tar package against binary-0.3. What  
 exactly is the error that you are getting?

No instance MonadFix Get (from memory, I can check this again once I
calm down...)

 
 By the way, I don't think that users of open source software have a  
 right to be pissed off, or at least authors don't have an obligation  
 to care about them being pissed off. What users do have is a right to  
 submit patches.

No sir, I always have a right to be pissed off.  What I don't have is a
right to demand anything from you.  The problem with patches is how do
you patch something as thoroughly messed up as 'base-2.0' vs. 'base-2.1'
vs. 'base-2.1.1'?  If I saw a way to fix it, you'd already have a patch,
but all I have right now is a GHC with an afroengineered package
configuration and a mutilated tar package...

 
 That said, I agree that the constantly changing packages make it hard  
 to keep dependencies up to date.

Moreover, the conical place to find packages is Hackage, right?  Tar is
there, unix-compat is and binary is, too.  But bytestring is missing.
Which means you have to hunt down bytestring separately, and
cabal-get will fail, too.  It also means that some of these packages
cannot work on any released version of GHC.


 I guess that this is price we pay for moving quickly.

Is it impossible to move quickly on GHC 6.4?


-Udo


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


Re: [Haskell] Re: Trying to install binary-0.4

2007-10-14 Thread Udo Stenzel
Ian Lynagh wrote:
 People interested in making it easy to use new versions of packages with
 old compiler releases can make a small script that installs empty Cabal
 packages called bytestring, containers, array, etc.

That completely misses the fact that bytestring cannot be upgraded, no
matter how many fake packages are available.


-Udo


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


Re: [Haskell] Re: Trying to install binary-0.4

2007-10-13 Thread Udo Stenzel
Simon Marlow wrote:
 - Provide a known good cabal.  Make sure it installs on GHC 6.6 and 6.4.
 
 Cabal 1.2 works all the way back to GHC 6.2.  The recommended way to build 
 new packages with an old GHC will be to upgrade Cabal first.

Can it be installed by a user?  Because I think my GHC 6.4 always picks
up Cabal-1.0, which is installed globally.  tar-1.0 then fails through
not finding Distribution.Simple.

 - Refrain from renaming stuff.  System.Posix is a fine name.
 
 Who renamed it?  It's still called System.Posix AFAIK.

tar references System.PosixCompat, which apparently comes from a library
called unix-compat.  I have no idea why the lib isn't just called unix
and the modules not System.Posix.*, for tar works fine with
System.Posix.*.

 
 Personally I object to ECT, it's too heavy.  I believe versioning belongs 
 in the package system where it currently is.

Well, versioning of shared libraries belongs into the dynamic linker,
where it currently is.  My gut says, Cabal is more like ld than apt-get.
Of course I don't care for the solution ultimately implemented, as long
as it works.  However, without guidelines for what can be changed
between versions of packages, nothing will.

 
 The main problem you seem to be running into is that base previously 
 contained bytestring, but you need to upgrade bytestring in order to use 
 binary, right?

Actually I'm more annoyed by the many small and unneccessary stumbling
blocks right now.  I mean, you could easily put an instruction into the
INSTALL file that says if you're on GHC 6.4 or 6.6, register this
replacement configuration for base to sanitize it.  You cannot write
if you're on 6.4, edit all references to System.PosixCompat, unless you
already installed unix-compat, and you absolutely need binary 0.4,
unless you're on 6.4, where you want binary 0.3 but need to patch it so
it has instance MonadFix Get, etc. pp. there, since something like that
just pisses off your users.

But yes, base and bytestring not liking each other is the showstopper,
since base can neither be hidden nor upgraded.  


 In that case, I think a reasonable hack is to modify the package 
 configuration for base to move Data.ByteString from exposed-modules to 
 hidden-modules (I'd be wary about removing it altogether).  Perhaps the 
 bytestring Setup.lhs should do this automatically when registering?

First off, this should be documented.  Having bytestring's Setup do the
messy registering would be a good solution, I think.  A better one than
a gazillion Cabal configurations, I might add.


-Udo


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


Re: [Haskell] Re: Trying to install binary-0.4

2007-10-12 Thread Udo Stenzel
Udo Stenzel wrote:
 - install exactly one version of cabal, 1.1.6.2, and *remove* all
   others,
 - ask ghc-pkg for the description of base, then edit Data.ByteString out
   of that and re-register it,

I forgot, I also tried tar-1.0 on GHC 6.6, and had the same problem
there.  Even after updating Cabal, there was no way to install
'bytestring' due to the conflict with 'base'.  A modified package
description for 'base' helped.

The reason that tar absolutely wants new stuff is 'instance MonadFix
Get', which is not in binary-0.3.  If you absolutely want users of GHC
6.6 to stick with binary-0.3, then you should provide a maintenance
release binary-0.3.1.  And we're back to Eternal Compatibility in
Theory...


-Udo


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


[Haskell] Re: Trying to install binary-0.4

2007-10-11 Thread Udo Stenzel
Don Stewart wrote:
 Since you're not using ghc 6.8, you should use binary 0.3 :)

That was PC for sorry, GHC 6.6 is no longer supported and don't even
ask about 6.4

The other day I tried to install the tar library on a GHC 6.4.  It's
nearly impossible.  The old base library gets in the way of installing
bytestring, binary 0.4 absolutely needs bytestring 0.9 and tar
absolutely needs binary 0.4, but still won't compile because
System.Posix is now called System.PosixCompat which actually makes it
incompatible.  Oh, and everything needs a new cabal, but the setup
scripts still picks up the wrong one (apparently, since
Distribution.Simple is supposed to be there but GHC doesn't find it).

Wanna know the solution?

- install exactly one version of cabal, 1.1.6.2, and *remove* all
  others,
- ask ghc-pkg for the description of base, then edit Data.ByteString out
  of that and re-register it,
- install bytestring 0.9,
- install binary 0.4,
- edit the Setup.lhs of tar (it still won't run, even though it should),
- edit the source of tar, changing System.PosixCompat to System.Posix,
- install it.

Should I mention that this is made even more difficult by not being root
on the machine in question?

All this happened with libraries that look as if they are supposed to be
stable, but absolutely nothing works right out of the box.  Oh, and
Cabal Configurations will make it worse, not better.

Here's what should be done, imho:

- Rename 'base' ASAP and especially before GHC 6.8 comes out, call it
  'foundation' or something else.  If you want to keep the name 'base',
  make sure Cabal considers 'base-2.x' a different library than
  'base-3.x'.
- Provide a replacement configuration for GHC 6.6 and 6.4 (yes, that one
  is still alive!) that removes the conflict between 'base' and
  'bytestring' and pretends to provide bytestring, containers, array,
  etc.
- Provide a known good cabal.  Make sure it installs on GHC 6.6 and 6.4.
- Start fixing dependencies.
- Refrain from renaming stuff.  System.Posix is a fine name.
- Refrain from always using the latest interface of everything.

While we're at it, the ability to have multiple versions of a library
installed under the same name is a recipe for desaster, too.  It should
be dropped, instead implementing Eternal Compatibility in Theory by
encoding version numbers in module names.

Sorry for the rant, but the situation was actually better before Cabal
tried to fix everything and in the process broke both versions of GHC
that are in widespread use right now.


-Udo



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


Re: [Haskell-cafe] XmlSerializer.deserialize?

2007-06-26 Thread Udo Stenzel
Hugh Perkins wrote:
 Is reflection hard in Haskell?  In C# its easy, and its one of the most
 powerful features of C#

That's another way of saying that the truly powerful features are
missing from C#...


 Yes, but I'm kindof stuck giving useful input to makeConstrM, so if
 anyone has any ideas?

You mean makeConstr?  Well, you don't call that at all.  But you do call
fromConstrM, and if you don't have suitable input for that, that's when
you realizie that you should have written the constructor name or index
when serializing.

 runM' :: (MonadState [String] m, Monad m, Data a) = m a
 runM' = do
value - gets head
modify tail
-- then one of: (pick the non-working function of your choice ;-)  :
-- return read (fromJust value)
-- return (fromJust $ cast value )
-- return (fst $ head $ gread( ( ++ value ++ ) ) )
-- return (fromConstrM runM' constr)
-- return (fromConstr contr)

Of course not.  Wild guesswork will get you nowhere, instead you should
read the second SYB paper at http://homepages.cwi.nl/~ralf/syb2/


-Udo


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


Re: [Haskell-cafe] dangerous inlinePerformIO in Data.Binary(?)

2007-06-17 Thread Udo Stenzel
Roberto Zunino wrote:
 Floating out (newBuffer defaultSize) as in
 
 | foo = newBuffer defaultSize
 |
 | toLazyByteString m = S.LPS $ inlinePerformIO $ do
 | buf - foo
 | return (runBuilder (m `append` flush) (const []) buf)
 
 would still be safe, AFAICS. Floating out buf instead should be 
 prevented by the implicit RealWorld parameter.

That's actually what I meant, though I wouldn't describe it as floating
out buf, since that's not the only thing that happens, and it is not
prevented.  Unfolding a bit gives you something like

| toLazyByteString m = S.LPS (
|   case newBuffer defaultSize RealWorld# of { ( buf, world1 ) -
|   runBuilder blahblah buf } )

since the scrutinee of the case expression is constant, it can float
anywhere:

| bufAndWorld1 = newBuffer defaultSize RealWorld# 
| 
| toLazyByteString m = S.LPS (
|   case bufAndWorld1 of { (# buf, world1 #) -
|   runBuilder blahblah buf } )

and that is bad.  It might simplify even further, making the resulting
bug even harder to detect.  The only reason this doesn't happen with
unsafePerformIO or runST is that it is not inlined.  One of them even
has a comment in the GHC library sources to the effect that the NOINLINE
pragma was forgotten, which resulted in a subtle and ugly bug.


-Udo
-- 
If you cannot in the long run tell everyone what you have been doing,
your doing was worthless.
-- Erwin Schrödinger


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


[Haskell-cafe] dangerous inlinePerformIO in Data.Binary(?)

2007-06-14 Thread Udo Stenzel
Greetings,

I was trying to understand the magic inside Data.Binary, and found two
somewhat suspicious uses of inlinePerformIO, which imho has a far too
innocuous name:

| toLazyByteString :: Builder - L.ByteString
| toLazyByteString m = S.LPS $ inlinePerformIO $ do
| buf - newBuffer defaultSize
| return (runBuilder (m `append` flush) (const []) buf)

Why is this safe?  Considering the GHC implementation of IO, isn't there
a real danger that 'newBuffer defaultSize' is floated out and therefore
every invocation of 'toLazyByteString' starts out with the same buffer?
Isn't that exactly the reason why unsafePerformIO and runST are declared
NOINLINE?

The other occurence is:

| unsafeLiftIO :: (Buffer - IO Buffer) - Builder
| unsafeLiftIO f =  Builder $ \ k buf - inlinePerformIO $ do
| buf' - f buf
| return (k buf')

which might be safe, since 'f buf' cannot float out of the lambda which
binds 'buf', but still, all this stuff is inlined, something constant
might get plugged in the place of buf and the result might be floated
out to give us an even harder to find Heisenbug.

Am I missing something and this is actually safe?  If not, what can be
done to avoid such errors?  I'd really hate to find building blocks that
crumble under pressure in standard libraries...


-Udo



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


Re: [Haskell] Fwd: Mutually dependent functions

2007-06-12 Thread Udo Stenzel
Michael Speer wrote:
 test x y = ( World , x , x ++   ++ y )
 main = let ( a , b , c ) = test Hello a
   in do
   print $ ( a , b , c )

This works, but in your code you actually wrote

  let ( ( a, b, c ), ( d, e, f ), ( g, h, i ) ) = ( foo, bar, baz )

with the right side involving the stuff on the left.  This won't work;
for Haskell to bind values to a, b, and so on, it has to examine the
value being matched to check whether it is really a tuple (and not _|_).
You can defer the check, and that's called a lazy or irrefutable pattern
binding:

  let ( ~( a, b, c ), ~( d, e, f ), ~( g, h, i ) ) = ( foo, bar, baz )

This would work.  The reason you didn't run into this earlier (and why I
apprently forgot a tilde) is that let-bindings are always lazy, as if
you had put a tilde there, but this doesn't hold for nested patterns.
This means that not tupling your three functions and instead using a
group of bindings would work, too, and look prettier anyway:

  let ( a, b, c ) = foo
  ( d, e, f ) = bar
  ( g, h, i ) = baz

Yes, let groups allow mutually recursive bindings, the same is true for
where clauses and mdo blocks.

 Is this a known problem that will one day be resolved, or is it
 considered beyond the scope of the language?

Neither, it's supposed to be this way.  Btw, you might consider posting
a _minimal_ code example when illustrating your next problem.  I didn't
even try to run your big chunk of code, so the above is only guesswork.


-Udo
-- 
Always call a spade a spade, except in classes that both dig holes and
play bridge.
-- a guideline for Eiffel programmers


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


Re: [Haskell-cafe] Re: Just for a laugh...

2007-06-02 Thread Udo Stenzel
Andrew Coppin wrote:
 Note that the challenge asks for the internal bitmap representation of 
 an IEEE double-precision integer

Actually it didn't.  It asked for the machine's internal representation
of a double precision float, and you are not guaranteed that this
representation conforms to IEEE 7-whatsit.  It is beyond me what you're
going to do with that unspecified representation, though.

 Did I mention that this is a silly challange yet?

Silly, yes.  Challenge, no.  We can do the same the C++ guy did, it's
only a question if we need to.  Something close to this:

| import Foreign.Marshal
| import Foreign.Ptr
| import Data.Word
| 
| valueToBytes :: Storable a = a - IO [Word8]
| valueToBytes a = with a $ \p - peekBytes (castPtr b) (sizeOf a)

Reversing the list and hammering it down to single bits is trivial after
that.


-Udo
-- 
Structure is _nothing_ if it is all you got. Skeletons _spook_ people if
they try to walk around on their own. I really wonder why XML does not.
-- Erik Naggum


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


Re: [Haskell] Re: Newbie: what are the advantages of Haskell?

2007-04-28 Thread Udo Stenzel
Michael T. Richter wrote:
 I wish I knew the language better so I could start working on
 those libraries.

Which ones?  those libraries cannot come into existence until someone
says what's actually missing.  (The bulk of CPAN is crap and is
certainly not worth being reimplemented.)


-Udo
-- 
Object-oriented programming is an exceptionally bad idea which could
only have originated in California.  -- E. W. Dijkstra


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


Re: [Haskell] Newbie: what are the advantages of Haskell?

2007-04-28 Thread Udo Stenzel
[EMAIL PROTECTED] wrote:
 what are the advantages of haskell over semi-functional programming languages
 such as Perl, Common Lisp, etc.?

A fundamental building block that is superior in maintainability and
reusability to objects and procedures, a type system that is actually of
help and not a hindrance, and mathematical purity.


 What are the mysterious side effects which are avoided by using Haskell, 
 which
 everyone talks about? Null pointers?

Side effects are changes made to the environment by a procedure (beyond
returning its result), particularly those that you forgot about, that
get executed in the wrong order, and that change values under your feet
when you least expect it.

 
 Don't you ever get null pointers in Haskell, including when doing IO?

What's a pointer?  But we do get bottoms sometimes (rarely, the type
system often prevents you from stumbling over them), which is simply the
price you have to pay if you want a Turing-complete system.


 Aren't Haskell's advantages outweighed by its complexity (Monads, etc.) and
 rigidity?

You know about Design Patterns?  *Those* are complex.  Dozens of
Rube-Goldberg-Machines designed to circumvent inadequacies in languages
that should have been abandoned 20 years ago.  

If you try to apply the Design Patterns book to Haskell, half of the
patterns vanish, because they solve non-problems, most of the rest
becomes much simpler and only a few are added.  One particularly simple
new pattern is the Monad, which the gang of four couldn't discover for
lack of a language powerful enough to express it.  (Monad easily
subsumes Composite, generalizing and simplifying it in the process.  The
application of Monad to IO is straight forward, and then Monad also
subsumes Command.)

Btw, there's nothing rigid about Haskell.  I can adapt my Haskell code
much quicker to new requirements than is possible with either C or Perl,
and the Haskell code has the added benefit of still working after the
change.

 
 Last but not least, I would like to learn from those among you who are former
 PERL developers, why you switched to Haskell.

Because Perl is a royal PITA and Haskell is not.  Haskell also has no
inclination to yell ARRAY(0xdeadbeef) or no method 5 in package
FooImpl at me instead of producing sensible output (see also: type
system).


-Udo
-- 
I can ALWAYS build faster code if it doesn't have to work. (unknown source)


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


Re: [Haskell-cafe] run-time type testing in haskell?

2007-04-28 Thread Udo Stenzel
Eric wrote:
 (1) Have Handlers implement a method handle(m: Msg). To add new types of 
 message, we declare message types which extend Msg. The Handler then 
 uses runtime type testing to decide how to deal with each message. The 
 advantage of this design is that we can add new Handler and new Msg 
 types without recompiling the Dispatcher.

Note however that the type of the handle method is a lie (your handlers
don't actually accept arbitrary messages).  I guess, you actually  want
a polymorphic Dispatcher, which will actually turn out to be a
function.  Of course, you give insufficient information to actually
solve your problem.

 
 Type classes allow us to adopt approach (0) in Haskell, but don't seem 
 to allow approach (1)

I consider that a good thing.


-Udo


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


Re: [Haskell-cafe] Is Excel a FP language?

2007-04-25 Thread Udo Stenzel
Albert Y. C. Lai wrote:
 I say Excel is a functional language. If there needs to be the quoted 
 distinction, fine: Excel the language is a functional language, and 
 Excel the application is an interpreter of said language.

Excel has functions, but does it treat functions as it treats other
data?  I don't think so, and that makes it non-functional
(dys-functional?).  As for VB... that may be functional, in the same
sense as XSLT is: if you step back and squint, it almost looks vaguely
like a functional language.
 
 (Does the opposition self-consistently distinguish Perl the language 
 from perl.exe the interpreter?)

Only perl can parse Perl.  (Yes, they do.)


-Udo
-- 
Science is like sex - sometimes something useful comes out of it, but
that's not what we are doing it for. -- Richard Feynman


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


Re: [Haskell-cafe] Re: Haskell version of Norvig's Python Spelling Corrector

2007-04-24 Thread Udo Stenzel
Pete Kazmier wrote:
   train:: [B.ByteString] - WordFreq
   train words = frequencyMap
   where
 frequencyMap = foldr incWordCount M.empty words
 incWordCount w m = M.insertWith (+) w 1 m
 
 So is 'incWordCount' strict in its second argument?  I'm still not
 sure exactly what that means.

Yes.  incWordCount is strict in its second argument since

incWordCount x undefined == undefined

Of course you cannot see that from the definition of incWordCount alone,
this depends on the behavior of M.insertWith.  

 According to the wiki page, if it is
 strict in the second argument, I should have used foldl' instead of
 foldr.

Remember that the difference between foldr and foldl is not one between
left and right; both have to recurse from the left.  But foldr is normal
recursion, while foldl is accumulator recursion.  You obviously wanted
an accumulator, and it should usually be strictly evaluated.

There is another bug of this sort in your code.  Consider

 incWordCount w m = M.insertWith (+) w 1 m

There is no reason to evaluate the sum inside the map, instead an
unevaluated thunk is put in there.  Unfortunately, you need to take the
long way of using M.lookup and M.insert to build a strict replacement
for M.insertWith.  (A strict variant of Data.Map would be useful here,
unfortunately, there is none.)


-Udo
-- 
Streitigkeiten dauerten nie lange, wenn nur eine Seite Unrecht hätte.
-- de la Rochefoucauld


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


Re: [Haskell-cafe] Re: Haskell version of Norvig's Python Spelling Corrector

2007-04-24 Thread Udo Stenzel
Bryan O'Sullivan wrote:
 Udo Stenzel wrote:
 
 There is another bug of this sort in your code.  Consider
 
 incWordCount w m = M.insertWith (+) w 1 m
 
 There is no reason to evaluate the sum inside the map, instead an
 unevaluated thunk is put in there.
 
 Would not Data.Map.insertWith' do the trick?

Oops, you're right, this is a fairly recent addition.  


-Udo
-- 
Walk softly and carry a BFG-9000.


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


Re: [Haskell-cafe] Why Perl is more learnable than Haskell

2007-04-12 Thread Udo Stenzel
kynn wrote:
 (I don't need elegant
 factorial or Fibonacci functions in my everyday work.)

I think you do.  Most of your utility programs probably fit into the
simple frame of

main = interact $ unlines . map f . lines

for suitable f.  Of course, f is hardly ever the factorial function, but
it is a function.  My guess is, you think you just wanted a loop when
in reality you need to lift a function to work over a list.


 Or I can always wait until I retire; then I'll probably have a sufficiently
 long stretch of free time in my hands

You may need patience, too.


-Udo


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


Re: [Haskell-cafe] runInteractiveCommand

2007-04-09 Thread Udo Stenzel
Sergey Perminov wrote:
 I wished to get output of unix commands in haskell code.
 
 So i wrote:
 --
 import System.IO
 import System.Process
 
 eval :: String - IO String
 eval s = do (_,hOutput,_,hProcess) - runInteractiveCommand s
   sOutput - hGetContents hOutput
   waitForProcess hProcess
   return sOutput
 --
 
 'eval' works well if output of evaluated command is less than 64Kb.
 If not - 'eval' never ends.
 
 What may cause this problem?

The laziness of hGetContents does.  As long as nothing needs sOutput, it
will not be read, the process becomes stuck on a clogged pipe,
waitForProcess does not return and therefore nobody needs sOutput.

There are two ways out: you can leave the waitForProcess out and trust
that it eventually terminates or you can make eval more strict:

 eval :: String - IO String
 eval s = do (_,hOutput,_,hProcess) - runInteractiveCommand s
 sOutput - hGetContents hOutput
 foldr seq (waitForProcess hProcess) sOutput
 return sOutput

...but you most certainly don't want to buffer large amounts of output
in a String.  Depending on your actual problem, there may be far better
solutions, such as

 eval :: String - (String - IO b) - IO b
 eval s k = bracket (runInteractiveCommand s)
(\(_,_,_,hProcess) - waitForProcess hProcess)
(\(_,output,_,_) - hGetContents output = k)

You will still run into problems if the called process writes to stdout,
though.


-Udo
-- 
You live and learn. At any rate, you live.
-- Marvin, the paranoid droid


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


Re: [Haskell-cafe] newbie concatenating monad question

2007-03-24 Thread Udo Stenzel
Leandro Penz wrote:
 buildStuff =
   func1 ++ func2 ++ func3 ++ func4
 
 My idea is to have a monad with a concatenating , so that I can:
 
 bulidStuff = do
   func1
   func2
   func3
   func4

buildStuff = concat [
func1,
func2,
func3,
func4 ]

Remember, functional programming was already useful without monads.

 
-Udo
-- 
It is the mark of an educated mind to be able to entertain a thought
without accepting it. 
-- Aristotle


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


Re: [Haskell-cafe] Newbie vs. laziness

2007-03-21 Thread Udo Stenzel
Alex Queiroz wrote:
 
 I don't quite get how ($!) works. I have this function:
 
   ids - liftM (map fromSql . concat ) $! quickQuery con query []

There's a difference between an IO action and the result of said action,
and similarly there's a difference between making sure an action is
evaluated and making sure the result of executing the action is
evalulated.  You did the former.

If you really wanted to evaluate the result to WHNF (only) before
finishing dbCreateIndices, this would work:

   ids - liftM (map fromSql . concat ) $ quickQuery con query []
   ids `seq` return $ IntMap.fromList $ zip ids [0..]

But you probably need to evaluate the complete list, so you need more:

   ids - liftM (map fromSql . concat ) $ quickQuery con query []
   foldr seq () ids `seq` return $ IntMap.fromList $ zip ids [0..]

Of course, if you insist on using ($!), that's also possible:

   ids - liftM (map fromSql . concat ) $ quickQuery con query []
   return $ IntMap.fromList $ flip zip [0..] $! foldr seq ids ids


HTH.

-Udo.


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


Re: [Haskell-cafe] LGPL libraries

2007-03-06 Thread Udo Stenzel
Neil Mitchell wrote:
 As others have said though, I wouldn't worry overly about it. The
 whole concept of static linking being wrong, but dynamic linking being
 fine, when you can flip between the modes just by changing compiler,
 is just silly. You don't infringe (or uninfringe) copyright with a
 command line flag.

But you do infringe copyright by shipping a program including an LGPL'd
library in such a way that the user cannot easily exchange said library
for a newer version, thereby violating the LGPL in letter as well as in
spirit.  (Duncan should have chosen another license if he intended to
allow Gtk2Hs being linked to proprietary software and then distributed.)


-Udo
-- 
The Turing test is turning out not to be a test of artificial
intelligence, but of human stupidity.
-- seen on slashdot.org


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


Re: [Haskell-cafe] Re: nested maybes

2007-02-05 Thread Udo Stenzel
Benjamin Franksen wrote:
 Udo Stenzel wrote:
  Sure, you're right, everything flowing in the same direction is usually
  nicer, and in central Europe, that order is from the left to the right.
  What a shame that the Haskell gods chose to give the arguments to (.)
  and ($) the wrong order!
 
 But then application is in the wrong order, too. Do you really want to write
 (x f) for f applied to x?

No, doesn't follow.  Unix pipes also read from left to right, even
though programs receive their arguments to the right of the program
namen, and that feels totally natural.


-Udo


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


Re: [Haskell-cafe] nested maybes

2007-02-04 Thread Udo Stenzel
J. Garrett Morris wrote:
 On 2/4/07, Udo Stenzel [EMAIL PROTECTED] wrote:
  exists s wmap = isJust $ Map.lookup (sort s) wmap = find (== s) . snd
 
 If you're going to write it all on one line, I prefer to keep things
 going the same direction:

Hey, doing it this way saved me a full two keystrokes!!!1

Sure, you're right, everything flowing in the same direction is usually
nicer, and in central Europe, that order is from the left to the right.
What a shame that the Haskell gods chose to give the arguments to (.)
and ($) the wrong order!

 exists s wmap = isJust $ find (==s) . snd = Map.lookup (sort s) wmap
 
 Normally, from there I would be tempted to look for a points-free
 implementation, but in this case I have a strong suspicion that would
 simply be unreadable.

Well, depends on whether we are allowed to define new combinators.  I
sometimes use

-- Kleisli composition
infixl 1 @@
(@@) :: Monad m = (a - m b) - (b - m c) - (a - m c)
f @@ g = join . liftM g . f

and the resulting

 exists s = Map.lookup (sort s) @@ find (== s) . snd  isJust

isn't all that bad.  (To be read as: one can get used to it.)  I also
think, (@@) and () belong in the Prelude and () at type ((a-b) -
(b-c) - (b-c)) should be known under a shorter name.  Unfortunately,
everything short but (?) is already taken...  

Of course, the remaining variable s could also be transformed away,
but that's really pointless.


-Udo
-- 
Never confuse motion with action. -- Ernest Hemingway


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


Re: [Haskell-cafe] Trouble understanding records and existential types

2007-01-26 Thread Udo Stenzel
John Ky wrote:
 On 1/25/07, BBrraannddoonn SS.. AAllllbbeerryy 
 KKFF88NNHH [EMAIL PROTECTED] wrote:
  I'm probably missing something, but:
 
  (a) Why not:
 
  data ANode = Branch { name :: String, description :: String,
  children :: [AnyNode] }
  | Leaf { name :: String, value :: String } -- this reuse
  is legal
  -- leaving Node available if you still need it
 
 Would I be able to this?
 
getLeaves :: ANode - [Leaf]


data Branch = Branch { name :: String, description :: String, children :: 
[AnyNode] }
data Leaf   = Leaf { name :: String, value :: String }

data AnyNode = Either Branch Leaf


Now if you absolutely insist on overloading the 'name' identifier, you
can do this:


data Branch = Branch { brName :: String, description :: String, children :: 
[AnyNode] }
data Leaf   = Leaf { lName :: String, value :: String }

data AnyNode = Either Branch Leaf

class HasName a where name :: a - Name
instance HasName Branch where name = brName
instance HasName Leaf where name = lName
instance HasName AnyNode where name = either brName lName


Okay, you lose record update and construction syntax for AnyNode, but I
don't think that's so much of a loss.

On a side note, all this has nothing to do with OOP.  If you wanted to
simulate objects, you would replace case by polymorphism, but I can't
demonstrate how to do that, since none of your objects has any
methods.


-Udo.
-- 
Technology is a word that describes something that doesn't work yet.
-- Douglas Adams, JavaOne keynote, 1999


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


Re: [Haskell-cafe] State monad strictness - how?

2007-01-11 Thread Udo Stenzel
Yitzchak Gale wrote:
 You're right, it is not in the docs. I don't think anyone would
 have planned it that way. StateT is strict only because there
 happens to be a line in a do-expression that looks like:
   (a, s') - runStateT m s
 The tuple pattern-match causes the strictness.
 That appears accidental, so it seems to be just an honest bug.

I agree that this is an accident, but the bug is in lazy State, for
three reasons:

- Being strict in the (result,state) pair does not for the evaluation of
  either result or state.  Not being strict could only ever be useful
  for a following action that made no use of either state or result, and
  I have a hard time imagining why you'd ever want to write such a
  beast, let alone in monadic style.  In fact, an unboxed tuple would be
  even better.

- Assuming that the State monad is lazy in the tuple, and you need to be
  strict in the state component, you are hosed.  No amount of 'seq' will
  help you.  On the other hand, were it strict and you needed it to be
  lazy, you could achieve that by manually boxing the data involved.

- (=) should also be head strict in the state component.  Again, if
  this is wrong, you can repair it.  If laziness turns out wrong, you
  can't.  Moreover, for most data types that you want to build lazily,
  especially lists, head strictness doesn't make a difference, as long
  as the tail is lazily evaluated.  For data where you need strictness,
  such as integers or tuples of them, having strictness available make
  all the difference.

I'd be fine with laziness being configurable, of course, but if it
isn't, I want strict state.  Come to think of it, it's probably just a
bad idea that _|_ and (_|_,_|_) are different things.


-Udo
-- 
The Seventh Commandments for Technicians:
Work thou not on energized equipment, for if thou dost, thy
fellow workers will surely buy beers for thy widow and console
her in other ways.


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


Re: [Haskell-cafe] State monad strictness - how?

2007-01-11 Thread Udo Stenzel
Ross Paterson wrote:
 This (like StateT) gives you strictness in the pair, but doesn't give
 the strictness in the state that the original poster wanted.

I think the OP wanted both.  If State is lazy in the pair, a long chain
of the form (a = (b = (c = ... = z))) gets build up and blows
the stack if it finally turns out that yes, all these steps are needed.
Worse than that, there's no way to correct this without changing the
definition of (=).

Laziness in the state component is annoying at times, but not as bad.
You can recover strictness by writing

put $! x
get = (put $!) . f

instead of

put x
modify f

provided that (=) is already strict in the pair.  (It gets even more
ugly if the state is a Data.Map that needs to be updated strictly, in
which Data.Map.update also doesn't work, even combined with the above
modifications.)


-Udo
-- 
The only problem with seeing too much is that it makes you insane.
-- Phaedrus


signature.asc
Description: Digital signature
___
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-03 Thread Udo Stenzel
Yitzchak Gale wrote:
 Here is a concrete example:
 
 Let's say you want to shuffle a large list randomly,
 within a larger application that lives inside some
 MTL monad stack. Among other things, your monad
 m satisfies (RandomGen g, MonadState g m), perhaps
 after a lift.
 
 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.
 
 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)

But why would you even want to do this?  It's ugly and cumbersome.
You'd plug a runST in there and get 

shuffle :: RandomGen g = [a] - g - ([a], g)

or lift it into a state monad.  Telling the world that you messed with
imperative code inside is completely pointless, since the only thing you
could possibly do with the result anyway is apply runST to it.


 Wouldn't it be nice if instead you could just write:
 
 shuffle :: (RandomGen g, MonadState g m) = [a] - m [a]
 shuffle = stToState . shuffleST

It seems, what you really want is

shuffleST :: RandomGen g = [a] - StateT g ST [a]

No need to stick the generator into a mutable variable.  Maybe you even
want a MonadST class, analogous to MonadIO.


 Uhm... use MonadState in the first place?
 
 You mean use ST in the first place.

No, I don't.


-Udo


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


Re: [Haskell-cafe] Arrays performance

2007-01-01 Thread Udo Stenzel
[EMAIL PROTECTED] wrote:
 I'm timing the following script.I'm not expert to evaluate th O'ness
 of this code, I hope someone can do it.  The program clusters n
 integers in m buckets based on their distance.  Anyway I thing should
 be linear.So I timed som executions changing the first arg.
 [...]
 mcluster :: [(Int,Int)] - [(Int,[Int])]
 mcluster ls = let
 (lr,lc) = (f *** f) (unzip ls) where f = length.nub  -- coo space width
 (k,r) = divMod lr lc
 CState cs _ _ _ = execState (devil ls k)
  CState{clusters = [],remi = r,colsHeap = constArray lc 0,rowsFlag = 
 constArray lr False }
   in map collapse . groupBy (comp fst (==)) . sort . map swap $ cs
 
 coupage ls = zip [0..] ls
 delta fxy xs ys = [(abs(x-y),(n,m))|(n,x) - coupage xs, (m,y) - coupage ys]
 decoupage ls n = fromJust $ lookup n (coupage ls)
 
 test xs ys =
let d = snd.unzip.sort $ delta (\x y - abs (x -y)) xs ys
in
   map (decoupage ys *** map (decoupage xs)) (mcluster d)

It isn't, but not for the reasons you might suspect.  You're using
'nub', which is quadratic, and your 'coupage' is also quadratic because
it uses 'lookup' on a list, which is linear, a linear number of times.
You can get this down to O(n * log n) if you replace these lists by
Data.Map and Data.Set, to get down to O(n) you need arrays there, too,
but that would be pointless, because you're also using 'sort', which is
already in O(n * log n).  The core of the algorithm is clearly linear in
the length of its input.  

(Btw, putting 'devil' into a state monad doesn't make much sense.  I
think, ordinary recursion would be more clear.  In fact, it's a
'foldl'.)


-Udo
-- 
You're damned if you do; you're damned if you don't.  -- Bart Simpson 


signature.asc
Description: Digital signature
___
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-01 Thread Udo Stenzel
Yitzchak Gale wrote:
 It seems to me that a natural notion of a state transformer
 in the ST monad is the type:
 
 STRef s st - ST s a

Are there any useful functions of this type?  I guess, your intention is
that this transformer makes no other use of the ST monad than reading
or writing a single variable.  It seems, every such function better had
a purely functional interface anyway, even if it makes use of runST
internally.

 
 stToState :: MonadState st m = (STRef s st - ST s a) - m a
 
 The type signatures above do ensure (as far as I can see)
 that the opacity of the ST state thread is not violated.

I doubt that.  The transformer you pass in could have captured
references from a different state thread, which is exactly the problem
the rank-2 type should prevent.  I guess, the type signature you want is

stToState :: MonadState st m = (forall s . STRef s st - ST s a) - m a

which should actually work with runST and which would also be a bit
pointless (see above).  At least if I got rank-2 types correctly, which
isn't guaranteed.


 Any ideas? A better approach?

Uhm... use MonadState in the first place?  The converse is comparatively
easily accomplished:

stateToST :: STRef s st - State st a - ST s a
stateToST ref action = do (a, st') - readSTRef ref = runState action
  writeSTRef ref st'
  return a
 

-Udo
-- 
Human legalese is the schema language of our society.
-- Tim Berners-Lee in http://w3.org/DesignIssues/Evolution


signature.asc
Description: Digital signature
___
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

2006-12-29 Thread Udo Stenzel
Steve Schafer wrote:
 Here's the essence of the problem. If I have this:
 
  process1 x y =
let u = foo x y;
v = bar u;
w = baz v
in  w
 
 I can easily rewrite it in point-free style:
 
  process1 = baz . bar . foo

That should have been

  process1 = (.) (baz . bar) . foo

or something similar.  You might want to define suitable combinators if
you have this pattern more often:

  infix 8 .
  (.) = (.) . (.)
  process1 = baz . bar . foo


 But if I have this:
 
  process2 x y =
let u = foo x y;
v = bar u;
w = baz v u
in  w
 
 then I can't avoid naming and using an intermediate variable.

Turns out you can.

  process2 = \x y - (\u - baz (bar u) u) (foo x y)
   = \x y - (\u - (baz . bar) u u) (foo x y)
   = \x y - liftM2 (baz . bar) (foo x y)
   = liftM2 (baz . bar) . foo

In fact, you never need named values.  Read How to Mock a Mockingbird
by Richard Bird (if memory serves) or the documentation for the Unlamda
(esoteric) programming language to find out how or let Lambdabot do the
transformation to pointless style for you.

You don't need to go fully points free in every case.  In your original
example, only one intermediate (y01) was actually used more than once
and deserves naming.  Everything else can be composed with the help of
'uncurry'.  'liftM2' is also surprisingly useful, but it's use at the
type constructor (r -) as in the last example probably deserves a name
of its own.


 The u in process2 is of no more value to me (pardon the
 pun) as the one in process1, but I am forced to use it simply because
 the data flow is no longer strictly linear.

Instead you could define intermediate functions by composing functions
with the help of a few combinators.  I guess, the construction (liftM2
(baz . bar)) could have a very meaningful name.  Some combinators might
also vanish if you reorder and/or tuple some of the arguments to
existing functions.

 
 The reason I brought up monads as a possible means of managing this
 problem is that the State, Reader and Writer monads already handle
 certain specific shapes of nonlinear data flow

Uhm... that could be said of Reader, but is no good description of the
others.  If you like, you could plug your y01 into a Reader Monad, but I
don't think it simplifies anything.  Sometimes naming values is simply
the right thing to do.


-Udo
-- 
Even if you're on the right track, you'll get run over if you just sit there.
-- Will Rogers


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


Re: [Haskell-cafe] State separation/combination pattern question

2006-12-22 Thread Udo Stenzel
Reto Kramer wrote:
 What I'm really looking for is not so much the chaining of StateT  
 compositions, but rather the isolation of StateA from StateB while  
 they both flow from the search loop into the respective library calls  
 (foo, bar) transparently to the application programmer.

How about this?

-- these two should be defined in two separate library modules, of course
trueFoo :: MonadState StateA m = m ()
trueBar :: MonadState StateB m = m ()

data AppStateRec = AppStateRec { a :: StateA, b :: StateB }

type Eval a = StateT AppStateRec Identity a

exec :: Eval ()
exec = do foo
  bar
  foo
  foo
  bar
  where
-- you might want to define combinators for the following pattern,
-- but for just two functions this is good enough
foo = do AppStateRec a b - get
 a' - runStateT trueFoo a
 put $ AppStateRec a' b
bar = do AppStateRec a b - get
 b' - runStateT trueBar b
 put $ AppStateRec a b'


-Udo
-- 
In the software business there are many enterprises for which it is not
clear that science can help them; that science should try is not clear
either.
-- E. W. Dijkstra


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


Re: [Haskell-cafe] Dynamic types through unsafeCoerce

2006-12-13 Thread Udo Stenzel
Alfonso Acosta wrote:
 On 12/13/06, Udo Stenzel [EMAIL PROTECTED] wrote:
 Finished!  Look Ma, no existentials, no Typeable, no wrappers, even the
 types have become simple!
 
 I like the fact that type parameters are removed, which makes them
 homegeneus and solves the problem of storing them in a list but as a
 drawback the Runner type is less intuitive than the simple run
 function.

Actually the Runner type _is_ a simple (impure) function.  The
complication is just that you wrote your example in such a way that
'run' has to return a new 'run' function, and that gives it the type
(a where a = IO a), which is not possible in Haskell without the use of
a newtype.


[...]

 As I said the example I posted is quite simplified. Actually the real
 descriptor (a naive translation from a C struct) is:
 
 
 
 -- hd and id are (void *) in C and modelled as type parameters in Haskell
 data Descriptor id hd =
 Descriptor {uniqueID   :: LadspaIndex,
  label  :: String,
  properties :: LadspaProperties,
  name, maker, copyright :: String,
  portCount  :: LadspaIndex,
  portDescriptors:: [PortDescriptor],
  portNames  :: [String],
  portRangeHints :: [PortRangeHint],
  implementationData :: id,
  instantiate:: Descriptor id hd
 - LadspaIndex -
   Maybe hd,
 -- In this case we are using lists to represent the port I/O buffers, so the
 -- port connections (buffer pointers of ports) is handled by the marshaller
 --connectPort   :: (hd - LadspaIndex - Ptr LadspaData - IO 
 hd)
  activate   :: Maybe(hd - IO ()),
  -- (LadspaIndex,PortData) indicates the portnumber and its data
  run:: hd   -
 LadspaIndex  -
 [(LadspaIndex,PortData)] -
 ([(LadspaIndex,PortData)], hd),
 -- Not yet implemented (is not mandatory for a plugin to provide them)
 --runAdding  ::
 --setAddingGain  ::
  deactivate :: Maybe(hd - IO ()),
  cleanup:: hd - IO ()}
 
 As you can see, apart from the run function , a Descriptor has some
 other data and other functions, which can be _optional_ ( see
 deactivate, and activate)

Okay, beautiful solution first, again splitting Discriptor in two and
ignoring some fields being optional.  Again, you have a factory and an
actual object, and we will implement it exactly this way, for the moment
ignoring the exports to C.  I'm also leaving out implementationData,
because it's impossible to see what that's used for.


data HdMaker = HdMaker { uniqueID :: LadspaIndex,
 label :: String,
 ...
 instantiate :: LadspaIndex - Maybe Hd }

data Hd = Hd { connectPort :: LadspaIndex - Ptr LadspaData - IO Hd
 , activate :: IO ()
 , run :: LadspaIndex - [(LadspaIndex, PortData)]
   - ([(LadspaIndex, PortData)], Hd)
 , deactivate :: IO ()
 , cleanup :: IO ()
 }

newHdMaker ... = HdMaker { ...
 , instantiate = newHandle }
  where
newHandle = Hd { connectPort =
   , activate =
   , run =
   , deactivate = 
   , cleanup =
   }
 

You should be able to see how this is to be fleshed out.  The important
point is that the fields of Hd (which are set in newHandle) don't need
to be passed a handle of sorts later, since that handle is already
available, though of course I can't infer where it is supposed to come
from.  As usual, add newStablePtr/derefStablePtr as needed.  I guess the
connectPort function has to construct yet another Hd.

Now you don't want to split the Descriptor record, because the C world
already decided to pass an additional opaque handle type.  That's no
problem: you handle is simple the set of functions that take handles as
parameters.

data Descriptor = Descriptor
{ uniqueID :: LadspaIndex,
  ...
  instantiate :: LadspaIndex - Maybe Hd,
  connectPort :: Hd - LadspaIndex  - Ptr LadspaData - IO Hd,
  activate :: IO ()
  ...
}

newDescriptor ... = Descriptor
{ ...
  instantiate = newHandle,
  connectPort Hd = hd_connectPort Hd,
  activate Hd = hd_activate Hd,
  ...
}

where the fields of Hd have to be suitably renamed.

 
 Those optional funcions cause a problem when

Re: [Haskell-cafe] Dynamic types through unsafeCoerce

2006-12-12 Thread Udo Stenzel
Alfonso Acosta wrote:
 If anyone finds a way of implementing something equivalent to this code 
 without unsafeCoerce#  and ...
 
 * Not changing chooseDesc or finding an equivalent
 * Not splitting  or changing Descriptor type (I already found an
 equivalent way which uses existentials and in which the type is
 splitted in two)

Well, all you need to do is to throw out your OO-Think (and with it
Typeable and casts) and you'll realize what you're actually doing here:
you're passing functions.  Say so and everything comes naturally.
(Warning:  untested code.)

-- --
type Descriptor = InstanceInitData - Runner
-- a function!  Who would have thought it?

newtype Runner = R { run :: IO Runner }
-- could be a plain (IO Runner) instead of a newtype, if only it
-- weren't a recursive type

descInt, descChar :: Descriptor
descInt = const (runInt 1)
  where
runInt n = R (do print n ; return . runInt $ n*2)

descChar = const (runChar 'a')
  where
runChar c = R (do print c ; return . runChar $ succ hd)

descList :: [Descriptor]-- homogenous!
descList = [ descInt, descChar ]
-- -

Finished!  Look Ma, no existentials, no Typeable, no wrappers, even the
types have become simple!  Descriptor doesn't even need a type argument
anymore, and indeed, why should it?  Its purpose is exactly to _hide_ an
Int/Char/whatever, not to expose it.

Okay, I cheated a bit: I _did_ split Descriptor in two.  That feels more
right anyway, since 'instantiate' is only going to be called once (I
think) and before 'instantiate' is called, there is no meaningful 'run'
function anyway (and of that I'm sure).  If you don't like that, feel
free to fuse Descriptor and Runner back into one record, but then you
need to think about what to initialize 'run' to.  In fact, even in
OO-Think you should be passing a constructor, err... factory to C land,
not a half-baked object.

Rest is wrappers to be able to call the above from the netherworlds,
foreign export statements snipped.  Oh, and lots of 'freeStablePtr'
are also missing.  Adding them will be left as a training exercise :)

-- -
chooseDesc :: Int - IO (StablePtr Descriptor)
chooseDesc n = newStablePtr (descList !! n)
 
cInstantiate ::
  StablePtr Descriptor - InstanceInitData - IO (StablePtr Runner)
cInstantiate ptr iid = do desc - deRefStablePtr ptr
  newStablePtr . desc $ iid
 
cRun :: StablePtr Runner- IO (StablePtr Runner)
cRun hdptr = deRefStablePtr hdptr = run = newStablePtr
-- -


-Udo
-- 
I've seen it.  It's rubbish.
-- Marvin the Paranoid Android


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


Re: [Haskell-cafe] Dynamic types through unsafeCoerce

2006-12-09 Thread Udo Stenzel
Alfonso Acosta wrote:
 I've been using Data.Dynamic but the Typeable requirement doesn't go
 well with FFI declarations (which don't accept type contexts).

You wouldn't need a Typeable context anyway; what's biting you is that
Dynamic is not one of the primitive types that can pass across the FFI.
There are good reasons for that and unsafeCoerce certainly cannot
invalidate them.

You want a StablePtr.


 would the use of unsafeCoerce be dangerous?

If you have to ask, then yes.


-Udo
-- 
Never confuse motion with action. -- Ernest Hemingway


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


Re: [Haskell-cafe] Beginner: IORef constructor?

2006-12-01 Thread Udo Stenzel
TJ wrote:
 --
 module Global where
 
 import Data.IORef
 
 theGlobalVariable = newIORef []
 
 testIt = do ref - theGlobalVariable
original - readIORef ref
print original
writeIORef ref [1,2,3]
new - readIORef ref
print new
 --

Wrong.  You get a fresh new variable everytime you access
'theGlobalVariable'.  


 I've got a lot to learn about Haskell...

Well, for starters:

- there are no variables in ordinary Haskell,
- there are variables in the ST and IO monads, but dragging IO
  everywhere is burdensome and you don't want to do that,
- you can probably fake global variables using 'unsafePerformIO', and
  you definitely don't want to mess with that (yet),
- you need to understand monads in general, the State monad, the ST
  monad and the IO monad, and in exactly this order.
  
Whatever you're trying to do right now, just forget that there are
variables in BASIC and do it without mutable state.


-Udo
-- 
They laughed at Einstein.
They laughed at the Wright Brothers.
But they also laughed at Bozo the Clown.
-- attributed to Carl Sagan


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


Re: [Haskell-cafe] Difficult memory leak in array processing

2006-11-23 Thread Udo Stenzel
Niko Korhonen wrote:
 I have the following code whose purpose is to add dither (noise) to a given
 array. The code looks very straightforward but apparently it has a memory leak
 somewhere.

No, it doesn't.  It can't, because it doesn't even compile.  After
correcting the obvious

 (lo, hi) - getBounds buf

to

  let (lo,hi) = bounds buf

it just works and needs 40MB plus epsilon.  Your problem has to be
somewhere else.


-Udo.
-- 
fork(2) 
New processes are created by other processes, just like new humans.
New humans are created by other humans, of course, not by processes.
-- Unix System Administration Handbook


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


Re: [Haskell-cafe] Re: Debugging partial functions by the rules

2006-11-15 Thread Udo Stenzel
Donald Bruce Stewart wrote:
 So how do we help out the beginners, other than warning about fromJust,
 and providing a useful error message as we can, for when they just go
 ahead and use head anyway?

Kill head and tail right now and provide a safe equivalent?  Either

  uncons :: [a] - Maybe (a,[a])

which is to be used in conjunction with 'maybe' (or with
fmap/first/second/unfoldr) or

  list :: r - (a - [a] - r) - [a] - r

in analogy with 'maybe' and 'either'.  Or combine it with 'foldr' to
form the paramorphism (if I got the terminology right).  Or even better,
don't mention the existence of uncons and encourage people to write list
consumers in terms of 'destroy'.


-Udo
-- 
Sturgeon's Law: Ninety percent of everything is crud.
(Sturgeon was an optimist.)


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


Re: [Haskell-cafe] split string into n parts

2006-10-23 Thread Udo Stenzel
jim burton wrote:
 I want to split a string into 5 parts of equal length, with the last fifth
 padded if necessary, but can't get it right - here's what I've got - 

fifths s = unwords.take 5.unfoldr (Just . splitAt l) $ s ++ repeat ' '
  where l = (length s + 4) `div` 5 


Of course no Haskeller in his right mind would carelessly apply the
final 'unwords' unless this was for immediate output.


Udo.
-- 
The Second Law of Thermodynamics:
If you think things are in a mess now, just wait!
-- Jim Warner


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


Re: [Haskell-cafe] memory, garbage collection and other newbie's issues

2006-10-22 Thread Udo Stenzel
Andrea Rossato wrote:
 Now, the state will not be entirely consumed/evaluated by the user,
 and so it will not become garbage. Am I right?

No.  The state cannot become garbage, because there is still a reference
to it.  As long as runStateT has not returned, any part of the state can
still be accessed, so it is not garbage.  Completely evaluating the
state will not reduce memory consumption in your case, because the list
of lists won't be substantially smaller that the thunk to create it.  In
fact, evaluating this thunk will consume memory.

 
 Where should I force evaluation? 

You can't.  Your state really is that large, at least in the toy
example.  You'd need a different data structure ((Array Int ByteString)
or (Map Int ByteString) come to mind) and then make that strict.


Udo.
-- 
The Seventh Commandments for Technicians:
Work thou not on energized equipment, for if thou dost, thy
fellow workers will surely buy beers for thy widow and console
her in other ways.


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


Re: [Haskell-cafe] memory, garbage collection and other newbie's issues

2006-10-21 Thread Udo Stenzel
Andrea Rossato wrote:
 I did not get an appreciable improvement with performGC, as you can
 see from here:
 http://gorgias.mine.nu/haskell/a.out.withPerformGC.ps
 
 But I found a solution: just write the opml state component to a file!

Obviously the values in question were not garbage, rather these were
unevaluated thunks.  Writing the data causes it to be evaluated, the
thunks become garbage and get collected.

The correct solution however, is the application of 'seq' at the right
places.  To understand where these are, perform a simulation of
Haskell's reduction strategy on paper.

 
  second, each Char in ghc occupies 12 bytes (!)
  
  multiplying this at 2.5 or even 3 factor which i described in previous
  letter means, say, 30 mb used
 
 30 Mega used for reading a feed is a number that I seem to get. 

Depends on what you're doing with the data.  If you scan a stream of
Chars exactly once, the space requirement per Char is next to
irrelevant.  If you're keeping lots of Strings around, using
PackedStrings will help (and be sure to pack strictly).  But I actually
suspect, you are running a backtracking parser over your input, so the
whole input is read into a String and cannot be disposed of as long as
the parser might backtrack.  If this is Parsec, you need to remove a
redundant 'try'.  If it is the Read class, you need to replace it by
Parsec or ReadP...


Udo.
-- 
Lorien Ich glaub vorher defragmentier ich meine Festplatte, schmeiß
alle CDs weg und installier Löwenzahn, Teletubbies, Pokemon usw. auf
meinem Rechner. Dann lauf ich amok. Das wird den Psychologen EINIGES
zu denken geben.


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


Re: [Haskell-cafe] Debugging Newton's method for square roots

2006-10-15 Thread Udo Stenzel
Vraj Mohan wrote:
 my_sqrt :: Float - Float
 my_sqrt x = improve 1 x
  where improve y x = if abs (y * y - x)  epsilon 
 then y 
 else improve ((y + (x/y))/ 2) x
epsilon = 0.1
 
 
 
 This works for several examples that I tried out but goes into an infinite 
 loop
 for my_sqrt 96. How do I go about debugging this code in GHC or Hugs?

1) As Jon said, by seperating the iteration from the selection of the
   result.  iterate, filter, head, etc. are your friends.  Makes the
   code more readable and maintainable, too.
2) By learning more about floating point numbers.  There is no Float y
   such that | y*y - 96 |  0.1.  That's why such an iteration is
   better terminated not when the result is good enough, but when it
   stops getting better.  It's also the reason why you code might work
   with -fexcess-precision or in an untyped language or with the next or
   previous compiler release or on rainy days or whatever else.

 
Udo.
-- 
Walk softly and carry a BFG-9000.


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


Re: [Haskell-cafe] [off-topic / administrative] List Reply-to

2006-10-11 Thread Udo Stenzel
Mikael Johansson wrote:
 On Tue, 10 Oct 2006, Misha Aizatulin wrote:
  Here is an argument against Reply-To munging. I'd say I agree with it:
 
 http://www.unicom.com/pw/reply-to-harmful.html
 
 * It provides no benefit to the user of a reasonable mailer.
 [...]
 1) get multiple copies of mails concerning discussions I participate in or
 2) have to manually re-edit the header each and every time I want to keep 
 a discussion on a mailing list, possibly with added trouble finding the 
 right adress to send to

A reasonable mailer has functions reply, reply-to-all and
reply-to-list.  I'm composing this mail using reply-to-list, have to
edit no headers, the reply goes to the list and nobody gets duplicate
copies.


 * It removes important information, which can make it impossible to 
 get back to the message sender.

This is the most important bit, actually.  Anyone who wants to post a
single question to haskell or haskell-cafe has to be subscribed, or the
reply may go to the list, no matter what he put into the reply-to
header.  Is it a good thing to shut out casual users?


 I view pine as something that should be classified as 
 reasonable

Pein (sic!) is not reasonable.  If you love it so much, please whip out
the source code, implement a reply-to-list function and get at least
one mailer removed from a silly debate.


 I disagree.
 I don't agree.
 I don't agree. 
 I don't agree.
 I don't agree.

Very convincing.  Keep up the good work.


Udo.
-- 
Hast du zum Leben kein Motiv --
steig mal vor, vielleicht geht's schief.
-- aus einem Gipfelbuch


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


Re: [Haskell-cafe] [off-topic / administrative] List Reply-to

2006-10-11 Thread Udo Stenzel
Robert Dockins wrote:
 FWIW, I'm using Apple's Mail.app, and it doesn't have a reply-to-
 list.  In fact, I don't know of a mail client off the top of my head
 that does

Mutt does.  But that's to be expected, considering that it was written
because the author was fed up with the poor handling of mailing lists.

 However, I don't recall problems with multiple copies of emails.

I did get your mail twice, which I don't consider a huge problem.


 I think (pure speculation) the haskell.org mail server is set up to  
 omit people from mail it sends if they appear in the To: or Cc: of  
 the original mail.

Actually it's Mailman that can be set up this way.  I don't think, it is
done on haskell.org, though.  Should an admin read this, you might
consider switching that option on (and leaving reply-to-munging off).


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] Haskell performance (again)!

2006-10-08 Thread Udo Stenzel
Yang wrote:
 type Poly = [(Int,Int)]
 
 addPoly1 :: Poly - Poly - Poly
 addPoly1 p1@(p1h@(p1c,p1d):p1t) p2@(p2h@(p2c,p2d):p2t)
| p1d == p2d = (p1c + p2c, p1d) : addPoly1 p1t p2t
| p1d  p2d = p1h : addPoly1 p1t p2
| p1d  p2d = p2h : addPoly1 p1 p2t
 addPoly1 p1 [] = p1
 addPoly1 [] p2 = p2
 addPoly1 [] [] = []
 
 But this doesn't use tail recursion/accumulation

Indeed it doesn't.  Now remind me, why is that supposed to be a Bad
Thing?  The above code exhibits a maximum of lazyness and runs with no
useless space overhead.  Apart from the expression (p1c + p2c), which
you probably want to evaluate eagerly, it is close to perfect.

 so I rewrote it: [...]
 
 But laziness will cause this to occupy Theta(n)-space of cons-ing
 thunks.

No, it doesn't.  Insisting on accumulator recursion does.  Actually,
using reverse does.  Think about it, a strict reverse cannot use less
than O(n) space, either.


 I was
 hoping for more in-depth insights on how to take advantage of laziness
 to write cleaner AND more efficient code.

Try to explain why your first iteration was bad.  You'll achieve
enlightenment at the point where your explanation fails.


Udo.
-- 
Hast du zum Leben kein Motiv --
steig mal vor, vielleicht geht's schief.
-- aus einem Gipfelbuch


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


Re: [Haskell-cafe] cutting long strings into lines

2006-09-30 Thread Udo Stenzel
Matthias Fischmann wrote:
 although this wasn't the original problem, i like it, too :).  but now
 i am stuck in finding an optimal implementation for lines.

Isn't the obvious one good enough?

lines [] = []
lines s = go s
  where
go [] = [[]]
go ('\n':s) = [] : lines s
go (c:s) = let (l:ls) = go s in (c:l):ls


Udo.
-- 
Money can't buy friends, but it can get you a better class of enemy.
-- Spike Milligan


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


Re: [Haskell-cafe] Slow IO

2006-09-13 Thread Udo Stenzel
Daniel Fischer wrote:
  Most certainly not.  I'm pretty sure this is to a bug in your code.
  Something retains a data structure which is actually unneeded.  Probably
 
 Apparently. And my money is on a load of lines from the file (of which I need 
 only the first and last Char).

Then you're doing it wrong[TM].  You shouldn't need to keep any part of
the input in memory.  Whatever it is, nobody can tell you without seeing
the code.  Try heap profiling, should you have no idea where to look for
leaks.


 How could I solve the problem without representing the graph in some way?

By using an advanced tool called brains.  Sorry for not being more
specific, but that's actually the fun part of the challenge and I'm not
going to spoil it for you.  ;-)


 Forgive the stupid question, but where if not RAM would the chunk currently 
 processed reside?

Oh, I overlooked chunk.  Well, yes, the chunk currently processed
needs to fit into RAM.  But how much of a problem could a single Char
pose?


Donald Bruce Stewart wrote:
 I agree. Some problems simply require you to hold large strings in
 memory. And for those, [Char] conks out around 5-10M (try reversing a
 10M [Char]).

Sure, this one just isn't of that kind.


Udo.
-- 
Irrationality is the square root of all evil
-- Douglas Hofstadter


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


Re: [Haskell-cafe] foreach

2006-09-13 Thread Udo Stenzel
Lemmih wrote:
  main = do
args - getArgs
flip mapM_ args $ \arg -
  flip mapM_ [1..3] $ \n -
putStrLn $ show n ++ )  ++ arg

Or even:

main = do
args - getArgs
putStr $ unlines [ show n ++ )  ++ arg
 | arg - args, n - [1..3] ]

I'm really at a loss trying to understand why some people seem to like
the imperative style.  In fact, most  of the time, the strings in the
code above are better replaced by Doc from Text.PrettyPrint.


Udo.
-- 
Worrying is like rocking in a rocking chair -- It gives
you something to do, but it doesn't get you anywhere.


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


Re: [Haskell-cafe] Slow IO

2006-09-13 Thread Udo Stenzel
Ketil Malde wrote:
 Daniel Fischer [EMAIL PROTECTED] writes:
 
  Maybe I've misused the word segfault.
 
 I think so.  A segfault is the operating-system complaining about an
 illegal memory access.  If you get them from Haskell, it is likely a
 bug in the compiler or run-time system (or you were using unsafeAt, or
 FFI). 

Far simpler:  This is really a segfault, and it's because of a
misfeature of Linux called memory overcommitment.  When physical
memory runs out, Linux happily hands out more to applications requesting
it, in the vain hope that at least some of it is never accessed.
Therefore, malloc() is always successful, but when the memory is finally
accessed, it suddenly turns out that there isn't anything to access,
which results in a segfault.  No amount of error checking can prevent
that and it could have hit any process allocating memory when it ran
out.

Sane people turn overcommitment off.  Sane people wouldn't have
implemented it in the first place, either.


Udo.
-- 
The reasonable man adapts himself to the world; the unreasonable one
persists in trying to adapt the world to himself. Therefore all progress
depends on the unreasonable man. 
-- George Bernard Shaw


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


Re: [Haskell-cafe] Slow IO

2006-09-12 Thread Udo Stenzel
Daniel Fischer wrote:
 The programme consumed more and more memory (according to top),
 kswapd started to have a higher CPU-percentage than my programme,
 programme died, system yelling 'Speicherzugriffsfehler', top displays 
 'kswapddefunct'.
 I believe that means my programme demanded more memory than I have available 
 (only 256MB RAM + 800MB swap). Is that a segfault or what is the correct 
 term?
 
 That is probably due to (apart from the stupidity of my IO-code) the large 
 overhead of Haskell lists.

Most certainly not.  I'm pretty sure this is to a bug in your code.
Something retains a data structure which is actually unneeded.  Probably
a case of foldl where foldl' should be used or a try in Parsec
code where it should be left out or a lot of updateWiths to a Map,
etc.  Or it could be a bad choice of data structure.  I bet, it's the
map you're using to represent the graph (which you don't even need to
represent at all, btw).


 So the chunk of the file which easily fits into my 
 RAM in ByteString form is too large as a list of ordinary Strings.

The chunk of file should never need to fit into RAM.  If that's a
problem, you also forgot to prime a crucial foldl.


Udo.
-- 
Proof by analogy is fraud. -- Bjarne Stroustrup


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


Re: [Haskell-cafe] HaXml and ghci unresolved symbol

2006-09-11 Thread Udo Stenzel
Andrea Rossato wrote:
 It seems related to dynamic linking: I created a separated module
 (Xml.hs) that imports Text.XML.HaXml and parses a xml string. I then
 created a file (xml.hs) that imports Xml and prints name, defined in
 Xml.hs. The expected output should be elementTest.

Whatever it is, I cannot reproduce any of your problems.  I installed
HaXml-1.13.2 from source using Cabal, and both ghc -c Xml.hs and ghc
--make xml.hs work as expected, even without the -package switch.  This
is GHC 6.4.1 on Linux.

 If I load in ghci the file xml.hs (that imports Xml.hs)

Could it be that you're on Windows, which cannot keep xml.hs and Xml.hs
apart?


-Udo
-- 
Eagles may soar but weasels don't get sucked into jet engines.
-- Steven Wright 


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


Re: [Haskell-cafe] HaXml and ghci unresolved symbol

2006-09-10 Thread Udo Stenzel
Andrea Rossato wrote:
 [12:03:[EMAIL PROTECTED]:~/devel/haskell/xml]$ ghci -package HaXml xml1.hs
 [logo]
 Loading package base-1.0 ... linking ... done.
 Loading package haskell98-1.0 ... linking ... done.
 Loading package HaXml-1.13.1 ... linking ... done.
 Skipping  Main ( xml1.hs, xml1.o )
 Ok, modules loaded: Main.
 Prelude Main main
 interactive: xml1.o: unknown symbol 
 `TextziXMLziHaXmlziParse_xmlParse_closure'

Hrm, you're accessing a symbol presumably found in a library that isn't
loaded.  Either GHC cannot find the library, which shouldn't happen if
you're using the right package switch, or the .hi file you compiled
against is out of synch with the library, which also shouldn't happen,
as both were compiled from the same source.

- Did you compile and install HaXml from source?  If not, was the binary
  meant for the version of GHC you're using?
- Did you update anything after doing so?  Some library, GHC itself, ...?
- Did you use weird compiler switches (profiling on/off with missing
  profiling libraries)?
- Did you move things around after compiling?  Broken package database?
  configure --user with install --global or vice versa?
- Did you install more than one version of HaXml?  Or are remnants of
  failed installation attempts still in the search path?

You could try the brute force approach of just exploding the source tree
of HaXml right into your project directory and not using the installed
package at all.  ghc --make should be able to pick up the sources and
compile them without further ado.  For hxml this might actually be the
right thing to do, because it's so small.  However, if you didn't mess
with the internals of some package, your problem is just weird.


Udo.
-- 
in the middle of a discussion about the evil mangler in GHC 5.04:
shapr the evil mangler uses *perl* ??
ChilliX yes...
ChilliX it is Evil after all


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


Re: [Haskell-cafe] NaN, Infinity literals

2006-09-07 Thread Udo Stenzel
Tamas K Papp wrote:
 Is there a way to use NaN and Infinity as literals, or at least to
 test if a value is NaN or Infinity?
 
 *Main let nan=0/0
 *Main nan
 NaN
 *Main nan==0/0
 False
 
 so storing the value does not work...

Not sure what you mean here.  In IEEE floating point, NaN is not equal
to anything, especially not to itself.  So the above worked, didn't it?
And therefore,

isNaN :: Double - Bool
isNaN x = not (x == x)

but this is wrong (I believe):

isNaN' :: Double - Bool
isNaN' x = x /= x

Anyway, isNaN is alerady in the Prelude, and so are isInfinite,
isDenormalized and isNegativeZero.

This is all a bit ill-defined, but you'll have to live with that.  If
you also want a personal advise: switch on signaling NaNs (there's a C
function to do that, simply foreign import it) and have your program
bomb out as soon as a NaN is formed.  Propagating them through
calculations just increases the headache.


Udo.
-- 
FORTUNE PROVIDES QUESTIONS FOR THE GREAT ANSWERS: #4
A:  Go west, young man, go west!
Q:  What do wabbits do when they get tiwed of wunning awound?


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


Re: [Haskell-cafe] Why does this program eat RAM?

2006-09-05 Thread Udo Stenzel
John Goerzen wrote:
 I have the below program, and I'm trying to run it on an input of about
 90MB.  It eats RAM like crazy, and I can't figure out why.
 
 wordfreq inp = Map.toList $ foldl' updatemap (Map.empty::Map.Map String Int) 
 inp
 where updatemap nm word = Map.insertWith updatefunc word 1 nm
   updatefunc _ x = x + 1

The culprit is insertWith, it inserts unevaluated thunks into your map
where you want a simple value.  To avoid a space leak, you want a strict
update function (yours is strict enough) and insertWith must be strict
in the newly inserted value (the result of applying updatefunc).  Since
you cannot influence the strictness of insertWith, no matter how many
seqs you sprinkle through your code, you need insertWith', which is
missing.  You can simulate it, however:

insertWith' f k v m = case Map.lookup k m of
Nothing - Map.insert k v m
Just w  - (Map.insert k $! f w v) m

IMHO all accumulating functions, especially foldl, State.update,
Map.insertWith, accumArray, absolutely need a strict version, because
the strictness cannot be recovered by the library's user.  If the
clutter of too many primed names is unbearable, leave out the _lazy_
version.  It's useless IME and lazyness can be recovered if the need
arises.


Udo.
-- 
Wo die Macht geistlos ist, ist der Geist machtlos.
-- aus einem Gipfelbuch


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


Re: Re[2]: [Haskell-cafe] Why does this program eat RAM?

2006-09-05 Thread Udo Stenzel
Bulat Ziganshin wrote:
 Data.HashTable may be a faster alternative for Map (if ordering isn't
 required)

Or it may not.  Finding a good hash function for the words John is
counting, is a challenge itself.  Finding a good one that doesn't look
at each character at least once, might be outright impossible.  That
means, a hash table cannot do significantly less work than the
appropriate data structure, which is a trie, aka Data.StringMap.


Udo.
-- 
Q:  Why do mountain climbers rope themselves together?
A:  To prevent the sensible ones from going home.


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


Re: [Haskell-cafe] [Parsec] No identEnd in ParsecToken?

2006-09-05 Thread Udo Stenzel
Stephane Bortzmeyer wrote:
 I'm trying to use Parsec for a language which have identifiers where
 the '-' character is allowed only inside identifiers, not at the start
 or the end.
 
 identifier = do
 start - letter
 rest - many (alphaNum | char '-') 
 end - letter   
 return ([start] ++ rest ++ [end])
   ? characters authorized for identifiers

identifier = do
start - letter
rest - many (alphaNum | try inner_minus)
return $ start : rest
where
inner_minus = do 
char '-' 
lookAhead alphaNum
return '-'


 because the parser created by many is greedy: it consumes
 everything, including the final letter.

Yes, it does.  You could implement you own non-greedy many combinator,
but you get the associated inefficiency.  Or you could use ReadP, which
doesn't have this problem (but replaces it with other surprises).  


Udo.
-- 
Eagles may soar but weasels don't get sucked into jet engines.
-- Steven Wright 


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


Re: [Haskell-cafe] Re: Re: A free monad theorem?

2006-09-03 Thread Udo Stenzel
Lennart Augustsson wrote:
 Well, bind is extracting an 'a'.  I clearly see a '\ a - ...'; it  
 getting an 'a' so it can give that to g.  Granted, the extraction is  
 very convoluted, but it's there.

Oh, that can be remedied...

 m = g = m . flip g

In fact, why even mention m?

 (=) = (. flip) . (.)

Anyway, there's no a extracted from m, since a function cannot be
deconstructed.  That lets the free theorem degenerate into m = k
does something with m and/or k, most of the time, which is kinda
meaningless and explains exactly nothing.


Udo.


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


Re: [Haskell-cafe] Re: Re: A free monad theorem?

2006-09-02 Thread Udo Stenzel
Benjamin Franksen wrote:
 Sure. Your definition of bind (=):
 ...
 applies f to something that it has extracted from m, via deconstructor
 unpack, namely a. Thus, your bind implementation must know how to produce
 an a from its first argument m.

I still have no idea what you're driving at, but could you explain how
the CPS monad 'extracts' a value from something that's missing something
that's missing a value (if that makes sense at all)?

For reference (newtype constructor elided for clarity):

type Cont r a = (a - r) - r

instance Monad (Cont r) where
   return a = \k - k a
   m = g = \k - m (\a - g a k)



Udo.
-- 
Streitigkeiten dauerten nie lange, wenn nur eine Seite Unrecht hätte.
-- de la Rochefoucauld


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


Re: [Haskell-cafe] Exercise in point free-style

2006-09-01 Thread Udo Stenzel
Julien Oster wrote:
 While we're at it: The best thing I could come up for
 
 func2 f g l = filter f (map g l)
 
 is
 
 func2p f g = (filter f) . (map g)
 
 Which isn't exactly point-_free_. Is it possible to reduce that further?

Sure it is:

func2 f g l = filter f (map g l)
func2 f g = (filter f) . (map g)-- definition of (.)
func2 f g = ((.) (filter f)) (map g)-- desugaring
func2 f = ((.) (filter f)) . map-- definition of (.)
func2 f = flip (.) map ((.) (filter f)) -- desugaring, def. of flip
func2 = flip (.) map . (.) . filter -- def. of (.), twice
func2 = (. map) . (.) . filter  -- add back some sugar


The general process is called lambda elimination and can be done
mechanically.  Ask Goole for Unlambda, the not-quite-serious
programming language; since it's missing the lambda, its manual explains
lambda elimination in some detail.  I think, all that's needed is flip,
(.) and liftM2.


Udo.
-- 
I'm not prejudiced, I hate everyone equally.


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


Re: [Haskell-cafe] ReadP question

2006-08-31 Thread Udo Stenzel
Chris Kuklewicz wrote:
 I just tried to mimic regular expression matching with ReadP and got what 
 seems like a non-terminating program.  Is there another way to use ReadP to 
 do this?
 
 -- Simulate (a?|b+|c*)*d regular expression
 test = star (choice [quest (c 'a')
 ,plus (c 'b')
 ,star (c 'c')]) + c 'd'

Indeed, this cannot work.  ReadP delivers parses in order of increasing
length, and your expression produces infinitely many parses of the empty
string, you never get to the interesting matches.  I'd say, the best
solution is to use an equivalent regex which does not contain something
of the form 'many (return x)':

 -- Simulate (a?|b+|c*)*d regular expression
 test' = star (choice [(c 'a')
  ,plus (c 'b')
  ,plus (c 'c')]) + c 'd'


Udo.
-- 
f u cn rd ths, u cn gt a gd jb n cmptr prgrmmng.


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


Re: [Haskell-cafe] state and exception or types again...

2006-08-29 Thread Udo Stenzel
Andrea Rossato wrote:
 Il Mon, Aug 28, 2006 at 09:28:02PM +0100, Brian Hulley ebbe a scrivere:
  data Eval_SOI a = SOIE {runSOIE :: State - (a, State, Output, Bool)}
 
 well, I thought that this was not possible:
 (=) :: m a - (a - m b) - m b

And you are right.  In case of an exception, you don't have a 'b' to
return, so you cannot construct the result (unless you put 'undefined'
in there, which is just silly).  Do it this way:

data Eval_SOI a = SOIE {runSOIE :: State - (Maybe a, State, Output)}

instance Monad Eval_SOI where
return a = SOIE $ \s - (Just a, s, [])
fail _ = SOIE $ \s - (Nothing, s, [])
m = k = SOIE $ \s0 -
let r@(ma, s1, o1) = runSOIE m s0
(mb, s2, o2) = runSOIE (k (fromJust ma)) s1
in case ma of Nothing - r
  Just _  - (mb, s2, o1 ++ o2)

output w = SOIE $ \s - (Just (), s, w)
put s = SOIE $ \_ - (Just (), s, [])
get = SOIE $ \s - (Just s, s, [])

I don't think it's unmanageably complicated, but still not as clean and
modular as using monad transformers.

 This is why I think that two constructors are needed, but with two
 constructors is not possible...;-)

Indeed.  Here they are Nothing and Just.  In principle, Maybe is
equivalent to a pair of a Bool and something else, but that only works
in an untyped language.


 I'm trying to dig into this problem also to see if it has to do with
 monad laws.

Uhh... no.  You should prove them, though.  (Try it, doing this is quite
instructive.)


Udo.
-- 
In the software business there are many enterprises for which it is not
clear that science can help them; that science should try is not clear
either.
-- E. W. Dijkstra


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


Re: [Haskell-cafe] [Parsec] A combinator to match between M and N times?

2006-08-29 Thread Udo Stenzel
Stephane Bortzmeyer wrote:
 Parsec provides count n p to run the parser p exactly n times. I'm
 looking for a combinator countBetween m n p which will run the
 parser between m and n times. It does not exist in Parsec.

infixr 2 :
(:) = ap . ap (return (:))

countBetween 0 0 _ = return []
countBetween 0 n p = p : countBetween   0   (n-1) p | return []
countBetween m n p = p : countBetween (m-1) (n-1) p

(Shortest solution yet, I think.  Is primitive recursion somehow out of
fashion?  Should I rewrite it as two folds?)

 Does anyone has a solution? Preferrably one I can understand, which
 means not yet with liftM :-)

As requested, though I believe a quick 'liftM2' would have been easier
than two 'ap's.  But if you prefer:

a : b = do x - a
 y - b
 return (a:b)

or what I'd ordinarily use:

(:) = liftM2 (:)


Udo.
-- 
As Will Rogers would have said, There is no such thing as a free
variable.


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


Re: [Haskell] [Haskell - I/O] Problem with 'readFile'

2006-08-27 Thread Udo Stenzel
L. J. wrote:
 Hi, I use the operation 'readFile' [...]
 
 How can I break that semi-closed handle for to write in the
 preaviously readed file? Thank you.

Not at all.  But you can get the same effect you get from 'readFile' if
you use 'openFile' and 'hGetContents'.  If you do the latter, you can
really close the semi-closed handle by calling 'hClose'.

However, chances are, that you will not have consumed the whole file at
the point where you close it (lazy evaluation can^W will be tricky), you
will find that you write a new file with empty content, because
apparently you read an empty file when in fact it wasn't empty, and so
on.  In short: don't do that.  Also, don't fight the error message,
understand, that it saved you from trashing a perfectly good file.

Instead, 'readFile' your data, 'writeFile' it into a new(!) file, then
'renameFile' the new over the old one.  Before doing anything else, get
a deep understanding of lazy IO.  (And this understanding will basically
be, that a database package (gdbm, Berkeley DB, you name it) will serve
you better.)


Udo.
-- 
The greatest dangers to liberty lurk in insidious encroachment by men
of zeal, well-meaning but without understanding.
-- Brandeis


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


Re: Re[2]: [Haskell] [Haskell - I/O] Problem with 'readFile'

2006-08-27 Thread Udo Stenzel
Bulat Ziganshin wrote:
length mates_str `seq` return ()
 
 it's the same. i recommend you to use:
 
 return $! tail mates_str
 
 'tail' should be slightly faster than 'len'

...but also slightly less correct.  You probably meant 'last'.  (But
it's still an ugly and dangerous programming style.)


Udo.
-- 
Why is television called a medium?
Because it is neither rare nor well-done.


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


Re: [Haskell-cafe] difference between type and newtype

2006-08-26 Thread Udo Stenzel
Andrea Rossato wrote:
 this is what I'm trying to do, sort of: turn the code at the button
 into the do-notation.[1]
 
 type MSO a = State - (a, State, Output)
 
 mkMSO :: a - MSO a
 mkMSO a = \s - (a, s, )
 
 bindMSO :: MSO a - (a - MSO b) - MSO b
 bindMSO m f = \x - 
  let (a, y, s1) = m x in
  let (b, z, s2) = f a y in
  (b, z, s1 ++ s2)

In principle (might need glasgow-exts), you could go ahead and declare

instance Monad MSO where
return = mkMSO
(=) = bindMSO

This doesn't work, because MSO ist just a function (the top type
constructor is (-)), and there is already a Monad instance for (-).
You could activate all sorts of extensions (glasgow-exts and
overlapping-instances at the very least) to allow the overlap, but I
guess, this will only serve to confuse first the type checker and later
you.

Instead, you have to make clear that MSO is represented as a function,
but is to be treated as different, and that's what 'newtype' is for.
After wrapping a function in a newtype, it is something else, so it has
to be unwrapped before it can be used as a function again:

 newtype MSO a = MSO { unMSO :: State - (a, State, Output) }
 
 mkMSO :: a - MSO a
 mkMSO a = MSO (\s - (a, s, ))
 
 bindMSO :: MSO a - (a - MSO b) - MSO b
 bindMSO m f = MSO (\x - 
  let (a, y, s1) = unMSO m x in
  let (b, z, s2) = unMSO (f a) y in
  (b, z, s1 ++ s2))

and now MSO can no longer be confused with other functions and you can
declare your Monad instance:

 instance Monad MSO where
   return = mkMSO
   (=) = bindMSO

 -- To be tested with:
 -- evalMSO (Add (Con 6) (Add (Con 16) (Add (Con 20) (Con 12 0

Now this won't work, since evalMSO produces an MSO, not a function.  You
have to unwrap it to use the function:

 unMSO (evalMSO (Add (Con 6) (Add (Con 16) (Add (Con 20) (Con 12) 0


Udo.
-- 
From the MFC source: 
// according to the Win98 docs, this should be 1 
// according to the WinNT docs, this should be 2 
// they are both wrong! 


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


Re: [Haskell-cafe] Space leak whilst implementing streams

2006-08-26 Thread Udo Stenzel
[EMAIL PROTECTED] wrote:
 I found a way to remove this space leak, however, I do not really
 understand why there was a space leak in the first place. I would
 really appreciate any light that could be shed on this.
 
 instance ArrowChoice SF where
  left (SF f)
  = SF (\xs - combine xs (f [y | Left y - xs]))
where combine (Left _:xs)  (z:zs) = Left z :combine xs zs
  combine (Right r:xs) zs = Right r:combine xs zs
  combine []   _  = []

The list comprehension is holding onto 'xs' until something of the 'zs'
is consumed.  That only happens when 'xs' contains 'Left _', and your
input input stream doesn't.  So the whole stream is leaked, which indeed
produces a linear space profile.  The easiest way to correct it, is to
consume the list 'xs' only once:

instance ArrowChoice SF where
 left (SF f) = SF (map f')
   where f' (Left x) = Left (f x)
 f' (Right y) = Right y

or simply

instance ArrowChoice SF where
 left (SF f) = SF (map (left f))


 instance ArrowChoice SF' where
  left (SF' f)
  = SF' (\xs - xs `combined` f (map drop_right xs))
where combined = zipWith merge_left

Here you're also risking the leak of a whole copy of 'xs', but since you
end up consuming both lists at the same pace, nothing bad happens.


Udo.
-- 
Nicht alles was hinkt ist ein Vergleich.


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


Re: [Haskell-cafe] stack overflow when using ST monad

2006-08-24 Thread Udo Stenzel
Hi Gregory,

Gregory Wright wrote:
 step :: Tag s - ST s (Maybe Integer)
 step t = do
 c - readSTRef (count t)
 s - readSTRef (state t)
 writeSTRef (count t) (c - 1)
 writeSTRef (state t) (nextState s)
 if (c = 0) then return Nothing else return (Just c)

just looking at the program, this seems to be the problem: writeSTRef
does not force the evaluation of the stored value.  So after repeated
calculation, you end up storing not the current counter and state, but
something like (nextState (...(nextState (nextState initState))...)).
The counter is evaluated for the conditional at the end, so it doesn't
exhibit this problem.  Your computation runs to its end, then that
deeply nested expression is evaluated and exhausts the control stack.
Try this instead:

 writeSTRef (state t) $! nextState s

If TagState is a more complicated data type, you may also need strict
fields in there.

[This comes up so often, shouldn't there be an FAQ about it somewhere?  It
could even offer a guideline along the lines of Whenever you repeatedly
update some value, chances are that you want to force strict
evaluation.]


Udo.


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


Re: [Haskell-cafe] Writing binary files

2006-08-21 Thread Udo Stenzel
Neil Mitchell wrote:
 I'm trying to write out a binary file, in particular I want the
 following functions:
 
 hPutInt :: Handle - Int - IO ()
 
 hGetInt :: Handle - IO Int
 
 For the purposes of these functions, Int = 32 bits, and its got to
 roundtrip - Put then Get must be the same.
 
 How would I do this? I see Ptr, Storable and other things, but nothing
 which seems directly useable for me.


hPutInt h = hPutStr h . map chr . map (0xff ..)
  . take 4 . iterate (`shiftR` 8)

hGetInt h = replicateM 4 (hGetChar h) =
return . foldr (\i d - i `shiftL` 8 .|. ord d) 0

This of course assumes that a Char is read/written as a single low-order
byte without any conversion.  But you'd have to assume a lot more if you
started messing with pointers.  (Strange, somehow I get the feeling, the
above is way too easy to be the answer you wanted.)


Udo.
-- 
Worrying is like rocking in a rocking chair -- It gives
you something to do, but it doesn't get you anywhere.


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


Re: [Haskell-cafe] Last statement in 'do' must be an expression error.

2006-08-17 Thread Udo Stenzel
Szymon Z??bkiewicz wrote:
 The compiler tells me thats there's an error on line 10:
 The last statement in a 'do' construct must be an expression

I think, you have reached the point where treating do-notation as magic
won't help you.  Remember, 

 do
 nr1 - read (prompt enter 1. number: )
 nr2 - read (prompt enter 2. number: )

is syntactic sugar for

 read (prompt enter 1. number: ) = \nr1 -
 read (prompt enter 2. number: ) = \nr2 -

and it obvious that something is missing after the last arrow.  That's
the expression the compiler is complaining about.  After the
translation, it is also completely clear, that there is no variable
which is ever declared and could be assigned.

On a side note, using trap values like the special 0 is an ugly style
inherited from C.  You might want to get used to explicit
representations for missing values.  Compare this:

 read_new :: Maybe (Int, Int) - IO (Int, Int)
 read_new (Just ab) = return ab
 read_new Nothing   = do
   n1 - read_prompt enter 1. number: 
   n2 - read_prompt enter 2. number: 
   return (n1, n2)
   where
 read_prompt p = prompt p = readIO

Also note the 'read_prompt' function; I'm pretty sure you got the types
of 'prompt' and 'read' messed up, too.  So in anticipation of your next
question: 'read'ing the 'prompt' action is not the same as 'read'ing the
result of the 'prompt' action.  Only the latter makes sense.


Udo.
-- 
Enthusiasm is contagious, and so is boredom. -- Paul Graham


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 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] Why Not Haskell? (sidenote on licensing)

2006-08-07 Thread Udo Stenzel
Matthias Fischmann wrote:
 But if GPL is stuck to any part of the code and
 manages to infect the rest, the client can make you sign as many NDAs
 as there can be.  The GPL still entitles you to sell it.

Nonsense.  The GPL says, *if* you distribute a binary, *then* you also
have to distribute the complete, machine readable source.  It also
specifically says that if that is impossible (because of an NDA or
whatever), you must not distribute the software at all.  Have you ever
read the damn thing?!


Udo.
-- 
Wo die Macht geistlos ist, ist der Geist machtlos.
-- aus einem Gipfelbuch


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


Re: [Haskell-cafe] Why Not Haskell? (sidenote on licensing)

2006-08-07 Thread Udo Stenzel
Matthias Fischmann wrote:
 And it's really not as easy to control as you suggest: If you ever
 take in a single patch under the GPL,

This kind of thing doesn't happen by accident.  Patches don't magically
creep into your code, you have to apply them deliberately and you should
always know whether you are allowed to do so.  Applying a BSD-licensed
patch and neglecting to mention the author may get you into exactly as
much trouble.


 or even implement a new feature
 in an obvious way that has been implemented by somebody else under the
 GPL, you are in trouble.

Bullshit again, for the GPL applies to code, not to ideas.  Unless you
believe that copyright law does indeed apply to ideas, *and* that a
GPL-developer will come after you for reimplementing (not copying) his
work, you have nothing to fear unless you outright steal code.

May I humbly suggest some reading, like the text of the GPL itself and
then something basic about copyright law?  


 AFAIR this happened to SSH.com with the
 bigint code in ssh-v1.3

SSH included GMP, which was licensed under the GPL.  Nothing happened
there, only the OpenSSH folks disliked the license and reimplemented
GMP.


Udo.
-- 
The imagination of nature is far, far greater than the imagination of man.
-- Richard Feynman


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


Re: [Haskell-cafe] Why Not Haskell?

2006-08-04 Thread Udo Stenzel
Hans van Thiel wrote:
 I'm wondering why I can't find any commercial Haskell applications on
 the Internet. Is there any reason for this?

Of course.  Corporations are conservative to the point of being
boneheaded.  So to avoid risk, they all went on the internet and said,
Gee, I can't find any commercial Haskell applications on the Internet.
There must be a reason for that, so I better use something else.


 Are there other reasons why there seem to be just a few thousand
 (hundred?) Haskell programmers in the world, compared to the 3 million
 Java programmers and x million C/C++ programmers?

Yah.  2.995 million programmer-wannabes were too lazy to think for
themselves and choose what everybody uses.

 
 Probably it doesn't make much sense to try and develop a
 tool in C++ or even Java, but if I have to go on my own on this, maybe
 Haskell could be feasible, both for fun and profit.

It never makes sense to limit yourself to only one programming language,
even if it happens to be Haskell.  There's always the FFI, should it
turn out that some part is better done in C or assembly or Fortran or
whatever comes to mind.


Udo.
-- 
The two most abundant things in the universe are hydrogen and
stupidity. -- Harlan Ellison 


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


Re: [Haskell-cafe] Why shouldn't variable names be capitalized?

2006-08-04 Thread Udo Stenzel
Martin Percossi wrote:
 Paul Hudak wrote:
 foo x y = ...
 
 We know that x and y are formal parameters, whereas if they were 
 capitalized we'd know that they were constructors.
 
 I agree that naming can be abused. But I think it should be *me* ...

Oh, you like to decide lexical ambiguities.  Well, I suppose you know a
bit of C++.  So what do you think this is:

* int *foo ;

It's the declaration of a pointer to 'int' named 'foo', isn't it?  now
what's this:

* x * y ;

*Obviously* this mulplies x and y and throws the result away, doesn't
it?

Now look more closely.  Do you see it?  Or does it get more blurred the
closer you look?  We don't have this problem in Haskell, and in a sane
world, C++ shouldn't have it either.

If you find second-guessing the programmer funny, try to write a parser
for C++.  You will have so much fun, it's almost impossible to describe.


Udo.
-- 
Even if you're on the right track, you'll get run over if you just sit there.
-- Will Rogers


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


Re: [Haskell-cafe] Filtering a big list into the IO monad

2006-08-03 Thread Udo Stenzel
Gabriel Sztorc wrote:
 I want to filter a list with a predicate that returns a IO value, 
 something that filterM is supposed to do. The problem is, filterM 
 overflows the stack for really big lists

Are you sure it's filterM's fault?  Can you post the code in question?
Stack overflows are usually caused by too much lazyness, but for filterM
that doesn't seem to make sense.


Udo.
-- 
xinkeT Lord grant me the serenity to accept the things I cannot
 change, the courage to change the things I can, and the wisdom
 to hide the bodies of the people I had to kill because
 they pissed me off.


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


Re: [Haskell-cafe] Re: [Parsec] Backtracking with try does not work for me?

2006-08-01 Thread Udo Stenzel
Stephane Bortzmeyer wrote:
  The first would be to test whether bb is followed by eof or
  comma before accepting it.
 
 notFollowedBy actually does the opposite (checking that there are no
 more letters).

Are you sure that you don't actually want

* many1 letter `sepBy1` comma

?  Just asking, because somehow I have a feeling that the next step is
to accept 'a,c,b'...


Udo.
-- 
The Force is what holds everything together.  It has its dark side, and
it has its light side.  It's sort of like cosmic duct tape.


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


Re: [Haskell-cafe] [Parsec] Backtracking with try does not work for me?

2006-07-31 Thread Udo Stenzel
Stephane Bortzmeyer wrote:
 minilang = do
char 'a'
try (optional (do {comma ; char 'b'}))
optional (do {comma ; char 'c'})
eof
return OK
 
 * CUT HERE ***
 
 parse error at (line 1, column 2):
 unexpected c
 expecting b
 
 Apparently, try was used (do note that the column number indicates
 that there was backtracking) but the parser still fails for
 a,c. Why?

Because 'try' can only help you if its argument fails.  If the argument to
'try' succeeds, then it behaves as if it wasn't there.  Now 'optional x'
always succeeds, so the 'try' is useless where you placed it.  You need
to 'try' the argument to 'optional':

 minilang = do
char 'a'
optional (try (do {comma ; char 'b'}))
optional (do {comma ; char 'c'})
eof
return OK

You could also factor your grammar or use ReadP, where backtracking is not
an issue.


Udo.
-- 
Ours is a world where people don't know what they want and are willing
to go through hell to get it. -- Don Marquis


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


Re: [Haskell-cafe] RE: ANN: System.FilePath 0.9

2006-07-29 Thread Udo Stenzel
Andrew Pimlott wrote:
 On Thu, Jul 27, 2006 at 09:59:37PM +0200, Udo Stenzel wrote:
  In fact, that's consistent with the current documentation, because
  
  * getFileName foo == foo
  * getFileName foo/ == 
 
 I have to disagree with that.

No, you don't.  That's the current behaviour of Neil Mitchell's
System.FilePath 0.9 according to the haddockumentation.  There isn't
much point in disagreeing about observable facts, is there?

 First of all,  is not a filename;

Most certainly it isn't.  Which is all the more reason not to like the
current design.  An empty filename just isn't the same as no filename.

 if you mean that foo/ has no filename, it makes much more sense to use
 something like a Maybe type.

It does very much.  In fact, I don't deem getFileName to be an essential
function when a simple pattern match would do the same thing.  foo/
really doesn't have a file name, as it very explicitly names a
directory.

 Second, foo is just as good a directory
 as foo/ to the system

...unless you have both (think Reiser4) or you want to create the file
(I think, but I'm not sure).  However, what's the point in being
ambiguous when we can be explicit?  Sometimes there is a difference,
libraries and tools shouldn't gloss over that without consideration.


 But if you wish to make the distinction,
 at least provide an operation that lets me force a path to be treated
 file-wise or directory-wise.

WTF?!  A path names either a directory or a file.  We might have some
operations that accept file names instead of path names.  What's there
to be treated?  Being explicit about the distinction makes any ambiguity
go away.

 Filesystems are ugly. :-)

So are microprocessors.  We can still have a nice programming language,
and we can also have a nice filesystem language.

 And it is about the slash: foo can be a directory.

No, it still isn't.  We can distinguish between Directory (but not
file, fifo, character or block special) and anything (if in doubt, not
directory), which is an essential semantic distinction and not just the
accidental presence of a slash (or backslash or colon or whatever
$EXOTIC_OS uses).

Also, parsing paths _once_ and printing them _once_ but doing everything
else by operating on their logical structure makes specifying any
intermediate operation a lot easier, if nothing else.  If this thread
shows anything, then it is that specifying path operations is harder
than expected.


Udo.
-- 
Structure is _nothing_ if it is all you got. Skeletons _spook_ people if
they try to walk around on their own. I really wonder why XML does not.
-- Erik Naggum


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


Re: [Haskell-cafe] RE: ANN: System.FilePath 0.9

2006-07-28 Thread Udo Stenzel
Andrew Pimlott wrote:
 On Wed, Jul 26, 2006 at 05:06:41PM -0400, David Roundy wrote:
  This doesn't apply uniformly to all programs--except that we can say
  that any path with a trailing '/' is intended to be a directory, and
  if it's not, then that's an error.
 
 I thought some more about this, and I think the right way to handle this
 is on parsing and printing.

Amen.

 After all, the trailing slash has no real
 meaning for any intermediate processing you might do.

Here I beg to differ.  I'd expect:

* setFileName foo bar == bar
* setFileName foo/ bar == foo/bar

In fact, that's consistent with the current documentation, because

* getFileName foo == foo
* getFileName foo/ == 

No matter whether I'm correct, whether my expectation is natural or
practical and whether others agree, the bahaviour has to be clearly
specified and the final slash certainly isn't unimportant.

 readPath :: String - (Path, Bool {- trailing delimiter -})
 showPath :: Path - String
 showPathTrailingSlash :: Path - String
 
 This is far simpler than trying to figure out what the slash means for
 every path operation.

It's also far uglier...  besides, it isn't about the slash, it is about
the difference between file and directory.


Udo.
-- 
If you cannot in the long run tell everyone what you have been doing,
your doing was worthless.
-- Erwin Schrödinger


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


Re: [Haskell-cafe] RE: ANN: System.FilePath 0.9

2006-07-26 Thread Udo Stenzel
Andrew Pimlott wrote:
  The drive functions stand on their own as a chunk, and are possibly
  not well suited to a Posix system, but are critical for a Windows
  system.
 
 Why are they critical for portable code?  I am fine with
 Windows-specific functions, but I think it's a mistake to bundle them
 [with] portable functions.

I couldn't agree more.  In fact, why can't we pretend the world is sane
at least within Haskell and just put away those drive letters?


 My criticism is that your properties are all specified in terms of
 string manipulation.

Exactly.  I believe, a FilePath should be an algebraic datatype.
Most operations on that don't have to be specified, because they are
simple and have an obvious effect.  Add a system specific parser and a
system specific renderer, maybe also define a canonical format, and the
headaches stop.  What's wrong with this?

data FilePath = Absolute RelFilePath | Relative RelFilePath
data RelFilePath = ThisDirectory 
 | File String
 | ParentOf RelFilePath 
 | String :|: RelFilePath

parseSystemPath :: String - Maybe FilePath
renderSystemPath :: FilePath - String

We can even clearly distiguish between the name of a directory in its
parent and the directory itself.  On Windows, the root directory just
contains the drive letters and is read-only,
drive-absolute-but-directory-relative paths are simply ignored (they are
a dumb idea anyway).  Seperator characters are never exposed, all we
need now is a mapping from Unicode to whatever the system wants.  



  pathSeparator :: Char
  The character that seperates directories.
 
 So what do I do with this?  If I need it, it seems like the module has
 failed.

Indeed.

 
  splitFileName bob == (, bob)
 
  is not a directory.

Some problems just vanish:

parseSystemPath bob == Just (Relative (File bob))
splitFileName (Relative (File bob)) = (Relative ThisDirectory, File bob)

 
  Windows: splitFileName c: == (c:,)
 
 c: is arguably not a directory.

parseSystemPath c: == Nothing
parseSystemPath c:\ == Absolute (C: :|: ThisDirectory)


 (Consider that dir c: lists the current directory on c:, not c:\)

I'd rather ignore that altogether.  Multiple roots with associated
current directories are just a needless headache.  Even a current
directory is somewhat ill-fitted for a functional language like
Haskell.


  getFileName test/ == 
 
  is not a filename.

getFileName (Relative (test :|: ThisDirectory))
== error pattern match failure

 
 Also, it looks from this that you treat paths differently depending on
 whether they end in a separator.  Yet this makes no difference to the
 system.  That seems wrong to me.

Not to the system, but some programs like to make a difference.  If you
give rsync a path that doesn't end in a slash, it will take that to mean
the directory.  With a slash, it means the contents of the directory.
The difference is an additional path component that ends up on the
target file system or doesn't.

 
  getDirectory :: FilePath - FilePath
  Get the directory name, move up one level. 
 
 What does this mean, in the presence of dots and symlinks?

You're right, this has to be ill-defined.  Instead it should be

moveUp :: FilePath - IO FilePath

which would end up in the parent of the linked-to directory after
following a symlink.  Cutting of a component is done by simple pattern
matching, no special functions needed.


Sorry for the rant, but this is Haskell, not Perl.  We have true data
types, not just strings...


Udo.
-- 
A politician is someone who calls a spade a portable, hand-operated
digging implement.
-- author unknown


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


Re: [Haskell-cafe] RE: ANN: System.FilePath 0.9

2006-07-26 Thread Udo Stenzel
Duncan Coutts wrote:
 On Wed, 2006-07-26 at 15:29 +0200, Udo Stenzel wrote:
 
  Exactly.  I believe, a FilePath should be an algebraic datatype.
 
 We've had this discussion before. The main problem is that all the
 current IO functions (readFile, etc) use the FilePath type, which is
 just a String.

So what's better?

- use an ADT (correct and portable by construction), convert to String
  when calling the IO library

- fumble with Strings, use an unholy mix of specialized and general
  functions, trip over a corner case


 So a new path ADT is fine if at the same time we provide
 a new IO library.

We should just wrap the old API, filePathToString any parameters and
liftIO the function while we're at it.


 That's another portability headache - file name string encodings.
 Windows and OSX use encodings of Unicode. Unix uses strings of bytes.

Indeed.  There are two ways out:

- declare that Unix uses Unicode too, take the appropriate conversion
  from the locale

- parameterize the FilePath ADT on the character type, you get (FilePath
  Word16) on Windows (which uses UCS-2, not UCS-4 and not UTF-16) and
  (FilePath Word8) on Unix; provide conversions from/to (FilePath
  String).

I tend towards the second option.  It at least doesn't make anything
worse than it already is.  It's also irrelevant, since pretending the
issue doesn't exist works equally well with an ADT.

 My point is it's not quite as simple as just making an ADT.

Mine is that it is :)  Moreover, a path already has internal structure.
Those string manipulating functions either reconstruct the structure,
then operate on that, then encode it back into a string or implement an
approximation to that.  The latter leads to surprises and making the
former explicit can never hurt.  Heck, NO library fumbles with strings,
neither parsers nor pretty printers nor Network... why should a FilePath
be different?


Udo.


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


Re: [Haskell-cafe] RE: ANN: System.FilePath 0.9

2006-07-26 Thread Udo Stenzel
Andrew Pimlott wrote:
 Maybe the trailing slash is important enough to take into account.

No, not the trailing slash.  The difference between a directory and its
contents is important enough.  This is ususally encoded using a trailing
slash, but I'd rather not worry about that detail in a program.

What does Emacs do with double separators?  I'm at a loss thinking of
anything they could denote, but it could be useful.


Udo.
-- 
Guy Steele leads a small team of researchers in Burlington,
Massachusetts, who are taking on an _enormous_challenge_ -- create a
programming language better than Java.
-- Sun.Com


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


Re: Re[2]: [Haskell-cafe] REALLY simple STRef examples

2006-07-20 Thread Udo Stenzel
Chad Scherrer wrote:
 But why should this...
 
 sumArrays [] = error Can't apply sumArrays to an empty list
 sumArrays (x:xs) = runSTArray (result x)
 where
 result x = do x0 - thaw x
   mapM_ (x0 +=) xs
   return x0
 
 work differently than this...
 
 sumArrays' [] = error Can't apply sumArrays to an empty list
 sumArrays' (x:xs) = runSTArray result'
 where
 result' = do x0 - thaw x
  mapM_ (x0 +=) xs
  return x0
 
 Are the types of (result x) and result' not exactly the same?

It's the monmorphism restriction, again.  Because result' doesn't look
like a function, a monomorphic type is inferred for it.  runST[U]Array
of course doesn't want a monomorphic type.  It's got nothing to do with
boxed vs. unboxed arrays (I think, I can't be bothered to test it right
now).

There are at least four ways out:

- make result' a function, either as in the first example above or by
  supplying a dummy () argument
- declare the correct polymorphic type for result'
- inline result'
- (GHC only) compile with -fno-monomorphism-restriction

Yes, it's a bit cumbersome.  Imperative code is supposed to be
cumbersome, after all.  :)


Udo.
-- 
They seem to have learned the habit of cowering before authority even
when not actually threatened.  How very nice for authority.  I decided
not to learn this particular lesson.
-- Richard Stallman


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


Re: [Haskell-cafe] Defining show for a function type.

2006-07-10 Thread Udo Stenzel
Johan Grönqvist wrote:
 I would like use a list (as stack) that can contain several kinds of values.
 
 data Element = Int Int | Float Float | Func : Machine - Machine  | ...
 
 Now I would like to have this type be an instance of the class Show, so 
 that I can see what the stack contains in ghci.
 
 deriving Show is impossible as Func is not instance of Show. Can I 
 make it instance of Show?

Of course you can:

instance Show Element where
showsPrec p (Int i) = showsPrec p i
showsPrec p (Float f) = showsPrec p f
showsPrec _ (Func _) = (function ++)
...


Udo.
-- 
Alcohol is the anesthesia by which we endure the operation of life.
-- George Bernard Shaw


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


Re: [Haskell] rawSystem unpredictable with signals

2006-07-06 Thread Udo Stenzel
John Goerzen wrote:
 When I hit Ctrl-C while the child process is running, sometimes:
 
   1) rawSystem returns ExitSuccess
 
 or
 
   2) rawSystem raises an IOError saying the child terminated with a
   signal
 
 I am totally at a loss as to explain this difference in behavior.  I
 would prefer it to choose option #2 always.

Could process #1 have caught SIGINT while process #2 didn't?  If so, GHC
is not at fault, because wait() doesn't tell about caught signals.


Udo.
-- 
Lebensmittelskandal: Gene im Mais entdeckt!
(angeblich eine Schlagzeile aus der BILD)


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


Re: [Haskell-cafe] A question about stack overflow

2006-06-27 Thread Udo Stenzel
Neil Mitchell wrote:
 Or if you don't want to go for a fold next, in a style more similar to
 the original:
 
 maximum [] = undefined
 maximum [x] = x
 maximum (a:b:xs) = maximum (max a b : xs)

It even reproduces the stack overflow, though for a different reason.
Better write it this way:

maximum [] = undefined
maximum [x] = x
maximum (a:b:xs) = let m = max a b in m `seq` maximum (m : xs)


Udo.
-- 
The condition of man is already close to satiety and arrogance, and
there is danger of destruction of everything in existence.
-- a Brahmin to Onesicritus, 327 BC,
   reported in Strabo's Geography


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


Re: [Haskell-cafe] Simple matrix

2006-06-22 Thread Udo Stenzel
Bjorn Lisper wrote:
 Here is one way to do it. First, you have to interpret operations on
 matrices as being elementwise applied. E.g, (*) is interpreted as zipWith
 (zipWith (*)) rather than matrix multiply

What's this, the principle of greatest surprise at work?  Nonono, (*)
should be matrix multiplication, fromInteger x should be (x * I) and I
should be the identity matrix.  Now all we need is an infinitely large
I, and that gives:

instance Num a = Num [[a]] where
(+) = zipWith (zipWith (+))
(-) = zipWith (zipWith (-))
negate = map (map negate)
fromInteger x = fix (((x : repeat 0) :) . map (0:))
m * n = [ [ sum $ zipWith (*) v w | w - transpose n ] | v - m ] 


Udo.


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


Re: [Haskell-cafe] Functional progr., images, laziness and all the rest

2006-06-22 Thread Udo Stenzel
[EMAIL PROTECTED] wrote:
 apparently - Clean has better handling of strictness
 issues [saying at the same time that he/she doesn't use Clean...]

Uhm... well... and does it?  From what I've heard, Clean has the same
mechanism as Haskell, which is the 'seq' primitive.  Clean just adds
some syntactic sugar to make functions strict in some arguments.  If
that's the only difference, I'm quite happy with the False-guard idiom
(and may be even more happy with !-patterns).

 And here apparently I am one of rare people  - I am not proud of it,
 rather quite sad, who defends laziness as an *algorithmisation tool*,
 which makes it easy and elegant to construct co-recursive codes. Circular
 programs, run-away infinite streams, hidden backtracking etc. 

And don't forget the Most Unreliable Method to Compute Pi!  That would
be plain impossible without lazy evaluation.  (Nice blend of humor and
insight in that paper, by the way.)

 
 In this context, I found Clean more helpful than Haskell, for ONE reason.
 Clean has a primitive datatype: unboxed, spine-lazy but head-strict lists.

If I understand correctly, you'd get the same in GHC by defining

* data IntList = Nil | Cons I# IntList

though it is monomorphic, and you'd get the same semantics from

* data List a = Nil | Cons !a (List a)

Now it is polymorphic and it may even get unpacked.


Udo.
-- 
If your life was a horse, you'd have to shoot it.


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


Re: [Haskell-cafe] user type declarations in Haskell

2006-06-22 Thread Udo Stenzel
Vladimir Portnykh wrote:
 I am trying to define the following types
 
 data MyStringType a = String deriving (Eq, Ord, Show)
 data QADouble a = Double deriving (Eq, Ord, Show)

These are not what you think they are.  MyStringType has a phantom type
parameter and only one value, which is the constant String (but not of
type String).  What you actually meant can only be guessed, and I'm not
even trying.

 
 So HType can represent strings or doubles.
 later I want to do something like the following:
 let a1 =QADouble 1
 let a2 =QADouble 2
 let a3 = a1 + a2

data HType = QADouble Double | QAString Double

 First, it is not working because Haskell complains about a3. it does not 
 know how to calculate it.

What did you expect?  What's the sum of a Double and a String if not an
error?  You have to define (+), which is already defined.  Use some
other name and give a definition:

QADouble x `plus` QADouble y = ...
QADouble x `plus` QAString y = ...
QAString x `plus` QAString y = ...
QAString x `plus` QADouble y = ...


Udo.
-- 
Lieber vom Fels zertrümmert als bei einer Frau verkümmert.
-- aus einem Gipfelbuch


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


Re: [Haskell-cafe] Simple matrix

2006-06-22 Thread Udo Stenzel
Bjorn Lisper wrote:
 - your definition of fromInteger will behave strangely with the elementwise
   extended operations, like (+). 1 + [[1,2],[3,4]] will become
   [[2,2],[3,5]] rather than [[2,3],[4,5]]. Array languages supporting this
   kind of overloading invariably have the second form of semantics.

Don't call an array a matrix.  If is named matrix, it should have
matrix multiplication, addition, and they should obey the expected laws.  


Udo.
-- 
Jeder Idiot kann seine Fehler verteidigen, was die meisten Idioten ja
auch tun.  -- Dale Carnegie


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


Re: [Haskell-cafe] what do you think of haskell ? (yes, it's a bit general ...:)

2006-06-15 Thread Udo Stenzel
minh thu wrote:
 but i consider to move back to c/c++.

I'm led to believe that you just haven't got the hang of the things that
just aren't there in C, such as Monads and higher order functions.  So
you cannot yet see what you would miss in C.  (And I guess, you're not
feeling at home in C++ either, since there is no language named C/C++.)

Whatever, if you believe a person can only master a single programming
language, it might as well be C for you...


 * array : if i want to write something involving array, i could use
 list, and a lot (too much!) of array types (io/st, mutable/immutable,
 c-friendly (storable).

I've never understood peoples preoccupation with arrays.  You lose all
flexibility just for O(1) lookup and O(1) destructive(!) update.  Most
of the time you're better served with a finite map.

 worst, code involving one type can need to be rewritten for another type.

Huh?  It doesn't, that's the point of the overloaded IArray/MArray
interface!

 
 * laziness / array (again)
 always with array code, i was forced (maybe it's because i dont know enough)
 to use iouarray : if not, performance|memory consumption were low|high.

You're putting unevaluated thunks into your data structure, probably
accumulating them there.  Bringing out the sledge hammer of IOUArray
only obscures the problem.  You should 'seq' data before writeArray'ing
it.

 
 * randomIO
 but the threading of the randomIO argument is really not explicit for
 me : it just means that the underlying/threaded state in the IO monad
 can encapsulated a lot of things.

Duh, don't use IO if you neither like nor need it.  Most random
functions are no IO actions for a reason.

 
 e.g. writing myfunction x1 .. xn | x1 `seq` ... False = undefined is
 not declarative

But it isn't all that bad either...

 (and i still have to learn to identify where it helps and where it doesn't)

...while this is the real problem.  You have to understand lazy
evaluation to make beneficial use of 'seq'.  It really helps to
reproduce some reductions on paper.

 
 the c language take some more time to learn at the beginning but that's it!

Oh come on, you cannot honestly believe that.  If so, please send me
some chunk of nontrivial C code, I send you back at least one location
where it produces undefined behaviour.  Yes, I'm confident that I'll
find some.

 
 did you had the same feeling ? does it disappear ? how ?

Never had that feeling, because C is just too ugly.  It will disappear
once you really understand lazy evaluation.


Udo.


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


Re: [Haskell-cafe] Combinations

2006-06-06 Thread Udo Stenzel
[EMAIL PROTECTED] wrote:
 I need a functions which takes as argument a list of lists like this one:
 
 [[1,2],[3],[4]]
 
 and gives me a list of list with all the possible combinations like this one:
 
 [[1,3,4],[2,3,4]]

sequence

Finding out why it is named that strangely is left as an excercise.  :-)


Udo.
-- 
The future isn't what it used to be.  (It never was.)


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


Re: [Haskell-cafe] Problem trying to get class Bounded to work

2006-05-23 Thread Udo Stenzel
Jacques Carette wrote:
 Bulat Ziganshin wrote:
 
 malloc :: Storable a = IO (Ptr a)
 malloc  = doMalloc undefined
  where
doMalloc   :: Storable b = b - IO (Ptr b)
doMalloc dummy  = mallocBytes (sizeOf dummy)
  
 
 Is there any reason to not code this as
 
 malloc :: Storable a = IO (Ptr a)
 malloc  = mallocBytes $ sizeof undefined
 ?

There is.  Don't you think there's a reason why doMalloc above has an
explicit type signature?  What would happen if you deleted it?


Udo.
-- 
You, sir, are nothing but a pathetically lame salesdroid!
I fart in your general direction!
-- Randseed on #Linux


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


Re: [Haskell-cafe] parsing machine-generated natural text

2006-05-21 Thread Udo Stenzel
Evan Martin wrote:
 Here's the beginning of
 the file, where it's not obvious to me how to distinguish elements in
 the :: section from the rest of the file.
  :: Judge: USDP  Game: dip  Variant: standard
  :: Deadline: F1901M Mon 20 Feb 2006 20:00 PST
  :: URL: http://www.diplom.org/dpjudge?game=dip

You could make :: the start-of-one-line-comment sequence or you could
just parse these three lines.  You can also throw them away like this:

string  ::  many (satisfy (/='\n'))  newline

 
 Movement results for Fall of 1901.  (dip.F1901M)
 I guess I could make Movement a reserved word?

Or simply treat it as such.  'reserved Movement' expands to 'lexeme
(string Movement)', so unless Movement appears as keyword where some
other identifier could also occur, you don't need to treat it specially.

 
 It's actually just for rendering nicer maps of the game state.
 http://neugierig.org/software/hsdip/mapview.html
 (It's draggable, too.)

That's nice, too.  There's not much Diplomacy software out there that
runs under Linux, and most that does is painfully slow.


Udo.
-- 
Hey, Perl-Scripte sind wie Klobürsten.  
Da ist man nicht stolz drauf! Und man 
gibt sie auch nicht weiter.  Schon gar 
nicht in benutzter Form.  -- F. v. Leitner


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


Re: [Haskell-cafe] parsing machine-generated natural text

2006-05-21 Thread Udo Stenzel
Jason Dagit wrote:
reserved units. | reserved unit.
 
 I always struggle with when I need to use 'try' with parsec.
 
 My understanding is that if 'unit.' appears in the input the first
 parser will parse up to the '.' and then fail and consume the input up
 to that point, leaving the alternative with only the period as input
 so it will also fail.
 
 So I'm wondering if someone could explain to me what is wrong with my
 understanding of parsec

Nothing at all.  'reserved' actually contains the necessary 'try', a
'notFollowedBy' in order not to swallow parts of longer identifiers and
a useful error message.  I tend to forget 'try', too, or add it in odd
places.  Actually, if ReadP hat better error reporting, I'd recommend
that over Parsec.


Udo.
-- 
Time is an illusion. Lunchtime doubly so. -- Douglas Adams


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


Re: [Haskell-cafe] parsing machine-generated natural text

2006-05-20 Thread Udo Stenzel
Evan Martin wrote:
 Unfortunately, the output is intended to be human-readable, and this
 makes parsing it a bit of a pain.  Here are some sample lines from its
 output:
 
 France: Army Marseilles SUPPORT Army Paris - Burgundy.
 Russia: Fleet St Petersburg (south coast) - Gulf of Bothnia.
 England: 4 Supply centers,  3 Units:  Builds   1 unit.
 The next phase of 'dip' will be Movement for Fall of 1901.

What's the difficulty?  SUPPORT and CONVOY are simply keywords, as
are Army and Fleet, only other words are identifiers for locations.
Parsec supports this out of the box; have a look at the Language and
Token modules .  Note that CONVOY orders can get complex, so a true
parser is probably the right tool.


 And that Supply centers line ends up being
 code filled with stuff lie char ':'; skipMany space.

do power
   colon
   integer
   reserved Supply centers,
   integer
   reserved Units:
   ((reserved Builds  return id) |
(reserved Disbands  return negate))
`ap` integer
   reserved units. | reserved unit.


Come on, it isn't nearly as bad as you make it sound.  Use the
combinators, they are far more powerful than ugly never-quite-correct
regexes.

Oh, and drop me a line when your Diplomacy bot is finished.


Udo.
-- 
Jeder echte Wettbewerb ist ruinös. Darum beruht jede funktionierende
Wirtschaft auf Schiebung.


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


  1   2   >