[Haskell-cafe] Re: I just don't get it (data structures and OO)

David Menendez zednenem at psualum.com
Mon Jun 4 18:18:24 EDT 2007


Arie Peterson writes:

> There are two things one typically wants to do when working with a
> substructure of some larger data structure: (1) extract the
> substructure; and (2) change the larger structure by acting on the
> substructure. A 'Ref cx t' encodes both of these functions (for a
> substructure of type 't' and larger structure (context) of type 'cx').
> 
> > data Ref cx t
> >  = Ref
> >    {
> >      select :: cx -> t
> >    , update :: (t -> t) -> cx -> cx
> >    }
> 
> A Ref is a bit like a typed and composable incarnation of apfelmus's
> indices, or a wrapper around Tillmann's change* functions, containing
> not only a setter but also the accompanying getter.

That's a neat idiom. I wonder how far one could usefully generalize it.

For example,

    type Ref cx t = forall f. Functor f => (t -> f t) -> cx -> f cx
    
    newtype Id a = Id { unId :: a }
    instance Functor Id where fmap f = Id . f . unId
    
    newtype K t a = K { unK :: t }
    instance Functor (K t) where fmap = K . unK
    
    
    select :: Ref cx t -> cx -> t
    select ref = unK . ref K
    
    update :: Ref cx t -> (t -> t) -> cx -> cx
    update ref f = unId . ref (Id . f)
    
    
    rfst :: Ref (a,b) a
    rfst f (x,y) = fmap (\x' -> (x',y)) (f x)
    
In this implementation, composition of Refs is just function
composition.

    select (rfst . rfst) :: ((a,b),c) -> a
-- 
David Menendez <zednenem at psualum.com> | "In this house, we obey the laws
<http://www.eyrie.org/~zednenem>      |        of thermodynamics!"


More information about the Haskell-Cafe mailing list