Re: How overload operator in Haskell?

2003-11-05 Thread Ketil Z. Malde
Andrew J Bromage [EMAIL PROTECTED] writes:

   class Plus a b c | a b - c where
   (+) :: a - b - c

   class Mult a b c | a b - c where
   (*) :: a - b - c

This kind of approach was discussed a while ago, and has a bunch of
things to recommend it.  Is the functional dependency sufficient to
avoid any ambiguity?

   class (Eq a, Show a,
  Plus a a a, Mult a a a, {- etc -}
 ) = Num a

 Apart from the possibility of naming these typeclasses better, this
 reorganisation gets my vote for Haskell 2.

Add the ability to do 

instance Num Foo where
a + b = ...
a - b = ...
a * b = ...

i.e when instantiating a derived class (if one can call it that),
allow implicit instantiation of base classes.

One thing to look out for, is a hierarchy of esoterically named
classes, and consequentially, error messages incomprehensible to
people unfamiliar with the details of the hierarchy.

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: GHC 6.2

2003-09-26 Thread Ketil Z. Malde
Simon Marlow [EMAIL PROTECTED] writes:

 The 'strange selectee 29' crash that you reported earlier is fixed in 6.2.  

Okay.  

 I saw your '.hp file contains NULs' reoprt, but there's not much we
 can do without a test case, unfortunately.  I've never seen this one
 myself.

I've only seen it once, and I was using a vim script on the file.  Not
everything shipped with Red Hat 9 is rock solid, so it might be a vim
bug. 

 Are there any other profiling bugs that I missed?

I've also gotten segmentation fault (w/ 6.0) when doing -h and -p
simultaneously.  I'm not sure if I can reproduce it, but I'll save a
snapshot if it happens again in a reproducible manner.  I did a quick
test now (v. 6.0.1), and it worked okay.

 The best estimate I can give is 4-6 weeks, but it could be sooner if
 things settle down quickly.

Great!

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHC 6.2

2003-09-26 Thread Ketil Z. Malde
Simon Peyton-Jones [EMAIL PROTECTED] writes:

 So far we have not been regarding 6.2 as ultra-urgent because we
 don't know of anyone who is really stuck with 6.0.  Please let us
 know if you are in fact stuck.

I already mentioned that I really need large file support, and I'd add
that I have some problems with profiling (segfaults, internal errors¹),
both under 6.0 and 6.0.1.  Is this known and/or fixed?  And was there
any answer to the original question:

 When can we expect 6.2?

I can work e.g. the large file issue by using multiple files, but as
it's going to be fixed RSN, I haven't bothered yet.  An approximate
schedule would be nice, I promise not to blame anybody if it doesn't
hold. :-)

-kzm

¹ If it's not a known issue, I can tar up one of these. It's a fairly
large example, but it seems to be consistently happening.
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHC 6.2

2003-09-26 Thread Ketil Z. Malde
Simon Peyton-Jones [EMAIL PROTECTED] writes:

 So far we have not been regarding 6.2 as ultra-urgent because we
 don't know of anyone who is really stuck with 6.0.  Please let us
 know if you are in fact stuck.

I already mentioned that I really need large file support, and I'd add
that I have some problems with profiling (segfaults, internal errors¹),
both under 6.0 and 6.0.1.  Is this known and/or fixed?  And was there
any answer to the original question:

 When can we expect 6.2?

I can work e.g. the large file issue by using multiple files, but as
it's going to be fixed RSN, I haven't bothered yet.  An approximate
schedule would be nice, I promise not to blame anybody if it doesn't
hold. :-)

-kzm

¹ If it's not a known issue, I can tar up one of these. It's a fairly
large example, but it seems to be consistently happening.
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: lexer puzzle

2003-09-26 Thread Ketil Z. Malde
Brandon Michael Moore [EMAIL PROTECTED] writes:

 Or was that supposed to be composition of a constructor with a function, A
 . f? Function composition, and higher order functions in general are
 likely to confuse an imperative programmer, but I think there isn't much
 syntax can do there.

I think there is a problem with too much overloaded syntax.  Perhaps
it is time to put non-ASCII characters to good use?

For instance, function composition could use the degree sign: ° 
and leave the . for module qualification.

Template Haskell could use double-angle quotation marks: «  »  
and the section sign: §
and avoid clashing with list comprehensions and the function
application operator. 

Implicit parameters could use an inverted question mark: ¿

And so on, just look for places where the semantics depend on spaces
in the right (or wrong) place.

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


Heap profiling dumped NULs

2003-09-23 Thread Ketil Z. Malde

Hi,

I can't reproduce it, but on one occasion running profiling with -hd,
I got corrupt .hp output, with a large block of NULs in an otherwise
normal output (The output is large, but I can make it available if
anybody wants it).  Rerunning the exact same command line produced a
normal .hp.

Just in case you'd like to know.

(GHC 6.0 from RPM on RH 9)

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: Syntax extensions (was: RE: The Future of Haskell discussionatthe Haskell Workshop)

2003-09-17 Thread Ketil Z. Malde
[EMAIL PROTECTED] writes:

  - There are features you might want to *disable*.  eg.
GHC lets you turn off the monomorphism restriction.

NoMonomorphismRestriction?

 Perhaps something like this:
  {-# LANGUAGE Haskell98 +FFI -MonomorphismRestriction #-}

 Nice!

I feel pragmas embedded in comments are a bit hackish, and I'd rather
have real syntax for this.  Of course, that would be an extension in
itself :-) 

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: The Future of Haskell discussion at the Haskell Workshop

2003-09-10 Thread Ketil Z. Malde
Iavor Diatchki [EMAIL PROTECTED] writes:

 Adrian Hey wrote:

 IMHO preserving the status quo wrt records should be low priority.
 It really doesn't bother me much if new (useful) language features break
 existing code. I think this is a better option than permanently
 impoverishing the language and/or forcing users to migrate their
 entire code to some other less impoverished language which may
 appear in the future.

 I also think that having backwards compatability is not much of an
 issue.  After all, ghc has introduces a  number of not backward
 compatable changes to haskell, and I never heard any complaints. 

Oh no?

Implicit parameters: I'm sure it is a great thing, but I'd already
used the (?) operator, and need -fglasgow-exts.  Now my program
depends on a bunch of well places spaces to compile.

Template Haskell: really cool new feature, which just happens to use
a syntax that overlaps with the list comprehension syntax.

And now, let's just screw any backwards compatibility, and re-engineer
the records system¹.

I don't need any of this, and it makes my life harder.  Are you guys
going to keep at it, until I regret ever using Haskell?  There was
recently a thread about using Haskell for something else than Haskell
compilers; well, if you actually want people to do this, then you
can't constantly keep changing the language.

-kzm

PS: For the record, I think the compiler developers are in general
doing a great job of augmenting the language *without sacrificing
backwards compatibility*.  But compatibility is important.  Branch GHC
and develop a new language instead!

-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: The Future of Haskell discussion at the Haskell Workshop

2003-09-10 Thread Ketil Z. Malde
Johannes Waldmann [EMAIL PROTECTED] writes:

 What about ad-hoc overloading (allowing visible entities to share names,
 as long as they can be distinugished by their typing).

 This is orthogonal to the proper records issue (?)
 but it might improve the current situtation (?)
 and it seems backward-compatible (?)

Yes.  Don't get me wrong; please go and define proper records,
improve the record system accordingly, adapt and implement. 

I just wanted to correct the impression that there were no complaints
about broken backwards compatibility.  Because it is - or at least, it
can be - a real problem.

Sometimes it has to be done in order to set things right, but it
shouldn't be done lightly.

There is also the issue of weighing down the language with features
and extensions.  It may give you more expressive power, but it also
makes the language harder to master, and programs more difficult to
maintain. 

 Of course this would need an extension of the type checker

Doesn't worry me overly, it is Somebody Else's Problem :-)

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: The Future of Haskell discussion at the Haskell Workshop

2003-09-10 Thread Ketil Z. Malde
Robert Ennals [EMAIL PROTECTED] writes:

[Heavy snippage, hopefully preserving semantics]

 data Foo = Foo {wibble :: Int, wobble :: String}
   deriving Wibble

 We could imagine the definition of Foo being automatically desugared to the 
 following:

 data Foo = Foo Int String

 instance Wibble Foo where
 wibble (x,_) = x
 wobbble (_,y) = y
 set_wibble x (_,y) = (x,y)
 set_wobble y (x,_) = (x,y)

Shouldn't that rather be:

class HasWibble a where
wibble :: a - Int
set_wibble :: a - Int - a

class HasWobble a where ...

data Foo = Foo Int String

instance HasWibble Foo where 
wibble (Foo x _) = x
set_wibble (Foo x y) z = Foo z y

instance HasWobble Fo where...

In order to let another record provide just a 'wibble' without a
'wobble'?

One danger of such an approach (implicit classes and instances) might
be non-intuitive error messages.

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: The Future of Haskell discussion at the Haskell Workshop

2003-09-10 Thread Ketil Z. Malde
[EMAIL PROTECTED] (Ketil Z. Malde) writes:

 Robert Ennals [EMAIL PROTECTED] writes:

BTW, isn't this more or less exactly what Simon suggested (at the very
top of this thread)?

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: Exhaustive Pattern-Matching

2003-08-29 Thread Ketil Z. Malde
Christian Maeder [EMAIL PROTECTED] writes:

 Indeed, I always try to avoid all warnings in my sources by using the
 flag -Wall, because I consider this to be good programming
 style. (In particular warnings about unused and shadowed variables
 prevented a lot of errors.) However some warnings are difficult to
 avoid. So how difficult would it be to implement non-exhaustive
 pattern warnings for nested patterns?

 data Color = Red | Green | Blue

 f :: Color - String
 f x = case x of
Red - r
_   -   ++ case x of
   Green - g
   Blue  - b

One way to do it, is to add

_ - error This can never happen

I do this occasionally, and it catches some errors or mistaken
assumptions on my part every now and then.

(Perhaps one could even have a special funcition, impossible, say,
that would tell the compiler that a particular branch would never be
taken.  In case the compiler is smart enough to figure it out, and
issue a warning for it -- it would know not to bother.)

Or one might wish for some kind of pragma to turn off this warning
selectively for a block of code.

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Poll: How to respond to homework questions

2003-08-29 Thread Ketil Z. Malde
Shawn P. Garbett [EMAIL PROTECTED] writes:

 For the How do I write a map function in Haskell?, how about an answer of 
 drop course immediately before your GPA is impacted further.

:-)

 Of course, this comes from someone whos made some stupid posts to this list, 
 and gotten polite answers which is very different than most netlists.

To quote Mr. Garrison, the South Park teacher:  Remember, kids, there
are no stupid questions, only stupid people.

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


interactive co-recursion

2003-08-25 Thread Ketil Z. Malde

I've no idea if the following is supposed to work, but the message
tells me to report it, so here it is.  Happens for all attempts to
define co-recursive functions, this is just the simplest example.

  Prelude let { f = g ; g = f}
  ghc-6.0: panic! (the `impossible' happened, GHC version 6.0):
getLinkDeps No iface for [pkg]DataziTuple
 
  Please report it as a compiler bug to [EMAIL PROTECTED],
  or http://sourceforge.net/projects/ghc/.

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: profiling for stack usage

2003-08-18 Thread Ketil Z. Malde
Simon Marlow [EMAIL PROTECTED] writes:

 1. Is there a way to profile stack usage, so that I can identify the
 culprit and deal with the problem at the root?

   
 http://www.haskell.org/ghc/docs/latest/html/users_guide/prof-heap.html#RTS-OPTIONS-HEAP-PROF+RTS
 
 in particular, the -xt flag.

Hmm, sorry for being so dense, but I'm having a tough time with this.
It seems profiling by itself tends to blow the stack -- is that
correct/normal behavior?  (I'm also using -O2, if that matters)

Is there any way to know what kind of data resides on the stack, or
what function generated it?  The TSO tells med its size, but isn't
really helpful beyond that (or am I missing something?)

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


profiling for stack usage

2003-08-15 Thread Ketil Z. Malde

Hi again,

I'm currently in a situation where my program runs easily out of
stack.  Depending on the input, stack usage often exceeds 10Mb.

1. Is there a way to profile stack usage, so that I can identify the
culprit and deal with the problem at the root?  Normal (time)
profiling tells me how many times a function is called, but it would
be interesting to know how many times it was recursively called, or
the size of its stack frames.  Is that information available?

Heap profiling -- well, it doesn't *sound* as if it would incorporate
the stack; does it anyway?

2. Is there a way to compile programs to use more than the default
stack?  I can of course pass +RTS -K10M -RTS on the command line, but
I would rather like to change the default, instead of kicking myself
for forgetting it all the time.  And is there any reason (except
excessive resource consumption and postponed failure from infinite
loops) not to run with huge stacks? 

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: internal error: eval_thunk_selector: strange selectee 29

2003-08-14 Thread Ketil Z. Malde
Simon Marlow [EMAIL PROTECTED] writes:

 There is something really fishy going on; I checked out the same code
 in a different directory, and built it in the same way, without
 getting the same behaviour.

 Hmm.  Profiling isn't deterministic though, because heap samples happen
 based on a timer interrupt, so you might get different results if you
 run it multiple times.

 I'm not quite sure what kind of confusion that led to the error (or
 the fact that my run times suddenly were tripled); possibly some old
 .o or .hi file got copied in by mistake?

 Possibly, or possibly a recompilation bug (are you using --make?).

Yes, I am.  I got the error several times, but when I cleaned
everything up, it seems to have gone away -- as did the tripled
running times (and yes, they were user/system times, not just wall
clock).  Very puzzling.

Unfortunately, a 'make clean' removed all the evidence -- if I stumble
over it again, I'll make a copy first.

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: link statically with libc?

2003-08-14 Thread Ketil Z. Malde
Simon Marlow [EMAIL PROTECTED] writes:

 I don't know how the Ada guys do it.  Perhaps they have an alternate
 set of compiled libraries with bounds-checking turned off?

Me neither, I've just heard the idea discussed, not the actual
technology. 

 I suppose I can do it by wrapping array accesses in a class or
 otherwise, with a safe and an unsafe implementation, and switch when
 I'm satisfied things work.

 Yes, that would do it.

Moving to unsafeAt gained me a couple of percent in my application.
Throwing in a -fliberate-case gave me a miniscule, but possibly
positive gain.

However, linking statically (with -optl-static) causes my program to
stack overflow!?  Sounds very strange to me, but I don't have time to
investigate that further today.  I'll look into it a bit more
tomorrow. 

 Large file support will be in 6.2.

Goodie!

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


link statically with libc?

2003-08-14 Thread Ketil Z. Malde

Hi,

Is it possible to link libc statically with GHC?  My Linux box has
been upgraded, and compiled binaries no longer work on older
systems. :-( 

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: link statically with libc?

2003-08-14 Thread Ketil Z. Malde
Simon Marlow [EMAIL PROTECTED] writes:

 -optl-static should do the trick.

That worked nicely, thanks!

(PS: Am I looking in the wrong places, or are a lot of GHC options
undocumented?  I seem to remember options being brandished about (turn
of array bounds checking, tuning unboxing and stuff) that I'm unable
to find documented anywhere.)

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: idiom for producing comma-seperated lists?

2003-08-14 Thread Ketil Z. Malde
Antony Courtney [EMAIL PROTECTED] writes:

 -- Example: format a list of strings, using a comma as a seperator:
 mkSepStr :: [String] - String
 mkSepStr xs = foldrs (\x s - x ++ ,  ++ s)  xs
 
 t0 = mkSepStr []   -- == 
 t1 = mkSepStr [hello]-- == hello
 t2 = mkSepStr [10,20,30] -- == 10, 20, 30
 
 What do the rest of you do to solve this particular problem?

Uh, concat and intersperse?

Prelude concat $ List.intersperse ,  $ []

Prelude concat $ List.intersperse ,  $ [hello]
hello
Prelude concat $ List.intersperse ,  $ [10,20,30]
10, 20, 30

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


Re: [String]-[[Bool]] 2

2003-08-14 Thread Ketil Z. Malde
Tn X-10n [EMAIL PROTECTED] writes:

 change :: String - Bool
 change 1  = True
 change 0  = False

  conv :: [String] - [Bool]==unable to declare [[Bool]]

Again: a String is a list of ?

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


Re: [String] - [[Bool]]

2003-08-14 Thread Ketil Z. Malde
Tn X-10n [EMAIL PROTECTED] writes:

 i am new wif haskell, i would like to know how can i get a list of
 string and convert it to a list of a list of bool

 [String]- [[Bool]]

What is the definition of a String?  (I.e. what is a String a list of?)
Write a function to convert one of these to the corresponding Bool.

Then write a function that uses that function to convert a String to a
list of Bool.

And then, in a similar manner, apply it to a list of Strings to
generate a list of lists of Bool.

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


Re: loop through the list...

2003-08-11 Thread Ketil Z. Malde
Fredrik Petersson [EMAIL PROTECTED] writes:

 something like [if (thenumber  index) then (index,int+1) \and break\ else
 (index,int) | (index,int) - [thelist]]

I think you need to write an explicit recursion, instead of using a
list comprehension. 

 Can i use some help-boolean to set it false when we have counted up once?

Using a fold(r|l) would be similar, but I think you'd be better
advised at this point to write the recursion explicitly.

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: Editor in Linux for Hint/Helium

2003-08-11 Thread Ketil Z. Malde
Glynn Clements [EMAIL PROTECTED] writes:

 Does anyone know of a good editor in Linux to do this or the commands for
 Emacs etc. that can be used from within Hint to achieve [jumping to
 lines with errors automatically]?

 Emacs and XEmacs allow you to go to a specified line using +number,

If you do M-x compile from within (X)Emacs, you should be able to jump
from errors/messages in the output buffer to the corresponding point
in the source.  It's been a while since I used this, since I prefer to
compile in a terminal, and type M-g line no RET to jump to the right
line; and I have no idea how well it integrates with Helium.

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


Re: [newbie] UTF-8

2003-08-11 Thread Ketil Z. Malde
Marcin 'Qrczak' Kowalczyk [EMAIL PROTECTED] writes:

 Dnia pon 11. sierpnia 2003 00:49, Wolfgang Jeltsch napisa:

 The main problem is that you need binary I/O. Haskell 98 only provides text
 I/O.

 You don't need binary I/O for UTF-8 now; because implementations use 
 ISO-8859-1, UTF-8 octets can be faked as characters by (chr . fromIntegral).

I wonder,

Would it cause a lot of compatibility trouble to wrap IO functions in
a class

class IOData a where
readFile :: FilePath - a
:

and do

instance IOData Char where ...
instance IOData Word8 where ...

(Defaulting to Char the same way as Integer)

Would this let us start writing byte-based IO without sacrificing
compatibility or designing specific interfaces for it?

Perhaps one could even do record-based IO by declaring instantiation
IOData for custom data structures?

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


Re: link statically with libc?

2003-08-10 Thread Ketil Z. Malde
Simon Marlow [EMAIL PROTECTED] writes:

 There isn't a flag to turn off array bounds checking - it would require
 compiling against different libraries.  

I must have misremembered it from somewhere, perhaps confusing it with
-fliberate-case-threshold mentioned a while ago (which probably
belongs in the experimental category?)

Turing off bounds checking could be fairly useful, I think, if there
is a significant speedup to be gained.  My impression is that the
typical Ada programmer tests the program thoroughly with bounds
checking, but compiles without for deployment. (Of course, we would
rather *know* a priori that we're not going out of bounds, rather than
just test for it, but it seems to work all right for them)

 There are array operations that
 avoid bounds checking, however (eg. unsafeRead, unsafeWrite).

I suppose I can do it by wrapping array accesses in a class or
otherwise, with a safe and an unsafe implementation, and switch when
I'm satisfied things work.

-kzm

PS: is large file support in the vicinity yet?
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHCi 6.0 buglet - segfault on input

2003-08-10 Thread Ketil Z. Malde
Simon Marlow [EMAIL PROTECTED] writes:

 Apparently, the function keys insert 'ESC O x', with varying x's,
 perhaps it's the ESC that breaks GHCi?

 Could be a readline bug, but I don't have a RedHat 9 system here to
 test on.

Apparently, Python behaves in the same way.  I'll file a report with
RH and move along.

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Decimal Literals

2003-07-11 Thread Ketil Z. Malde
Ashley Yakeley [EMAIL PROTECTED] writes:

 There should be a separate syntax for that. As it stands, the string 
 3.1415926536 unambiguously specifies a rational number. Perhaps 
 something like 3.1415926536... should be interpreted as the 'simplest' 
 rational that agrees with the given digits, which would then be passed 
 to fromRational.

I.e. for 3.14, allow any rational number in [3.14,3.15), or
perhaps (3.135,3.145]?  Or restrict it to just the rational number in
range with the least total digits?

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


Re: ghc on alpha-linux?

2003-07-07 Thread Ketil Z. Malde
Simon Peyton-Jones [EMAIL PROTECTED] writes:

 Ken Shan was making good progress on an Alpha port of GHC.   Ken, could
 you update us on the status?

Courtesy of the good people at SGI, I have now access to an SGI Altix
(8 Itanium processors, and lots of RAM that I Really Need).  So, I'm
very interested in any information on how to get current GHCs running
on 64bit architectures.

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


stack space overflow

2003-06-20 Thread Ketil Z. Malde

Hi,

I have a small function to find all indices in an array where a given
subword can be found, looking like this:

 ind i ws ar 
   | i+length ws-1  len e   = []
   | and [ar!(i+j) == ws!!j | j-[0..length ws-1]] = i : ind (i+1) ws ar
   | otherwise   = ind (i+1) ws ar

(i::Int is the position, ws::[a] is the word to look for, while
ar::Array Int a is the array wherein to look)

This occasionally blows up with a stack overflow, perhaps I'm being
dense, but I'm not sure why.  Any suggestions?

BTW, is there a general way to track down stack overflows?  I use the
-xc option, are there any other tricks I should know about?  And does
heap profiling (GHC) imply more stack usage -- I seem to get overflows
much more easily when profiling.

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: @-bindings broken in 6.0?

2003-06-18 Thread Ketil Z. Malde
Simon Peyton-Jones [EMAIL PROTECTED] writes:

 Yes, I'm afraid so.  With -fglasgow-exts Template Haskell captures
   [t|  ...  |]
 and
   [p| ... |]
 and similarly [d| and [e| 
 for quotations.

I had a similar experience when I defined the (?) operator.  Which
obviously clashes with the syntax for implicit paramters, unless
surrounded by spaces.

 But maybe this isn't what you found?Better syntax here would be
 welcome if anyone can think of some. 

I think lumping all these extensions under one switch is the
problem.  I find it hard to do useful stuff without some extensions,
but would rather not be bitten by this kind of things.

Isn't it possible to provide e.g. implicit parameters and template
Haskell as magical modules?  So that import Template enables the
syntax above, and I could use import MultiParameterTCs but not
ImplicitParams, for instance?

Or at least, provide different -fglasgow-exts flags to fine tune which
extensions are being used.

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: ICFP Programming Contest

2003-06-18 Thread Ketil Z. Malde
John Hughes [EMAIL PROTECTED] writes:

 ICFP Programming Contest
 
 
 There are just ten days to go to the sixth ICFP Programming Contest!

This *is* announced to all relevant groups (as in comp.lang.*, at
least)? 

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: happy, ghc and {# OPTIONS #} pragma

2003-06-10 Thread Ketil Z. Malde
Martin Norbäck [EMAIL PROTECTED] writes:

 {-# OPTIONS -fglasgow-exts -cpp #-}
 -- parser produced by Happy Version 1.13
 {-# OPTIONS -fno-warn-unused-matches #-}

Generally, it'd be nice to be able to occasionally suppress warnings
for sections of code (with better than module granularity), where you
know the code is safe. 

Any chance of something like that?

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


forall quantifier

2003-06-04 Thread Ketil Z. Malde

Hi,

This is one of those topics everybody else seems to be familiar with,
but which I don't quite understand, and can't seem to find any good
information about.

I have a function declared as:

  anova2 :: (Fractional c, Ord b)
= [a-b] - (a-c) - [a] - [Anova1 c]

where the first parameter is a list of classifiers.  I could simplify
it, I guess, to something like

  classify :: Eq b = [a-b] - [a] - [[[a]]]
  classify cs xs = ...

where for each classifying function in cs, I would get the xs
partitioned accordingly.  E.g.

  classify [fst,snd] [(1,0), (1,2), (2,0)] 

would yield

  [ [(1,0), (1,2)], [(2,0)] -- classified by `fst`
  , [(1,0), (2,0)], [(1,2)]] -- classified by `snd`

Now, obviously, the problem is that fst and snd, being passed in a
list, needs to be of the same type; this complicates classifying a
list of type [(Int,Bool)], for instance¹.

I have a vague notion this is solvable using quantifiers (since I
ever only use Eq operations on the type), but I'm not sure exactly
how, I can't seem to find a good tutorial, and my Monte-Carlo
programming approach doesn't seem to be leading anywhere :-)

Can somebody suggest a solution, or a place to look?

-kzm

¹ I guess I can convert Bool to Int (True-1, False-0), but it's not
very appealing, IMHO.
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: how to track down out-of-bounds error?

2003-05-29 Thread Ketil Z. Malde
David Roundy [EMAIL PROTECTED] writes:

 The problem is trying to figure out where I'm doing this.  Unfortunately, I
 have only been able to see this error on a rather large test repository,
 where it takes seven minutes for the test to show up.

Hah!  *My* program can take hours before it crashes.

 Any suggestions how I might most easily track this bug down?

Did you try compiling with -prof -auto-all, and running with +RTS -xc?

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


Re: parsing e-mail messages (Re: African money)

2003-03-25 Thread Ketil Z. Malde
Peter Simons [EMAIL PROTECTED] writes:

 Mark Carroll writes:

 Perhaps I'll have to look out for a library for parsing e-mail
 messages.

 I have written a set of parser functions for RFC 2822 messages, which
 should do exactly that. It's not finished yet, but if you're
 interested in using the code (and in providing feedback), I'll gladly
 give you -- and anybody else, for that matter -- a copy.

..and if anybody cares, I've cooked up functions that build word
frequency tables, and compare them using a Bayesian approach (more or
less like Paul Graham's A Plan for Spam).  Haskell, of course.

Need a bit of tweaking, but works reasonably well, last time I
looked. 

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


Re: ANNOUNCE: GHC vesrion 5.04.3 released

2003-03-12 Thread Ketil Z. Malde

I notice the release notes say a few architectures should be possible
to port to, in particular AIX/POWER.  How possible is that, exactly?
Has anybody done it with any success?  Alternatively, is there any
alternative Haskell compiler (I guess that would be NHC?) that works
for this architecture? 

And does GHC or anybody else support 64bit address spaces?

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: int to float problem

2003-03-03 Thread Ketil Z. Malde
Mike T. Machenry [EMAIL PROTECTED] writes:

   I am having a problem. I recently desided I wanted a bunch function to return
 float instead of Int. I changed their type and wrote a new function that
 returned a float. I figured it'd be okay if all the others still returned
 Int since it's trivial to convert Int to Float.

Perhaps the other functions could be written with a more general type?
(E.g. :: Num a = ... - a)

Try to remove the type declaration, and see what Hugs or GHCi :t has
to say about it!

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: int to float problem

2003-03-03 Thread Ketil Z. Malde
Matthew Donadio [EMAIL PROTECTED] writes:

 Thank does sound like a pain, but it's better than putting fromIntegral
 all over my code. Why can't Haskell unify a an expected float with an
 infered int? It seems that this would make life alot easier.

Personally, I think that one of the things that made my life easier
with Haskell compared to C++, is the lack of implicit type
cast/conversions/coercions.   Now, obviously C++ does this in a quite
byzantine way, it's possible that a simpler and better system exists. 

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: Regular expressions as Haskell Type Generators?

2003-02-25 Thread Ketil Z. Malde
Steffen Mazanek [EMAIL PROTECTED] writes:

 I am wondering if it would be worth while (and possible) to allow the
 definition of types by regular expressions, e.g.

 data Date = Date #RegExp([0-9][0-9]-[0-9][0-9]-[0-9][0-9][0-9][0-9])

 or easier with some auxiliary constructs.

Not sure I follow this.  Why not declare Date = Date String (or
whatever format), making the constructor private?  Then you could
of course export date-constructing functions that maintain any
invariants you like. 

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: Debugging haskell

2003-02-23 Thread Ketil Z. Malde
Joe English [EMAIL PROTECTED] writes:

 Sengan Baring-Gould wrote:

 http://www.catb.org/~esr/writings/taoup/html/ch01s06.html

 states that debugging often occupies three-quarters or more
 of development time.  I don't think that is my experience
 in Haskell... more like 1/4 at most. I was wondering what
 others felt.

 Me either; in fact even 1/4 of the time debugging
 sounds quite high.

I think it depends a lot on various factors, and that more important
than language is project size, programmer experience, and effort spent
in the design phase.  For a small, one-programmer project, debugging
is IMHO much simpler than in a multi-programmer, multi-year project,
in particular an ill-designed one.

I think this is a fairly accepted fact in the field of software 
engineering. 

 When I first started using Haskell, most of my time
 went to fighting with the typechecker, but once the
 code checked it almost always Just Worked.  This is a
 pleasant experience.

I can relate to that.  On the other hand, finding the really obscure
bugs is (at least to me) *hard*.  The bugs would probably be hard
regardless of language, except perhaps lazyness-related bugs (if you
can call that kind of undesirable behaviour a bug).

 Nowadays, I spend the most time trying to understand
 the problem, relying on the typechecker to tell me when
 I've misunderstood something.

I think the type syntax itself, just not the checking tools, help.
E.g. reading Paul Graham's A Plan for Spam, I note that in order to
segregate strings from headers and body, he rather awkwardly prepended
header strings with the originating header -- e.g. Subject: foo were
stored as Subject*foo.  Much nicer to do

data Token = Header String | Body String deriving ...

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


Histogram-building code (was: Re: Yet another weakly defined bug report)

2003-02-18 Thread Ketil Z. Malde

Just a quick status report, and to note a couple of lessons learned:

Things work adequately, as far as I can tell.  I can now process heaps
of data, without blowing up anything.  Appears to be faster than
spam-stat.el, at least, although I haven't measured.

I'm back to using readFile for file IO, and it works nicely, as long
as I make sure all the file is processed.  I think this is a good way
of processing large amounts of data (where the processing reduces the
data size), reading the entire file into memory strictly is quickly
going to be too costly (expanded to linked lists of unicode, ugh)

Don't trust finiteMap to evaluate anything.  I have evidence one of
the major space leaks was FM only evaluating the strings used as keys
to the point they were proved unique.  (Is this right?)  Strictifying
the strings helped a lot.

One question though, about hFlush.  I print out the status by
repeatedly putStr'ing blah blah \r.  With NoBuffering set, it works,
but when following the putStr with 'hFlush stdout', it doesn't (only
outputs very sporadically.  I guess I'm misunderstanding the function
of hFlush, anybody care to elaborate?)

And a final lesson, unlike cockroaches, computer bugs hide in light as
well in the darkness.  One bug in the very trivial token parsing code
caused a lot of words that should have been ignored to be included. 

Thanks to everybody who helped out.

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Histogram-building code (was: Re: Yet another weakly defined bug report)

2003-02-18 Thread Ketil Z. Malde

Just a quick status report, and to note a couple of lessons learned:

Things work adequately, as far as I can tell.  I can now process heaps
of data, without blowing up anything.  Appears to be faster than
spam-stat.el, at least, although I haven't measured.

I'm back to using readFile for file IO, and it works nicely, as long
as I make sure all the file is processed.  I think this is a good way
of processing large amounts of data (where the processing reduces the
data size), reading the entire file into memory strictly is quickly
going to be too costly (expanded to linked lists of unicode, ugh)

Don't trust finiteMap to evaluate anything.  I have evidence one of
the major space leaks was FM only evaluating the strings used as keys
to the point they were proved unique.  (Is this right?)  Strictifying
the strings helped a lot.

One question though, about hFlush.  I print out the status by
repeatedly putStr'ing blah blah \r.  With NoBuffering set, it works,
but when following the putStr with 'hFlush stdout', it doesn't (only
outputs very sporadically.  I guess I'm misunderstanding the function
of hFlush, anybody care to elaborate?)

And a final lesson, unlike cockroaches, computer bugs hide in light as
well in the darkness.  One bug in the very trivial token parsing code
caused a lot of words that should have been ignored to be included. 

Thanks to everybody who helped out.

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Yet another weakly defined bug report

2003-02-17 Thread Ketil Z. Malde
Dean Herington [EMAIL PROTECTED] writes:

 Yes, getting the right amount of strictness--and in the right places--can be
 tricky. 

Tell me about it!

 You should do the counting strictly:
 
 Just n - case n+1 of n1 - addToFM f w n1

Thanks for the tip.  Just performing this change didn't perceptibly
change anything, though.  It seems to be working all right now, but to
my amazement, it may have been upgrading to 5.04.2 that did it?!  (I
had a lot of heapCensus trouble)  Is this at all possible?

 Right, except that, as Simon M. mentioned, the file is opened so that any opening
 exceptions are triggered.

Yeah.  I keep forgetting the IO monad is imperative.

 Perhaps.  You're only demanding the head of the list.  Conceivably, the FM logic
 might be able to determine the lowest key/element pair without evaluating the
 entire map.

 I find the above approach a bit risky, as you are closing the file after having
 only shallowly demanded the result of addHist.  My earlier suggestion, return $!
 addHist fm x, makes exactly the same shallow demand, but if that demand is
 insufficient, loses performance but not correctness.

..but then I could equally well use readFile, couldn't I?

Anyway, thanks for all the suggestions, all of you.

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Yet another weakly defined bug report

2003-02-14 Thread Ketil Z. Malde
Dean Herington [EMAIL PROTECTED] writes:

 Ketil Z. Malde wrote:

 -- | add data from a file to the histogram
 addFile :: FiniteMap String Int - String - IO (FiniteMap String Int)
 addFile fm name = do
 x - readFile name
 return (addHist fm x)

I changed this to read x strictly, but it turned out that wasn't quite
enough.  See below.

 -- | add data from all files in a directory to the histogram
 addDir :: FiniteMap String Int - String - IO (FiniteMap String Int)
 addDir fm dir = do
   dc - getDirectoryContents dir
   fs - filterM doesFileExist (map ((dir++/)++) dc)
   foldM addFile fm fs

 addHist :: FiniteMap String Int - String - FiniteMap String Int
 addHist fm = foldl add1 fm . words
where add1 f w = case lookupFM f w of
Just n - addToFM f w (n+1)
Nothing - addToFM f w 1

 The string won't be evaluated until the finite map is demanded.  None of the
 code you've shown so far makes that demand.

[I'll leave my ramblings here, skip to the  for the solution]

Right.  But if I do

f - addFile emptyFM foo

then no IO should be performed either, right?  And when I later do

print (head . fmToList f)

the whole FM needs to be computed, no?

If this is unsound (too lazy) in any way, I don't see it.  How much
memory can I expect an FM to consume, anyway?  I would expect
something like 

(log n * sizeof(branch node)) + n*sizeof(key+element)

Which should be roughly equivalent to n*sizeof(key+element), which in
my case (building a frequency count for words) should be roughly
equivalent to the number of different words times their average
length (times 8 bytes per character in a list).  Is this far off?

Experiments show that doing x - addDir emptyFM on a directory
containing 13Mb of files, the process grows to about 400Mb.
Surprisingly, asking for the head requires a lot more memory and takes
considerable time.

=

So, what's really happening?  Well, it seems the files were read
strictly, but the FMs weren't constructed yet.  So the result was a
lot of files residing in memory, stored as expansive [Char]s.
Changing addFile to:

 addFile :: FiniteMap String Int - String - IO (FiniteMap String Int)
 addFile fm name = do
 h - openFile name ReadMode
 x - hGetContents h
 let f = addHist fm x 
 hClose (f `seq` h) -- thanks to Peter Thiemann
 return f


With this, I can at least plough through the 13Mb of files
comfortably.  After fixing a bug in my overlong word elimination code,
but a directory with 50Mb is still out of reach.

What is the limit on open files, and why?  I think it'd be nice to
just schedule a huge amount of IO operations, and have them all be
performed when required (i.e. when the FM is first accessed).
Apparently, my addDir took the trouble to open the files, but not
generate the FMs -- any idea why?

Finally, the nice thing about Haskell is that the frequency counting
code was written and tested in less than five minutes.  The downside
is that getting the IO and strictness right, took around five
hours. :-/ 

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Yet another weakly defined bug report

2003-02-13 Thread Ketil Z. Malde

Hi,

when toying around with GHCi, I got a bunch of 

  Prelude :r
  phase `Literate pre-processor' failed (exitcode = 1)

  Prelude :l Hist
  phase `Literate pre-processor' failed (exitcode = 1)

ghc -c -Wall didn't find anything suspicious, and in the end, exiting
and restarting ghci did the trick.

I've no idea what trigged this, perhaps running out of file handles? 

Just in case you'd like to know,

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: Yet another weakly defined bug report

2003-02-13 Thread Ketil Z. Malde
[EMAIL PROTECTED] (Ketil Z. Malde) writes:
[EMAIL PROTECTED] (Ketil Z. Malde) writes:

   Prelude :r
   phase `Literate pre-processor' failed (exitcode = 1)

 I've no idea what trigged this, perhaps running out of file handles? 

I forgot: GHC version 5.04.1.  It seems that this is definitely
trigged by running out of file handles, so apparently, I did have an
idea. 



The following code runs out of file handles, so I am seeking
enlightenment as to why.

 -- | add data from a file to the histogram
 addFile :: FiniteMap String Int - String - IO (FiniteMap String Int)
 addFile fm name = do
 x - readFile name
 return (addHist fm x)
 
 -- | add data from all files in a directory to the histogram
 addDir :: FiniteMap String Int - String - IO (FiniteMap String Int)
 addDir fm dir = do
   dc - getDirectoryContents dir
   fs - filterM doesFileExist (map ((dir++/)++) dc)
   foldM addFile fm fs

Running addDir on a directory with few hundred files trigs it.
Shouldn't all of each file's contents be consumed by each addFile, and
thus the handle be released? 

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: Yet another weakly defined bug report

2003-02-13 Thread Ketil Z. Malde
Simon Marlow [EMAIL PROTECTED] writes:

   -- | add data from a file to the histogram
   addFile :: FiniteMap String Int - String - IO (FiniteMap 
  String Int)
   addFile fm name = do
   x - readFile name
   return (addHist fm x)
   
   -- | add data from all files in a directory to the histogram
   addDir :: FiniteMap String Int - String - IO (FiniteMap 
  String Int)
   addDir fm dir = do
 dc - getDirectoryContents dir
 fs - filterM doesFileExist (map ((dir++/)++) dc)
 foldM addFile fm fs

 It's not possible to tell from this code whether the readFiles will be
 fully evaluated or not: it depends on how much evaluation addHist does,
 and to what extend the result FiniteMap is demanded, amongst other
 things.

Of course.  Never cut code, I suppose; I thought the parts my
understanding would be weakest would be the monadic stuff, not this: 

 addHist :: FiniteMap String Int - String - FiniteMap String Int
 addHist fm = foldl add1 fm . words
where add1 f w = 
 case lookupFM f w of
Just n - addToFM f w (n+1)
Nothing - addToFM f w 1

I felt pretty sure that this would evaluate the string to the end.  Am
I wrong?
 
 These things are always tricky to understand, which is why I recommend
 not using lazy I/O.  File reading is not a pure operation: running out
 of file descriptors is a good counter-example.

Okay.  Perhaps renaming readFile to unsafeReadFile? :-)

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: Yet another weakly defined bug report

2003-02-13 Thread Ketil Z. Malde
[EMAIL PROTECTED] (Ketil Z. Malde) writes:
[EMAIL PROTECTED] (Ketil Z. Malde) writes:

   Prelude :r
   phase `Literate pre-processor' failed (exitcode = 1)

 I've no idea what trigged this, perhaps running out of file handles? 

I forgot: GHC version 5.04.1.  It seems that this is definitely
trigged by running out of file handles, so apparently, I did have an
idea. 



The following code runs out of file handles, so I am seeking
enlightenment as to why.

 -- | add data from a file to the histogram
 addFile :: FiniteMap String Int - String - IO (FiniteMap String Int)
 addFile fm name = do
 x - readFile name
 return (addHist fm x)
 
 -- | add data from all files in a directory to the histogram
 addDir :: FiniteMap String Int - String - IO (FiniteMap String Int)
 addDir fm dir = do
   dc - getDirectoryContents dir
   fs - filterM doesFileExist (map ((dir++/)++) dc)
   foldM addFile fm fs

Running addDir on a directory with few hundred files trigs it.
Shouldn't all of each file's contents be consumed by each addFile, and
thus the handle be released? 

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Yet another weakly defined bug report

2003-02-13 Thread Ketil Z. Malde
Simon Marlow [EMAIL PROTECTED] writes:

   -- | add data from a file to the histogram
   addFile :: FiniteMap String Int - String - IO (FiniteMap 
  String Int)
   addFile fm name = do
   x - readFile name
   return (addHist fm x)
   
   -- | add data from all files in a directory to the histogram
   addDir :: FiniteMap String Int - String - IO (FiniteMap 
  String Int)
   addDir fm dir = do
 dc - getDirectoryContents dir
 fs - filterM doesFileExist (map ((dir++/)++) dc)
 foldM addFile fm fs

 It's not possible to tell from this code whether the readFiles will be
 fully evaluated or not: it depends on how much evaluation addHist does,
 and to what extend the result FiniteMap is demanded, amongst other
 things.

Of course.  Never cut code, I suppose; I thought the parts my
understanding would be weakest would be the monadic stuff, not this: 

 addHist :: FiniteMap String Int - String - FiniteMap String Int
 addHist fm = foldl add1 fm . words
where add1 f w = 
 case lookupFM f w of
Just n - addToFM f w (n+1)
Nothing - addToFM f w 1

I felt pretty sure that this would evaluate the string to the end.  Am
I wrong?
 
 These things are always tricky to understand, which is why I recommend
 not using lazy I/O.  File reading is not a pure operation: running out
 of file descriptors is a good counter-example.

Okay.  Perhaps renaming readFile to unsafeReadFile? :-)

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Arrays and arrays

2003-01-23 Thread Ketil Z. Malde
Simon Marlow [EMAIL PROTECTED] writes:

 OTOH, doing lots of small (//) seems to be faster than doing a few
 large ones (containing the same updates).  Go figure.

 That's bizarre.  Perhaps the results are obscured by some other
 optimisations which are happening.

It is probably an operator error.  I.e., me making a mistake; I had to
rewrite the program a bit in order to make the change.  Still,
profiling shows that it's the array updates that take almost all the
time.  I'll try to sort out the benchmarks a bit next week, and if I
still observe that behaviour, I'll try to distill a clean example for you.

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



Re: Arrays vs Lists and Specialization

2003-01-22 Thread Ketil Z. Malde
Matthew Donadio [EMAIL PROTECTED] writes:

 OK, my question then has to do with the efficiency of lists versus
 arrays.  Do the latest compilers handle handle arrays efficiently, or
 are lists really the way to go?  

I've currently struggled a bit with arrays.  I have a list based
program (calculating suffix arrays, since you ask), and since I
experience a notably lower performance than array based C equivalents,
I thought using arrays would help me out.

Currently, I've been able to use arrays efficiently as read-only data
structures. I've tried to use STArrays to do updates imperatively, but
it's still slow, and uses a lot of memory (that doesn't show up in the
heap profiling).  I'll try to wrap more of the program in the ST
monad, to see if it helps.

 If there is a performace difference, is it generally big enough to
 warrant rewriting algorithms?

I think it is hard to answer that generally.  For some algorithms, the
benefit can be significant; it depends on your application, your data
set, and your resources. 

But remember that correct is better than fast, and readable is better
than correct. :-)

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Database Mailing List

2003-01-22 Thread Ketil Z. Malde
Dominic Steinitz [EMAIL PROTECTED] writes:

 Would it be possible to set up a mailing list for those interested?

We're getting a lot of these lists now (gui, libs, cafe) -- are they
really warranted?  Couldn't they all fit in the libraries list?  I'd
like to keep an ear to all of these developments, and it's not like
traffic is all that high at the moment.

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Arrays and arrays

2003-01-22 Thread Ketil Z Malde
Simon Marlow [EMAIL PROTECTED] writes:

 That's because currently large objects aren't included in the profile.

Okay, I didn't know that.

 I'll look into fixing this.

Great!  But just knowing about it also helps a lot.

Since you're on the line, could you confirm or deny that the (//)
operator is something equivalent to (roughly):

a // ps = runST (thaw a = \u - update ps  unsafeFreeze u)

I.e. that the list of updates are treated as an atomic operation?
Because doing it that way explicitly sure didn't seem to help.

OTOH, doing lots of small (//) seems to be faster than doing a few
large ones (containing the same updates).  Go figure.

BTW: does anybody know an accepted fastest way of doing in-place
permutations on an array?

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



Re: Arrays and arrays

2003-01-21 Thread Ketil Z. Malde
[EMAIL PROTECTED] (Ketil Z. Malde) writes:

 Hal Daume III [EMAIL PROTECTED] writes:

 Yes, (//) is terrible.  It *never* tries to update in-place.  

 Any reason it couldn't be done in-place?  (I.e. thaw, update all, and
 freeze again)  Am I missing something -- Could partial results be
 used, the update list be infinite, or anything like that?

I'm toying with STArrays in order to fix this.  In prinicple it should
be simple, but it ended up a tangled mess of incomprehensible warnings
and strange errors.  Oh well, I've boiled it down to something like:

  replace :: UArray Int Int - [(Int,Int)] - UArray Int Int
  replace a p = runST (thaw a = \u - update u p  freeze u)

  update :: STUArray () Int Int - [(Int,Int)] - ST () ()
  update u ps = mapM_ (uncurry (writeArray u)) ps

Which gives me

  Compiling SuffixArray  ( SuffixArray.lhs, interpreted )

  SuffixArray.lhs:131:
Cannot unify the type-signature variable `s' with the type `()'
Expected type: ST s a
Inferred type: ST () (b Int Int)
In the expression: (thaw a) = (\ u - (update u p)  (freeze u))
In the first argument of `runST', namely
`((thaw a) = (\ u - (update u p)  (freeze u)))'

I've tried rearranging the code in various ways, but I can get no
further. 

Sounds to me that setting s=() and a=(b Int Int) would do the trick,
but apparently the compiler disagrees.  I haven't used the ST monad
before, so perhaps I'm missing something obvious?

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



Re: Arrays and arrays

2003-01-21 Thread Ketil Z. Malde
[EMAIL PROTECTED] (Ketil Z. Malde) writes:

 [EMAIL PROTECTED] (Ketil Z. Malde) writes:

 Hal Daume III [EMAIL PROTECTED] writes:
 
 Yes, (//) is terrible.  It *never* tries to update in-place.  

   replace :: UArray Int Int - [(Int,Int)] - UArray Int Int
   replace a p = runST (thaw a = \u - update u p  freeze u)
 
   update :: STUArray () Int Int - [(Int,Int)] - ST () ()
   update u ps = mapM_ (uncurry (writeArray u)) ps

 I've tried rearranging the code in various ways, but I can get no
 further. 

It's funny, you know, how asking questions on the internet gets you
the answer quickly.  Just after sending this, I scratched my head, and
did:

update :: STUArray s Int Int - [(Int,Int)] - ST s ()

and, well, that apparently worked.  Like a charm.  The 's' parameter
is apparently just magic, or in Marcin Kowalczyk's words (old (26 Feb
2001) post to the haskell list):

| The type variable 's' is used in a very tricky way, to ensure
| safety when
|runST :: (forall s. ST s a) - a
| is used to wrap the ST-monadic computation in a purely functional
| interface. It does not correspond to the type of data being
| manipulated.

(I'll be right back with the benchmarks.)

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



Re: Arrays and arrays

2003-01-21 Thread Ketil Z. Malde
[EMAIL PROTECTED] (Ketil Z. Malde) writes:

   replace :: UArray Int Int - [(Int,Int)] - UArray Int Int
   replace a p = runST (thaw a = \u - update u p  freeze u)
 
   update :: STUArray s Int Int - [(Int,Int)] - ST s ()
   update u ps = mapM_ (uncurry (writeArray u)) ps

 (I'll be right back with the benchmarks.)

I know you're all eagerly waiting for this, so here's a small progress
report.  Or lack-of-progress report, if you like.

Apparently, I get really huge memory consumption when using the above
repeatedly.  Normally, I can deal with it, but profiling (-h) doesn't
show any likely culprit, the curves stay well below 60k for the most
part.  I know there are different kinds of memory profiles (retainer
profile, etc), is that where I have too look?  Or is the problem
something else?

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



Re: Arrays and arrays

2003-01-21 Thread Ketil Z. Malde
Hal Daume III [EMAIL PROTECTED] writes:

[snip my functions that use the ST monad to do (//)]

 You shouldn't try to write these functions.  You should do all array
 modifications within the ST monad, rather than looking for a pure
 solution.

All right, but why?  It seems an obvious trick, take some pieces that
benefit from imperative processing, and wrap them in ST, leaving the
rest of the program as it were.

Can you (or anybody else) explain the memory behaviour I see (using
hundreds of megabytes, but only tens of K visible in the profiling
output)? 

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



Re: Arrays and arrays

2003-01-21 Thread Ketil Z. Malde
Hal Daume III [EMAIL PROTECTED] writes:

 Any reason it couldn't be done in-place?  (I.e. thaw, update all, and
 freeze again)  Am I missing something -- Could partial results be
 used, the update list be infinite, or anything like that?

 I believe that's essentially what normal arrays are doing, 

Makes sense, I believe -- and I don't seem to be getting any better
performance by doing it explicitly, so you're probably right.

 but that's not inplace.  

But it's O(n), not O(n^2).  It's just a factor of two compared to
entirely in place, not a big deal.  In theory.

 In the process of thawing, you're copying the array.  If you're
 not copying it, then the results are unsound.

Right.  So I noticed (trying to use unsafeThaw; unsafeFreeze is okay,
of course).

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



Re: comparison of execution speed of array types

2003-01-20 Thread Ketil Z. Malde
Zdenek Dvorak [EMAIL PROTECTED] writes:

DiffArray seems to be broken :).  Either that or I'm using it
incorrectly.

 I've tried to use DiffArray recently and it is terribly slow.

Just another data point.  I'm fumbling around with Arrays these days
(see my recent post on haskell-cafe) and thought I'd try DiffArray.
After all, I'm building large lists of index/values, and applying (//)
to them.

Now, the docs on how to use DAs aren't all that extensive, but I
replaced the type signatures, and at least the type checker is happy.
However, quickCheck (great tool) just prints a digit and hangs there.
Running the compiled program gave:

sefirot% !nice
nice time ./a.out +RTS -p -h -K16M

Fail: thread blocked indefinitely

Command exited with non-zero status 1
1.08user 0.03system 0:01.13elapsed 97%CPU (0avgtext+0avgdata 0maxresident)k
0inputs+0outputs (272major+1756minor)pagefaults 0swaps

I'm probably missing something essential, any idea what it might be?

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Arrays and arrays

2003-01-20 Thread Ketil Z. Malde

Hi

Having written a suffix-array based program using lists, I thought I'd
speed it up a bit, and perhaps more importantly, save space, using
arrays.  Basically, the problem is to sort all suffixes of a string,
represented as an array of offsets, alphabetically.

(Does anybody have such code?  Efficient?)

The good news is that space consumption is reduced -- except for a few
weird spikes (which makes me suspect there are many of them, living
for very short durations), memory use is low.

But speed is another issue -- the list based version is a lot faster.
Okay, I use UArrays and permute them by (//), and this operation is
totally dominant in the profile.  Is it correct that GHC is very naive
about updating them, and even small updates cost O(n)?  Is it better
to (//) over few large lists than over many small ones?

I'll try a IOUArray next; however, is there anything else I
could/should try?  I know there has been array sorts implemented
previously, are anybody aware of recent results?

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



Re: Arrays and arrays

2003-01-20 Thread Ketil Z. Malde
Hal Daume III [EMAIL PROTECTED] writes:

 Yes, (//) is terrible.  It *never* tries to update in-place.  

Any reason it couldn't be done in-place?  (I.e. thaw, update all, and
freeze again)  Am I missing something -- Could partial results be
used, the update list be infinite, or anything like that?

 DiffArrays are very flaky and I would recommend staying away from them,

Yep, my program crashed with them :-)  (I may inadvertently be doing
something nasty or illegal, though.  The docs I found weren't all that
great) 

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



non-question, instance decl

2003-01-14 Thread Ketil Z. Malde

Hi,

experimenting with QuickCheck, I write

   instance (Arbitrary e) = Arbitrary (Array Int e) where
arbitrary = undefined

and I get:

|Illegal instance declaration for `Arbitrary (Array Int e)'
|   (The instance type must be of form (T a b c)
|where T is not a synonym, and a,b,c are distinct type variables)
|In the instance declaration for `Arbitrary (Array Int e)'
|Failed, modules loaded: QuickCheck.

Okay, after experimenting a bit (more fun than reading documentation)
I see what's happening:  I can't instantiate a halfway specialized
type, but 'Ix i = Arbitrary (Array i e)' is Okay.

Unfortunately, I really depend on i being Int in my (real) definition
of 'arbitrary'.  I got around it by liberal doses of 'fromInteger' and
a 'Num' context -- ugly, but it seems to work.

I suppose there's a solid reason why my previous attempt is illegal?

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



Re: tuple component functions

2003-01-03 Thread Ketil Z. Malde
[EMAIL PROTECTED] writes:

 S.D.Mechveliani writes:

 As Haskell has the standard functions  fst, snd  to decompose  (a,b),
 maybe, it worths to provide also [...]

 I've found some of these useful, except I named them differently:

 fst3 :: (a,b,c) - a
 snd3 :: (a,b,c) - b
 thd3 :: (a,b,c) - c

  never got around to quadruples etc.

I'd like a general 'nth', but of course that would restrict us to
monotyped tuples (e.g.,

nth :: Int - (a,a,...,a,a) - a
) 

This isn't possible to do more generally with some language extension,
is it?

A better way might be to define classes:

class TwoTuple t a b | t - a b where
fst :: t - a
snd :: t - b

instance TwoTuple (a,b) where ...

class (TwoTuple t) = ThreeTuple t c | t - c where
thd :: t - c

instance TwoTuple (a,b,c) where ...
instance ThreeTuple (a,b,c) where ...

 --and so on.

Quite verbose, but avoids the need to tag the functions with the tuple
size.

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Parsing date and time specifications

2002-12-26 Thread Ketil Z Malde
Simon Marlow [EMAIL PROTECTED] writes:

 That may well be true, and I've heard others suggest that the library is
 inconvenient.  I'm trying to get at whether that is due to current bugs
 in the implementation, or whether the design is fundamentally broken.

Well; perhaps the right thing to do is to implement a rich cron
replacement and perhaps other calendar-using functions, and see what
we need for that? 

 non-consistent CalendarTimes,

 Ok, I don't consider that to be a problem.  The toClockTime operation
 should fail if the CalendarTime is inconsistent.  

I'm on a piece of string, so I didn't check, but I think GHC and the
spec says it just ignores redundant parts?

 and there are multiple ways
 to represent the same interval as TimeDiff -- in fact, two TimeDiffs
 may or may not be equal, depending on what CalendarTime they apply
 to.  (The 'deriving' of Eq makes this a moot point, perhaps, but
 seems to make equality rather non-intuitive)

 I think this is the wrong way to look at it: two TimeDiffs should be
 equal if and only if all their components are respectively equal (i.e.
 the deriving Eq meaning).

Okay.  This loses a lot of nice algebraic properties, but perhaps
that's unavoidable.

 And another thing: it should be specified that diffClockTimes gives a
 TimeDiff in units of seconds  picoseconds, because these are the only
 forms of TimeDiff that have the same meaning independent of what
 ClockTime they are added to.
  [...]
 I think TimeDiffs are deltas for ClockTimes only.  Why do you say they
 are intervals of calendar times too?

Well, they do have fields for days, months etc.  From their
definition, it seems reasonable to use them in that way.

If the two concepts are separate, I think it makes more sense to have
TimeDiff contain only s/ps fields, and have a CalendarDiff convertible
to a TimeDiff, given a specific CalendarTime.  Or something.

But the whole thing seems a bit Pascallish to me.  Why no generating
functions and combinators for all dates, all Fridays, all second
Tuesdays of months starting with 'J'?  Where's the Functional Spirit? 

:-)

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



Re: Parsing date and time specifications

2002-12-20 Thread Ketil Z. Malde
Peter Simons [EMAIL PROTECTED] writes:

 CalendarTime [...]
 TimeDiff [...]
 I briefly looked at the Posix module  [...]
 non-standard. *sigh* [...]

 Any suggestions what I could do?

Yes. 

I think it is widely agreed that the time and date structures in the
standard libraries are brok^H^H^H^Hslightly less than useful.

I suggest you feel free to rewrite it as you see fit, and then lobby
for its inclusion in the hierarchical libraries. 

(My preju^H^Hference would be to store a date-time internally in a
posix-like manner (seconds,microsecond since the epoch).)

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



Re: Tree insert, lookup with keys

2002-12-20 Thread Ketil Z. Malde
Ingo Wechsung [EMAIL PROTECTED] writes:

 class Keyed a where { -- Type a is keyed if it has a key function.
   key :: Ord b = a - b; -- key is a function, that, when applied to
 a yields some b that is comparable
 }

But it isn't obvious what b is supposed to be.  Try multi-parameter
type classes e.g.

class (Ord b) = Keyed a b where
key :: a - b

(I'm possibly messing up the placement of the 'Ord b' qualifier)

 and then

 data Sym  = Sym String Int Ty;-- Ty  is another algebraic type
instance Keyed Sym String where
key (Sym a _ _) = a

(Requires -fglasgow-exts)

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



Re: Parsing date and time specifications

2002-12-20 Thread Ketil Z. Malde
Simon Marlow [EMAIL PROTECTED] writes:

 (My preju^H^Hference would be to store a date-time internally in a
 posix-like manner (seconds,microsecond since the epoch).)

 I'm still not sure I understand why the Time library is considered to be
 broken

I was probably a bit quick on the trigger there.  Sorry!

It't been a while since I tried using CalendarTime and friends; I did
have some difficulty making things fit, and eventually gave up the
whole thing.  My impression (which may well be a wrong one) was that
others also had trouble adapting the library to their uses, too, and
that the Time library was one of the less successful ones.

Looking at it now, possible criticisms could arise from the data types
containing redundancy and non-uniqueness: e.g. one can easily
construct non-consistent CalendarTimes, and there are multiple ways
to represent the same interval as TimeDiff -- in fact, two TimeDiffs
may or may not be equal, depending on what CalendarTime they apply
to.  (The 'deriving' of Eq makes this a moot point, perhaps, but
seems to make equality rather non-intuitive)

It seems that TimeDiffs perform two functions; deltas for ClockTimes
(in the functions) and intervals of calendar times (specification of
the data type), and I'm not sure it's a good idea to mix those.

Let's sketch a different suggestion.  I haven't given this a lot of
thought, so feel free to shoot it down!

sketch
ClockTime -- as is
ClockInterval -- a delta for ClockTimes, diffClockTimes:: CT - CT - CI

CalendarTime -- as is, only used as *output* from functions
-- for input, have non-redundant data structures
CalendarDate -- normal, non-redundant date information
CalendarYearDay -- (year, day of year,time)
-- add functions for computing the correct CalendarTime from any of these

CalendarInterval -- a (user constructed) time interval, which allows
the user to do normal arithmetic (e.g. add 1 month)
to CalendarTimes

Notably, ClockIntervals and CalendarIntervals aren't mixable; using
CalendarIntervals (probably?) require locale information, and
converting one into the other (probably) requires a specific reference
point in time. 
/sketch

Since it's almost Christmas, I'd also like a way to specify things
like first Tuesday of every month, or the day before (last Thursday
of every month).  And a GHC target for my Palm Pilot :-)  We could
build a really cool Cron replacement, and become rich and famous.

(BTW,

 the weekday/yearday in a CalendarTime are ignored by the
 toClockTime in GHC's Time library, so you can set them to anything).

This seems to be standardized behaviour specified in the Report)

Anyway:

Oh well.  I'm not using Time at the moment, so its not an issue that
will ruin my holiday for me :-)  When I have a concrete use for it
that it doesn't support, I'll be sure to let you know! :-)

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



Re: Random

2002-12-18 Thread Ketil Z. Malde
Mark Carroll [EMAIL PROTECTED] writes:

 On 17 Dec 2002, Ketil Z. Malde wrote:

 Ah - I was never sure what to make of that - I normally just use the GHC
 online Haddockised stuff which tells me no more than the type signatures,
 but I suppose split must be more than (\x-(x,x))! 

Well, as SPJ said, you can browse the library report.  Basically, it
splits a random generator, so that you can pass it to a function and
forget about it.  

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



Re: Random

2002-12-17 Thread Ketil Z. Malde
Mark Carroll [EMAIL PROTECTED] writes:

 The dice function gives you back the new state of the rng which maybe
 you should keep around to start the next set of rolls with. (main throws
 it away with snd.) I'd certainly be interested to see how this could be
 written more nicely. I avoided making the list of die rolls an infinitely
 long lazy list in case we wanted to use the same RNG for other stuff too

Okay, since you've already done his homework for him... :-)

main = do
r - newStdGen
print (dice 4 r)

dice :: Integer - StdGen - [Integer]
dice n g = take n $ randomRs (1,6) g

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



Re: Random

2002-12-17 Thread Ketil Z. Malde
Mark Carroll [EMAIL PROTECTED] writes:

 On 17 Dec 2002, Ketil Z. Malde wrote:
 (snip)
 dice :: Integer - StdGen - [Integer]
 dice n g = take n $ randomRs (1,6) g

 Can we still do this concisely and get the new state of the rng back out
 the other end after the die has been thrown a few times?

Oops; I missed that part!

 Or are things like newStdGen meant to be so cheap that it's fine to
 use lots of different RNGs instead of one that you thread through
 everything?

I've no idea - I've always used StdGen's as if they were going out of
style.  (You can, of course, `split` them and get two for the price of
one)

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



Options in hs files; Bug report?

2002-12-10 Thread Ketil Z. Malde

I posted something on haskell@, but perhaps this is a better forum for
possible bug reports (I didn't get any replies, at any rate).

(Edited severely for brevity and relevance)

-kzm


---BeginMessage---
[...]

Talking about warnings, it is probably patently stupid to put

{-# OPTIONS -fglasgow-exts -package lang #-}

at the top of my Main.lhs.  But why does GHC (5.04-1) fail to find any
of my imports as a consequence?  Bug?


---End Message---


-- 
If I haven't seen further, it is by standing in the footprints of giants



Re: AW: Editor Tab Expansion

2002-12-10 Thread Ketil Z. Malde
matt hellige [EMAIL PROTECTED] writes:

 I would
 PREFER if haskell enforeced a strict distinction between spaces and
 tabs for layout purposes, i.e., this:

 let x = y
 ^I  z = q
   ^Iw = l
 in ...

 should be an error. 

Simon¹ is usually very positive to adding enhancements, if this really
turns out to be a problem, I propose that you ask for e.g.

  -fno-tabs  : indentation with tabs is an error, only spaces allowed
  -fconsistent-indent : indents must be exactly matching in a block

or whatever floats your boat, and helps you enforce your particular
coding standard.  Extra credit if you supply the patch to GHC, of
course. :-)

-kzm

¹ Haven't used the other compilers as much, but it's not my impression
that they are any less open to persuasion.
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Completeness of pattern matching

2002-12-06 Thread Ketil Z. Malde
[EMAIL PROTECTED] (Ketil Z. Malde) writes:

 Malcolm Wallace [EMAIL PROTECTED] writes:
 
  Ingo Wechsung [EMAIL PROTECTED] writes:
  I wonder if the compiler could check, if all possible combinations have
  been checked in a pattern match.
 
  In ghc, use the compile-time option -fwarn-incomplete-patterns
 
 Is there a warning to warn if a block is delimited (or not) with a mix
 of tabs and spaces?  Or somehow otherwise warn against dangerously
 looking layout?

Talking about warnings, it is probably patently stupid to put

{-# OPTIONS -fglasgow-exts -package lang #-}

at the top of my Main.lhs.  But why does GHC (5.04-1) fail to find any
of my imports as a consequence?  Bug?

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Editor Tab Expansion

2002-12-06 Thread Ketil Z. Malde
John Meacham [EMAIL PROTECTED] writes:

 rather than start layout blocks right after the 'let' 'do' or 'where',
 put them on the next line with one more tabstop than the current
 line.

I've also a bit baffled by all the people apparently struggling with
layout; I realize the rules are a bit complex, but it's something that
just works for me.  
But then I also use this convention, (except in really simple cases:

f x = let y = g x in h y
f x = h y where y = g x

(It could be because I use Emacs, though, where the hs mode has TAB
cycling through the possible indentations.)

 this makes your code independent of the tabstop and much easier to work
 with IMHO.

Also it is safer if you are using non-ASCII characters, e.g.

f \x06de = case \x06de of foo - bar
 blah -   -- where to align this?

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



Re: Completeness of pattern matching

2002-12-06 Thread Ketil Z. Malde
Malcolm Wallace [EMAIL PROTECTED] writes:

 Ingo Wechsung [EMAIL PROTECTED] writes:
 I wonder if the compiler could check, if all possible combinations have
 been checked in a pattern match.

 In ghc, use the compile-time option -fwarn-incomplete-patterns

Is there a warning to warn if a block is delimited (or not) with a mix
of tabs and spaces?  Or somehow otherwise warn against dangerously
looking layout?

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



Re: AW: Editor Tab Expansion

2002-12-06 Thread Ketil Z. Malde
Ingo Wechsung [EMAIL PROTECTED] writes:

 Simon wrote:
 
 There's no reason not to use 8 column tab stops, so please don't do it.

 Ok, if it just looks better to me is no reason, 

Tabs and spaces aren't visually distinguishable, so I'm not sure why
you conclude that looks don't matter.

As has been pointed out, how the tab character is displayed doesn't
have to be related to what happens when you press the -| button.

 then the following also holds:
 There's no reason not to use braces and semicolons, so please use them.

I think braces/semicolons are unnecessary clutter.  But if configuring
your editor is too much trouble, feel free to use them.

I don't really want this to become yet another editor flame war, but
is the reason I don't have trouble with layout that

a) I use sane layout conventions 
b) I use Emacs with a sane haskell-mode instead of a vi clone
c) I'm almost entirely restricted to working as a one-person-team

I'd like your opinions, private mail is fine, and I can summarize
if anybody wants.

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



Re: nub

2002-11-29 Thread Ketil Z. Malde
Richard Braakman [EMAIL PROTECTED] writes:

 On Thu, Nov 28, 2002 at 10:21:53PM +, Alistair Bayley wrote:
 Wouldn't this have been better called unique? (analogous to the Unix
 program uniq). I was looking for a unique in the GHC Data.List library a
 few days ago, and didn't see one, so I wrote my own (not realising that was
 what nub did).

BTDT.

 No, Unix uniq makes only a single pass.
 uniq = map head . group

 Hmm, but with that said, I don't think I disagree with you.  Renaming
 nub to unique makes it clear that it is similar, but not identical
 to what Unix uniq does.

And of course the traditional Unix idiom for nub is 'sort | uniq'
(or (uniq . sort) if you prefer)

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: HCA Report: Haskell 98 Report copyright

2002-11-12 Thread Ketil Z. Malde
Ian Lynagh [EMAIL PROTECTED] writes:

 I note with some sadness the more restrictive license that may be placed
 on the Haskell 98 Report, as reported by the HCA.

I have a hard time imagining what this actually means.  The report, as
it is licensed now allows for:

 I have just grabbed a copy of the latest revised report under the
 current licence. AIUI I can continue to publish this under the current
 licence and [..] incorporate any fixes etc

So what exactly is it they want copyright to?  Obviously, they can
have the copyright to the *book* and it's layout and such (i.e., one
cannot xerox it), but the contents is already in the free, isn't it?

 assuming I change the name,

Do they get to own the name?

 I would really prefer it if such forking wasn't necessary

I'm not sure it would be forking, unless somebody plans on maintaining
CUP's official version for them.

 I must admit to not seeing what CUP would be getting
 out of it if this is so, though.

Exactly.  They can't really get an exclusive copyright to a document
that's free, can they?  Some publishers are mostly worried about
having the right to do what they will, rather than restricting
others. I think at any rate it's important to be up front with CUP
with this, so they know what's going to happen, so that they don't
feel cheated or mislead.

strong opinion
I'd love to have it in book form, but it's much more important to have
it freely available (e.g. in Debian).
/

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Enum on Float/Double

2002-10-25 Thread Ketil Z Malde
George Russell [EMAIL PROTECTED] writes:

 The situation with Enum on Ratio is pretty bad but at least
 it's not hopeless, since rational numbers are at least exact.  But
 for Float/Double it seems to be a total disaster area.  

My vote would be to scrap it.  Enum sounds like it defines an ordering
of elements, and that's IMHO not what the actual implementation looks
like.  But I suppose it will have to wait.

 My preference would be for succ (+-0) to return the smallest positive
 real, since then you could define succ x to be the unique y with
 x  y and forall z . z  y = not (x  z), where such a y exists, and
 I'm not sure if the Haskell standard knows about signed zeros.

Is this really useful?  Why would you need this number?  Peano
artithmetic on reals? :-)

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Enum on Float/Double

2002-10-25 Thread Ketil Z Malde
Ketil Z Malde [EMAIL PROTECTED] writes:

 My vote would be to scrap it.  Enum sounds like it defines an ordering
 of elements, and that's IMHO not what the actual implementation looks

Just before everybody else points it out; that's a bit imprecise.
But the IMHO obvious way to regard succ would be to provide a
succession of all the elements in a set, rather than just add one to
a numeric interpretation of the value.

Defining [x..y] in terms of succ sound counter-intuitive to me (and
isn't a different mechanism needed for [x,y..z] anyway?)

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



A run-time problem?

2002-10-18 Thread Ketil Z. Malde

Hi,

I'm occasionally getting an error, when running a compiled program, I
get: 

| fatal error: GetMBlock: misaligned block 0x401fe000 returned when
| allocating 1 megablock(s) at 0xbff0

apparently, this only happens on one computer (Red Hat 7.1), and not
others (Red Hat 7.2), which leads me to suspect it's a library issue. 

This is a known problem, yes?  Is it possible to resolve this, apart
from upgrading the OS, or recompiling? 

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: Building Both Regular and Profiling Libraries

2002-10-10 Thread Ketil Z. Malde

Ashley Yakeley [EMAIL PROTECTED] writes:

 I did notice that for -osuf you seem to need the '.' but for -hisuf you 
 don't...

Weird, I've never seen that behavior (GHC 5.02 and 5.04, x86-Linux and
Sparc-Solaris).  I just checked with 5.04 on my Linux box, and 5.02 on
a Sun, just to make sure.

What system and compiler version are you using?

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



infinite (fractional) precision

2002-10-10 Thread Ketil Z. Malde


Hi

I was just browsing around on comp.arch a bit, and there was this
discussion about various ways to represent non-integer numeric
values. 

It seems one could easily (I'll get back to that in a moment)
calculate the fractional part of numbers lazily, generating the needed
precision, and nothing more.  Does any such implementation exist in
Haskell? 

I realize it's probably far from trivial, e.g. comparing two equal
numbers could easily not terminate, and memory exhaustion would
probably arise in many other cases.

So, if such implementations exist, how does one deal with these
issues?  Is it indeed possible to make this useful in practice?  

(And if it hasn't been implemented, would anybody be interested if I
gave it a try?)

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



Re: infinite (fractional) precision

2002-10-10 Thread Ketil Z. Malde

Ashley Yakeley [EMAIL PROTECTED] writes:

 At 2002-10-10 01:29, Ketil Z. Malde wrote:
 
 I realize it's probably far from trivial, e.g. comparing two equal
 numbers could easily not terminate, and memory exhaustion would
 probably arise in many other cases.
 
 I considered doing something very like this for real (computable) 
 numbers, but because I couldn't properly make the type an instance of Eq, 

instance Eq InfPoint where
x (==) y == compareToPrecision epsilon x y
where epsilon = unsafePerformIO ...

A bit (perhaps not just a bit either) ugly, but comparable to using a
fixed point, no?

 I left it. Actually it was worse than that. Suppose I'm adding two 
 numbers, both of which are actually 1, but I don't know that:
 
  1.0 +
  0.9

Could it be represented as

data InfPoint = IP Integer FractionalPart
data FractionalPart = FP Word8 | Repeat FractionalPart 

Thus:

1.00.. - IP 1 (Repeat (FP 0))
0.99.. - IP 0 (Repeat (FP 9))

where the latter could be normalized to the former?

Okay, you still get the problem comparing 

sqrt 2 == sqrt (sqrt 4)

But wait a second:

 The trouble is, as far as I know with a finite number of digits, the 
 answer might be

  1.99937425

 or it might be

 2.00013565

 ...so I can't actually generate any digits at all. 

But if you want to calcualte the sum for a finite number of digits, do
you really care if you calculate it as

1.999..9
or  2.000..0
?

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



Re: No GHC support for a week

2002-10-03 Thread Ketil Z. Malde

Hal Daume III [EMAIL PROTECTED] writes:

 If you have a short program which demonstrates the same problem, I'm sure
 Simon would love to get a copy...

I have a longish program that demonstrates the same problem; that is,
it only fails when the moon is aligned or something. :-)

It happens (has happened) rarely enough that it's not a problem for
me. 

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: deriving weirdness on newtypes

2002-10-03 Thread Ketil Z. Malde

Hal Daume III [EMAIL PROTECTED] writes:

 So I love the fact that I can derive anything I want on
 newtypes.  However, there seem to be problems with it.  If I write:
 
 newtype Foo = Foo Int deriving (Show)
 x = show (Foo 5)
 
 Then x is Foo 5
 
 However, if I do
 
 newtype Foo = Foo Int deriving (Num)
 x = show (Foo 5)
 
 Then the definition of 'x' claims that there is no Show instance of Foo.
 
 However (this is where it gets weird).  If I do:
 
 newtype Foo = Foo Int deriving (Num)
 x = show ((Foo 5) + 4)
 
 then x is *valid* and has value 9, not Foo 9.  

Did you check the type of x?  (I'd do it but I just found out that I
no longer have GHCi after my 5.04 upgrade)  Did you try different
compilers? 

I guess that there's an automatically derived instance of Show
(annoyingly being necessary for Num) after all, and that it is
constructed as (show.toInteger) or something like that?

 Moreoever, I can even do:
 x = show ((5::Foo) + 4)

Same thing, isn't it?  5::Foo = fromInteger 5 :: Foo = Foo 5

 IMO, the correct value of show (Foo 5) no matter which of the above we
 have is Foo 5.  I think the deriving mechanism should be changed in two
 ways.

I agree.

   (1) If you derive X on a newtype and X is a subclass of Y,
   you must have an instance of Y on that newtype.  This is 
   how it works on data types, and I think makes sense.  

It could lead to rather long 'deriving' lists with a deep hierarchy,
but apart from that, yeah.

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: No GHC support for a week

2002-10-02 Thread Ketil Z. Malde

Simon Marlow [EMAIL PROTECTED] writes:

 GHC support will be intermittent at best for the next week or so, as
 Simon  I are both heading out to Pittsburgh for ICFP and the Haskell
 workshop.  Catch you all later...

And here I recently started using GHC 5.04 from the provided RH7.2
packages, and getting occasional heapCensus errors.  Relatively
rare, difficult to reproduce, rerunning on the same data usually
works. 

(I was going to forward another question about a heap usage problem I
had, but it turned out it was just a question of applying a bit more
strictness in the right place. :-)

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Performance question

2002-10-02 Thread Ketil Z. Malde


At the moment, I have a user defined data type on which I have defined
some operations, instantiated (not derived) Eq and so on.  However,
for efficiency I'm storing the actual data in UArrays of Word8.

In order for everything to work, I need functions 'toW8' and 'fromW8'
to map between the data type and its representation in the array.

I gather it is impossible to hide the 'Eq' instance of Word8 and/or
redefine it, but could this be circumvented by instead of

data Foo = F | G

instance Eq Foo where
F == _ = True
_ == _ = False

defining something like

newtype Foo = F Word8
f, g, h :: Foo
f = F 0
g = F 1

and using the same instance declaration?  And will it still fit into a
UArray? 

(It is of course possible that, while profiling indicates otherwise,
the conversion functions have little impact in practice; i.e. the
optimizer will do away with them.)

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: Word8-Based IO

2002-08-22 Thread Ketil Z. Malde

Wolfgang Jeltsch [EMAIL PROTECTED] writes:

 In my opinion, the mailing list software should include an appropriate
 Reply-To header field in every mail sent to the list so that replies are
 automatically sent to the list.
[...]
 Reply-To fields from several other lists I'm subscribed to and wonder
 why it isn't applied to the Haskell related lists. Are there any
 arguments against it?

Yes.

With a Reply-To: set to the list, it becomes more difficult to reply
privately, and the result (at least on the lists I've been subscribed
to that implements this policy) is that the list is polluted with mail
intended privately, quickly followed up by apologies for sending
private mail to the list.

Having a list-intended mail end up in somebody's personal mail instead
is of course a risk, but at least it's an error that affects fewer
people, keeping the noise down on the list.  And, IME, it's also a
less common error.

Having the list specify a Reply-To: also precludes me from specifying
my own; perhaps I would like private replies in order to post a
summary later to the list, perhaps I would like responses to go
somewhere else (haskell-cafe, say).

The appropriate list address is in the To:-header, and as far as I can
tell, most mail user agents have the facility of replying to all
adressees, which includes the list, *or* just to the originator. 
(If you have an extensible MUA, you could also hack it to use the
List-Post: field added by Mailman.)

The real hassle without Reply-To: is IMHO that participants in debates
end up receiving multiple replies if people are too lazy to edit the
headers; but then smart MUAs stow away duplicates.

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Question about sets

2002-08-20 Thread Ketil Z. Malde

Scott J. [EMAIL PROTECTED] writes:

 I have a question. Why are sets not implemented in Haskell?

What do you mean?  Isn't 

http://www.haskell.org/ghc/docs/latest/html/hslibs/set.html

sufficient?  (Remember to tell GHC '-package data')

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



Re: Analyzing Efficiency

2002-08-14 Thread Ketil Z. Malde

Shawn P. Garbett [EMAIL PROTECTED] writes:

 I've come up with three different methods of approach to solve the same 
 problem in haskell. I would like to compare the three in terms of reductions, 
 memory usage, and overall big O complexity.
 
 What's the quickest way to gather these stats?

I don't know about quickest, but if you haven't yet tried GHC's
profiling, this might be a good time to do so.

Build your project, using e.g.

ghc --make -prof -auto-all ...

(I like to add '-hisuf p.hi -osuf p.o' in order to keep files apart
from non-profiling builds, since linking with both kinds will crash
your program)

Then run it with

./a.out (or whatever) +RTS -p -RTS

and look at the resulting file a.out.prof.  Replace -p with -h to do
heap profiling.  Have a look at the online GHC documentation for all
the details, it's pretty comprehensive and readable, IMO.

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



Re: UTF-8 library

2002-08-09 Thread Ketil Z. Malde

anatoli [EMAIL PROTECTED] writes:

 Dependence on the current locale is EXTREMELY inconvenient.
 Imagine that you're writing a Web browser.

Web browsers get input with MIME declarations, and shouldn't rely on
*any* default setting.   Instead, they should read [Word8] and decode
the contents according to Content-Type/Content-Transfer-Encoding.

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Text in Haskell: a second proposal

2002-08-09 Thread Ketil Z. Malde

Ken Shan [EMAIL PROTECTED] writes:

 I suggest that the following Haskell types be used for the five items
 above:
 
  1. Word8
  2. CChar
  3. CodePoint
  4. Word16
  5. Char
 
 On most machines, Char will be a wrapper around Word8.  (This
 contradicts the present language standard.)

Can you point out any machine where this is not the case?  One with a
Haskell implementation, or likely to have one in the future?

If not, I don't see much point, and agree with Ashley to restrict
real IO to [Word8].  

I like the Encoding data structure, though. 

data Encoding text code
   = Encoding { encode :: [text] - Maybe [code]
   , decode :: [code] - Maybe [text] }

utf8 :: Encoding CodePoint Word8
iso88591 :: Encoding CodePoint Word8

Perhaps changing it to 

data Encoding text code 
= Encoding { encode :: text - Maybe code, ...}

so that

utf8 :: Encoding String [Word8]

but more importantly

jpeg :: Encoding Image [Word8]

Perhaps [Word8], if it is the basis for IO, should be the target for
*all* Encodings?  And encoding, can it really fail?  How about:

data Encoding text -- or rather, 'data_item' or something?
= Encoding {encode :: text - [Word8],
decode :: [Word8] - Maybe text}

?

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Yet more text pedantry

2002-08-09 Thread Ketil Z. Malde

George Russell [EMAIL PROTECTED] writes:

 Ketil wrote (quoting Ken)

 On most machines, Char will be a wrapper around Word8.  (This
 contradicts the present language standard.)

 Can you point out any machine where this is not the case?  One with a
 Haskell implementation, or likely to have one in the future

 That's easy enough.  On Sun/Solaris (which I use and which came out as
 being very popular on the Haskell survey) characters are SIGNED, so the
 values run from -128 to 127 and the wrapper would be not Word8 but Int8.

How does the file system know the difference?  I think you mean that
C chars on Solaris are signed, not that files and sockets don't
contain octets. 

 I think this demonstrates the perils of saying It's safe to assume
 everything is 8 bit because everything is now.

I don't think it does so at all.  There may be a peril in assuming
octet IO, but frankly I think trying to anticipate different futures
will only make things messy, and have a great likelyhood of turning
out useless anyway. 

Remember, worse is better.

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Yet more text pedantry

2002-08-09 Thread Ketil Z. Malde

George Russell [EMAIL PROTECTED] writes:

 How does the file system know the difference?  I think you mean that
 C chars on Solaris are signed, not that files and sockets don't
 contain octets.

 Well, you can define the files to contain only directed graphs if it makes
 you feel any happier,  but the fact is that the standard access functions 
 return characters*, 

What standard access functions? The functions found in C libraries?
From Solaris man pages, the read system call reads bytes into a void
* buffer.

I would propose that the standard access functions in *Haskell* return
Word8, *regardless* of operating system or C libraries.  As long as
you have primitives to do octet IO, this should be straightforward,
regardless of whether the OS (or other programming languages or
libraries) thinks the octet is signed or not. 

 and on Solaris the default representation of a characters is as a
 signed quantity. 

Why should we care?

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Yet more text pedantry

2002-08-09 Thread Ketil Z Malde

George Russell [EMAIL PROTECTED] writes:

 Ketil Z. Malde wrote:
 [snip]

 and on Solaris the default representation of a characters is as a
 signed quantity.

 Why should we care?

 If you want to talk to any C libraries or C programs which use
 characters, which some  of us do.  GNU readline and regex come to
 mind. 

Yes, which is why we all agree on CChar for FFI purposes.
But we were discussing IO, weren't we?

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: mergesort. Reply

2002-06-28 Thread Ketil Z. Malde

Serge D. Mechveliani [EMAIL PROTECTED] writes:

 ButsortBy' (compare) [1 .. n]

 costs too much, even for  n = 11000.
 It costs (on worst data) many times more than  mergeSort.

Yes, but why do you want to sort sorted data?  

I think the multiple value cost, i.e. that

sortBy (compare) (take n $ repeat 1)

is equally expensive, is a bigger problem.  Okay, probably because it
caught me unawares, but also because the mantra is quicksort is
pessimal on sorted data.

But if mergesort (or heapsort for that matter) can be made to behave
nicely, I think that's a good alternative.  I haven't run numbers, but
I was under the impression that mergesort was quite a bit slower than
quicksort in the expected case.  I, for one, am sorting expected, not
worst-case, data :-)

gripe
What's this obsession with worst-case behaviour anyway?  While I have
linear-time algorithms I could use, I'm using one that's linear
expected, quadratic worst-case -- but with better cache behaviour. And
why not?  There are O(2^n) possible inputs, who cares about the almost
none that are pessimal?

And that's cache as in the six-orders-of-magnitude access time
difference between RAM vs. disk, not the relatively low cost of L2
cache misses. 
/

One solution I've seen suggested, is to use quicksort to a depth of
c log n (for some c), and fall back to mergesort thereafter.  Or to
pick a random pivot, rather than the first element.  

BTW, I'm fully in favor of keeping an insertion (or other) sort around
that behaves nicely for sorted/almost sorted data, as a separate
function available for the discriminating programmer.

Okay, that was kind of rambling, to sum up:

1. The default sorting should, in order of approximate preference
1. scale well (probably means O(n log n))
2. scale beyond available RAM
3. be fast (i.e. have low constant overhead)
?. be stable (always a nice property)

2. Other sorts should be provided for special cases that the
programmer might know about, and where a different algorithm could be
a win, possibly:
- short sequences (bubble?)
- sequences of sequences (radix?)
- almost sorted/reverse sorted sequences (bubble/insertion?)
- limited range (bucket?)

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: [ADMINISTRIVIA]: Change list submission policy please?

2002-06-28 Thread Ketil Z. Malde

Ralf Hinze [EMAIL PROTECTED] writes:

 The haskell mailing list is getting an increasing amount of
 spam, viruses, and virus warnings.  Would it be possible
 to change the list policy to only allow submissions from
 subscribed members?  Please?

 I'd like to second this. The amount of spam etc is becoming
 more and more annoying ...

Thirded!  While we won't easily get rid of Outlook-viruses (since the
list may appear in people's address books), at least we can get rid of
the loads of warnings from misconfigured mail servers following them.

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



  1   2   >