# Comonadic Iterator Implementation Attempt ## Haskell Implementation ```haskell= {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE MultiParamTypeClasses #-} -- Comonad (as in Control.Comonad which is not yet? in the standard library) class Functor w => Comonad w where extract :: w a -> a duplicate :: w a -> w (w a) duplicate = extend id extend :: (w a -> b) -> w a -> w b extend f = fmap f . duplicate -- Identity comonad data Identity a = Id a instance Functor Identity where fmap f (Id x) = Id (f x) instance Comonad Identity where extract (Id x) = x duplicate = Id -- ComonadStore (as in Control.Comonad.Store.Class which is not yet? in the standard library) class Comonad w => ComonadStore s w | w -> s where pos :: w a -> s peek :: s -> w a -> a peeks :: (s -> s) -> w a -> a peeks f w = peek (f (pos w)) w seek :: s -> w a -> w a seek s = peek s . duplicate seeks :: (s -> s) -> w a -> w a seeks f = peeks f . duplicate experiment :: Functor f => (s -> f s) -> w a -> f a experiment f w = fmap (`peek` w) (f (pos w)) -- Iterator data type, a ComonadStore -- exactly following the definition of StoreT in Control.Comonad.Store.Class -- note: having w other than Identity comonad might be an overkill (see Haskell StoreT vs. Store) data Iterator i w v = It (w (i -> v)) i instance Functor w => Functor (Iterator i w) where fmap f (It wf i) = It (fmap (f .) wf) i instance Comonad w => Comonad (Iterator i w) where duplicate (It wf i) = It (extend It wf) i extend f (It wf i) = It (extend (\wf' i' -> f (It wf' i')) wf) i extract (It wf i) = extract wf i instance Comonad w => ComonadStore i (Iterator i w) where pos (It _ i) = i peek i (It wf _) = extract wf i peeks f (It wf i) = extract wf (f i) seek i (It wf _) = It wf i seeks f (It wf i) = It wf (f i) -- Connectivities as functions type Conn i = i -> Integer -> i -- deref is comonad’s extract deref :: Comonad w => Iterator i w v -> v deref = extract -- partial shifting does not seem to be implementable using comonadic operations -- at least not if partial shifting changes the index type pshift :: Comonad w => Conn i -> Iterator i w v -> Iterator Integer Identity (Iterator i w v) pshift c it = It (Id (\i -> seeks (`c` i) it)) 0 -- ??? -- integer-shifting is easy (if we have iterators with integer index type) ishift :: Comonad w => Integer -> Iterator Integer w v -> Iterator Integer w v ishift o = seeks $ (+) o -- this is IR-style application of integer shifting, -- that is, the composition of deref and shifting cishift :: Comonad w => Comonad ww => Integer -> Iterator Integer w (Iterator i ww v) -> Iterator i ww v cishift o = deref . ishift o -- alternative definition, directly using monad interface: -- cishift o = peeks $ (+) o -- combined shifting is just the composition of partial shifting and integer shifting cshift :: Comonad w => (Conn i, Integer) -> Iterator i w v -> Iterator i w v cshift (c, o) = cishift o . pshift c -- alternative defintion, directly using monad interface: -- cshift (c, o) = seeks (`c` o) ``` Problems: - I failed to find a partial shifting implementation based on the comonad interface. - This specific definition of partial shifting suffers from the same problems as Anton’s iterator of iterator approach: it makes full shifting of partial shifted iterators impossible Example usage in REPL: ```haskell= > x = It (Id id) (3, 5) > deref x (3, 5) > iconn (i, j) o = (i + o, j) > jconn (i, j) o = (i, j + o) > deref $ cshift (iconn, 1) x (4, 5) > deref $ ishift 3 $ cshift (iconn, 1) $ pshift jconn $ cshift (iconn, 1) x ERROR! ``` ## Non-comonadic Implementations ### Iterators as Recursive Data Types ```haskell= type Conn i = i -> Integer -> i data Iterator i v = It i (i -> v) | Partial (Conn i) (Iterator i v) cshift :: (Conn i, Integer) -> Iterator i v -> Iterator i v cshift (c, o) (It i f) = It (c i o) f cshift (c, o) (Partial cc it) = Partial cc (cshift (c, o) it) pshift :: Conn i -> Iterator i v -> Iterator i v pshift c it = Partial c it ishift :: Integer -> Iterator i v -> Iterator i v ishift o (Partial c it) = cshift (c, o) it deref :: Iterator i v -> v deref (It i f) = f i ``` Here, everything works as expected. Example usage in REPL: ```haskell= > x = It (3, 5) id > deref x (3, 5) > iconn (i, j) o = (i + o, j) > jconn (i, j) o = (i, j + o) > deref $ cshift (iconn, 1) x (4, 5) > deref $ ishift 3 $ cshift (iconn, 1) $ pshift jconn $ cshift (iconn, 1) x (5, 8) ``` ### Iterators using Stack of Connectivities (Using the Recursive List Type) ```haskell= type Conn i = i -> Integer -> i data Iterator i a = It [Conn i] i (i -> a) cshift :: (Conn i, Integer) -> Iterator i a -> Iterator i a cshift (c, o) (It cs i f) = It cs (c i o) f pshift :: Conn i -> Iterator i a -> Iterator i a pshift c (It cs i f) = It (c:cs) i f ishift :: Integer -> Iterator i a -> Iterator i a ishift o (It (c:cs) i f) = cshift (c, o) (It cs i f) deref :: Iterator i a -> a deref (It [] i f) = f i ``` Here, everything works as expected. Example usage in REPL: ```haskell= > x = It [] (3, 5) id > deref x (3, 5) > iconn (i, j) o = (i + o, j) > jconn (i, j) o = (i, j + o) > deref $ cshift (iconn, 1) x (4, 5) > deref $ ishift 3 $ cshift (iconn, 1) $ pshift jconn $ cshift (iconn, 1) x (5, 8) ```