Re: [Haskell-cafe] Splitting a list

2004-04-22 Thread Joe Fasel
This is a classic greedy algorithm, much like the text-wrapping
problem.

My main suggestion would be that you're not making use of some standard
list functions that would simplify things.  For example, your
runningSum is just scanl1 (+) .  Similarly, splitAll should use
unfoldr.  Another thing is that I would reverse the order of
arguments of splitFirst and splitAll, since curried applications
are probably more useful that way:

splitAll :: (Real a) = a - [a] - [[a]]
splitAll = unfoldr . split
   where split _ [] = Nothing
 split n xs = let (ys,zs) = break (( n) . snd)
  (zip xs (scanl1 (+) xs))
  in Just (map fst ys, map fst zs)

Now, if you're concerned about all that zipping and projecting,
you can instead define split via a straightforward recursion,
or you could use a different kind of unfold that preserves the
terminating value:

unfoldrG :: (b - Either (a,b) b) - b - ([a],b)
unfoldrG f = unfold
 where unfold x = case f x of
Right y - ([],y)
Left (a,y) - let (bs,z) = unfold y
  in (a:bs,z)

Here, you will define split by unfolding a pair consisting of a
running sum and remaining list.

Cheers,
--Joe

On 2004.04.21 07:42, Steve Schafer wrote:
 I have a list of integers, e.g.:
 
  [1,5,3,17,8,9]
 
 I want to split it into a pair of lists, with the criterion being that
 the sum of the elements in the first list is as large as possible, but
 not exceeding a threshold value. For example, if the threshold is 10,
 the result should be:
 
  ([1,5,3],[17,8,9])
 
 and then I want to recursively apply this process to the remainder of
 the list, with the end result being a list of lists of integers. Using
 the same list along with a threshold of 18, I would get:
 
  [[1,5,3],[17],[8,9]]
 
 I have devised a means of doing this:
 
 1) Create an auxiliary list of integers, where the n'th element is equal
 to the sum of the first n elements of the original list.
 
 2) Zip the auxiliary list with the original list.
 
 3) Use span to break the list in two according to the threshold.
 
 4) Unzip the two resulting lists and discard the auxiliary portions.
 
 5) Repeat from step 1, operating on the tail of the list, until there's
 nothing left.
 
 Here's the code that implements this:
 
 runningSum   ::  (Ord a, Num a) = [a] - [a]
 runningSum []=   []
 runningSum (i:[])=   i : []
 runningSum (i:j:js)  =   i : runningSum (i+j : js)
 
 zipWithSum   ::  (Ord a, Num a) = [a] - [(a,a)]
 zipWithSum xs=   zip (runningSum xs) xs
 
 threshold::  (Ord a, Num a) = [a] - a - ([(a,a)],[(a,a)])
 threshold xs t   =   let test x = (t = (fst x))
  in span test (zipWithSum xs)
 
 splitFirst   ::  (Ord a, Num a) = [a] - a - ([a],[a])
 splitFirst xs t  =   let (ys,zs) = threshold xs t
  in (snd (unzip ys), snd (unzip zs))
 
 splitAll ::  (Ord a, Num a) = [a] - a - [[a]]
 splitAll [] _=   []
 splitAll xs t=   let (ys, zs) = splitFirst xs t
  in ys : (splitAll zs t)
 
 (One thing that's missing from this code is a check to verify that no
 single element in the list is greater than the threshold, which should
 raise an error, rather than get stuck in an infinite loop.)
 
 The algorithm as implemented works fine, but it seems overly complicated
 and not very elegant. I get the feeling that I'm missing some obvious
 simplification, but I can't find it. Any ideas?
 
 Thanks,
 
 -Steve Schafer
 
 ___
 Haskell-Cafe mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 

Joseph H. Fasel, Ph.D.  email: [EMAIL PROTECTED]
Systems Planning and Analysis   phone: +1 505 667 7158
University of Californiafax: +1 505 667 2960
Los Alamos National Laboratory  post: D-2 MS F609; Los Alamos, NM 87545
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Splitting a list

2004-04-22 Thread Joe Fasel

On 2004.04.22 15:02, I wrote:
 splitAll :: (Real a) = a - [a] - [[a]]
 splitAll = unfoldr . split
  where split _ [] = Nothing
  split n xs = let (ys,zs) = break (( n) . snd)
   (zip xs (scanl1 (+) xs))
   in Just (map fst ys, map fst zs)

a slight improvement:

splitAll :: (Real a) = a - [a] - [[a]]
splitAll n = unfoldr split
 where split [] = Nothing
   split xs = let (ys,zs) = break (( n) . snd)
  (zip xs (scanl1 (+) xs))
  in Just (map fst ys, map fst zs)

But in fact, I think you can do better still by not holding n
constant but using a higher threshold on each split and not
projecting out the values of the second component, thus only
zipping the whole list once.

--Joe

Joseph H. Fasel, Ph.D.  email: [EMAIL PROTECTED]
Systems Planning and Analysis   phone: +1 505 667 7158
University of Californiafax: +1 505 667 2960
Los Alamos National Laboratory  post: D-2 MS F609; Los Alamos, NM 87545
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Hugs/GHC incompatibility

