Skip to content

Instantly share code, notes, and snippets.

@barrucadu
Last active December 17, 2015 18:09
Show Gist options
  • Save barrucadu/5651188 to your computer and use it in GitHub Desktop.
Save barrucadu/5651188 to your computer and use it in GitHub Desktop.
Adventures with indexable data types, as talked about in http://blog.barrucadu.co.uk/2013/05/25/indexing-collections-in-haskell/
{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-}
module Indexable where
-- Our Indexables are all Traversables, and for the default implementation
-- of (!!!) we need fromJust.
import Data.Maybe (fromJust)
import Data.Traversable (Traversable(..))
-- For lists, we want to be able to index by any integral type, so we
-- need the generic functions from Data.List
import Data.List (genericLength, genericIndex)
-- We also want to be able to index maps
import Data.Map (Map(..), lookup)
-- Why not trees, as well?
import Data.Tree (Tree(..), flatten)
-- Let's also go for arrays
import Data.Ix (Ix(..))
import Data.Array.IArray (Array(..), (!), indices)
-- Finally, we need these in order to implement some more types we'll want
-- to be able to index.
import Control.Applicative (liftA, liftA2)
import Data.Foldable (Foldable(..))
import Data.Monoid (mappend)
-- Intuitively, an Indexable type is a container which can be indexed
-- by some value (be it a numeric key or some other type). Furthermore,
-- I don't think it makes sense to have a container which can be indexed,
-- but which can't be folded or mapped over. The two type classes which
-- implement this behaviour in a sane way are Foldable and Functor, and
-- a foldable functor is a Traversable.
class (Traversable t, Ord k) => Indexable t k where
(!!!) :: t a -> k -> a
(!+!) :: t a -> k -> Maybe a
ix !!! k = fromJust $ ix !+! k
ix !+! k = Just $ ix !!! k
-- Being able to deal with indexables hidden inside monads also sounds like
-- it could be a useful operation, so let's include some functions (and the
-- standard output-discarding variant) to do just this.
indexM :: (Monad m, Indexable i k) => m (i a) -> k -> m a
indexM ix k = ix >>= \i -> return $ i !!! k
indexM' :: (Monad m, Indexable i k) => m (i a) -> k -> m (Maybe a)
indexM' ix k = ix >>= \i -> return $ i !+! k
-- Not using `void` here, as I want to keep the type of `m` the same
-- as in the regular functions, but `void` has a Functor constraint.
indexM_ :: (Monad m, Indexable i k) => m (i a) -> k -> m ()
indexM_ ix k = indexM ix k >> return ()
-- The Indexable type is quite clearly a generalisation of [] and Map, and so
-- here are instances for those types!
instance Integral i => Indexable [] i where
(!!!) = genericIndex
xs !+! i | i < genericLength xs = Just $ xs !!! i
| otherwise = Nothing
instance Ord k => Indexable (Map k) k where
(!+!) = flip Data.Map.lookup
-- We can index trees as well, where the indexing depends on which
-- order we traverse the tree in. For simplicity, let's just go for a
-- pre-order.
-- This is inefficient, as it traverses the tree, however if we used a
-- balanced binary tree, this could be done in log time.
instance Integral i => Indexable Tree i where
tr !!! k = flatten tr !!! k
tr !+! k = flatten tr !+! k
-- For a final example on the standard types, let's consider
-- arrays. Unfortunately, UArray has no Traversable instance, although
-- I don't see why one couldn't be written.
instance Ix i => Indexable (Array i) i where
(!!!) = (!)
ar !+! i | i `elem` indices ar = Just $ ar !!! i
| otherwise = Nothing
-- Can't make tuples an instance of Indexable, as we can't specify a
-- homogeneous tuple type which must still be parameterised. However,
-- we can do the next best thing:
newtype Pair a = Pair { getPair :: (a, a) }
instance Functor Pair where
fmap f (Pair (a, b)) = Pair (f a, f b)
instance Foldable Pair where
fold (Pair (a, b)) = a `mappend` b
instance Traversable Pair where
sequenceA (Pair (a, b)) = liftA Pair $ liftA2 (,) a b
instance Integral i => Indexable Pair i where
(Pair (a, _)) !+! 0 = Just a
(Pair (_, b)) !+! 1 = Just b
_ !+! _ = Nothing
-- We can also implement Triple, ... as desired.
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment