[Haskell-cafe] Infinite lists in real world programs

Brent Yorgey byorgey at seas.upenn.edu
Thu Dec 16 19:16:53 CET 2010


On Thu, Dec 16, 2010 at 06:52:58PM +0100, Yves Parès wrote:
> Okay, I started to experiment things, and I came to some remarks:
> First, I cannot use bare lists, because of the way their Applicative
> instance is declared.
> I have to use the newtype ZipList (in Control.Applicative).
> So I have roughly this :
> 
> import Control.Applicative
> 
> newtype AgentSig a = AgentSig (ZipList a)
>   deriving (Functor, Applicative)
> 
> (<+>) :: a -> AgentSig a -> AgentSig a
> v <+> (AgentSig (ZipList sig)) = AgentSig . ZipList $ v:sig
> 
> toList :: AgentSig a -> [a]
> toList (AgentSig (ZipList sig)) = sig
> 
> fromList :: [a] -> AgentSig a
> fromList = AgentSig . ZipList
> 
> This enables me to do things like :
> agent3 a b = (/) <$> a <*> b
> run = z
>   where x = agent1 y
>         y = 100 <+> agent2 x
>         z = agent3 x y
> 
> One problem though: How to make an instance of Monad out of AgentSig?

You can make a monad instance out of AgentSig as long as AgentSig
always contains an infinite list (otherwise the monad laws are not
satisfied).  It is based on the idea of "diagonalization".

  instance Monad AgentSig where
    return = fromList . repeat
    (AgentSig (ZipList xs)) >>= f = fromList $ diag (map (toList . f) xs)
      where diag ((y:_):zs) = y : diag (map tail zs)

So in the result of (a >>= f), the first element is taken from the
first element of applying f to the first element of a; the second
element is the second element in the result of applying f to the second
element of a; and so on.  Off the top of my head I am not sure what
this corresponds to in terms of agents or where it would be useful,
but I'm sure it must correspond to something interesting.

-Brent



More information about the Haskell-Cafe mailing list