Generalize indexing function

I noticed that the list indexing function, (!!), is generalizable. I'm showing some instances: {-# LANGUAGE MultiParamTypeClasses #-} import Data.Complex import Data.Functor.Compose import Data.Functor.Product import Data.Functor.Sum import Data.List.NonEmpty import Data.Maybe infix 9 !? infixl 9 ! class Indexable i a where (!?) :: i b -> a -> Maybe b (!) :: Indexable i a => i b -> a -> b x ! n = fromJust (x !? n) instance Indexable [] Int where [] !? _ = Nothing (x:_) !? 0 = Just x (_:xs) !? n | n < 0 = Nothing | otherwise = xs !? (n-1) instance Indexable ((->) a) (Identity a) where f !? Identity n = Just (f n) instance Indexable ((,) a) () where (_,x) !? _ = Just x instance Indexable Complex Bool where (x :+ _) !? False = Just x (_ :+ y) !? True = Just y instance (Indexable f a, Indexable g b) => Indexable (Compose f g) (a,b) where Compose z !? (m,n) = do y <- z !? m y !? n instance (Indexable f a, Indexable g b) => Indexable (Product f g) (Either a b) where Pair x _ !? Left m = x !? m Pair _ y !? Right n = y !? n instance (Indexable f a, Indexable g a) => Indexable (Sum f g) (Identity a) where InL x !? Identity n = x !? n InR y !? Identity n = y !? n instance Indexable NonEmpty Int where (x :| xs) !? n = (x : xs) !? n

