Library for overloaded indexing (a la (!))

Hello all, I put together a small library for the purpose of creating overloaded indexing operators. The library is available at https://hackage.haskell.org/package/keyed . I would like to solicit some advice on the design of this library. Q1: The library uses TypeFamilies to determine which types to use for the index type (which is used to look up a value) and the value type (which is returned from a lookup). I originally did this using MultiParamTypeClasses and FunctionalDependencies, but thought this was cleaner; are there any good reasons to go back to using FunDeps? Q2: Data.Keyed provides pure indexing, while Data.MKeyed provides monadic indexing (e.g. for mutable vectors or concurrent STM-based maps). I'm having some trouble with the fact that mutable vectors are keyed on the PrimState of their corresponding PrimMonad. Right now, there is a type in the MKeyed class definition called MContainer. This is the type of the Monad that the lookup operation returns. I.e. (!) :: MKeyed d => d -> MKey d -> MContainer d (MValue d) ~ (!) :: IOVector a -> Int -> IO a or (!) :: STVector s a -> Int -> ST s a Unfortunately, this causes an overlap (because both IOVector and STVector are aliased to MVector). I tried making an instance for MVector, but the problem is that it's difficult to actually go from `IOVector a = MVector RealWorld a` to `IO` or `STVector s a = MVector s a` to `ST`, because neither `IO` nor `ST` appears in the type of the vector. I can't do instance (PrimMonad m, s ~ PrimState m) => MKeyed (MVector s a) where ... type MContainer (MVector (PrimState m) a) = m because you can't have type synonyms on the LHS of the type. I tried bringing `m` into scope using RankNTypes, but that didn't work. Is there some syntax I can use to bring `m` into scope here? Or should I be doing this part entirely differently? Q3: Is there any way to automatically derive all instances of Keyed for all types of Data.Vector (using Data.Vector.Generic)? Using `instance Vector v a => Keyed (v a) where ...` doesn't work, as it overlaps with everything of the form `(d :: * -> *) (a :: *) :: *`, like `[a]`. Thanks, Will

FWIW lens has a bit more powerful implementation of Data.Keyed:
https://hackage.haskell.org/package/lens-4.12.3/docs/Control-Lens-At.html#t:...
On Thu, Aug 13, 2015 at 7:18 AM, William Yager
Hello all,
I put together a small library for the purpose of creating overloaded indexing operators. The library is available at https://hackage.haskell.org/package/keyed .
I would like to solicit some advice on the design of this library.
Q1: The library uses TypeFamilies to determine which types to use for the index type (which is used to look up a value) and the value type (which is returned from a lookup).
I originally did this using MultiParamTypeClasses and FunctionalDependencies, but thought this was cleaner; are there any good reasons to go back to using FunDeps?
Q2: Data.Keyed provides pure indexing, while Data.MKeyed provides monadic indexing (e.g. for mutable vectors or concurrent STM-based maps).
I'm having some trouble with the fact that mutable vectors are keyed on the PrimState of their corresponding PrimMonad.
Right now, there is a type in the MKeyed class definition called MContainer. This is the type of the Monad that the lookup operation returns. I.e.
(!) :: MKeyed d => d -> MKey d -> MContainer d (MValue d) ~ (!) :: IOVector a -> Int -> IO a or (!) :: STVector s a -> Int -> ST s a
Unfortunately, this causes an overlap (because both IOVector and STVector are aliased to MVector).
I tried making an instance for MVector, but the problem is that it's difficult to actually go from `IOVector a = MVector RealWorld a` to `IO` or `STVector s a = MVector s a` to `ST`, because neither `IO` nor `ST` appears in the type of the vector. I can't do
instance (PrimMonad m, s ~ PrimState m) => MKeyed (MVector s a) where ... type MContainer (MVector (PrimState m) a) = m
because you can't have type synonyms on the LHS of the type.
I tried bringing `m` into scope using RankNTypes, but that didn't work.
Is there some syntax I can use to bring `m` into scope here?
Or should I be doing this part entirely differently?
Q3: Is there any way to automatically derive all instances of Keyed for all types of Data.Vector (using Data.Vector.Generic)? Using `instance Vector v a => Keyed (v a) where ...` doesn't work, as it overlaps with everything of the form `(d :: * -> *) (a :: *) :: *`, like `[a]`.
Thanks, Will
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