2004-01-21 Thread Joe Fasel

On 2004.01.21 15:03, Iavor S. Diatchki wrote:
 hi,
 not that it matters, but i think commonly when specifications say
 that something is undefined, that means that the behaviour can be whatever,
 i.e. the implementors can do what they like.   this is not to be confused
 with the entity undefined defined in the Prelude.
 -iavor

Well, except that denotationally, they are the same.

--Joe

Joseph H. Fasel, Ph.D.  email: [EMAIL PROTECTED]
Systems Planning and Analysis   phone: +1 505 667 7158
University of Californiafax: +1 505 667 2960
Los Alamos National Laboratory  post: D-2 MS F609; Los Alamos, NM 87545
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: Hugs/GHC incompatibility

2004-01-21 Thread Joe Fasel
On 2004.01.21 15:03, Iavor S. Diatchki wrote:
 hi,
 not that it matters, but i think commonly when specifications say
 that something is undefined, that means that the behaviour can be whatever,
 i.e. the implementors can do what they like.   this is not to be confused
 with the entity undefined defined in the Prelude.

On second thought, I wouldn't think that an implementation is
entitled to yield a defined value in place of bottom.

Cheers,
--Joe

Joseph H. Fasel, Ph.D.  email: [EMAIL PROTECTED]
Systems Planning and Analysis   phone: +1 505 667 7158
University of Californiafax: +1 505 667 2960
Los Alamos National Laboratory  post: D-2 MS F609; Los Alamos, NM 87545
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: drop take [was: fixing typos in Haskell-98]

2000-01-25 Thread Joe Fasel

Phil Wadler writes:
| I'm with Jon Fairbairn on this.  Negative arguments are an error
| because the domain of take and drop is the naturals.  The problem
| is that we use Int to represent naturals.  -- P
| 
|  For the people that share this sentiment, can you please
|  explain why ints that are too big should not similarly
|  give an error?  I can see both being ok, or both being
|  errors.  I just don't see why one should be ok and the
|  other an error.

I'm with Phil and Jon on this.  The "natural" domain for take
and friends is the naturals.  The question of whether negative arguments
are an error or are equivalent to zero may be slightly tricky, though:
If we did have the naturals as a type, how would we define the
predecessor function on zero?  It's either zero or undefined.  Negative
arguments to take should go the same way.

Cheers,
--Joe

Joseph H. Fasel, Ph.D.  email:  [EMAIL PROTECTED]
Technology Modeling and Analysisphone:  +1 505 667 7158
University of Californiafax:+1 505 667 2960
Los Alamos National Laboratory  postal: TSA-7 MS F609
Los Alamos, NM  87545




Re: drop take [was: fixing typos in Haskell-98]

2000-01-25 Thread Joe Fasel

Chris Okasaki writes:
| But if the type *says* Int, then it should have reasonable behavior
| for ints.  I look at the negative case as being equivalent to
| standard mathematical treatment of ranges such as i..j, where the
| range is considered to be empty if j  i.  Allowing take/drop to
| handle negative arguments should be useful to exactly the same
| extent as that mathematical convention.

I find this persuasive.  That suggests these definitions:

 take _ [] = []
 take n _ | n = 0 = []
 take (n+1) (x:xs) = x : take n xs

 drop _ [] = []
 drop n xs | n = 0 = xs
 drop (n+1) (_:xs) = drop n xs

 splitAt n xs = (take n xs, drop n xs)

The call some have made for the tightest possible error
checking also has merit, however.  That would suggest
these definitions:

 takeExactly 0 _ = []
 takeExactly (n+1) (x:xs) = x : takeExactly n xs
 takeExactly _ _ = undefined

 dropExactly 0 xs = xs
 dropExactly (n+1) (_:xs) = dropExactly n xs
 dropExactly _ _ = undefined

 splitAtExactly n xs = (takeExactly n xs, dropExactly n xs)

I would say that the more loosely-defined functions definitely
belong in the library and that it is a matter of taste whether
or not to include the tighter ones.

Cheers,
--Joe

Joseph H. Fasel, Ph.D.  email:  [EMAIL PROTECTED]
Technology Modeling and Analysisphone:  +1 505 667 7158
University of Californiafax:+1 505 667 2960
Los Alamos National Laboratory  postal: TSA-7 MS F609
Los Alamos, NM  87545





Re: `partition'

2000-01-19 Thread Joe Fasel

S.D.Mechveliani [EMAIL PROTECTED] writes
| Marcin 'Qrczak' Kowalczyk  [EMAIL PROTECTED]  writes 
|  partition _ [] = ([],  [])
|  partition p (x:xs) = if p x then (x:ys, zs) else (ys, x:zs)
|  where (ys, zs) = partition p xs
| 
|  runs your example in constant space.
| 
| 
| Probably, this will do. What the Haskell implementors say?
| And we have to add that this was suggested 2-3 days ago by someone in 
| this maillist. 

This probably works fine for many applications, but of course,
it is a different function.  What applications of partition need
to preserve list order?

Cheers,
--Joe

Joseph H. Fasel, Ph.D.  email:  [EMAIL PROTECTED]
Technology Modeling and Analysisphone:  +1 505 667 7158
University of Californiafax:+1 505 667 2960
Los Alamos National Laboratory  postal: TSA-7 MS F609
Los Alamos, NM  87545





partition and lifted products

2000-01-19 Thread Joe Fasel

Folks,

I claimed that these are different functions:

  partition1 p xs = (filter p xs, filter (not . p) xs)

  partition2 p = foldr (\x (ys, zs) - if p x then (x:ys,zs) else (ys,x:zs))
   ([],[])

I was correct, but not for the reason I thought.  Nota bene:

  partition1 p bottom = (bottom, bottom)

  partition2 p bottom = bottom

*Sigh*  And the language named in honor of Haskell Curry
for which Currying is not a valid transformation strikes
again!

Cheers,
--Joe

Joseph H. Fasel, Ph.D.  email:  [EMAIL PROTECTED]
Technology Modeling and Analysisphone:  +1 505 667 7158
University of Californiafax:+1 505 667 2960
Los Alamos National Laboratory  postal: TSA-7 MS F609
Los Alamos, NM  87545





Re: Sisal (was: RE: Cryptarithm solver - Haskell vs. C++)

1999-09-24 Thread Joe Fasel

Olivier LeFevre wrote,

| "R.S. Nikhil" [EMAIL PROTECTED] wrote,
| 
|  Sisal researchers [...] deliberatly chose to avoid higher-order functions, 
|  polymorphism, laziness, etc.
| 
| In a first release, yes, but I believe higher-order functions were included in 
| Sisal 2.0, which was almost ready for shipping when the Sisal project was 
| abruptly terminated by LANL management. 
| 
| From what I understand, internal LANL politics, not internecine warfare within 
| the FP community, was the cause of the shutdown. LANL seems to be betting the 
| farm on C++ (PETE, POOMA). Personally I find the tecniques uased in PETE 
| interesting but they amount to pushing work that ought to be done by the 
| compiler (at least IMO) into the libraries and onto the library writers, which 
| uncharitable souls might call a cop-out.

The Sisal project was at LLNL (Lawrence Livermore).  PETE and POOMA are
indeed LANL (Los Alamos) projects.

The Sisal project was funded primarily by the US Department of Energy's
Basic Energy Science office, and if I recall correctly, when the DOE funding
was lost, Livermore management did manage to keep Sisal going for a time.

Cheers,
--Joe

Joseph H. Fasel, Ph.D.  email:  [EMAIL PROTECTED]
Technology Modeling and Analysisphone:  +1 505 667 7158
University of Californiafax:+1 505 667 2960
Los Alamos National Laboratory  postal: TSA-7 MS F609
Los Alamos, NM  87545







Re: Non-strictness vs. laziness (was RE: Sisal)

1999-09-24 Thread Joe Fasel

Frank Christoph wrote,

| Ah, right. Someone mentioned just recently (I forget who---sorry) that
| nothing in the Report forces a Haskell implementation to use call-by-need. I
| guess this is a manifestation of the change of direction, from laziness to
| non-strictness...?

My point was meant to be just that there was no change in direction involved
in incorporating Id folks in in our effort.  Despite our determination to
do "semantics first" in our language design, we were at first referring to an
implementation technique, lazy evaluation, instead of the semantic notion
of nonstrictness.

Now, when I mentioned Id, I should have specified the purely functional
core of Id.  This is a pure, nonstrict, higher-order functional language
like Haskell.  Lazy sequential and speculative parallel implementations
will not be distinguishable.  When you introduce I-structures and M-structures,
however, an observable difference arises:  You can't have infinite structures
with Id's operational semantics, because they must be fully evaluated
for their effects.  These effects are narrowly limited, but still,
there they are.  (You may think at some point that you have the result
of your evaluation in hand, but you must wait for all computation to
cease, in case an erroneous duplicate assignment occurs.)

(If I have misspoken, I trust Nikhil will correct me.)

At any rate, Arvind and Nikhil participated in the design of Haskell
without bringing the impure aspects of Id into the discussion.  Some
years later, pH is part of the fruit of this collaboration.

By the way, I think you could have a speculative parallel system that
is fully lazy in the sense that no computation is duplicated.  That is,
some unnecessary computation is done, but nothing is done twice.

Cheers,
--Joe

Joseph H. Fasel, Ph.D.  email:  [EMAIL PROTECTED]
Technology Modeling and Analysisphone:  +1 505 667 7158
University of Californiafax:+1 505 667 2960
Los Alamos National Laboratory  postal: TSA-7 MS F609
Los Alamos, NM  87545







Re: Plea for Change #1: Why, O why, `Main'?

1999-03-29 Thread Joe Fasel

Tommy Thorn writes
| Jens' question gave my a perfect opportunity to open my a pet peeve of 
| mine: the ditatorship of `Main'.
| 
| In Haskell, the `main' function must reside in the `Main' module.
| Add to this that the `Main' module must reside in a `Main' file and
| you have an unfortunate consequence that you can only have one `Main'
| function in each directory.  This in turn means that to have, for
| example several variants of a program, you *must* defer to either
| messing with a preprocessor or dealing with multi-directory
| compilation, not a pretty sight in either case and especially daunting 
| to a beginner.
| 
| In this Haskell is in contrast to most other popular programming
| language.  The alternative seems quite straightforward and there are
| no technical difficulties:
| 
|   1) Accept the `main' function can be put in any module, and/or
|   2) Introduce a nothing of "anonymous" modules, of which the file
|  name can be anything.
| 
| I'd prefer 1) alone.  
| 
| /Tommy
| 

I heartily concur.  I have always disliked the requirement for the
module-name "Main".  To me, it reeks of PL/I:

main: procedure options(main);

Department of Redundancy Department

More seriously, C (I believe) established the convention of a main
routine named "main", but did not require that it be defined in a
file named "main.c".  (The file name is the closest analogue to our
module name in classic C.)  A Java application must have a method
named "main", but the class name is not restricted.

Cheers,
--Joe


Joseph H. Fasel, Ph.D.  email:  [EMAIL PROTECTED]
Technology Modeling and Analysisphone:  +1 505 667 7158
University of Californiafax:+1 505 667 2960
Los Alamos National Laboratory  postal: TSA-7 MS F609
Los Alamos, NM  87545






Re: Random comments

1998-12-03 Thread Joe Fasel

| I think using monads, and specially a powerful one like IO, everywhere is
| a mistake.  I can't see the need for most uses of random numbers.
| 
|  -- Lennart

Besides that, isn't the name "randomIO" a bit unfortunate?  It sounds
like it contrasts with "sequentialIO".

--Joe

Joseph H. Fasel, Ph.D.  email:  [EMAIL PROTECTED]
Technology Modeling and Analysisphone:  +1 505 667 7158
University of Californiafax:+1 505 667 2960
Los Alamos National Laboratory  postal: TSA-7 MS F609
Los Alamos, NM  87545






Re: Maybe type

1997-07-08 Thread Joe Fasel

It looks like a mistake to me, too.

--Joe

| The definition of Maybe (at least in the Hugs prelude) is:
| 
| data Maybe a = Just a | Nothing
|deriving (Eq, Ord, Read, Show)
| 
| The (to me) unfortunate consequence of this is that "Nothing" is the upper
| bound of the type (as opposed to the lower bound, which makes more sense to
| me intuitively).
| 
| Was this a conscious design decision?
| ...and if so, why?
| 
| Thanks.
| --Artie
| 
| 
| 
|Arthur Gold   Austin, Texas
|  ---
| | [EMAIL PROTECTED][EMAIL PROTECTED] |
|  ---
| 
| 


Joseph H. Fasel email:  [EMAIL PROTECTED]
Technology Modeling and Analysisphone:  +1 505 667 7158
University of Californiafax:+1 505 667 2960
Los Alamos National Laboratory  postal: TSA-7 MS F609
Los Alamos, NM  87545







Re: Making argv a constant

1997-01-17 Thread Joe Fasel

I think Fergus's efficiency argument may be a red herring.
Here is an excerpt from a compiler I wrote recently:

 data JvlArgs = JvlArgs {optNoLink :: Bool,
 optVerbose :: Bool,
 jvlClassNames :: [String]}
 deriving Show
  
 jvlArgs :: JvlArgs
 jvlArgs = getJvlArgs (unsafePerformIO getArgs)
  JvlArgs {optNoLink = False,
   optVerbose = False}
  
 getJvlArgs :: [String] - JvlArgs - JvlArgs
 getJvlArgs ("-c":ss) args = getJvlArgs ss (args {optNoLink = True})
 getJvlArgs ("-v":ss) args = getJvlArgs ss (args {optVerbose = True})
 getJvlArgs (s@('-':_):_) _ = error ("bad option: " ++ s)
 getJvlArgs ss args = args {jvlClassNames = map internalClassName ss}

Note that argv (= unsafePerformIO getArgs) is a constant (as is
jvlArgs), defaults are dealt with systematically, error handling
(not very extensive in this case) is done, and the arguments are
scanned only once (lazily, in fact).

Cheers,
--Joe

Fergus Henderson wrote:
| Simon L Peyton Jones wrote:
|  
|  I agree with Sigbjorn about argv, rather strongly, though apparently nobody
|  else does.
|
| No, I agree Sigbjorn's proposal is probably a good idea, although I don't
| feel strongly either way.  (I was just disagreeing with the reasoning that
| he used to motivate it.)
|
|  module CmdLineOpts where
|  
|  argv = unsafePerformIO getArgs
|  
|  unfoldSize :: Int
|  unfoldSize = lookupInt "-funfold-size" argv
|  
|  useCleverFiniteMap :: Bool
|  useCleverFiniteMap = lookup "-fclever" argv
|
| I have a comment, and couple of questions.
|
| First, this will involve scanning argv once for each possible option;
| I guess option handling is not likely to be a bottleneck, but still...
| this offends some aesthetic sense of mine.
|
| Second, how do you handle syntax errors in the command line arguments?
| What does lookupInt do if the integer overflows, or if the argument
| is not valid syntax for an integer?  Do you check for misspelt or
| invalid option names?
|
|  PS. I'm less steamed up about the stdin issue; but I think you missed
|  Sigbjorn's point.  Yes stdin is a constant now, but he'd like stdin *not* to
|  be a constant, so that he could take a value of type IO () that used stdin,
|  and reconnect its stdin to (say) a file.
|
| Even if stdin remains a constant, you could still do that, because even
| if the handle is a constant, the connection between handle and file can
| still vary, just as the file contents can vary.
|
| -- 
| Fergus Henderson [EMAIL PROTECTED]   |  "I have always known that the pursuit
| WWW: http://www.cs.mu.oz.au/~fjh   |  of excellence is a lethal habit"
| PGP: finger [EMAIL PROTECTED] | -- the last words of T. S. Garp.
|

Joseph H. Fasel, Ph.D.  email:  [EMAIL PROTECTED]
Technology Modeling and Analysisphone:  +1 505 667 7158
University of Californiafax:+1 505 667 2960
Los Alamos National Laboratory  postal: TSA-7 MS F609
Los Alamos, NM  87545






Re: Making argv a constant

1997-01-17 Thread Joe Fasel

Fergus,

Quite right.  I used "error" because I was lazy.

In fact, the lazy evaluation of the arguments is also a red herring,
because the compiler is in fact strict in argv.  (How else does it
know what to compile?)  All the flag arguments must be scanned
in order to retrieve "jvlClassNames jvlArgs".

I suppose that a better way to do this is something like this:

 getJvlArgs :: [String] - JvlArgs - Either JvlArgs String

 processedArgs :: Either JvlArgs String
 processedArgs = getJvlArgs argv JvlArgs {optNoLink = False,
  optVerbose = False}

 jvlArgs :: JvlArgs
 jvlArgs = case processedArgs of
  Left args - args
  Right msg - error ("mishandled arguments: " ++ msg) 

Then the main IO monad of the compiler can check processedArgs
once when it picks up the list of class names and proceed with
compilation or yield an IO error.  This scheme still avoids plumbing
jvlArgs through the rest of the compiler.

But I'm a lazy programmer.  ;-)

At this point, I may be leaning more toward Lennart's position,
as I'm less convinced of how valuable the "convenience" is.

--Joe