Might be more convenient to use an associated type family. And in practice, using types like '()' and 'Bool' as indexes is not super useful when you've already committed to using 'Int' as the (partial) index type of '[]'.
- Keith
Sent from my phone with K-9 Mail.
On April 10, 2021 10:48:42 PM UTC, Dannyu NDos
I noticed that the list indexing function, (!!), is generalizable. I'm showing some instances:
{-# LANGUAGE MultiParamTypeClasses #-}
import Data.Complex import Data.Functor.Compose import Data.Functor.Product import Data.Functor.Sum import Data.List.NonEmpty import Data.Maybe
infix 9 !? infixl 9 !
class Indexable i a where (!?) :: i b -> a -> Maybe b
(!) :: Indexable i a => i b -> a -> b x ! n = fromJust (x !? n)
instance Indexable [] Int where [] !? _ = Nothing (x:_) !? 0 = Just x (_:xs) !? n | n < 0 = Nothing | otherwise = xs !? (n-1)
instance Indexable ((->) a) (Identity a) where f !? Identity n = Just (f n)
instance Indexable ((,) a) () where (_,x) !? _ = Just x
instance Indexable Complex Bool where (x :+ _) !? False = Just x (_ :+ y) !? True = Just y
instance (Indexable f a, Indexable g b) => Indexable (Compose f g) (a,b) where Compose z !? (m,n) = do y <- z !? m y !? n
instance (Indexable f a, Indexable g b) => Indexable (Product f g) (Either a b) where Pair x _ !? Left m = x !? m Pair _ y !? Right n = y !? n
instance (Indexable f a, Indexable g a) => Indexable (Sum f g) (Identity a) where InL x !? Identity n = x !? n InR y !? Identity n = y !? n
instance Indexable NonEmpty Int where (x :| xs) !? n = (x : xs) !? n

On Sat, 10 Apr 2021, Keith wrote:
Might be more convenient to use an associated type family.
I have done something similar here: http://hackage.haskell.org/package/comfort-array

I really like the landscape of indexinbg flavores you've included henning! i've def thought about similar stuff, and its nice to see it fleshed out :) On Sat, Apr 10, 2021 at 8:15 PM Henning Thielemann < lemming@henning-thielemann.de> wrote:
On Sat, 10 Apr 2021, Keith wrote:
Might be more convenient to use an associated type family.
I have done something similar here: http://hackage.haskell.org/package/comfort-array _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Does this class have any laws? From what I can tell, this is useful only as
an overloading of some identifiers - I don't see what useful functions I
could write in terms of this as an abstraction.
Cheers,
George
On Sun, 11 Apr 2021, 08:49 Dannyu NDos,
I noticed that the list indexing function, (!!), is generalizable. I'm showing some instances:
{-# LANGUAGE MultiParamTypeClasses #-}
import Data.Complex import Data.Functor.Compose import Data.Functor.Product import Data.Functor.Sum import Data.List.NonEmpty import Data.Maybe
infix 9 !? infixl 9 !
class Indexable i a where (!?) :: i b -> a -> Maybe b
(!) :: Indexable i a => i b -> a -> b x ! n = fromJust (x !? n)
instance Indexable [] Int where [] !? _ = Nothing (x:_) !? 0 = Just x (_:xs) !? n | n < 0 = Nothing | otherwise = xs !? (n-1)
instance Indexable ((->) a) (Identity a) where f !? Identity n = Just (f n)
instance Indexable ((,) a) () where (_,x) !? _ = Just x
instance Indexable Complex Bool where (x :+ _) !? False = Just x (_ :+ y) !? True = Just y
instance (Indexable f a, Indexable g b) => Indexable (Compose f g) (a,b) where Compose z !? (m,n) = do y <- z !? m y !? n
instance (Indexable f a, Indexable g b) => Indexable (Product f g) (Either a b) where Pair x _ !? Left m = x !? m Pair _ y !? Right n = y !? n
instance (Indexable f a, Indexable g a) => Indexable (Sum f g) (Identity a) where InL x !? Identity n = x !? n InR y !? Identity n = y !? n
instance Indexable NonEmpty Int where (x :| xs) !? n = (x : xs) !? n
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

It's distributive under IsList.
fromList (xs !! n) == (fromList xs) !! n
On Sat, Apr 10, 2021, 11:33 PM George Wilson
Does this class have any laws? From what I can tell, this is useful only as an overloading of some identifiers - I don't see what useful functions I could write in terms of this as an abstraction.
Cheers, George
On Sun, 11 Apr 2021, 08:49 Dannyu NDos,
wrote: I noticed that the list indexing function, (!!), is generalizable. I'm showing some instances:
{-# LANGUAGE MultiParamTypeClasses #-}
import Data.Complex import Data.Functor.Compose import Data.Functor.Product import Data.Functor.Sum import Data.List.NonEmpty import Data.Maybe
infix 9 !? infixl 9 !
class Indexable i a where (!?) :: i b -> a -> Maybe b
(!) :: Indexable i a => i b -> a -> b x ! n = fromJust (x !? n)
instance Indexable [] Int where [] !? _ = Nothing (x:_) !? 0 = Just x (_:xs) !? n | n < 0 = Nothing | otherwise = xs !? (n-1)
instance Indexable ((->) a) (Identity a) where f !? Identity n = Just (f n)
instance Indexable ((,) a) () where (_,x) !? _ = Just x
instance Indexable Complex Bool where (x :+ _) !? False = Just x (_ :+ y) !? True = Just y
instance (Indexable f a, Indexable g b) => Indexable (Compose f g) (a,b) where Compose z !? (m,n) = do y <- z !? m y !? n
instance (Indexable f a, Indexable g b) => Indexable (Product f g) (Either a b) where Pair x _ !? Left m = x !? m Pair _ y !? Right n = y !? n
instance (Indexable f a, Indexable g a) => Indexable (Sum f g) (Identity a) where InL x !? Identity n = x !? n InR y !? Identity n = y !? n
instance Indexable NonEmpty Int where (x :| xs) !? n = (x : xs) !? n
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Yeah, I mis-composed that. Pretty sure there's a formulation around take/head that works but I'm clearly not in a headspace to find it! On Sun, Apr 11, 2021, 3:03 AM Henning Thielemann < lemming@henning-thielemann.de> wrote:
On Sun, 11 Apr 2021, Akhra Gannon wrote:
It's distributive under IsList. fromList (xs !! n) == (fromList xs) !! n
fromList (xs !! n) ?
I think, xs!!n is a single element.

On Sun, Apr 11, 2021 at 12:03:04PM +0200, Henning Thielemann wrote:
On Sun, 11 Apr 2021, Akhra Gannon wrote:
It's distributive under IsList. fromList (xs !! n) == (fromList xs) !! n
fromList (xs !! n) ?
I think, xs!!n is a single element.
Presumably `xs !! n == fromList xs !! n`

`xs !! () == fromList xs !! ()` seems to be a type error?
-- Keith
Sent from my phone with K-9 Mail.
On April 11, 2021 10:35:53 AM UTC, Tom Ellis
On Sun, Apr 11, 2021 at 12:03:04PM +0200, Henning Thielemann wrote:
On Sun, 11 Apr 2021, Akhra Gannon wrote:
It's distributive under IsList. fromList (xs !! n) == (fromList xs) !! n
fromList (xs !! n) ?
I think, xs!!n is a single element.
Presumably `xs !! n == fromList xs !! n` _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Maybe `xs !! n == fromList xs !! fromEnum n`?
-- Keith
Sent from my phone with K-9 Mail.
On April 11, 2021 10:35:53 AM UTC, Tom Ellis
On Sun, Apr 11, 2021 at 12:03:04PM +0200, Henning Thielemann wrote:
On Sun, 11 Apr 2021, Akhra Gannon wrote:
It's distributive under IsList. fromList (xs !! n) == (fromList xs) !! n
fromList (xs !! n) ?
I think, xs!!n is a single element.
Presumably `xs !! n == fromList xs !! n` _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Sorry to spam, just realized that destroys the Map and (->) instances.
-- Keith
Sent from my phone with K-9 Mail.
On April 11, 2021 10:35:53 AM UTC, Tom Ellis
On Sun, Apr 11, 2021 at 12:03:04PM +0200, Henning Thielemann wrote:
On Sun, 11 Apr 2021, Akhra Gannon wrote:
It's distributive under IsList. fromList (xs !! n) == (fromList xs) !! n
fromList (xs !! n) ?
I think, xs!!n is a single element.
Presumably `xs !! n == fromList xs !! n` _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
participants (7)
-
Akhra Gannon
-
Carter Schonwald
-
Dannyu NDos
-
George Wilson
-
Henning Thielemann
-
Keith
-
Tom Ellis