Re[6]: All Monads are Functors

2006-08-14 Thread Bulat Ziganshin
Hello Taral,

Tuesday, August 15, 2006, 3:11:37 AM, you wrote:

>> > Do we complain about a duplicate instance declarations?
>>
>> yes. after all, this is just syntax sugar of giving both declarations:

> Not necessarily. If A doesn't have any Functor declarations, it could
> be considered just a Monad without a Functor.

in this case we lose "class Functor a => Monad a" base class
declaration. so what will be the meaning of this:

class Monad m where
  instance Functor m
  return :: ...
  

and this:

class Monad m where
  instance Functor m where
 fmap = return ...
  return :: ...
  

?



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re[2]: map and fmap

2006-08-14 Thread Bulat Ziganshin
Hello Duncan,

Tuesday, August 15, 2006, 2:37:50 AM, you wrote:

> If it goes in that direction it'd be nice to consider the issue of
> structures which cannot support a polymorphic map. Of course such
> specialised containers (eg unboxed arrays or strings) are not functors
> but they are still useful containers with a sensible notion of map.

unboxed arrays - not if you using implementation from ArrayRef lib

ByteStrings - can be also parameterized by its type elements, as i
always suggested. of course, these elements should be unboxable and
belong to the Storable class in order to allow peek/poke them

there is also faking solution:

type ByteStr a = ByteString
instance Functor ByteStr

(although i never tested it)


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: [pup...@pupeno.com: Binary IO]

2006-08-14 Thread Bulat Ziganshin
Hello Donald,

Tuesday, August 15, 2006, 8:23:51 AM, you wrote:

> I just want to express that I really would like to see this. I was coding a
> DNS server in Haskell and the main reason I stopped was because binary IO was
> very, very painful (so many different library, or half libraries, whenever I
> was using one it seemed to be the wrong one).

i'm sorry for lacking docs, but the library is here - look at
http://haskell.org/haskellwiki/Library/AltBinary  and
http://haskell.org/haskellwiki/Library/Streams


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


[pup...@pupeno.com: Binary IO]

2006-08-14 Thread Donald Bruce Stewart
While we're thinking a little about the libraries, I received the
following:

- Forwarded message from Pupeno <[EMAIL PROTECTED]> -

Date: Tue, 8 Aug 2006 07:44:04 +
Subject: Binary IO

Hello,

I've seen that you have been assigned the task of evaluating binary IO for 
inclusion in Haskell: http://hackage.haskell.org/trac/haskell-prime/ticket/15
I just want to express that I really would like to see this. I was coding a 
DNS server in Haskell and the main reason I stopped was because binary IO was 
very, very painful (so many different library, or half libraries, whenever I 
was using one it seemed to be the wrong one).
Thank you.

