
‘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!

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

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.

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

On Thu, Mar 8, 2012 at 11:19 AM, 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?
Perhaps Data.Key meets your needs? http://hackage.haskell.org/packages/archive/keys/2.1.2/doc/html/Data-Key.htm... Anthony

(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.

On 8 March 2012 18:32, Anthony Cowley
Perhaps Data.Key meets your needs?
http://hackage.haskell.org/packages/archive/keys/2.1.2/doc/html/Data-Key.htm...
Ah, perhaps indeed. Thanks!
On 8 March 2012 19:12, Francesco Mazzoli
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… ;-)

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

On Thu, Mar 08, 2012 at 07:53:48PM +0100, Christopher Done wrote:
On 8 March 2012 18:32, Anthony Cowley
wrote: Perhaps Data.Key meets your needs?
http://hackage.haskell.org/packages/archive/keys/2.1.2/doc/html/Data-Key.htm...
Ah, perhaps indeed. Thanks!
On 8 March 2012 19:12, Francesco Mazzoli
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

On 8 March 2012 21:43, Brent Yorgey
‘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!
participants (4)
-
Anthony Cowley
-
Brent Yorgey
-
Christopher Done
-
Francesco Mazzoli