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

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.

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

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

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

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

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

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

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.

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 [] = []

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

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

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

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

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]

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