
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