Re: [Haskell-cafe] Re: The Proliferation of List-Like Types

2008-02-20 Thread Neil Mitchell
Hi

 full - Maybe (item, full)

  Hrm, what exactly is the return data here?  Is is the head and the
  tail if the list has = 1 item, or Nothing otherwise?  Or...?

Yes, its the projection onto another type:

[] = Nothing
(x:xs) = Just (x, xs)

  What is the problem with MPTC in base?

MPTC is not a part of any Haskell standard. The rules surrounding MPTC
are not clear. People want to remove MPTC's/functional dependencies,
or modify them with associated types. Compilers such as nhc and yhc
can't implement them. Once they are in Haskell', with an associated
set of restrictions/overlap rules etc, then they can be freely used
with the base library.

Thanks

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


Re: [Haskell-cafe] Re: The Proliferation of List-Like Types

2008-02-20 Thread Jules Bean

John Goerzen wrote:

On 2008-02-20, John Goerzen [EMAIL PROTECTED] wrote:

I notice that Data.Foldable does some similar things but does not use
multi-parameter type classes.  I seem to recall that I attempted to do
this in the same manner, but got tripped up somewhere.  I can't
remember now exactly what the problem was, but I can go back and look
if nobody knows off-hand.


I went back and looked.

The problem is that ByteString doesn't work as a member of Foldable,
or of ListLike without it being MPTC.  Trying to do so yields:

ListLike.hs:217:20:
Kind mis-match
Expected kind `* - *', but `BS.ByteString' has kind `*'
In the instance declaration for `F.Foldable BS.ByteString'

Is there any way around that, other than MPTC?


Not directly, no.

The point about Foldable, Functor, and Monad, is that they enforce the 
connection between container and contents. If the contents is of type 
a, the container is of type f a for a fixed type constructor 'f'. 
This works for [], Seq, and so on, but fails for ByteString.


To go to the next level, for ByteString you either need type-level 
functions (to generalise 'f' from type constructor to arbitrary 
function :: * - *), or MPTCs (to make the association between 
container and contents explicit).


However, passing around dictionaries is certainly a solution which works 
in haskell98. I haven't thought it through enough to see if it would be 
unpleasantly verbose in practice.


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


Re: [Haskell-cafe] Re: The Proliferation of List-Like Types

2008-02-20 Thread Antoine Latter
On Feb 20, 2008 12:48 PM, Chad Scherrer [EMAIL PROTECTED] wrote:
  StorableVector should fill this gap.
 http://code.haskell.org/~sjanssen/storablevector/
 

 Yes, it could, but
 (1) it's way behind ByteString in terms of optimizations (== fusion)
 (2) there's (as far as I know) not a StorableVector.Lazy, which is very much
 needed

 To catch up on both fronts, we're looking at a lot of duplicate code.

For anyone looking into it - the StorableVector fusion would have to
be quite different from the current ByteString fusion framework.
Maybe it would be enough to lay down a Stream fusion framework for
StorableVectors.

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


Re: [Haskell-cafe] Re: The Proliferation of List-Like Types

2008-02-20 Thread Chad Scherrer
On Feb 20, 2008 10:57 AM, Antoine Latter [EMAIL PROTECTED] wrote:
 For anyone looking into it - the StorableVector fusion would have to
 be quite different from the current ByteString fusion framework.
 Maybe it would be enough to lay down a Stream fusion framework for
 StorableVectors.

I must be missing something. Why would it have to be so different?

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


Re: [Haskell-cafe] Re: The Proliferation of List-Like Types

2008-02-20 Thread Antoine Latter
On Feb 20, 2008 12:59 PM, Chad Scherrer [EMAIL PROTECTED] wrote:
 On Feb 20, 2008 10:57 AM, Antoine Latter [EMAIL PROTECTED] wrote:
  For anyone looking into it - the StorableVector fusion would have to
  be quite different from the current ByteString fusion framework.
  Maybe it would be enough to lay down a Stream fusion framework for
  StorableVectors.

 I must be missing something. Why would it have to be so different?


From what I saw of Data.ByteString.Fusion, it relies on the assumption
that the elements of the output array are of the same size and
alignment as the elements of all of the arrays in the fused
intermediate steps.  That way, all of the intermediate stages can
mutate the output array in place.

This works because all of the fusable bytestring functions have types
along the lines of:

map :: (Word8 - Word8) - ByteString - ByteString

With StorableVector, it'd be nice to support the fusion of:

map :: (a - b) - Vector a - Vector b

All of this just comes from me reading the code, so I could be
miss-interpreting something.

The NDP papers probably have something interesting to say about this,
but I haven't taken the time to try and understand/simplify what they
do.

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


Re: [Haskell-cafe] Re: The Proliferation of List-Like Types

2008-02-20 Thread Chad Scherrer
Antoine Latter [EMAIL PROTECTED] wrote:
 From what I saw of Data.ByteString.Fusion, it relies on the assumption
 that the elements of the output array are of the same size and
 alignment as the elements of all of the arrays in the fused
 intermediate steps.  That way, all of the intermediate stages can
 mutate the output array in place.

I see a lot in there involving the elimination of intermediate data
structures, but nothing about destructive updates. The API is purely
functional, and what you're talking about would need to be done in the
IO monad to be sure you don't throw away stuff you might need to use
again.

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


Re: [Haskell-cafe] Re: The Proliferation of List-Like Types

2008-02-20 Thread David Roundy
On Wed, Feb 20, 2008 at 11:18:51PM +0100, Ben Franksen wrote:
 John Goerzen wrote:
 
  On 2008-02-20, Jules Bean [EMAIL PROTECTED] wrote:
  Not directly, no.
 
  The point about Foldable, Functor, and Monad, is that they enforce the
  connection between container and contents. If the contents is of type
  a, the container is of type f a for a fixed type constructor 'f'.
  This works for [], Seq, and so on, but fails for ByteString.
  
  Right.  In a pure abstract sense, we humans know there is a
  relationship between container and contents: a ByteString always
  contains a Word8 (or a Char8 if we choose the alternative
  implementation).
  
  But that is not expressed in the type of ByteString.
 
 Hm, making a function out of a constant is easy on the value level, just use
 (const x) instead of (x). So, what about wrapping ByteString in a GADT,
 like this
 
   data ByteString' a where
 BS' :: Word8 - ByteString' Word8
 
 ? I probably overlooked something important here...

The problem is that while this would change the kind of ByteString to the
same as the kind expected by Functor, you still couldn't define a proper
Functor instance, since only ByteString' Word8 can ever actually be
created.  i.e. how could you implement

fmapBS :: (a - b) - ByteString' a - ByteString' b
-- 
David Roundy
Department of Physics
Oregon State University
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: The Proliferation of List-Like Types

2008-02-20 Thread ajb

G'day all.

Quoting Neil Mitchell [EMAIL PROTECTED]:


Yes, its the projection onto another type:

[] = Nothing
(x:xs) = Just (x, xs)


Also known as msplit:

http://www.haskell.org/haskellwiki/New_monads/MonadSplit

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


Re: [Haskell-cafe] Re: The Proliferation of List-Like Types

2008-02-20 Thread David Menendez
On Wed, Feb 20, 2008 at 10:46 PM,  [EMAIL PROTECTED] wrote:
  Quoting Neil Mitchell [EMAIL PROTECTED]:

   Yes, its the projection onto another type:
  
   [] = Nothing
   (x:xs) = Just (x, xs)

  Also known as msplit:

  http://www.haskell.org/haskellwiki/New_monads/MonadSplit

Almost. The projection has type f a - Maybe (a, f a), but msplit has
type f a - f (Maybe (a, f a)).

-- 
Dave Menendez [EMAIL PROTECTED]
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe