Re: deleteBy type

1999-12-05 Thread Mariano Suarez Alvarez

On Sun, 5 Dec 1999, S.D.Mechveliani wrote:

> Is not deleteBy :: (a->Bool) -> [a] -> [a]
> more natural for the library than
>deleteBy :: (a->a->Bool) -> a -> [a] -> [a]
> ?

isn't the first deleteBy simply filter?

-- m

---------------
Mariano Suarez Alvarez
Departamento de Matematica - Universidad Nacional de Rosario
Pellegrini 250 - Rosario 2000 - Argentina 

El autor no responde de las molestias que puedan ocasionar sus escritos:
Aunque le pese
El lector tendra que darse siempre por satisfecho.

Nicanor Parra, `Poemas y antipoemas' (Advertencia al lector)

---




Re: To all those who don't like ad-hoc overloading

1999-10-04 Thread Mariano Suarez Alvarez

On Mon, 4 Oct 1999, Kevin Atkinson wrote:

> On Mon, 4 Oct 1999, Joe English wrote:
> 
> > I don't quite see what algorithm you're using
> > to decide how many arguments are passed
> > to the function.
> 
> Neither do I.  I meant to express a general idea.  Perhaps that is not the
> best way to do it but that is what I would like to be able to do.
> 
> > What would you get if you typed:
> > 
> > foo = foldr union []
> 
> since foldr expects the function to have the signature
> (a->b->b) it will use the union which matches it, which
> will be the union :: [a] -> [a] -> [a] and not
> union :: ( a -> a -> Bool) -> [a] -> [a] -> [a].

The problem is the two might match! Consider the definitions

union :: [a] -> [a] -> [a]
unionBy :: (a -> a -> a) -> [a] -> [a] -> [a]
union = error ""
unionBy = error ""

f = union . map fst

g = unionBy . map fst

(I have dropped the (Eq a) context in the signature for union for
simplicity.) This goes thru the typechecker, and hugs tells me that

f :: [(a,b)] -> [a] -> [a]
g :: (a -> (a -> a, b)) -> [a] -> [a] -> [a]


If one were allowed to write union for both union and unionBy, so which
one should one choose?

-- m

---
Mariano Suarez Alvarez
Departamento de Matematica - Universidad Nacional de Rosario
Pellegrini 250 - Rosario 2000 - Argentina 

El autor no responde de las molestias que puedan ocasionar sus escritos:
Aunque le pese
El lector tendra que darse siempre por satisfecho.

Nicanor Parra, `Poemas y antipoemas' (Advertencia al lector)

---







Re: how to write a simple cat

1999-06-04 Thread Mariano Suarez-Alvarez

On Thu, 3 Jun 1999, Hans Aberg wrote:

> >A ``category with + and ^ '' is called cartesian closed aditive
> >category, cf MacLane, Category Theory for the Working Mathematician
> 
> Is this a suggestion or a theorem?

A definition.

-- m






Re: how to write a simple cat

1999-06-03 Thread Mariano Suarez-Alvarez

On Wed, 2 Jun 1999, Hans Aberg wrote:

> But it can be a spin-off for thoughts: A category is essentially an object
> with I and *, and a functor is a map preserving those. So what about the
> two other operations, + and ^ ?.

A ``category with + and ^ '' is called cartesian closed aditive
category, cf MacLane, Category Theory for the Working Mathematician

Mariano Suarez Alvarez 







Re: suggestions for Haskell-2

1998-07-27 Thread Mariano Suarez Alvarez

On Mon, 27 Jul 1998, S.D.Mechveliani wrote:

> Obstacle 2:
> 
> Haskell rejects this  `=> RightModule r r'  
> 
> How can we express the meaning  
>... RightModule m r  where  m  is the identical constructor
>  (m a = a)
> ?
> Scripting
>   newtype Id a = Id a  deriving(...)
> 
>   instance Ring r => RightModule Id r  where 
>cMul (Id r) r' =  Id (mul r r')
> is an awkward way-out.
> Because from this point on, the programmer has to convert the data
> explicitly between  r  and  Id r.  This is not exactly what the 
> application domain means.

Actually and strictly speaking, the `awkward' way out is here the correct
one, because it makes explicit the difference between the ring and the
canonical module over itself it determines. 
The instance Ring r => RightMod Id r can be regarded as an expression of
the fact that Id : Rng -> Mod is a functor, (which can't be an identity
functor, because domain and codomain aren't the same!) 

cheers,

-- m

---
Mariano Suarez Alvarez
Departamento de Matematica  
Universidad Nacional de Rosario
Pellegrini 250
2000 Rosario - Argentina 
e-mail: [EMAIL PROTECTED]

El autor no responde de las molestias que puedan ocasionar sus escritos:
Aunque le pese
El lector tendra que darse siempre por satisfecho.

Nicanor Parra, `Poemas y antipoemas' (Advertencia al lector)

---







RE: multi param type classes

1998-07-08 Thread Mariano Suarez Alvarez

On Wed, 8 Jul 1998 [EMAIL PROTECTED] wrote:

> Each expression then has a set of possible types, and the ambiguity is   
> resolved by an explicit type signature.
> 
> At present it is quite frustrating in Haskell that when a name is used in   
> one place it is then lost for use in any other context -- the example of   
> an overloaded size function strikes me as very sound.

I don't see why something like

class HasSize a where
  size :: a -> Int

doesn't solve this...

-- m

-----------
Mariano Suarez Alvarez
Departamento de Matematica  
Universidad Nacional de Rosario
Pellegrini 250
2000 Rosario - Argentina 
e-mail: [EMAIL PROTECTED]
---

El autor no responde de las molestias que puedan ocasionar sus escritos:
Aunque le pese
El lector tendra que darse siempre por satisfecho.

Nicanor Parra, `Poemas y antipoemas' (Advertencia al lector)

---






Re: Exceptions are too return values!

1998-06-09 Thread Mariano Suarez Alvarez

On Mon, 8 Jun 1998, S. Alexander Jacobson wrote:

> 1. it is not logically consistent to treat exceptions as return values

A function cannot do anything but return a value, can it? 

> For example, suppose that we define a new function:
> 
> > foo' a b = a + b -- foo' is strict in its arguments
> 
> Our intuition is that foo' is commutative.  foo' a b = foo' b a.
> But that turns out not to be true when you have exceptions.

That's the problem with intuitions: they can be wrong...  
Anyhow, if one is to have exceptions procteting +, I don't think that
commutativity of foo' is reasonable: to handle exceptions, you have to do
checks, and that you can only do in one order or another. 

> Take x and y from before,
> 
> > z = foo' x' y'
> 
> What is the value of z? Haskell does not promise to evaluate arguments in
> any particular order so, depending on implementation, z may be either
> Exception DivideByZero or Exception NotFactorialDomain -1.  

Actually, using a monad to manage exceptions you can (maybe, have to) 
choose a definite order of evaluation of non-exceptionality-conditions. 

> Truly exceptional conditions are those that truly are outside of the
> domain of the function being evaluated. e.g. factorial -1
> The VALUE of (factorial -1) is not an exception.  Neither is the value of
> (factorial (1 `div` 0)).
> When a function is passed bad arguments, it is not meaningful (from a
> functional perspective) to have it return a value.

In a typed language, a function *cannot* be applied to something outside
its domain. That's the whole point!

> The value of a function over arguments outside its domain is undefined.
> When such an event occurs, the logically consistent behavior is to exit
> function evaluation and tell the caller what was wrong with the
> arguments passed (to the extent it is possible to do).

One can rightfully argue that, if one is willing to consider bottom (which
is a value we cannot test for!) a return value, which we are, considering
an exception a return value is *very* consistent. 
 
-- m

---
Mariano Suarez Alvarez  The introduction of
Departamento de Matematica   numbers as coordinates
Universidad Nacional de Rosario [...] is an act of violence
Pellegrini 250  A. Weyl
2000 Rosario - Argentina
e-mail: [EMAIL PROTECTED]
---





RE: Pattern Match Success Changes Types

1998-05-12 Thread Mariano Suarez Alvarez

On Tue, 12 May 1998, Koen Claessen wrote:

> Frank A. Christoph wrote:
> 
>  | With regard to merging Either instances, I agree with Simon that for most
>  | programs this will not buy you much, but there are two common kinds of
>  | programs where one could expect a significant effect on performance, just
>  | because of sheer scale.
> 
> It is not only Either instances who suffer from this. Consider the
> following definition of "map", which could be made by a naive user:
> 
>   map :: (a -> b) -> [a] -> [b]
>   map f (x:xs) = f x : map f xs
>   map f xs = xs
> 
> Same problem here.

Where is the CSE in theis def of map? Why is it naive? (Hugs & ghc define
map on lists exactly like that.) Maybe I'm naive...

-- m

-----------
Mariano Suarez Alvarez  The introduction of
Departamento de Matematica   numbers as coordinates
Universidad Nacional de Rosario [...] is an act of violence
Pellegrini 250  A. Weyl
2000 Rosario - Argentina
e-mail: [EMAIL PROTECTED]
---






Re: quicksort and compiler optimization

1998-05-11 Thread Mariano Suarez Alvarez

On 10 May 1998, Carl R. Witty wrote:

> > > qsort [] = []
> > > qsort (x:xs) = let (a,b) = foldr (\y -> (y ?: (=x))) ([],[]) xs
> > >in qsort a ++ [x] ++ qsort b
> > > f # g  = \(x,y) -> (f x,g y)
> > > x ?: p = if p x then (x:) else id
> > > qsort' [] = []
> > > qsort' (x:xs) = qsort' [y | y<-xs, y=x]
> > >
> > > the proof is easy. 
> Yes, I think this is sound, but is it an optimization?  

The paper by Launchbury, Peyton Jones & Gill (which is where I got it
from) introduces it as such... This is very fallacious as an 
argumentation, I know... :)

> This discussion began as a way to keep xs (from the definition of
> qsort' above) from being live in this situation.  The definition of
> qsort above does this--possibly (if xs were not shared elsewhere)
> freeing up some cons cells--but only at the cost of introducing some
> much larger data structures.  Note that all the elements of xs are
> still live in both cases.

I don't think that keeping xs from being alive be possible, at least in
general, because if >= might lead to bottom when < doesn't, one has to
keep all the elements in xs somewhere.  qsort and qsort' are both (at
least) linear in space; different constant factor. The much larger data 
structures needed in the qsort case recall the fact that the list has
already been traversed: we are trading space for time...

One might write

> qsort2 [] = []
> qsort2 (x:xs) = qsort2 a ++ [x] ++ qsort2 b
>   where (a,b) = partition (= being one the negation of the other, which we are not
assuming, as in the T example (I can't think of *one* meaningful example
where < and >= are as in the Ord T instance) 

-- m

---
Mariano Suarez Alvarez  The introduction of
Departamento de Matematica   numbers as coordinates
Universidad Nacional de Rosario [...] is an act of violence
Pellegrini 250  A. Weyl
2000 Rosario - Argentina
e-mail: [EMAIL PROTECTED]
---









Re: quicksort and compiler optimization

1998-05-10 Thread Mariano Suarez Alvarez

qsort can be rewritten (by the compiler, ideally...) so that the list is
traverse once, without losing any laziness:

> infix 5 #
> infix 6 ?:

Define

> qsort [] = []
> qsort (x:xs) = let (a,b) = foldr (\y -> (y ?: (=x))) ([],[]) xs
>in qsort a ++ [x] ++ qsort b

where (#) is cartesian product of functions

> f # g  = \(x,y) -> (f x,g y)

and ?: is a conditional cons

> x ?: p = if p x then (x:) else id

This definition of qsort is equivalent (on reasonable lists, ie finite
with no bottoms inside) to the original

> qsort' [] = []
> qsort' (x:xs) = qsort' [y | y<-xs, y=x]

The proof is easy.

With this definition of qsort, we have no problem evaluating result below:

> data T = T deriving (Eq,Show)

> instance Ord T where
>  T < T= False
>  T <= T   = True
>  T > T= False
>  T >= T   = error "Oops!"

> result = head (qsort [T,T,T,T])

qsort could be made a little simpler if one were allowed to assume (I
think one isn't?) that Ord instances satify the usual laws for an (linear)
order, such as < being the negation of >= (the instance for T above
doesnt'). 

The same idea works in general: if E is some expression,

E (foldr f1 b1 xs) (foldr f2 b2 xs)
  = let (a,b) = (foldr f1 b1 xs,foldr f2 b2 xs)
in E a b
  = let (a,b) = (foldr f1 b1 xs,foldr f2 b2 xs)
in E a b
  = let (a,b) = foldr (\x -> (f1 x # f2 x)) (b1,b2) xs
in E a b

This is useful, since usually list traversing functions can be writen 
using foldr. I remember reading about this somewhere...

-- m

---
Mariano Suarez Alvarez  The introduction of
Departamento de Matematica   numbers as coordinates
Universidad Nacional de Rosario [...] is an act of violence
Pellegrini 250  A. Weyl
2000 Rosario - Argentina
e-mail: [EMAIL PROTECTED]
---







Re: quicksort and compiler optimization

1998-05-09 Thread Mariano Suarez Alvarez

On 8 May 1998, Carl R. Witty wrote:

> > > Is it necessary that the compiler do this?  It strikes me that when the
> > > compiler encounters a function that requires multiple comprehensions of
> > > the same list, it should be smart enough to consolidate them into a single
> > > loop (which would also avoid the space leak).  Is my intuition correct
> > > here?
> > 
> > This optimization would probably be a win most of the time, so
> > yes, ideally compilers would do things like that.  Currently however
> > those sort of optimizations are past the limits of what most Haskell
> > compilers will do.
> 
> Watch out...this optimization is invalid.  Consider the following

The problem is that something like (head (qsort [whatever])) is not strict
in the whole resulting sorted list, so merging the comprehensions is not a
win but a loss (a big loss: now we've got bottom!). 

If the compiler could prove that the resulting list is needed strictly,
the merging is ok. This happens in (length (qsort [whatever])). This
sounds difficult...

The compiler might generate two versions for qsort, one to be used when
the result is needed strictly, and the other when it is not... 

Do present compilers do this kind of things?

-- m

-------
Mariano Suarez Alvarez  The introduction of
Departamento de Matematica   numbers as coordinates
Universidad Nacional de Rosario [...] is an act of violence
Pellegrini 250  A. Weyl
2000 Rosario - Argentina
e-mail: [EMAIL PROTECTED]
---






Re: the overloading of ==

1998-03-12 Thread Mariano Suarez Alvarez

On Thu, 12 Mar 1998, Koen Claessen wrote:

> Sadly, this example shows that Haskell 1.4 does not have a principal
> typing property. Your function has the type
> 
>   all' :: Eq a => (a -> Bool) -> [a] -> Bool
>
> As well as:
> 
>   all' :: Eq a => (a -> Bool) -> F a -> Bool
> 
> (for a suitable Monad F). But Haskell is not capable of finding the one
> type that contains them all: 
> 
>   all' :: (Monad m, Eq (m a)) => (a -> Bool) -> m a -> Bool
 
What is the reason for that? It is a language design choice or is there a 
fundamental reason like, say, that allowing such things make the type
system undecidable?

m

---
Mariano Suarez Alvarez  The introduction of
Departamento de Matematica   numbers as coordinates
Universidad Nacional de Rosario [...] is an act of violence
Pellegrini 250  A. Weyl
2000 Rosario - Argentina
e-mail: [EMAIL PROTECTED]
---






Re: Monads and their operational behaviour

1997-11-27 Thread Mariano Suarez Alvarez

On Thu, 27 Nov 1997, Malcolm Wallace wrote:

> >> What's the behaviour of NHC/HBC in these cases?
> 
> >hbc has 876 bytes in use on the heap and the stack is 13 entries deep.
> 
> nhc13 has 220 bytes in use in the heap.

What do these numbers mean?

---------------
Mariano Suarez Alvarez  The introduction of
Departamento de Matematica   numbers as coordinates
Universidad Nacional de Rosario [...] is an act of violence
Pellegrini 250  A. Weyl
2000 Rosario - Argentina
e-mail: [EMAIL PROTECTED]
---






Haskell program manipulator

1997-09-20 Thread Mariano Suarez Alvarez

Has anyone written a Haskell program manipulator? 
What I have in mind is some kind of interactive environment allowing one
to, say, fold/unfold definitions, typecheck (sub)expressions,
etc...e??Xa?^aZOUo^aUu[ZaaG??E?u?u 

---
Mariano Suarez Alvarez  The introduction of
Departamento de Matematica   numbers as coordinates
Universidad Nacional de Rosario [...] is an act of violence
Pellegrini 250  A. Weyl
2000 Rosario - Argentina
e-mail: [EMAIL PROTECTED]
---