Re: [Haskell-cafe] Future Edison directions

2006-08-01 Thread Brian Hulley

Brian Hulley wrote:

   splitWith :: (v -> Bool) -> c -> (c,c)
   splitWith p t
   | isEmpty t = (empty, empty)
   | p (measure t) =
 let
(l,x,r) = splitWithInternal p mempty t
 in (l, pushL x r)
   | otherwise = (empty, empty)


Sorry it should be:

 | otherwise = (t, empty)

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


Re: [Haskell-cafe] Future Edison directions

2006-08-01 Thread Brian Hulley

Jared Updike wrote:

This page:

 http://jaortega.wordpress.com/2006/03/17/programmers-go-bananas/

lists some references at the bottom. Perhaps they would be useful.


Thanks! That page looks really interesting and useful,
Brian.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Future Edison directions

2006-08-01 Thread Brian Hulley

Robert Dockins wrote:
[snip]

7) Finally, I somehow feel like there should be a nice categorical
formulation of these datastructure abstractions which would help to
drive a refactoring of the API typeclasses in a principled way,
rather than on an ad-hoc I-sort-of-think-these-go-together sort of
way.


For the last few months (!!!) I've been thinking about the relationship 
between measured sequences and plain sequences and also whether or not every 
sequence should by indexable by Int. I'm wondering if something like the 
following might be a possible factoring of the ops relating to 
indexing/measurements:


   -- from http://www.soi.city.ac.uk/~ross/papers/FingerTree.html
   class Monoid v => Measured v a where
   measure :: a -> v

   instance Measured () a where measure _ = ()

   -- then (also based mostly on FingerTree ideas)
   class (Monoid v, Ord i) => IndexMeasure v i where -- no fundep
   index :: v -> i

   class BasicSeq c a | c -> a where
   length :: c -> Int
   empty :: c
   isEmpty :: c -> Bool
   atL :: c -> a
   atR :: c -> a
   pushL :: a -> c -> c
   viewL :: Monad m => c -> m (a, c)
   -- pushR, viewR

   class (Measured v a, Measured v c, BasicSeq c a)  => Measurable c v a | 
c -> v where

   -- precondition: pred is True for v `mappend` (measure c)
   splitWithInternal :: (v -> Bool) -> v -> c -> (c, a, c)

   splitWith :: (v -> Bool) -> c -> (c,c)
   splitWith p t
   | isEmpty t = (empty, empty)
   | p (measure t) =
 let
(l,x,r) = splitWithInternal p mempty t
 in (l, pushL x r)
   | otherwise = (empty, empty)

   splitAt :: IndexMeasure v i => i -> c -> (c,c)
   splitAt i = splitWith (\v -> i < index v)

   size :: IndexMeasure v i => c -> i
   size c = index (measure c)

   -- take, drop, takeWith, dropWith, in terms of split and splitWith

   atWith :: (v -> Bool) -> c -> a
   atWith p t = (\(_,x,_)->x) (splitWithInternal p mempty t)

   at :: IndexMeasure v i => i -> c -> a
   at i = atWith (\v -> i < index v)

where splitWith p s returns (l,r) such that the measure of l `mappend` the 
measure of the first element of r satisfies p (FingerTree paper has 
explanation of this - I assume monotonic p for any useful use).


The idea of the above design would be to allow multiple indexes for the same 
sequence (though the element type is the same in each case so possibly this 
could be confusing though could be prevented by using a fundep in the 
IndexMeasure class), as well as allowing sequences with an arbitrary measure 
that isn't an index (just by having no instances of IndexMeasure) eg:


 data TextBuffer = ...

 newtype Line = Line Int
 newtype CharPos = CharPos Int

 data TextBufferMeasure = ...

 instance IndexMeasure TextBufferMeasure Line where ...
 instance IndexMeasure TextBufferMeasure CharPos where ...

 instance Measureable TextBuffer TextBufferMeasure Char where ...

 Line lineCount = size textbuf
 CharPos charCount = size textbuf

 (before, after) = splitAt (CharPos 56) textbuf

Of course this doesn't solve the problem of using nested sequences, but it 
at least allows general measurement with predicate search to coexist with 
simple indexing and size-with-respect-to-index where these are applicable to 
the relevant concrete sequence.


Anyway just a very rough idea at the moment. I'm looking forward to seeing a 
nice categorical factoring ;-)


Regards, Brian.
--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com 


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


Re: [Haskell-cafe] Future Edison directions

2006-08-01 Thread Jared Updike

This page:

 http://jaortega.wordpress.com/2006/03/17/programmers-go-bananas/

lists some references at the bottom. Perhaps they would be useful.

 Jared.

On 8/1/06, Brian Hulley <[EMAIL PROTECTED]> wrote:

Robert Dockins wrote:
[snip other points]
> 7) Finally, I somehow feel like there should be a nice categorical
> formulation of these datastructure abstractions which would help to
> drive a refactoring of the API typeclasses in a principled way,
> rather than on an ad-hoc I-sort-of-think-these-go-together sort of
> way.  Unfortunately, my category-fu is quite weak, so all I have is
> this vague intuition that I can't substantiate.  I'm sort of familiar
> with initial algebras, but I think they may be too concrete.  I'm
> looking for some way to classify algebras that have, eg, the property
> of having folds, or of being set-like, etc.  If anybody can point me
> in the right direction wrt this, that would be great.

I'd love to find out more about these categorical abstractions also, since
Monads and Monoids (the only ones I know about) are an incredible source of
power and expressiveness in Haskell programming, so I've got the feeling
that I'm wasting tremendous amounts of time reinventing the wheel when other
abstractions that may be equally useful are just waiting to be used...

Can anyone recommend a good book or web tutorial about category theory
that's not too difficult? I'm thinking about something which would have lots
of diagrams and discussion about the relevance of the concepts to practical
computing problems but not something loaded with complicated proofs or LaTeX
symbols :-)

Thanks, Brian.

--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com

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




--
http://www.updike.org/~jared/
reverse ")-:"
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Future Edison directions

2006-08-01 Thread Brian Hulley

Robert Dockins wrote:
[snip other points]

7) Finally, I somehow feel like there should be a nice categorical
formulation of these datastructure abstractions which would help to
drive a refactoring of the API typeclasses in a principled way,
rather than on an ad-hoc I-sort-of-think-these-go-together sort of
way.  Unfortunately, my category-fu is quite weak, so all I have is
this vague intuition that I can't substantiate.  I'm sort of familiar
with initial algebras, but I think they may be too concrete.  I'm
looking for some way to classify algebras that have, eg, the property
of having folds, or of being set-like, etc.  If anybody can point me
in the right direction wrt this, that would be great.


I'd love to find out more about these categorical abstractions also, since 
Monads and Monoids (the only ones I know about) are an incredible source of 
power and expressiveness in Haskell programming, so I've got the feeling 
that I'm wasting tremendous amounts of time reinventing the wheel when other 
abstractions that may be equally useful are just waiting to be used...


Can anyone recommend a good book or web tutorial about category theory 
that's not too difficult? I'm thinking about something which would have lots 
of diagrams and discussion about the relevance of the concepts to practical 
computing problems but not something loaded with complicated proofs or LaTeX 
symbols :-)


Thanks, Brian.

--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com 


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