Pupeno <[EMAIL PROTECTED]> (http://pupeno.com)

- End forwarded message -
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: map and fmap

2006-08-14 Thread Duncan Coutts
On Mon, 2006-08-14 at 20:55 +0100, Jon Fairbairn wrote:
> On 2006-08-14 at 12:00PDT "Iavor Diatchki" wrote:
> > Hello,
> > I never liked the decision to rename 'map' to 'fmap', because it
> > introduces two different names for the same thing (and I find the name
> > `fmap' awkward).
> 
> I strongly concur. There are far too many maps even without
> that, and having two names for the same thing adds to the
> confusion.

If it goes in that direction it'd be nice to consider the issue of
structures which cannot support a polymorphic map. Of course such
specialised containers (eg unboxed arrays or strings) are not functors
but they are still useful containers with a sensible notion of map.

The proposals to allow this involve MPTCs where the element type is a
parameter. That allows instances which are polymorphic in the element
type or instances which constrain it.

Duncan

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: map and fmap

2006-08-14 Thread Robert Dockins


On Aug 14, 2006, at 3:00 PM, Iavor Diatchki wrote:


Hello,
I never liked the decision to rename 'map' to 'fmap', because it
introduces two different names for the same thing (and I find the name
`fmap' awkward).

As far as I understand, this was done to make it easier to learn
Haskell, by turning errors like "Cannot discharge constraint 'Functor
X'" into "X =/= List".  I am not convinced that this motivation is
justified, although I admit that I have very limited experience with
teaching functional programming to complete beginners.  Still,
students probably run into similar problems with overloaded literals,
and I think, that a better approach to problems like these would be to
have a simplified "learning Prelude" for the beginners class, rather
than changing the standard libraries of the language (writing type
signatures probably also helps...)


This idea has been kicked around a few times, but, AFAIK, it's never  
really been fleshed out.  Has anyone ever put anything concrete on  
the table?  It seems to me that most complaints are about hard-to- 
understand error messages, and these almost always arise from  
typeclasses.  They are especially confusing when they arise from  
syntax sugar.  I suppose a prelude with no typeclasses and compiler  
options to make all syntax non-overloaded would be one way to start.


On a related note, I've seen a number of Haskell design decisions  
justified by the "beginners find it difficult" argument.  Is this  
argument really valid?  Is there any reason not to just tell  
beginners to use Helium?  Is there a case for something between  
Helium and full H98 (or H')?




Renaming 'fmap' to 'map' directly would probably break quite a bit of
code, as all instances would have to change (although it worked when
it was done the other way around, but there probably were fewer
Haskell programs then?).  We could work around this by slowly phasing
out 'fmap': for some time we could have both 'map' and 'fmap' to the
'Functor' class, with default definitions in terms of each other.  A
comment in the documentation would say that 'fmap' is deprecated.  At
some point, we could move 'fmap' out of the functor class, and even
later we could completely remove it.

This is not a big deal, but I thought I'd mention it, if we are
considering small changes to the standard libraries.

-Iavor



Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: map and fmap

2006-08-14 Thread Jon Fairbairn
On 2006-08-14 at 12:00PDT "Iavor Diatchki" wrote:
> Hello,
> I never liked the decision to rename 'map' to 'fmap', because it
> introduces two different names for the same thing (and I find the name
> `fmap' awkward).

I strongly concur. There are far too many maps even without
that, and having two names for the same thing adds to the
confusion.

> As far as I understand, this was done to make it easier to learn
> Haskell, by turning errors like "Cannot discharge constraint 'Functor
> X'" into "X =/= List".  I am not convinced that this motivation is
> justified, although I admit that I have very limited experience with
> teaching functional programming to complete beginners.  Still,
> students probably run into similar problems with overloaded literals,
> and I think, that a better approach to problems like these would be to
> have a simplified "learning Prelude"

Agreed.

-- 
Jón Fairbairn  Jon.Fairbairn at cl.cam.ac.uk


___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


map and fmap

2006-08-14 Thread Iavor Diatchki

Hello,
I never liked the decision to rename 'map' to 'fmap', because it
introduces two different names for the same thing (and I find the name
`fmap' awkward).

As far as I understand, this was done to make it easier to learn
Haskell, by turning errors like "Cannot discharge constraint 'Functor
X'" into "X =/= List".  I am not convinced that this motivation is
justified, although I admit that I have very limited experience with
teaching functional programming to complete beginners.  Still,
students probably run into similar problems with overloaded literals,
and I think, that a better approach to problems like these would be to
have a simplified "learning Prelude" for the beginners class, rather
than changing the standard libraries of the language (writing type
signatures probably also helps...)

Renaming 'fmap' to 'map' directly would probably break quite a bit of
code, as all instances would have to change (although it worked when
it was done the other way around, but there probably were fewer
Haskell programs then?).  We could work around this by slowly phasing
out 'fmap': for some time we could have both 'map' and 'fmap' to the
'Functor' class, with default definitions in terms of each other.  A
comment in the documentation would say that 'fmap' is deprecated.  At
some point, we could move 'fmap' out of the functor class, and even
later we could completely remove it.

This is not a big deal, but I thought I'd mention it, if we are
considering small changes to the standard libraries.

-Iavor
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: All Monads are Functors

2006-08-14 Thread Iavor Diatchki

Hello,
I know we have discussed this before, I am just posting this so that
it does not appear that the "community" does not care.  Here is a
summary of why I think Functor should be a super class of Monad.  The
extra code that a programmer would have to write is very small:


instance Functor MyMonad where fmap f m = do { x <- m; return (f x) }
(or use liftM)


Furthermore, I don't think I have defined a new monad for ages,
instead I use a library which already has all the necessary instances.

The benefit of having Functor as a super class of Monad shows up in
polymorhic code: we can reduce contexts like '(Functor m, Monad m)' to
just 'Monad m'.  Currently I sometimes use 'liftM' (or the 'do' form
like above) instead of using 'fmap' just to avoid having the extra
constraints, which probably makes my code less readable.

-Iavor

On 8/13/06, Lennart Augustsson <[EMAIL PROTECTED]> wrote:

If I remember right, Functor was a superclass of Monad in Haskell
early on, but it was taken away.  I think this was the wrong
decision, but I seem to remember that the rationale was that it would
be too onerous to require programmers to write a Functor instance
every time they want a Monad instance.  Bah!

-- Lennart

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: All Monads are Functors

2006-08-14 Thread John Meacham
On Mon, Aug 14, 2006 at 12:02:58AM -0500, Taral wrote:
> In my opinion, an instance definition of a subclass should allow the
> superclass's methods to be defined as if they were part of the
> subclass, e.g.:
> 
> instance Monad [] where
>fmap = map
>return x = [x]
>join = concat
> 
> It's so pretty! (But a little inefficient. You'd probably want to
> define ap/lift2 in there.)

This is actually a big can of worms to allow despite looking simple at
first. it was discussed during the class aliases thread.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re[4]: All Monads are Functors

2006-08-14 Thread Bulat Ziganshin
Hello Taral,

Monday, August 14, 2006, 3:34:29 PM, you wrote:

> On 8/14/06, Jon Fairbairn <[EMAIL PROTECTED]> wrote:
>> of course, there's no reason to do that, but what I'm
>> proposing is that we allow default instance declarations in
>> class declarations in much the same way as default methods:

> I just realized that default superclass methods have a small problem:

> module A contains instance Monad []
> module B contains instance Functor []
> module C imports A and B.

> Do we complain about a duplicate instance declarations?

yes. after all, this is just syntax sugar of giving both declarations:

instance Monad [] where
  fmap = map
  return = (:[])

is equivalent to

instance Functor [] where
  fmap = map

instance Monad [] where
  return = (:[])


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Re[2]: All Monads are Functors

2006-08-14 Thread Taral

On 8/14/06, Jon Fairbairn <[EMAIL PROTECTED]> wrote:

of course, there's no reason to do that, but what I'm
proposing is that we allow default instance declarations in
class declarations in much the same way as default methods:


I just realized that default superclass methods have a small problem:

module A contains instance Monad []
module B contains instance Functor []
module C imports A and B.

Do we complain about a duplicate instance declarations? If not, does
the use of fmap in A use the default definition, or the one from B?

--
Taral <[EMAIL PROTECTED]>
"You can't prove anything."
   -- Gödel's Incompetence Theorem
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


allow to give default implementatoions for methods of base class

2006-08-14 Thread Bulat Ziganshin
Hello Jon,

Monday, August 14, 2006, 1:49:58 PM, you wrote:

>> > instance Monad [] where
>> > fmap = map
>> > return x = [x]
>> > join = concat
>> 
>> i support this idea. [...]

> I'm not sure it's quite right. Surely it only makes sense if
> it defines all the (necessary) superclass methods -- in
> other words, what you are doing is defining an instance,
> just omitting the "instance Functor []" line, which doesn't
> seem like a great advantage.

This shrinks size of code that is especially important when writing
a lot of small instances. second, it allows me to think that all the
methods belongs to the same class instead of specifying each and every class:

class Show s => Stream s where
  sTell :: ..
class Stream s => OutputStream s where
  sPutChar :: ..

instance Show s where
  show = ..
instance Stream s where
  sTell = ..
instance OutputStream s where
  sPutChar = ..

i might prefer to write just

instance OutputStream s where
  sPutChar = ..
  sTell = ..
  show = ..

- and as you can see i also changed the ordering/grouping of
operations. of course it's just syntax sugar, but i like it - it will
shrink class declarations and bring them closer to OOP style when
derived class also "owns" all the methods of base classes


> If we are going to play around
> with this stuff, here's another suggestion that solves my
> original problem more neatly:

> In a class declaration, a superclass context is a
> requirement that instances of the class have instances of
> the superclass; this is similar to the type declarations of
> the methods. We could have had

> class Monad m where
>   instance Functor m
>   (>>=):: ...

> instead of

> class Functor m => Monad m where
>   (>>=):: ...

> of course, there's no reason to do that, but what I'm
> proposing is that we allow default instance declarations in
> class declarations in much the same way as default methods:

>> class Functor m => Monad m where

i think, you mean:

>> class Monad m where
>>   instance Functor m where
>>fmap f =  (>>= return . f)
>>   (>>=):: ...
>>   return:: ...
>>   join:: ...

i support this too. but bringing these two ideas together the class
declaration should look as

class Functor m => Monad m where
  fmap f =  (>>= return . f)
  (>>=):: ...
  return:: ...
  join:: ...

and instance declaration should be:

instance Monad [] where
fmap = map
return x = [x]
join = concat

instead of:

> instance Monad [] where
> return x = [x]
> join = concat
> instance Functor [] where
>  fmap = map

this proposal should be named as subj, independent of syntax form used

--
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Re[2]: All Monads are Functors

2006-08-14 Thread Jon Fairbairn
On 2006-08-14 at 12:03+0400 Bulat Ziganshin wrote:
> Hello Taral,
> 
> Monday, August 14, 2006, 9:02:58 AM, you wrote:
> 
> > In my opinion, an instance definition of a subclass should allow the
> > superclass's methods to be defined as if they were part of the
> > subclass, e.g.:
> 
> > instance Monad [] where
> > fmap = map
> > return x = [x]
> > join = concat
> 
> i support this idea. [...]

I'm not sure it's quite right. Surely it only makes sense if
it defines all the (necessary) superclass methods -- in
other words, what you are doing is defining an instance,
just omitting the "instance Functor []" line, which doesn't
seem like a great advantage. If we are going to play around
with this stuff, here's another suggestion that solves my
original problem more neatly:

In a class declaration, a superclass context is a
requirement that instances of the class have instances of
the superclass; this is similar to the type declarations of
the methods. We could have had

class Monad m where
  instance Functor m
  (>>=):: ...

instead of

class Functor m => Monad m where
  (>>=):: ...

of course, there's no reason to do that, but what I'm
proposing is that we allow default instance declarations in
class declarations in much the same way as default methods:

> class Functor m => Monad m where
>   (>>=):: ...
>   return:: ...
>   join:: ...
>   instance Functor m where
>fmap f =  (>>= return . f)

This shouldn't be hard to implement: all the compiler has to
do when reading an instance declaration for Monad is to
generate an instance declaration for Functor, substituting
the espression for m that comes from the instance
declaration for Monad.

I don't know whether there's anything to be gained by adding
the option of overriding the default inside an instance
declaration:

> instance Monad [] where
> return x = [x]
> join = concat
> instance Functor [] where
>  fmap = map


but clearly a top-level instance declaration would override
the default anyway.



-- 
Jón Fairbairn  Jon.Fairbairn at cl.cam.ac.uk


___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re[2]: All Monads are Functors

2006-08-14 Thread Bulat Ziganshin
Hello Taral,

Monday, August 14, 2006, 9:02:58 AM, you wrote:

> In my opinion, an instance definition of a subclass should allow the
> superclass's methods to be defined as if they were part of the
> subclass, e.g.:

> instance Monad [] where
> fmap = map
> return x = [x]
> join = concat

i support this idea. in my Streams library i forced now to group and
order function definitions according to type classes to which they are
split




-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime