Generalize indexing function

Akhra Gannon tanuki at gmail.com
Sun Apr 11 07:01:47 UTC 2021


It's distributive under IsList.

fromList (xs !! n) == (fromList xs) !! n

On Sat, Apr 10, 2021, 11:33 PM George Wilson <george at wils.online> wrote:

> 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, <ndospark320 at gmail.com> 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 at haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
>>
> _______________________________________________
> Libraries mailing list
> Libraries at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/libraries/attachments/20210411/c5f41de1/attachment.html>


More information about the Libraries mailing list