Re: [Haskell-cafe] The container problem

2008-09-29 Thread Albert Y. C. Lai

Andrew Coppin wrote:

Seriously, that sounded like gibberish.


Please don't say that.

I think we are too polite to rudeness.

While we shouldn't condemn people to "RTFM", we shouldn't tolerate 
people calling us "gibberish" either. I mean unless we say something 
objectively gibberish.


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


Re: [Haskell-cafe] The container problem

2008-09-28 Thread David Menendez
On Sat, Sep 27, 2008 at 9:24 AM, Andrew Coppin
<[EMAIL PROTECTED]> wrote:
> David Menendez wrote:
>>
>> I wouldn't say that. It's important to remember that Haskell class
>> Monad does not, and can not, represent *all* monads, only (strong)
>> monads built on a functor from the category of Haskell types and
>> functions to itself.
>>
>> Data.Set is a functor from the category of Haskell types *with
>> decidable ordering* and *order-preserving* functions to itself. That's
>> not the same category, although it is closely related.
>>
>
> I nominate this post for the September 2008 Most Incomprehensible Cafe Post
> award! :-D
>
> Seriously, that sounded like gibberish. (But then, you're talking to
> somebody who can't figure out the difference between a set and a class,
> so...)

Sorry about that. I was rushing out the door at the time.

> All I know is that sometimes I write stuff in the list monad when the result
> really ought to be *sets*, not lists, because
>
> 1. there is no senamically important ordering
>
> 2. there should be no duplicates
>
> But Haskell's type system forbids me. (It also forbids me from making Set
> into a Functor, actually... so no fmap for you!)

I understand your frustration. The point that I was trying to make is
that this isn't just some arbitrary limitation in Haskell's type
system. Data.Set and [] can both be thought of as monads, but they
aren't the same kind of monad.



Incidentally, there are other ways to simulate a set monad. Depending
on your usage pattern, you may find this implementation preferable to
using the list monad:

> {-# LANGUAGE PolymorphicComponents #-}
>
> import Control.Monad
> import qualified Data.Set as Set
> type Set = Set.Set
>
> newtype SetM a = SetM { unSetM :: forall b. (Ord b) => (a -> Set b) -> Set b }
>
> toSet :: (Ord a) => SetM a -> Set a
> toSet m = unSetM m Set.singleton
>
> fromSet :: (Ord a) => Set a -> SetM a
> fromSet s = SetM (\k -> Set.unions (map k (Set.toList s)))
>
> instance Monad SetM where
>   return a = SetM (\k -> k a)
>   m >>= f  = SetM (\k -> unSetM m (\a -> unSetM (f a) k))
>   
> instance MonadPlus SetM where
>   mzero = SetM (\_ -> Set.empty)
>   mplus m1 m2 = SetM (\k -> Set.union (unSetM m1 k) (unSetM m2 k))

It will still duplicate work. For example, if you write,

return x `mplus` return x >>= f

then "f x" will get evaluated twice. You can minimize that by
inserting "fromSet . toSet" in strategic places.

-- 
Dave Menendez <[EMAIL PROTECTED]>

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


Re: [Haskell-cafe] The container problem

2008-09-27 Thread Ariel J. Birnbaum
> I'm not actually bothered about every possible monad being representable
> as such in Haskell. I'd just like Set to work. ;-)

What would "work" mean in this case? I see two different meanings:

1. Use monadic operations (mapM, guard) on Sets. 

 How would you decide which operations are allowed and which aren't? A 
possible answer would be: if you can add an implicit Ord constraint for every 
argument of m (where m is constrained to be a Monad), you can instantiate m 
as Set. So
  sequence :: (Monad m) => [m a] -> m [a]
would work since [a] is an instance of Ord whenever a is but
  ap :: (Monad m) => m (a -> b) -> m a -> m b
wouldn't since we can't have a (meaningful) Ord instance for a -> b even if a 
and b are themselves instances.

 Such a mechanism is, of course, broken.

 Consider the following alternative definition for liftM2:
   liftM2 :: (Monad m) => (a -> b -> c) -> m a -> m b -> m c
   liftM2 f ma mb mc = return f `ap` ma `ap` mb `ap` mc
   -- deliberately avoiding Applicative and Functor

 While the type of liftM2 indicates it should work (and the definition found 
on GHC actually does), in this case it would utterly break at the "return f" 
and the "ap"s. In other words, one can't rely on the type alone to know 
whether a monadic operation is applicable to Set. In OOP, I think they'd call 
this a violation of Liskov's Substitution Principle.

2. Make the nice monadic syntax work for sets.

 In this case I'd restate the problem as not being able to extend Haskell's 
syntax within your program (a problem shared by most non-Lisp languages). 
While TH provides a fairly decent solution in this respect, it's still far 
from Lisp's flexibility. In this respect, does anyone know how the Liskell 
project is doing? The site and mailing list seem pretty silent...

-- 
Ariel J. Birnbaum
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] The container problem

