comonad-extras-4.0.1: Exotic comonad transformers

Copyright(C) 2008-2015 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityprovisional
Portabilityportable
Safe HaskellSafe
LanguageHaskell98

Control.Comonad.Store.Pointer

Contents

Description

The array-backed store (state-in-context/costate) comonad transformer is subject to the laws:

x = seek (pos x) x
y = pos (seek y x)
seek y x = seek y (seek z x)

Thanks go to Russell O'Connor and Daniel Peebles for their help formulating and proving the laws for this comonad transformer.

This basic version of this transformer first appeared on Dan Piponi's blog at http://blog.sigfpe.com/2008/03/comonadic-arrays.html.

Since this module relies on the non-Haskell 98 arrays package, it is located here instead of in comonad-transformers.

NB: attempting to seek or peek out of bounds will yield an error.

Synopsis

The Pointer comonad

pointer :: Array i a -> i -> Pointer i a Source #

runPointer :: Pointer i a -> (Array i a, i) Source #

The Pointer comonad transformer

data PointerT i w a Source #

Constructors

PointerT (w (Array i a)) i 
Instances
(ComonadEnv m w, Ix i) => ComonadEnv m (PointerT i w) Source # 
Instance details

Defined in Control.Comonad.Store.Pointer

Methods

ask :: PointerT i w a -> m #

(Comonad w, Ix i) => ComonadStore i (PointerT i w) Source # 
Instance details

Defined in Control.Comonad.Store.Pointer

Methods

pos :: PointerT i w a -> i #

peek :: i -> PointerT i w a -> a #

peeks :: (i -> i) -> PointerT i w a -> a #

seek :: i -> PointerT i w a -> PointerT i w a #

seeks :: (i -> i) -> PointerT i w a -> PointerT i w a #

experiment :: Functor f => (i -> f i) -> PointerT i w a -> f a #

(ComonadTraced m w, Ix i) => ComonadTraced m (PointerT i w) Source # 
Instance details

Defined in Control.Comonad.Store.Pointer

Methods

trace :: m -> PointerT i w a -> a #

Ix i => ComonadTrans (PointerT i) Source # 
Instance details

Defined in Control.Comonad.Store.Pointer

Methods

lower :: Comonad w => PointerT i w a -> w a #

Ix i => ComonadHoist (PointerT i) Source # 
Instance details

Defined in Control.Comonad.Store.Pointer

Methods

cohoist :: (Comonad w, Comonad v) => (forall x. w x -> v x) -> PointerT i w a -> PointerT i v a #

(Functor w, Ix i) => Functor (PointerT i w) Source # 
Instance details

Defined in Control.Comonad.Store.Pointer

Methods

fmap :: (a -> b) -> PointerT i w a -> PointerT i w b #

(<$) :: a -> PointerT i w b -> PointerT i w a #

(Comonad w, Ix i) => Comonad (PointerT i w) Source # 
Instance details

Defined in Control.Comonad.Store.Pointer

Methods

extract :: PointerT i w a -> a #

duplicate :: PointerT i w a -> PointerT i w (PointerT i w a) #

extend :: (PointerT i w a -> b) -> PointerT i w a -> PointerT i w b #

(Comonad w, Ix i) => Extend (PointerT i w) Source # 
Instance details

Defined in Control.Comonad.Store.Pointer

Methods

duplicated :: PointerT i w a -> PointerT i w (PointerT i w a) #

extended :: (PointerT i w a -> b) -> PointerT i w a -> PointerT i w b #

runPointerT :: PointerT i w a -> (w (Array i a), i) Source #

pointerBounds :: (Comonad w, Ix i) => PointerT i w a -> (i, i) Source #

Extract the bounds of the currently focused array