Thanks! Looks like they're doing it much the same way.
However, the purpose of this was for syntactic simplicity, which I think
it's hard to argue Lens provides in this case. "^? ix" isn't exactly
user-friendly, and it only provides a substitute for "!?", not "!". (Or at
least, I couldn't figure out how to get "!" behavior cleanly.)
The idea here is that you might want some sort of universal, simple
indexing syntax like brackets in other languages, particularly if you have
lots of different indexed structures in your module. It can be annoying to
have to index Seq, Map, etc. in the same scope.
--Will
On Thu, Aug 13, 2015 at 3:04 AM, Patrick Chilton
FWIW lens has a bit more powerful implementation of Data.Keyed: https://hackage.haskell.org/package/lens-4.12.3/docs/Control-Lens-At.html#t:...
On Thu, Aug 13, 2015 at 7:18 AM, William Yager
wrote: Hello all,
I put together a small library for the purpose of creating overloaded indexing operators. The library is available at https://hackage.haskell.org/package/keyed .
I would like to solicit some advice on the design of this library.
Q1: The library uses TypeFamilies to determine which types to use for the index type (which is used to look up a value) and the value type (which is returned from a lookup).
I originally did this using MultiParamTypeClasses and FunctionalDependencies, but thought this was cleaner; are there any good reasons to go back to using FunDeps?
Q2: Data.Keyed provides pure indexing, while Data.MKeyed provides monadic indexing (e.g. for mutable vectors or concurrent STM-based maps).
I'm having some trouble with the fact that mutable vectors are keyed on the PrimState of their corresponding PrimMonad.
Right now, there is a type in the MKeyed class definition called MContainer. This is the type of the Monad that the lookup operation returns. I.e.
(!) :: MKeyed d => d -> MKey d -> MContainer d (MValue d) ~ (!) :: IOVector a -> Int -> IO a or (!) :: STVector s a -> Int -> ST s a
Unfortunately, this causes an overlap (because both IOVector and STVector are aliased to MVector).
I tried making an instance for MVector, but the problem is that it's difficult to actually go from `IOVector a = MVector RealWorld a` to `IO` or `STVector s a = MVector s a` to `ST`, because neither `IO` nor `ST` appears in the type of the vector. I can't do
instance (PrimMonad m, s ~ PrimState m) => MKeyed (MVector s a) where ... type MContainer (MVector (PrimState m) a) = m
because you can't have type synonyms on the LHS of the type.
I tried bringing `m` into scope using RankNTypes, but that didn't work.
Is there some syntax I can use to bring `m` into scope here?
Or should I be doing this part entirely differently?
Q3: Is there any way to automatically derive all instances of Keyed for all types of Data.Vector (using Data.Vector.Generic)? Using `instance Vector v a => Keyed (v a) where ...` doesn't work, as it overlaps with everything of the form `(d :: * -> *) (a :: *) :: *`, like `[a]`.
Thanks, Will
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

However, the purpose of this was for syntactic simplicity, which I think it's hard to argue Lens provides in this case. "^? ix" isn't exactly user-friendly, and it only provides a substitute for "!?", not "!". (Or at least, I couldn't figure out how to get "!" behavior cleanly.)
Look at the type: [1,2,3,4] ^. ix 2 :: (Num a, Monoid a) => a It typechecks, but the result must be a Monoid that has a Num instance. There are Product and Sum wrappers for Num (because the identity element can be either 0 or 1, depending on mappend, which can be + or *). So, this works fine: getSum $ [1,2,3,4] ^. ix 2 => 3 getSum $ [1,2,3,4] ^. ix 42 => 0

That's completely different behavior than indexing, and introduces even
more syntactic noise if you just want to index.
If I mis-index a vector, I don't want it to fail silently with mempty; I
want it to fail loudly. What you've described (default value on
out-of-bounds access) is not correct for most use cases. Sometimes
exceptions are the right behavior.
--Will
On Thu, Aug 13, 2015 at 11:13 PM, Nikita Karetnikov
getSum $ [1,2,3,4] ^. ix 42 => 0
Oh, one more thing: this is a bit different from ! or !! (in a good way) because it doesn't raise an exception.

On Thu, Aug 13, 2015 at 10:31:53PM -0700, William Yager wrote:
it only provides a substitute for "!?", not "!". (Or at least, I couldn't figure out how to get "!" behavior cleanly.)
(Don't you want ^?!)? http://haddock.stackage.org/lts-3.0/microlens-0.2.0.0/Lens-Micro.html#v:-94-... and also available in Control.Lens. Tom

Yep, that'll do it! Alright, so we've established how to replicate (!) and (!?) using lens; what about (!!) and (!!?)? Those were the ones that gave me typing trouble. Also, I'm still interested in auto-deriviation of Ixed/Keyed instances for all Vector types through Vector.Generic. Thanks, Will On Thu, Aug 13, 2015 at 11:29 PM, Tom Ellis < tom-lists-haskell-cafe-2013@jaguarpaw.co.uk> wrote:
On Thu, Aug 13, 2015 at 10:31:53PM -0700, William Yager wrote:
it only provides a substitute for "!?", not "!". (Or at least, I couldn't figure out how to get "!" behavior cleanly.)
(Don't you want ^?!)?
http://haddock.stackage.org/lts-3.0/microlens-0.2.0.0/Lens-Micro.html#v:-94-...
and also available in Control.Lens.
Tom _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

On Thu, Aug 13, 2015 at 11:36:01PM -0700, William Yager wrote:
Alright, so we've established how to replicate (!) and (!?) using lens; what about (!!) and (!!?)? Those were the ones that gave me typing trouble.
Can't you just define an indexed getter for the particular case you care about?

On 14/08/15 09:21, William Yager wrote:
If I mis-index a vector, I don't want it to fail silently with mempty; I want it to fail loudly. What you've described (default value on out-of-bounds access) is not correct for most use cases. Sometimes exceptions are the right behavior.
Precisely. «An element is not found, so I'll just return 0[*] or "".» Even JavaScript knows better than that. Granted, there *is* a way to use this API properly (using Maybe-like monoids). But it's also easy to make the wrong code type-check without realizing it. [*] that's essentially what Nikita proposed earlier in the thread
participants (5)
-
Nikita Karetnikov
-
Patrick Chilton
-
Roman Cheplyaka
-
Tom Ellis
-
William Yager