2008-09-27 Thread Bulat Ziganshin
Hello Andrew,

Saturday, September 27, 2008, 9:23:47 PM, you wrote:

> Can anybody actually demonstrate concretely how FDs and/or ATs would
> solve this problem? (I.e., enable you to write a class that any 
> container can be a member of, despite constraints on the element types.)

you may find comprehensive explanation in ghc user manual, it's
chapter about FDs use this as motivating example :)


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] The container problem

2008-09-27 Thread Matthieu Sozeau


Le 27 sept. 08 à 15:24, Andrew Coppin a écrit :


David Menendez wrote:


I wouldn't say that. It's important to remember that Haskell class
Monad does not, and can not, represent *all* monads, only (strong)
monads built on a functor from the category of Haskell types and
functions to itself.

Data.Set is a functor from the category of Haskell types *with
decidable ordering* and *order-preserving* functions to itself.  
That's

not the same category, although it is closely related.



I nominate this post for the September 2008 Most Incomprehensible  
Cafe Post award! :-D


Seriously, that sounded like gibberish. (But then, you're talking to  
somebody who can't figure out the difference between a set and a  
class, so...)


All I know is that sometimes I write stuff in the list monad when  
the result really ought to be *sets*, not lists, because


1. there is no senamically important ordering

2. there should be no duplicates

But Haskell's type system forbids me. (It also forbids me from  
making Set into a Functor, actually... so no fmap for you!)


Think about it this way: fmap is supposed to be an homomorphism on the  
functor's structure, it just changes the type of the holes in the  
structure. To implement such map function in Set (not debating if Set  
should require Ord or not here!) and keep the structure invariants,  
the function you give to map should be order-preserving. Actually,  
Set.map accepts any function but it must construct the new Set using a  
fold behind the scenes because otherwise the function may break the  
internal balancing invariants. But map_monotonous is there for the  
case where it does respect the orders and the map can be done much  
more naturally and efficiently.


There's simply no way to state that a function must be monotonous  
using haskell's limited type system. except by using a new datatype  
that represents only the order-preserving functions between any two  
types A and B (is that even possible?). So you only see the [Ord]  
constraint getting in the way of defining a functor on Sets, but it's  
more profound than that, the functions themselves don't fit exactly.


Otherwise, to implement Sets correctly I think you need at least [Eq]  
(and give [Eq] preserving functions to fmap).
You can certainly declare a new EqFunctor (f : * -> *) where eqfmap :  
Eq a, Eq b => (a -> b) -> f a -> f b and assume that functions are  
[Eq]-preserving there (similarly with [Ord]).


Hope this helps,
-- Matthieu___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] The container problem

2008-09-27 Thread Antoine Latter
On Sat, Sep 27, 2008 at 12:23 PM, Andrew Coppin
<[EMAIL PROTECTED]> wrote:
>
> Can anybody actually demonstrate concretely how FDs and/or ATs would solve
> this problem? (I.e., enable you to write a class that any container can be a
> member of, despite constraints on the element types.)
>

Sure!  Using type-families:

> class Container c where
>type Elem c
>insert :: Elem c -> c -> c

> instance Container [a] where
>type Elem [a] = a
>insert = (:)

> instance Container ByteString where
>type Elem ByteString = Word8
>insert = BS.cons

> instance Ord a => Container (Set a) where
>type Elem (Set a) = a
>insert = Set.insert

In GHCi:

> :t insert
insert :: forall c. (Container c) => Elem c -> c -> c

Now the hard part is coming up with a proper API and class hierarchy.

-Antoine
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] The container problem

2008-09-27 Thread Andrew Coppin

Albert Y. C. Lai wrote:

Andrew Coppin wrote:
If I understand this correctly, to solve this problem you need either 
Functional Dependencies or Associated Types. Is that correct?


A motivating example in papers on FD is exactly typeclasses for 
containers. Okasaki puts this into practice in the Edison library. 
Despite its comprehensiveness, elegance, and the Okasaki name brand, 
it did not become mainstream. I don't know why.


Can anybody actually demonstrate concretely how FDs and/or ATs would 
solve this problem? (I.e., enable you to write a class that any 
container can be a member of, despite constraints on the element types.)


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


Re: [Haskell-cafe] The container problem

2008-09-27 Thread Andrew Coppin

Brandon S. Allbery KF8NH wrote:

On 2008 Sep 27, at 12:41, Andrew Coppin wrote:
I'm not sure how that qualifies set as "not really a true monad 
anyway" - but then, I don't know what a monad is, originally. I only 
know what it means in Haskell.


I think you read him backwards:  Map and Set are category-theory 
("true") monads, but they can't be Haskell Monads because Haskell 
isn't expressive enough to represent more than a subset of 
category-theoretical monads.


Ah, OK. That makes more sense then...

What (if anything) do we do about that?

I'm not actually bothered about every possible monad being representable 
as such in Haskell. I'd just like Set to work. ;-)



Also... Who or what is an Oleg, and why do I keep hearing about it? ;-)


Oleg Kiselyov.  http://okmij.org/ftp/
He's somewhat legendary in the Haskell community for his ability to 
make Haskell do what people think it can't, and his tendency to 
program at the type level instead of at the value level like most 
people.  :)


Ah - so the "Prolog programs as type signatures" thing is *his* fault?! ;-)

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


Re: [Haskell-cafe] The container problem

2008-09-27 Thread Brandon S. Allbery KF8NH

On 2008 Sep 27, at 12:41, Andrew Coppin wrote:
I'm not sure how that qualifies set as "not really a true monad  
anyway" - but then, I don't know what a monad is, originally. I only  
know what it means in Haskell.


I think you read him backwards:  Map and Set are category-theory  
("true") monads, but they can't be Haskell Monads because Haskell  
isn't expressive enough to represent more than a subset of category- 
theoretical monads.


Also... Who or what is an Oleg, and why do I keep hearing about  
it? ;-)


Oleg Kiselyov.  http://okmij.org/ftp/
He's somewhat legendary in the Haskell community for his ability to  
make Haskell do what people think it can't, and his tendency to  
program at the type level instead of at the value level like most  
people.  :)


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] The container problem

2008-09-27 Thread Andrew Coppin

Brandon S. Allbery KF8NH wrote:

On 2008 Sep 27, at 9:24, Andrew Coppin wrote:
I nominate this post for the September 2008 Most Incomprehensible 
Cafe Post award! :-D


Seriously, that sounded like gibberish. (But then, you're talking to 
somebody who can't figure out the difference between a set and a 
class, so...)


That response required a certain amount of category theory to grok.


No kidding. ;-)

When you have a typeclass, the constraints (that is, the (Foo a =>) 
contexts) on it are the exact constraints on members of the class.  
You can't add more or leave some out.


Set and Map both require an additional constraint over those of 
Functor and Monad:  (Ord a =>).  Since you can't add constraints on 
top of a typeclass, you can't make them members of Functor or Monad.  
(Unless you use some Oleg-style hackery.)


Yes. This I understand. And ByteString constrains the element type to 
just Word8. Or Char, depending which one you use. And in principle other 
containers might exist with other constraints. (E.g., hashtables require 
hash functions.)


I'm not sure how that qualifies set as "not really a true monad anyway" 
- but then, I don't know what a monad is, originally. I only know what 
it means in Haskell.


Also... Who or what is an Oleg, and why do I keep hearing about it? ;-)

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


Re: [Haskell-cafe] The container problem

2008-09-27 Thread Brandon S. Allbery KF8NH

On 2008 Sep 27, at 9:24, Andrew Coppin wrote:

David Menendez wrote:

