Monads and data structures

1996-05-16 Thread Klaus Georg Barthelmann

Dear friends of Haskell,
a few days ago I asked the question:
   2) The library proposal does not contain any advanced data structures (yet). 
  How would one declare, for example, ordered sets as an instance of
  Monad[Plus]?

Alastair Reid answered as follows:
 Ordered sets are a problem because constructor classes aren't up to
 the job of describing the constraints (Eq, Ord, Ix, Hashable, etc) on
 the elements of data structures.  The best you can do at the moment is
 to use the module system and qualified names to provide libraries with
 similarily interfaces.  John Peterson and I wrote about this last year
 at the Haskell Workshop:
 
 ftp://haskell.cs.yale.edu/pub/haskell/yale/libs-discussion.dvi.gz
 
 ftp://haskell.cs.yale.edu/pub/haskell/yale/libs.dvi.gz
   -- draft companion paper which discusses the interface in more detail.
   -- note that libs.ps.gz is a MUCH OLDER version of this paper.

Well... The latter paper tells us (on page 2):
 At the time of writing, it seems unlikely that constructor classes will be
 included in Haskell 1.3.
Therefore, some proposals should perhaps be reconsidered under the new
situation. I don't see what prevents code like, for example,
 instance Ord t = Monad (Set t) where ...

 (You might also want to download Hugs 1.01 from any of the usual
  ftp sites.  (eg ftp.cs.nott.ac.uk)   It's more or less Haskell 1.2
  but does add constructor classes - so you could play around
  with those while waiting for a full implementation of Haskell 1.3.)

HUGS does not allow the above construction. I consider this a bug. It renders
constructor classes almost useless.

By the way, I get the impression that Prelude and the libraries don't make full
use of monads yet. For example, what do you think about the following function?
 lookup :: (Eq a, Monad m, MonadZero n) = a - m (a,b) - n b
 lookup i ps = do (k,v) - ps
  if k==i then return v else zero
It surely generalises the lookup function in PreludeList (m:=[], n:=Maybe).

Best regards,
  Klaus






Re: Monads and data structures

1996-05-16 Thread Klaus Georg Barthelmann

Hi!
I was told by Magnus Carlsson and Enno Scholz that my proposal
 lookup :: (Eq a, Monad m, MonadZero n) = a - m (a,b) - n b
 lookup i ps = do (k,v) - ps
  if k==i then return v else zero
isn't well-typed. I'm sorry for this bug. (I cannot access a compiler for
Haskell 1.3 yet.)
So let's do it in less generality:
 lookup :: (Eq a, MonadZero m) = a - [(a,b)] - m b
 lookup i = foldr (\ (k,v) rest - if k==i then return v else rest) zero
for example. I'll start another attempt at the original version as soon as I
can test it...
My apologies,
  Klaus






Re: *By functions in list utilities library

1996-05-16 Thread Sigbjorn Finne


Following up to my own post :-{, but after further communication with
Mike Gunter, a good example for why generalising some of the *By
functions List is a good idea was presented, namely that of
deleteFirstsBy

  deleteFirstsBy :: (a - a - Bool) - [a] - [a] - [a]

generalising it to

  deleteFirstsBy :: (a - b - Bool) - [a] - [b] - [a]

is genuinely useful, i.e.,

   foo = deleteFirstsBy 
 (\ rec id - id == personId rec) 
 list_of_records
 list_of_ids_to_delete

So, if my first reply suggested otherwise, I'm positive to the
proposed generalisation of the *By functions:

  deleteBy :: (a - Bool) - [a] - [a]
  deleteFirstsBy   :: (a - b - Bool) - [a] - [b] - [a]
  notElemBy,elemBy :: (a - Bool) - [a] - [a]  -- or just stick with any?
  lookupBy :: (a - Bool) - [(a,b)] - Maybe b
  maximumBy, minimumBy :: (a - a - Bool) - [a] - a
  nubBy:: (a - a - Bool) - [a] - [a]
  elemIndexBy  :: (a - Bool) - [a] - Int
  groupBy  :: (a - a - Bool) - [a] - [[a]]

(the second arg. to List's deleteBy, elemBy, notElemBy, lookupBy and
 elemIndexBy have been applied to the predicate here - I'm not fussed
 either way).

The benefit of `elemBy' over `any' still eludes me though, anyone
care to enlighten me :-)

--Sigbjorn

  
 From: Sigbjorn Finne [EMAIL PROTECTED]
 Date: Tue, 14 May 96 21:04:28 +0100 
 
 
  I noticed that the *By functions (deleteBy, deleteFirstsBy, elemBy,
  etc.) in the current on-line HTML library documentation have type signatures
  which restrict the types beyond that required by the implementation.
  For instance:
  
elemBy, notElemBy   :: (a - a - Bool) - a - [a] - Bool
elemBy eq _ []  =  False
elemBy eq x (y:ys)  =  x `eq` y || elemBy eq x ys
  
  My recollection is that when I brought this up last on this mailing
  list, public input ran in favor of not restricting the type signature.
  (For instance
elemBy, notElemBy   :: (a - b - Bool) - a - [b] - Bool
  )
  
 
 I'm probably missing the point of the (elemBy, notElemBy) pair
 alltogether, but why not just stick with `any'? i.e., of the 
 two value bindings
 
   ls :: [HaskellImplementation]
   wibble = elemBy (inTheBallpark) 1.3 ls
   frob   = any (inTheBallpark 1.3) ls
 
 `frob' is clearer than `wibble' - YMMV.
 
 What is the motivation for including {not}elemBy in List?  If it is
 the wish to have 1-1 match of *By functions with PreludeList defns
 that uses type class predicates (from Eq and Ord) then elemBy should
 stay as is, and any uses of `non-standard' equality predicates (e.g.,
 a - b - Bool) are better coded up using `any', `filter' etc., 
 since the generalised predicate is not applicable to all *By functions
 (cf. deleteFirstsBy, nubBy).
 
 All IMHO, of course.
 






Re: *By functions in list utilities library

1996-05-16 Thread reid-alastair

Mike Gunter and Sigbjorn Finne propose generalising the type of the
*By functions as follows:

deleteBy :: (a - Bool) - [a] - [a]
deleteFirstsBy   :: (a - b - Bool) - [a] - [b] - [a]
notElemBy,elemBy :: (a - Bool) - [a] - [a]  -- or just stick with any?
lookupBy :: (a - Bool) - [(a,b)] - Maybe b
maximumBy, minimumBy :: (a - a - Bool) - [a] - a
nubBy:: (a - a - Bool) - [a] - [a]
elemIndexBy  :: (a - Bool) - [a] - Int
groupBy  :: (a - a - Bool) - [a] - [[a]]

  (the second arg. to List's deleteBy, elemBy, notElemBy, lookupBy and
   elemIndexBy have been applied to the predicate here - I'm not fussed
   either way).

I believe I'm to blame for proposing the *By functions - so I should
comment on this porposal.

My old argument against generalisation was that programmers would
benefit from having a simple rule that tells them how the name, type
signature and semantics of the overloaded function relates to the
non-overloaded function.  Generalising the signature breaks this (eg
it doesn't make sense to require that a function of type (a - b -
Bool) be an equivalence.)  Sigbjorn's partial application makes the
connection even more tenuous.

If we stop thinking of (most of) these functions as being
generalisations of Eq and Ord functions these problems go away.  For
example, I've no objections to these signatures.

-- these don't directly generalise any Prelude functions
deleteFirst:: (a - Bool) - [a] - [a]
deleteFirsts   :: (a - b - Bool) - [a] - [b] - [a]
find   :: (a - Bool) - [(a,b)] - Maybe b
indexOf:: (a - Bool) - [a] - Int

-- these generalise Prelude functions
maximumBy, minimumBy :: (a - a - Bool) - [a] - a
nubBy  :: (a - a - Bool) - [a] - [a]
groupBy:: (a - a - Bool) - [a] - [[a]]

(and remove elemBy, notElemBy and deleteBy)

There may be better names - the main point is that the "By" suffix
only gets used if we've replaced Eq/Ord in the context with (a - a -
Bool).  We could also argue about whether indexOf should return "Maybe
Int".


Alastair Reid
Yale Haskell Project

ps
Sigbjorn also says:
  The benefit of `elemBy' over `any' still eludes me though, anyone
  care to enlighten me :-)

1) Consistency.

2) If you are trying to write a generalised version of some function
   that you'd normally write using "elem", it may be clearer to use
   "elemBy eq x ys" than to use "any (eq x) ys".







Haskell 1.3 - what's it all about?

1996-05-16 Thread Magnus Carlsson

Maybe you have seen some mail lately on this list about something
called "Haskell 1.3", and wondered 

What is this "Haskell 1.3" anyway?,
Can I buy it?,
or
Do I have it?

By compiling and running the following two-module Haskell program, you
will at least get an answer to the last question.

-- Put in M.hs ---

module M where data M = M M | N ()

-- Put in Main.hs 

import M
main = interact (const (case (M.N) () of M (N ()) - "No\n"; N () - "Yes\n"))

---

Magnus  Thomas