[Haskell-cafe] The (!) operation

2012-03-08 Thread Christopher Done
‘Ello.

Is there a generalization of this operator? It's all over the place,
it's basically

(!) :: (Monad m, Indexed collection index value) = index -
container - m value

We have `(!!)` on lists, `(!)` on maps, vectors, json objects, …
(doesn't seem there's one for bytestring)

(Though I seem to recall the monadic return value being frowned upon
but I don't recall why.)

Thoughts?

Ciao!

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


Re: [Haskell-cafe] The (!) operation

2012-03-08 Thread Francesco Mazzoli

On 08/03/12 16:19, Christopher Done wrote:

‘Ello.

Is there a generalization of this operator? It's all over the place,
it's basically

 (!) :: (Monad m, Indexed collection index value) =  index -
container -  m value

We have `(!!)` on lists, `(!)` on maps, vectors, json objects, …
(doesn't seem there's one for bytestring)

(Though I seem to recall the monadic return value being frowned upon
but I don't recall why.)

Thoughts?

Ciao!



Ciao!

It doesn't exist as far as I know, but a Map typeclass can be easily 
envisioned, e.g.:


{-# LANGUAGE MultiParamTypeClasses
   , FunctionalDependencies
   , FlexibleInstances
  #-}
module MapClass (MapClass(..)) where

import Data.Map (Map)
import qualified Data.Map as Map
import Data.Hashable (Hashable)
import Data.HashMap.Lazy (HashMap)
import qualified Data.HashMap.Lazy as HashMap

import qualified Data.List as List

class MapClass m k v | m - k, m - v where
empty  :: m
lookup :: k - m - Maybe v
insert :: k - v - m - m

instance Ord k = MapClass [(k, v)] k v where
empty  = []
lookup = List.lookup
insert k v = ((k, v) :)

instance Ord k = MapClass (Map k v) k v where
empty  = Map.empty
lookup = Map.lookup
insert = Map.insert

instance (Hashable k, Eq k) = MapClass (HashMap k v) k v where
empty  = HashMap.empty
lookup = HashMap.lookup
insert = HashMap.insert

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


Re: [Haskell-cafe] The (!) operation

2012-03-08 Thread Francesco Mazzoli
Ops sorry, I had misunderstood, you don't want key-lookups but a simple 
indexing. In that case you might want an almost identical class but with 
different instances (e.g IxClass [a] Int a, etc.).


Also, I don't see why you need to throw monads in.

Francesco.

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


Re: [Haskell-cafe] The (!) operation

2012-03-08 Thread Francesco Mazzoli
Ok, this should suit your needs better, without functional dependencies 
as a bonus:


{-# LANGUAGE TypeFamilies, ScopedTypeVariables, FlexibleInstances #-}
module IxClass (IxClass(..)) where

import Data.Map (Map)
import qualified Data.Map as Map
import Data.Hashable (Hashable)
import Data.HashMap.Lazy (HashMap)
import qualified Data.HashMap.Lazy as HashMap

import qualified Data.List as List

class IxClass a where
type Ix a:: *
type Value a :: *

index  :: Ix a - a - Maybe (Value a)

(!) :: IxClass a = a - Ix a - (Value a)
a ! k = case index k a of
Just v  - v
Nothing - error IxClass.(!): index not found

instance IxClass [a] where
type Ix [a]= Int
type Value [a] = a

index _ []   = Nothing
index 0 (x : _)  = Just x
index n (_ : xs) = index (n - 1) xs

instance Ord k = IxClass (Map k v) where
type Ix (Map k v)= k
type Value (Map k v) = v

index = Map.lookup

instance (Hashable k, Eq k) = IxClass (HashMap k v) where
type Ix (HashMap k v)= k
type Value (HashMap k v) = v

index = HashMap.lookup

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


Re: [Haskell-cafe] The (!) operation

2012-03-08 Thread Anthony Cowley
On Thu, Mar 8, 2012 at 11:19 AM, Christopher Done
chrisd...@googlemail.com wrote:
 ‘Ello.

 Is there a generalization of this operator? It's all over the place,
 it's basically

    (!) :: (Monad m, Indexed collection index value) = index -
 container - m value

 We have `(!!)` on lists, `(!)` on maps, vectors, json objects, …
 (doesn't seem there's one for bytestring)

 (Though I seem to recall the monadic return value being frowned upon
 but I don't recall why.)

 Thoughts?

Perhaps Data.Key meets your needs?

http://hackage.haskell.org/packages/archive/keys/2.1.2/doc/html/Data-Key.html

Anthony

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


Re: [Haskell-cafe] The (!) operation

2012-03-08 Thread Francesco Mazzoli



(Though I seem to recall the monadic return value being frowned upon
but I don't recall why.)



The type signature that you wrote is very generic and doesn't help in 
introducing effects while retrieving the indexed value, which I imagine 
is what you wanted to do.


I guess you could define a type family for the monad type as well, e.g.:

type family Index f
type family IndexMonad f :: * - *

class Functor f = Indexed f where
index :: Index f - f a - (IndexMonad f) (Maybe a)

Francesco.

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


Re: [Haskell-cafe] The (!) operation

2012-03-08 Thread Christopher Done
On 8 March 2012 18:32, Anthony Cowley acow...@seas.upenn.edu wrote:
 Perhaps Data.Key meets your needs?

 http://hackage.haskell.org/packages/archive/keys/2.1.2/doc/html/Data-Key.html

Ah, perhaps indeed. Thanks!

On 8 March 2012 19:12, Francesco Mazzoli f...@mazzo.li wrote:
 The type signature that you wrote is very generic and doesn't help in
 introducing effects while retrieving the indexed value, which I imagine is
 what you wanted to do.

Because Maybe is already a monad and it's nice to fail in the monad of
choice, e.g. if I'm in the list monad I get empty list instead, or if
I'm in the Result monad from JSON it'll fail in there. ‘Course fail
is suboptimal and MonadError might be better.

 I guess you could define a type family for the monad type as well, e.g.:

 type family Index f
 type family IndexMonad f :: * - *

 class Functor f = Indexed f where
    index :: Index f - f a - (IndexMonad f) (Maybe a)

Right, that sounds interesting, similar to Data.Key above!

It seems like a type family is a good approach. I'll try this keys
library out.

Grazie mille, a dopo… ;-)

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


Re: [Haskell-cafe] The (!) operation

2012-03-08 Thread Francesco Mazzoli

Because Maybe is already a monad and it's nice to fail in the monad of
choice, e.g. if I'm in the list monad I get empty list instead, or if
I'm in the Result monad from JSON it'll fail in there. ‘Course fail
is suboptimal and MonadError might be better.


'fail' really shouldn't be in Monad. My brain ignores its existence by 
now :).



Grazie mille, a dopo… ;-)


A dopo!

Francesco

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


Re: [Haskell-cafe] The (!) operation

2012-03-08 Thread Brent Yorgey
On Thu, Mar 08, 2012 at 07:53:48PM +0100, Christopher Done wrote:
 On 8 March 2012 18:32, Anthony Cowley acow...@seas.upenn.edu wrote:
  Perhaps Data.Key meets your needs?
 
  http://hackage.haskell.org/packages/archive/keys/2.1.2/doc/html/Data-Key.html
 
 Ah, perhaps indeed. Thanks!
 
 On 8 March 2012 19:12, Francesco Mazzoli f...@mazzo.li wrote:
  The type signature that you wrote is very generic and doesn't help in
  introducing effects while retrieving the indexed value, which I imagine is
  what you wanted to do.
 
 Because Maybe is already a monad and it's nice to fail in the monad of
 choice, e.g. if I'm in the list monad I get empty list instead, or if
 I'm in the Result monad from JSON it'll fail in there. ‘Course fail
 is suboptimal and MonadError might be better.

Monads have nothing to do with failure.  Instead of Monad you would
want to use something like MonadZero or MonadError.  However, these
are also suboptimal because in monads which carry extra information
about the failure (i.e. anything other than [] or Maybe), the lookup
function now has to make up an error message, when it almost certainly
it doesn't know enough to give a good one.  This is why the use of
Maybe is encouraged: Maybe is the *initial* instance of MonadZero, so
you can map from it to failure in whatever monad you happen to be
using.  Instead of being an annoyance this is encouraged style,
because in doing the conversion *you* get to pick a meaningful error
message.  For example

  fromMaybe (throwError WidgetNotFound) (lookup foo blah)

or

  fromMaybe (Left Missing wurble specification: flozz) (lookup foo blah)

-Brent

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


Re: [Haskell-cafe] The (!) operation

2012-03-08 Thread Christopher Done
On 8 March 2012 21:43, Brent Yorgey byor...@seas.upenn.edu wrote:
  ‘Course fail is suboptimal and MonadError might be better.

 Monads have nothing to do with failure.  Instead of Monad you would
 want to use something like MonadZero or MonadError.

Yeah that's what I said. GOSH. /NapoleanDynamite

 However, these are also suboptimal because in monads which carry
 extra information about the failure (i.e. anything other than [] or
 Maybe), the lookup function now has to make up an error message,
 when it almost certainly it doesn't know enough to give a good one.

Good point! I had sort of felt this way regarding the monadic return
in the past, but thought there might be some hidden wisdom behind the
idea that I hadn't seen, and why it was in some base libraries some
time back. Hadn't paid much attention to it, though.

Indeed, the lookup function can't show the key to provide a useful
exception message. Another problem, even if you make it like lookup ::
MonadError (LookupError key) m = key - collection - m a, there's
still the problem that the error isn't polymorphic in the same monad,
so if lookup throws e :: LookupError the whole monad needs to be that
because the functional dep is m - e. Making MonadError kinda
pointless. MonadZero gives no information and can't be handled
trivially like Maybe, too.

 This is why the use of Maybe is encouraged: Maybe is the *initial*
 instance of MonadZero, so you can map from it to failure in whatever
 monad you happen to be using.  Instead of being an annoyance this is
 encouraged style, because in doing the conversion *you* get to pick
 a meaningful error message.

Good points. I already use the fromMaybe style for this with lookup
and such-like.

Thanks for clarifying some things!

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


Re: [Haskell-cafe] List operation question

2007-02-05 Thread ihope

On 2/4/07, Eric Olander [EMAIL PROTECTED] wrote:

Hi,
   I'm still somewhat new to Haskell, so I'm wondering if there are better
ways I could implement the following functions, especially shiftl:

 moves the last element to the head of the list
shiftl :: [a] - [a]
shiftl [] = []
shiftl x = [last x] ++ init x


Well, you could try this, though I'm actually sure it's any faster:


shiftl (x1:x2:xs) = last:x1:init
  where last:init = shiftl (x2:xs)
shiftl [x] = [x]
shiftl [] = error shiftl: empty list


Or, if you don't want to give an error on [], omit the last line and
replace both of the [x] with xs.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] List operation question

2007-02-05 Thread Eric Olander

That's a clever routine.  It should be faster than mine since it only makes
a single pass though the list.  Thanks for all the suggestions from everyone
that responded.  Here is a link to some more info on the project I'm working
on if anyone is interested:  http://ehaskell.blogspot.com/

-Eric

On 2/5/07, ihope [EMAIL PROTECTED] wrote:


On 2/4/07, Eric Olander [EMAIL PROTECTED] wrote:
 Hi,
I'm still somewhat new to Haskell, so I'm wondering if there are
better
 ways I could implement the following functions, especially shiftl:

  moves the last element to the head of the list
 shiftl :: [a] - [a]
 shiftl [] = []
 shiftl x = [last x] ++ init x

Well, you could try this, though I'm actually sure it's any faster:

 shiftl (x1:x2:xs) = last:x1:init
   where last:init = shiftl (x2:xs)
 shiftl [x] = [x]
 shiftl [] = error shiftl: empty list

Or, if you don't want to give an error on [], omit the last line and
replace both of the [x] with xs.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

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


[Haskell-cafe] List operation question

2007-02-04 Thread Eric Olander

Hi,
  I'm still somewhat new to Haskell, so I'm wondering if there are better
ways I could implement the following functions, especially shiftl:


moves the first element to the end of the list

   shiftr :: [a] - [a]
   shiftr [] = []
   shiftr (x:y) = y ++ [x]


moves the last element to the head of the list

   shiftl :: [a] - [a]
   shiftl [] = []
   shiftl x = [last x] ++ init x

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


Re: [Haskell-cafe] List operation question

2007-02-04 Thread Lennart Augustsson
Not much better.  You could define shiftl such that is does a single  
traversal and
returns both the last element and all but the last.  That will save  
you one traversal.


On Feb 4, 2007, at 18:44 , Eric Olander wrote:


Hi,
   I'm still somewhat new to Haskell, so I'm wondering if there are  
better ways I could implement the following functions, especially  
shiftl:


 moves the first element to the end of the list
shiftr :: [a] - [a]
shiftr [] = []
shiftr (x:y) = y ++ [x]

 moves the last element to the head of the list
shiftl :: [a] - [a]
shiftl [] = []
shiftl x = [last x] ++ init x

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


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


Re: [Haskell-cafe] List operation question

2007-02-04 Thread Yitzchak Gale

Nicolas Frisby wrote:

I've always thought that when certain operations are of particular
interest, it's time to use more appropriate data structures, right?
Lists are great and simple and intuitive, but if you need such
operations as shifts, something like a deque is the way to go.


This sounds like a job for Data.Sequence.

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


Re: [Haskell-cafe] List operation question

2007-02-04 Thread Lennart Augustsson
I agree.  If performance is important enough to worry about is shiftl  
traverses the list once or twice then it's time to switch to a better  
data type.


On Feb 4, 2007, at 19:27 , Yitzchak Gale wrote:


Nicolas Frisby wrote:

I've always thought that when certain operations are of particular
interest, it's time to use more appropriate data structures, right?
Lists are great and simple and intuitive, but if you need such
operations as shifts, something like a deque is the way to go.


This sounds like a job for Data.Sequence.

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


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


Re: [Haskell-cafe] List operation question

2007-02-04 Thread Bryan Donlan

Eric Olander wrote:

Hi,
   I'm still somewhat new to Haskell, so I'm wondering if there are 
better ways I could implement the following functions, especially shiftl:


  moves the first element to the end of the list
shiftr :: [a] - [a]
shiftr [] = []
shiftr (x:y) = y ++ [x]
   
  moves the last element to the head of the list

shiftl :: [a] - [a]
shiftl [] = []
shiftl x = [last x] ++ init x


If you use Data.Sequence (new in 6.6, I think), these can be O(1):

import qualified Data.Sequence as Seq
import Data.Sequence ( (|), (|), (:), (:) )

shiftr seq = go (Seq.viewl seq)
  where
go (EmptyL) = Seq.empty
go (e : remain) = remain | e

shiftl seq = go (Seq.viewr seq)
  where
go (EmptyR) = Seq.empty
go (remain : e) = e | remain

Decomposing by elements like this is a bit unwieldy, but using the 
functions in Data.Traversable and Data.Foldable it shouldn't be too bad, 
depending on what you're doing.

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


Re: [Haskell-cafe] List operation question

2007-02-04 Thread Robert Dockins
On Sunday 04 February 2007 14:24, Nicolas Frisby wrote:
 I've always thought that when certain operations are of particular
 interest, it's time to use more appropriate data structures, right?
 Lists are great and simple and intuitive, but if you need such
 operations as shifts, something like a deque is the way to go.

 I'm not a data structure pro, but I'm sure someone on this list could
 post a neat example. Or you could look for work by Osaki - he seems to
 be the reference for functional data structures. Finger trees and
 tries also get a lot of attention around here.


Also, take a look at Edison.  It has a variety of sequence implementations 
with different properties.  Several of them have efficient access to both 
ends of the sequence.


http://www.eecs.tufts.edu/~rdocki01/edison.html


 Enjoy.

 On 2/4/07, Lennart Augustsson [EMAIL PROTECTED] wrote:
  Not much better.  You could define shiftl such that is does a single
  traversal and
  returns both the last element and all but the last.  That will save
  you one traversal.
 
  On Feb 4, 2007, at 18:44 , Eric Olander wrote:
   Hi,
  I'm still somewhat new to Haskell, so I'm wondering if there are
   better ways I could implement the following functions, especially
  
   shiftl:
moves the first element to the end of the list
  
   shiftr :: [a] - [a]
   shiftr [] = []
   shiftr (x:y) = y ++ [x]
  
moves the last element to the head of the list
  
   shiftl :: [a] - [a]
   shiftl [] = []
   shiftl x = [last x] ++ init x
  
   -Eric
   ___
   Haskell-Cafe mailing list
   Haskell-Cafe@haskell.org
   http://www.haskell.org/mailman/listinfo/haskell-cafe
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe

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