I wouldn't say that. It's important to remember that Haskell class
Monad does not, and can not, represent *all* monads, only (strong)
monads built on a functor from the category of Haskell types and
functions to itself.

Data.Set is a functor from the category of Haskell types *with
decidable ordering* and *order-preserving* functions to itself.  
That's

not the same category, although it is closely related.


I nominate this post for the September 2008 Most Incomprehensible  
Cafe Post award! :-D


Seriously, that sounded like gibberish. (But then, you're talking to  
somebody who can't figure out the difference between a set and a  
class, so...)


That response required a certain amount of category theory to grok.

When you have a typeclass, the constraints (that is, the (Foo a =>)  
contexts) on it are the exact constraints on members of the class.   
You can't add more or leave some out.


Set and Map both require an additional constraint over those of  
Functor and Monad:  (Ord a =>).  Since you can't add constraints on  
top of a typeclass, you can't make them members of Functor or Monad.   
(Unless you use some Oleg-style hackery.)


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] The container problem

2008-09-27 Thread Andrew Coppin

David Menendez wrote:


I wouldn't say that. It's important to remember that Haskell class
Monad does not, and can not, represent *all* monads, only (strong)
monads built on a functor from the category of Haskell types and
functions to itself.

Data.Set is a functor from the category of Haskell types *with
decidable ordering* and *order-preserving* functions to itself. That's
not the same category, although it is closely related.
  


I nominate this post for the September 2008 Most Incomprehensible Cafe 
Post award! :-D


Seriously, that sounded like gibberish. (But then, you're talking to 
somebody who can't figure out the difference between a set and a class, 
so...)


All I know is that sometimes I write stuff in the list monad when the 
result really ought to be *sets*, not lists, because


1. there is no senamically important ordering

2. there should be no duplicates

But Haskell's type system forbids me. (It also forbids me from making 
Set into a Functor, actually... so no fmap for you!)




PS. Text is unpredictable, so just in case... If this post sounds like a 
flame, it isn't meant to be. ;-)


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


Re: [Haskell-cafe] The container problem

2008-09-26 Thread Derek Elkins
On Fri, 2008-09-26 at 22:37 +0100, Andrew Coppin wrote:
> Derek Elkins wrote:
> > One aspect of it is a bit of a You Aren't Going To Need It.
> >   
> 
> Personally, I haven't had a huge problem with this in practice.

I suspected as much.  Personally I'd recomend worrying about the
problems you actually encounter, rather than worrying about problems
that maybe you'll have later.  Solving problems that you don't have
isn't very gratifying for you.

> > Finally, there -are- several more or less standard classes that capture
> > different general operations on data structures (though there certainly
> > could be more.) They, of course, have different names and different
> > interfaces and different factorings from imperative equivalents.  We
> > have Functor, Applicative, Monad, MonadPlus, Monoid, Foldable,
> > Traversable, IArray, MArray and others.  Notice how the ridiculous
> > proliferation of array types in Haskell has pressed the issue and led to
> > the creation of IArray and MArray.
> >   
> 
> As already noted, Data.Set *should* be a Monad, but can't be. 

No it shouldn't.  Data.Set forms a categorical monad but not one over
Haskell which is what the Monad class expresses.  Data.Set doesn't meet
the interface of Monad and doesn't provide the same guarantees.
Incidentally, Java would have the same problem if it was capable of
expressing something equivalent to the Monad type class; the "issue" is
with parametric polymorphism not type classes. So unsurprisingly the
type system is right because, in my opinion, parametricity is a property
to valuable to lose.  This does have the effect, however, that join
corresponds to the useful function unions with it's same definition only
using different "monad" operations.  Note that, for this particular
example there is a beautiful solution.  We don't really need to take the
union of a -Set- of Sets, all we need to be able to do is traverse the
outer structure.  Taking a hint from my previous reply, we could
specialize to lists and we would end up with mconcat from the Data.Set
instance of Data.Monoid.  If we didn't feel like imposing the conversion
to lists on the user we could write combine = mconcat . toList.
Conveniently, Data.Foldable has a generic toList function, however, even
more conveniently the function we're looking for is simply
Data.Foldable.fold.