Fergus Henderson wrote,
| I'm still not entirely happy with the error handling, though.
| As a general rule, I try to use `error' only for internal software
| errors, not for error messages that can result from the user's
| mistakes.  (But perhaps that is another functional programmer's
| death wish... what do other people think about this issue?)
|
| Also, the fact that the arguments are scanned lazily is in fact
| slightly worrying -- I hope your program is guaranteed to always
| evaluate jvlArgs, since I don't think it would be a good idea to ignore
| syntax errors in the command-line options just because you don't happen
| to execute a part of the program that needs to examine them.

Joseph H. Fasel, Ph.D.  email:  [EMAIL PROTECTED]
Technology Modeling and Analysisphone:  +1 505 667 7158
University of Californiafax:+1 505 667 2960
Los Alamos National Laboratory  postal: TSA-7 MS F609
Los Alamos, NM  87545






Re: Lifted Tuples

1993-11-07 Thread Joe Fasel


Paul writes
| It has occurred to me that unlifted tuples achieved via a special
| "newtype" decl are not the same as those achieved with strictness
| annotations.  This is because with "newtype" it seems that people want
| a situation where (_|_,_|_) = _|_.  But with strictness annotations on
| both arguments a few other things also happen:
| 
|   (x,_|_) = _|_
|   (_|_,y) = _|_

Well said--This is what I was trying to say the other day, that with the
strictness annotations on lifted tuples we would have unlifted, but not lazy
products.  Anyway, I don't think this (by itself) will do.

--Joe




Re: Laws

1993-11-04 Thread Joe Fasel


Just a small addendum to Mark's response to Warren:

Overloading (even just polymorphism, as Mark says) does compromise
equational reasoning, in much the same way that lexical scoping does.
That is   x = y  |-  f x = f y  , provided it's the same x and the same y.

Cheers,
--Joe




Re: Lifted functions

1993-11-04 Thread Joe Fasel


Simon writes
| I have never, never been tripped up by the liftedness of tuples, but the
| argument that ``we are prepared to pay for laziness so why not this too''
| has a certain masochistic charm.  I'll try the effect on performance of
| making all tuple-matching lazy in the nofib suite.

Good idea, but in terms of being tripped up by lifted tuples.  Wouldn't
you think it would be good never to have to twiddle a tuple pattern?

|   putString = \cs - case cs of
|(c:cs) - \s - case (putChar c) of
| (_,s') - putString cs s
|
| Never mind the details, just focus on that \s inside the branch of
| the case.  I'd *like* now to transform to
|
|   putString = \cs s - case cs of
|   (c:cs) - case (putChar c) of
|  (_,s') - putString cs s
|
| That is, I'd like to float the \s outside the case.  Currently
| I'm allowed to do that, and it is advanatageous to do so because
| it brings the two \'s together.  (I'll elaborate for anyone who's interested.)
| But with lifted function spaces this transformation is Wrong.
|
| What upsets me about this example is that the sort of inner loop which
| appears a lot in our I/O and array-manipulation system, so I'm reluctant to 
| take a performance hit there. 

Great!  Now, is there a similar argument about transformations and lifted
tuples?  Here's at least one example (which I've probably mentioned on
this list before):  In a comment in PreludeList, I said

span p xs  =  (takeWhile p xs, dropWhile p xs)

In fact, this is false, because when xs diverges, the left side is _|_,
but the right side is (_|_,_|_).  This represents an important transformation,
known in the imperative world as loop fusion.  It would be nice if it
were valid.

Here's another way of looking at this issue:  An imperative routine can
easily have multiple effects, whereas a function (for syntactic reasons,
essentially) must return a tuple to have multiple results.  It's important
that this artificial packaging of values not have any cost.  If we insist
that a tuple has some meaning beyond the meanings of its components, we
run the risk of paying for that distinction.  (I think this is what Arvind
was referring to when he mentioned the importance of tuple elimination in
the Id compiler.)  I think this is rather like the problems Simon uncovered,
arising from considering a function to be anything more than its extensional
behavior.

--Joe




Re: Strictness

1993-11-01 Thread Joe Fasel


Paul writes:
| Like Ian, I would like to suggest that we lift functions in Haskell.
| Originally there was a good reason not to:  there was no need (and
| indeed no way) to distinguish _|_ from \x-_|_.  But now there are
| some compelling reasons to make the distinction:

I would say that there is still no compelling reason to distinguish
them.

| 1) It solves the strict constructor business without resorting, 
|for example, to Simon's "Data" class.

But perhaps such a class is an entirely appropriate solution to the
problem.

| 2) This in turn solves the lifted/unlifted product and ADT issue
|without resorting to a new kind to datatype decl ("newtype").

Taking Ian's view of ! as a bottomless type constructor, I suppose
that a lifted product of delifted types is something like an unlifted
product, but I wouldn't think this would be a _lazy_ product.

Actually, I agree that it would be better not to have a new kind of
data declaration, but I think a better solution is to have data types
be lifted sums of unlifted proudcts (where a single-constructor type
is not a sum).  Of course, this discussion has been with us since day
one of the Haskell committee; I beg the indulgence of those who are
tired of hearing about it, for the possible benefit of some who haven't
been around this block before.  In past discussions on this point,
those favoring unlifted products have pointed out that we could maintain
full flexibility by also providing an explicit Lift constructor.
In fact, such a constructor could be programmed:

data Lift a = Lift a | Never

where that second constructor is never used.  Some people, quite
reasonably, find this solution unpalatable, however.

Interestingly, there is some evidence that the Yale Haskell project has
implicitly taken the unlifted product view of single-constructor
types:

1.  Sandra Loosemore's paper on the optimizer lists "folding
is-constructor when the corresponding data type has only
the one constructor" as one of the miscellaneous
optimizations.

2.  John Peterson's paper on the Lisp interface says that a
Lisp type to be regarded as a k-constructor algebraic type
must be provided with the k constructors, k is-constructor
predicates, and component projections (e.g., nil, cons,
null, cons-p, car, cdr), but that the predicate may be
omitted for a single-constructor type.

| 3) It makes theory closer to practice:  Haskell will look more like
|Abramsky and Ong's lazy lambda calculus.

The lazy lambda calculus is certainly interesting and valuable as a model
of a pure calculus with head-normal-form reduction, but the question is
how relevant this is to Haskell.  The crucial issue is one of abstractness
and observability.  I think most of would agree that Haskell, Miranda,
and the like aren't quite like the pure lambda calculus, but more like
the lambda calulus augmented with base types and delta rules, where only
the base types are observable.  We say that the only operation on
functions is application, which with a lazy semantics naturally leads to
unlifted functions, since the only reason to evaluate a function is
to apply it.

Similarly, I would say the only operations on products are projections,
so that as a lazy language, Haskell in inconsistent, not in having
unlifted functions, but in having lifted products.

| 4) It conforms better to (at least my) intuition: current Haskell
|implementations in a sense CAN distinguish _|_ from \x-_|_:
|just return a functional value from the whole program, and in
|one case the implementation is likely to print something like
|"function", and in the other case, nothing (or "error", or whatever).
|To formalize this we could include a bulit-in instance decl for
|functions in the class Text.

As a matter of fact, we have, at John Peterson's suggestion:

instance  Text (a - b)  where
readsPrec p s  =  error "readsPrec{PreludeCore}: Cannot read functions."
showsPrec p f  =  showString "function"

Notice that showsPrec is a constant function.  The argument f need
not be evaluated to print the result.  Even if we don't bring show into
the act, if the implementation has the static types of the program
available to it, the same behavior can result:  If all the evaluator
needs to tell you about the main value is "It's a function,"  it doesn't
need to do any evaluation to tell you that.  (Now, if the language were
not statically typed, things would be different:  The implementation
would have to evaluate the main program just to discover the type,
and also, bottom and (\x - bottom) could probably be trivially
distinguished by an isFunction type predicate.)

Your implementation may well have different representations corresponding
to bottom and (\x - bottom), but that's a far cry from saying that
they shouldn't abstractly be regarded as the same value.

If Haskell is fundamentally a lazy 

More on strictness

1993-11-01 Thread Joe Fasel


I wrote:
|Thus, it would indeed be reasonable for the type of seq to determine
|that  f x `seq` y  is all right, whereas f `seq` y is not permissible.
|Similarly, I think it would be consistent to have unlifted products,
|but not give them data instances, so that  (x,y) `seq` z  is not allowed,
|the programmer needing to choose between  x `seq` y `seq` z  and
|y `seq` x `seq` z.

An equally reasonable approach would be to give such types instance
declarations like the following:

instance Data (a - b) where
seq f x  =  x

instance Data (a,b) where
seq p x = x

Operationally, this would be like saying that any value of one of these
types is already in head normal form, I suppose.

--Joe




Re: re. Arrays and Assoc

1993-10-05 Thread Joe Fasel


Nikhil says,

| Thomas Johnsson says:
|
| If I recall correctly, the := to be used in array comprehensions was a
| consession to the FORTRAN/Id/Sisal community, so that array comprehensions
| would look more like they were used to.
|
| Both Arvind and I think this is notation is awful, and I don't recall
| either of us ASKING for it, so this was probably someone else's idea
| of a ``concession'' to the Id community!
|
| Nikhil

All right!  I'm sorry!  ;-)

As I recall, Nikhil is right that neither he nor Arvind asked for this.
Some scientific programmers of my acquaintance did, though.  Id uses
= for this purpose, together with square brackets around the index.
This, of course, was not possible for Haskell.  The motivation was not
so much a "concession" to the Id community, as a concern for the
readability of

[((i,j), (f i j, g i j)) |

versus

[(i,j) := (f i j, g i j) |

or Id's

{matrix (1,N),(1,N) | [i,j] = (f i j, g i j) ||

(if I have that somewhere close to right).  The use of := for pairing
(or if you like, binding, or single-assignment) rather that assignment
did have a precedent in Val and Sisal.

All this syntax may seem of little consequence now, but at the time,
there was a genuine concern about the unpalatability of some choices
of syntax to a large community of programmers.

--Joe




Re: Arrays and Assoc

1993-10-05 Thread Joe Fasel


John Launchbury says,
| Here are three comments directed particularly at Haskell 1.3 people, but
| obviously open to general feedback.
|
| 1. We should get rid of Assoc.
|
| When explaining my programs to other people I find this is a point of
| confusion. Imagine exaplaining array construction, "When I define an array,
| the comprehension produces a list of index/value pairs, only they are not
| written as pairs--these's this special type called Assoc. Oh, and don't be
| confused by :=. That's not assignment. It is an infix pairing operator."
| All of this is entirely unnecessary. Pairs have been used in maths for
| decades to represent exactly this sort of thing. I simply do not believe
| that [Assoc a b] provides me with any better information than [(a,b)].
| Worse, I often find myself having to redefine standard pair functions on
| elements of Assoc.

Mea maxima culpa.  I must admit that the reason for introducing Assoc
was syntactic.  Making a semantic distinction between pairs and assocs
for a syntactic purpose should have set off alarms; somehow, I managed
to ignore them.

At the time this decision was made, arrays and array syntax were something
of a contentious issue.  Even the use of infix ! for indexing was a
source of anguish for potential users of arrays, and the fear was that
pair syntax in "array comprehensions" would be unwieldy, particularly
for multidimensional arrays.  Consider a matrix of pairs (a typical
construction in scientific mesh algorithms).

Lennart asks whether we should be concerned about an upward compatibility
problem.  Thomas suggests that we could drop the syntactic restrictions
on constructor and nonconstructor symbols and define (:=) as a pairing
function.  That almost does the job, but there are some programs that
pattern-match Assocs.  Also, I think there will be objection in some
quarters to dropping the separation of name spaces.  Here are two more
possibilities:

2.  Provide a way to declare synonyms for constructors, and
use it to equate := with (,).

3.  Don't provide such a general facility, but hack in :=
as a special case (rather like prefix minus).


| 2. Arrays should be lazier.
|
| I'm expecting Lennart to agree with me here as LML has the Right Thing. I
| am convinced that there is no semantic problem with this, and I think that
| even Simon isn't horrified at the implementation implications. The ability
| to define arrays by self reference is just as important as it is for lists.
| I am assuming that the fact that lazy indexes provide a better match with
| laziness elsewhere is clear, but I am willing to expand on this point if
| someone wants.

I agree, but I also agree with Lennart that both sorts of arrays are needed.
The historical context again:  Accumulators had been added to Id because
too many scientific programs couldn't live without them (or else effects).
Pragmatically, the accumulations in these programs were almost always
sums.  (histogramming, Monte Carlo tallying)  People needed to be convinced
that this could be done efficiently.


| 3. AccumArray should mimic foldr, not foldl.
|
| This is tied up with the last point. The only advantage I can see with the
| present scheme would be if the array element could be used as the
| accumulator while the array was under construction. However, as arrays are
| non-strict in their *elements* this seems to be of no benefit. It seems to
| me highly sensible that the structure of the computation at each point
| should reflect the structure of the input sequence (i.e. the elements are
| in the same order). Furthermore, if a lazy operation is used (such as (:))
| then the result becomes available early (assuming point 2. above).
|
| John.
|

Agreed again.  The historical reason for the choice of foldl should be
evident from the remarks above.

Since all of these decisions had to do with Id arrays, I'm pleased
to hear from Nikhil that pH people are thinking along the same lines
as John and Lennart.  Consensus!

--Joe




Re: Polymorphic recursive calls possible via type classes

1993-07-28 Thread Joe Fasel


Phil Writes:

|However, for the extended type system that allows polymorphism in
|recursion, this is no longer the case -- my thanks to Lennart
|Augustsson for pointing this out.  The counter-example (similar
|to one of Mark's) is:
|
|g :: a - Bool
|g x  =  g [x]
|
|This function is silly, as it never terminates, but there are less
|silly examples; see below.  Note that the trick for translating
|polymorphic recursion into type classes (as described by Konstantin) no
|longer works here.  The closest one can come is
|
|class G a where
|g :: a - Bool
|g x = g [x]
|
|instance G Int where
|instance G [Int] where
|instance G [[Int]] where
|...
|
|which requires an infinite number of instance declarations.

Can't this be written as follows?

instance G Int where
instance (G a) = G [a] where

Now, this is still an infinite number of instances, though not
declarations, so the point still holds that it can't be monomorphized.

--Joe
Joseph H. Fasel
Los Alamos National Laboratory




Re: Prefix negation

1993-07-28 Thread Joe Fasel


| From: [EMAIL PROTECTED]
|
| I'm puzzled by a detail in the Report, which seems to contradict itself.
|
| On page 13 it says:
|
| The special form -e denotes prefix negation, [...] and is simply
| syntax for negate (e), where negate is as defined in the standard
| prelude.
|
| The standard prelude defines negate as a function, which by default has
| precedence 10.  But the context free syntax on page 134 says:
|
| lexp6 ::= - exp7
|
| which gives prefix - precedence 6.

Hi, Norman.

It says, "is simply syntax for negate (e)", not "is syntactically
equivalent to negate (e)".  In other words, prefix minus is a special
syntactic form, with syntactic precedence 6, as given by the context-
free syntax.  Semantically, the form denotes an application of the
standard function negate.  OK?

--Joe




Re: + and -: syntax wars!

1993-05-26 Thread Joe Fasel


John Peterson
  Lennart Augustsson
Joe Fasel

|  This whole issue regarding redefinition of + and - is getting confused
|  unnecessarily.  Both of these are in PreludeCore and cannot be renamed
|  or hidden.  Because of this their fixities cannot be changed.  It is
|  possible to locally shadow + and - but this cannot change their
|  fixities and has no effect on + in n+k patterns.
| Exactly!  But what I find a bit strange is that even when + and -
| are overridden locally n+k and prefix - still have their old meanings.
| Well, it's just one more exception to the rule to remember about Haskell.

Yes, but we need to emphasize that rebinding such operators is a Bad Idea.
(Maybe Phil is right, that we should simply forbid it.)  What you want
to do instead is provide a Num (in this case) instance.  If you complain
that your funny + and - don't have the right types to be part of a Num
instance, I have no sympathy.  ("Pathetic, ruddy planet---I've no sympathy
at all.")

--Joe




Re: Successor patterns in bindings and n+k patterns

1993-05-19 Thread Joe Fasel


| Another strange thing about n+k patterns.
|
| Its definition uses = , but = is not part of the class Num.
| Does that mean that n+k patterns have to be instances of class Real?

Certainly.  In fact, they're really meant to apply only to class
Integral (and it would be natural numbers, if we had them).

| One could leave it class Num, if the translation were expressed
| in terms of "signum" rather than "=".

Being able to match complex numbers (along the positive real axis only!)
with n+k patterns would be a dubious advantage, IMHO.

| Question:
| Can one misuse the feature of n+k-patterns to simulate
| n*k+k' patterns?  [I am talking about weird user-defined
| instances of Num.]

quite possibly.

| Stefan Kahrs

--Joe Fasel




Re: n+k patterns

1993-05-18 Thread Joe Fasel


|Another question along the same lines: What if (+) has been rebound?
|Are n+k patterns still allowed?
|
|-- Lennart

The answer should be that n+k patterns are still allowed, but (+), (-),
and (=) from PreludeCore are used in the translation.

--Joe