> The type 
> system won't allow it. (And I know I'm not the first person to notice 
> this...) Similar fun and frolics with Functor, and presumably 
> Applicative and Foldable (I haven't actually heard of these until just now).
> 
> Frankly, the whole "array" thing is slightly crazy to me. There are 
> several things which the array libraries ought to support, but don't:


> - Making "slices" of arrays. (I.e., generating a subarray in O(1) by 
> using transparent reindexing.)
> - Linked lists of arrays that provide an array-like interface. 
> (ByteString.Lazy does this, but only for Word8 or Char.)
> - It really ought to be possible to unbox *any* type. Technically this 
> is implementable now, but I can't find details of how...
> - Performing "map" in-place for mutable arrays. (This must surely be a 
> very common operation.)
> - Build-in functions for joining arrays together, and splitting at a 
> given index.
> - Array sorting. [Arrays have O(1) indexing, which has big implications 
> for what sorting algorithm to choose.]
> - Lists have about 5,000,000 functions for processing them. Arrays have, 
> like, a dozen. Just how efficient is it to convert an array to a list, 
> process it, and then convert it back?

With the exception of slicing, none of these are interface issues and
thus are irrelevant to the topic of this thread.  All the functions you
want can be implemented with reasonable efficiency and correct
asymptotic complexity in terms of the provided interface.  Whether these
functions are in the standard library or not has no effect on the
contractual obligations between chunks of code.  Slicing can't be
implemented with the correct asymptotic behaviour in terms of these
operations.  So then it comes down to a cost/benefit analysis of whether
the cost of adding it to the interface is justified by the benefits of
being able to slice generically.  In this case, I think the scales tilt
in favor of adding such support.


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


Re: [Haskell-cafe] The container problem

2008-09-26 Thread Don Stewart
bulat.ziganshin:
> Hello Andrew,
> 
> Saturday, September 27, 2008, 1:37:12 AM, you wrote:
> 
> answering your questions
> 
> 1) there is 2 libs providing common Java-like interfaces to
> containers: Edison and Collections. almost noone uses it
> 
> 2) having common type class for various things is most important when
> you write library that whould be able to deal with any if these
> things. when you just write application program, having the same
> interface plus ability to change imports in most cases are enough. and
> such meta-libraries are rather rare in Haskell world
> 
> 3) as laready said, we have classes for traversing containers that
> probably covers most of usage scenarios for Java too
> 
> now about arrays - they are much less used in Haskell than in
> imperative languages, especially mutable ones. to some degree, you may
> use parallel arrays, which are still informally supported, to some
> degree you may add required operations yourself (array package is
> pretty basic), and for some of your operations you need to provide
> more advanced array datastructure supporting slicing. try to use lists
> when something you need cannot be implemented with arrays. of my
> 10kloc "realworld" program, i had only one place when arrays are used

Bulat, have you looked at any of the newer array libraries, such as
uvector, vector, carray or hmatrix?

I'd be interested what you think of them. Especially uvector's
interface.

-- Don
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] The container problem

2008-09-26 Thread Dan Weston
More specifically, although a set is a perfectly good (lowercase) 
functor, Set is not a (Haskell) Functor.


Set's map has an Ord constraint, but the Functor type constructor is 
parametric over *all* types, not just that proper subset of them that 
have a total ordering.


But see attempts to fix this:

http://okmij.org/ftp/Haskell/types.html#restricted-datatypes
http://www.randomhacks.net/articles/2007/03/15/data-set-monad-haskell-macros

Dan

Jonathan Cast wrote:

On Fri, 2008-09-26 at 15:25 -0700, Jason Dusek wrote:

Can someone explain, why is it that Set can not be a Monad?


It can't even be a functor (which all monads are).  You can't implement

fmap (+) $ Set.fromList [1, 2, 3]

with Data.Set, because you can't order functions of type Integer ->
Integer in a non-arbitrary way.  So you can't have a balanced binary
tree of them in a non-arbitrary way, either.  Something like

fmap putStrLn $ Set.fromList ["Hello", "world"]

is similar.

Since Data.Set is implemented in Haskell, it can only use facilities
available to Haskell libraries.  So it can't work for arbitrary
elements; but a Functor instance requires that it does work.


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


Re[2]: [Haskell-cafe] The container problem

2008-09-26 Thread Bulat Ziganshin
Hello Andrew,

Saturday, September 27, 2008, 1:37:12 AM, you wrote:

answering your questions

1) there is 2 libs providing common Java-like interfaces to
containers: Edison and Collections. almost noone uses it

2) having common type class for various things is most important when
you write library that whould be able to deal with any if these
things. when you just write application program, having the same
interface plus ability to change imports in most cases are enough. and
such meta-libraries are rather rare in Haskell world

3) as laready said, we have classes for traversing containers that
probably covers most of usage scenarios for Java too

now about arrays - they are much less used in Haskell than in
imperative languages, especially mutable ones. to some degree, you may
use parallel arrays, which are still informally supported, to some
degree you may add required operations yourself (array package is
pretty basic), and for some of your operations you need to provide
more advanced array datastructure supporting slicing. try to use lists
when something you need cannot be implemented with arrays. of my
10kloc "realworld" program, i had only one place when arrays are used

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] The container problem

2008-09-26 Thread Jonathan Cast
On Fri, 2008-09-26 at 15:25 -0700, Jason Dusek wrote:
> Can someone explain, why is it that Set can not be a Monad?

It can't even be a functor (which all monads are).  You can't implement

fmap (+) $ Set.fromList [1, 2, 3]

with Data.Set, because you can't order functions of type Integer ->
Integer in a non-arbitrary way.  So you can't have a balanced binary
tree of them in a non-arbitrary way, either.  Something like

fmap putStrLn $ Set.fromList ["Hello", "world"]

is similar.

Since Data.Set is implemented in Haskell, it can only use facilities
available to Haskell libraries.  So it can't work for arbitrary
elements; but a Functor instance requires that it does work.

jcc


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


Re: [Haskell-cafe] The container problem

2008-09-26 Thread Jason Dusek
  Can someone explain, why is it that Set can not be a Monad?

--
_jsn
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] The container problem

2008-09-26 Thread David Menendez
On Fri, Sep 26, 2008 at 5:37 PM, Andrew Coppin
<[EMAIL PROTECTED]> wrote:
>
> As already noted, Data.Set *should* be a Monad, but can't be. The type
> system won't allow it. (And I know I'm not the first person to notice
> this...)

I wouldn't say that. It's important to remember that Haskell class
Monad does not, and can not, represent *all* monads, only (strong)
monads built on a functor from the category of Haskell types and
functions to itself.

Data.Set is a functor from the category of Haskell types *with
decidable ordering* and *order-preserving* functions to itself. That's
not the same category, although it is closely related.

-- 
Dave Menendez <[EMAIL PROTECTED]>

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


Re: [Haskell-cafe] The container problem

2008-09-26 Thread Andrew Coppin

Derek Elkins wrote:

One aspect of it is a bit of a You Aren't Going To Need It.
  


Personally, I haven't had a huge problem with this in practice.

What it basically means is that if you write a library function, *you* 
have to decide what containers you're going to use. It's not really 
possible to let the user decide. You kind of have to hard-wire it 
yourself. That's the only real problem with it. Sometimes it's 
irritating to convert an array to a list, feed it to some function, and 
then immediately convert it back to an array again, for example. (Not 
only annoying, but presumably not that efficient.)



Another reason is that often you can use an intermediate data structure,
especially lists, for operations.  Lists are the
iterators/IEnumerable/generators of Haskell.  So if I just need to
traverse a data structure, I can just write an interface that accepts a
list.
  


This is the other part of it. In Haskell, a list in some sense "is" a 
control-flow loop. If the compiler's inlining is half as good as it's 
supposed to be, converting an array to a list and then feeding it to 
some function hopefully ends up being inlined so that you end up with 
the function directly iterating over the array. Hopefully the function's 
output ends up being similar. So it's not like you build a while list in 
memory and then consume it. It's not even like the GC has to go round 
and free all the list cells. The list itself never actually exists as 
such at runtime.


Alternatively, I'm talking complete nonesense... o_O


Of course, since Haskell isn't Java, I'm not subject to the choice of
interfaces the data structure implementer decided to implement or not.
When this happens in Java the "standard" solution is to use an adapter
class.  In Haskell, I can just write the instance.  In particular, I can
decide on whatever interface I need, write my code to that interface and
just instantiate it for the relevant data types and users can
instantiate it for their data types.  If you want an OrderableCollection
class, you can simply write one today.  You don't need to ask anyone's
permission or coordinate with anyone.
  


Haskell class membership is "open" in this way - a useful feature, IMHO.


Finally, there -are- several more or less standard classes that capture
different general operations on data structures (though there certainly
could be more.) They, of course, have different names and different
interfaces and different factorings from imperative equivalents.  We
have Functor, Applicative, Monad, MonadPlus, Monoid, Foldable,
Traversable, IArray, MArray and others.  Notice how the ridiculous
proliferation of array types in Haskell has pressed the issue and led to
the creation of IArray and MArray.
  


As already noted, Data.Set *should* be a Monad, but can't be. The type 
system won't allow it. (And I know I'm not the first person to notice 
this...) Similar fun and frolics with Functor, and presumably 
Applicative and Foldable (I haven't actually heard of these until just now).


Frankly, the whole "array" thing is slightly crazy to me. There are 
several things which the array libraries ought to support, but don't:
- Making "slices" of arrays. (I.e., generating a subarray in O(1) by 
using transparent reindexing.)
- Linked lists of arrays that provide an array-like interface. 
(ByteString.Lazy does this, but only for Word8 or Char.)
- It really ought to be possible to unbox *any* type. Technically this 
is implementable now, but I can't find details of how...
- Performing "map" in-place for mutable arrays. (This must surely be a 
very common operation.)
- Build-in functions for joining arrays together, and splitting at a 
given index.
- Array sorting. [Arrays have O(1) indexing, which has big implications 
for what sorting algorithm to choose.]
- Lists have about 5,000,000 functions for processing them. Arrays have, 
like, a dozen. Just how efficient is it to convert an array to a list, 
process it, and then convert it back?



Ultimately, it would still be beneficial to have some more standard
interfaces for this sort of thing.  There just hasn't been enough of a
fire under the community's rear.  This again suggests that YAGNI.
  


I see... ;-)

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


Re: [Haskell-cafe] The container problem

2008-09-26 Thread Derek Elkins
On Fri, 2008-09-26 at 19:15 +0100, Andrew Coppin wrote:
> Take a look around you. Haskell provides several sorts of container. We 
> have:
> 
>   Data.List
>   Data.Set
>   Data.Map
>   Data.Hashtable
>   Data.ByteString
>   Data.Sequence
>   Data.Array
>   Data.Tree
>   Data.IntSet
>   Data.IntMap
>   ...
> 
> In other words, we have *a lot* of different data containers. And yet, 
> each one provides its own unique API.
> 
> To anybody used to OO languages, that sounds pretty crazy. In something 
> like Java or Smalltalk or Eiffel, you have an abstract class that 
> represents "container", and maybe a seperate one for "ordered 
> container", and then concrete subclasses for each kind of container. 
> Each one may add a few unique methods of its own, but basically all the 
> containers have a uniform API, and you can write functions that work for 
> any arbitrary [ordered] container.
> 
> In Haskell, you can't do this. Why is that?

Obviously you certainly can.  That there isn't a "standard" form is in
my opinion not really historical or limitations of H98, though there are
certainly some aspect of those.  You can do a not horrible job in just
H98.  You can do a much better job using common extensions (and yes, in
particular MPTCs and fundeps.)  As Albert Lai alluded to, you can use
Edison if you want this, right now, today.  I think the problem is again
that the Perfect Interface hasn't been found and for several reasons
which I'll enumerate, there is not a pressing desire for a reasonable
compromise.

One aspect of it is a bit of a You Aren't Going To Need It.
Particularly for applications, there is usually very little gain in
practice and for Haskell many of the container libraries have identical
interface subsets so that you do end up being able to change
implementation by changing a single import.  This is further reinforced
by there being a single obvious choice for common data structures.
Admittedly, it would still be nice to be more explicit about this and to
program to interfaces, especially for library code.

Another reason is that often you can use an intermediate data structure,
especially lists, for operations.  Lists are the
iterators/IEnumerable/generators of Haskell.  So if I just need to
traverse a data structure, I can just write an interface that accepts a
list.

Of course, since Haskell isn't Java, I'm not subject to the choice of
interfaces the data structure implementer decided to implement or not.
When this happens in Java the "standard" solution is to use an adapter
class.  In Haskell, I can just write the instance.  In particular, I can
decide on whatever interface I need, write my code to that interface and
just instantiate it for the relevant data types and users can
instantiate it for their data types.  If you want an OrderableCollection
class, you can simply write one today.  You don't need to ask anyone's
permission or coordinate with anyone.

There are some general reasons too.  Typically asymptotic complexity
guarantees are considered part of the interface for a data structure.
If you do this you either end up with loose constraints that aren't very
useful or tight ones that provide nice guarantees but exclude all but a
few data structures.  This leads back to the first reason, YAGNI.  You
often have particular properties that you want and thus end up with
particular data structures.  Admittedly, you can still require tight
complexity constraints and if someone wants to violate them, the
performance problems are their fault but maybe convenience outweighs
performance in that case.  Usually, though, there are convenient
conversions between the types.

Finally, there -are- several more or less standard classes that capture
different general operations on data structures (though there certainly
could be more.) They, of course, have different names and different
interfaces and different factorings from imperative equivalents.  We
have Functor, Applicative, Monad, MonadPlus, Monoid, Foldable,
Traversable, IArray, MArray and others.  Notice how the ridiculous
proliferation of array types in Haskell has pressed the issue and led to
the creation of IArray and MArray.

Ultimately, it would still be beneficial to have some more standard
interfaces for this sort of thing.  There just hasn't been enough of a
fire under the community's rear.  This again suggests that YAGNI.

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


Re: [Haskell-cafe] The container problem

2008-09-26 Thread Albert Y. C. Lai

Andrew Coppin wrote:
If I understand this correctly, to solve this problem you need either 
Functional Dependencies or Associated Types. Is that correct?


A motivating example in papers on FD is exactly typeclasses for 
containers. Okasaki puts this into practice in the Edison library. 
Despite its comprehensiveness, elegance, and the Okasaki name brand, it 
did not become mainstream. I don't know why.

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


[Haskell-cafe] The container problem

2008-09-26 Thread Andrew Coppin
Take a look around you. Haskell provides several sorts of container. We 
have:


 Data.List
 Data.Set
 Data.Map
 Data.Hashtable
 Data.ByteString
 Data.Sequence
 Data.Array
 Data.Tree
 Data.IntSet
 Data.IntMap
 ...

In other words, we have *a lot* of different data containers. And yet, 
each one provides its own unique API.


To anybody used to OO languages, that sounds pretty crazy. In something 
like Java or Smalltalk or Eiffel, you have an abstract class that 
represents "container", and maybe a seperate one for "ordered 
container", and then concrete subclasses for each kind of container. 
Each one may add a few unique methods of its own, but basically all the 
containers have a uniform API, and you can write functions that work for 
any arbitrary [ordered] container.


In Haskell, you can't do this. Why is that?

To me, it seems that there are two sticking points:

1. Historical reasons.

2. The Haskell '98 type system.

(1) is obviously solvable. (2) is harder.

Some containers can contain *any* type of data. Haskell permits 
parametric polymorphism, so this is no problem:


 Data.List.map :: (a -> b) -> [a] -> [b]

Other containers only support *one* type of data:

 Data.ByteString.Char8.map :: (Char -> Char) -> ByteString -> ByteString

The type has a different kind, and the function parameter's type is more 
constrained. Yet still this poses no problem.


However... now try writing a class that both of these functions could be 
methods of. Good luck with that, by the way...


This is AFAIK also the reason why, e.g., Set is *not* an instance of 
Monad; you can't write a valid instance. The type checker won't have it.


To ears accustomed to the OO way, all this makes it sound like Haskell's 
type system sucks. (Which is rich, because in half the OO languages, you 
can't write a type-safe container that works for arbitrary element types 
in the first place! Haskell is a Big Win here.)


If I understand this correctly, to solve this problem you need either 
Functional Dependencies or Associated Types. Is that correct?


I also gather that "FDs have problems" - although I have no idea what 
those problems are. Everybody's hoping that ATs will fix this, but ATs 
are still kinda new. (Are they even fully implemented in GHC yet?)


Can anybody correct/expand on this state of affires? I just want to make 
sure I understand our position correctly...


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