Infinite lists in real world programs

Hello Café, I was wondering if using infinite lists was a viable and efficient solution in haskell programs (I mean not simple prototypes) : I was considering using them to model agents in a hierarchical multi-agent application for school. A list would representate the state of an agent at a step of the program. Let's say we have two simple agents, one multiplying its input by 2 and the other dividing it by 4 : agent1 = fmap (*2) agent2 = fmap (/4) allValues = xs where ys = agent1 xs xs = 100:agen2 ys main = do mapM_ print $ take 100 allValues Of course, in a real program, an agent would rather take a list of multiple agents (i.e. a list of lists) in input, so that its ouput could depend on what several agents feed him. Some could state what I'm trying to do is FRP, and I agree. But it remains a simple goal so I'd like to keep the program simple, and not go into the whole complexity of a FRP framework (and I'm working with a non-haskeller). For instance, with my solution, I cannot dynamically connect or disconnect agents during the runtime, but I'll will not need to do that in my program. Besides, I'd like to try to implement this myself, not use an already existing framework. So is it viable or would the use of multiple infinite lists kill the performances?

On Wed, Dec 15, 2010 at 02:52:11PM +0100, Yves Parès wrote:
Hello Café,
So is it viable or would the use of multiple infinite lists kill the performances?
Sounds perfectly reasonable to me. I don't see any reason why using multiple infinite lists would have anything to do with the performance of your program -- unless you do something silly like try to compute their length. =) -Brent

try to compute their length
Yes ^^, that's silly.
I don't see any reason why using multiple infinite lists would have anything to do with the performance
That's comforting. Well, it seems to be a very simple, haskellish and
elegant solution, so basic pragmatism -- with an slice of pessimism -- tells
it was too good too be true ^^.
2010/12/15 Brent Yorgey
On Wed, Dec 15, 2010 at 02:52:11PM +0100, Yves Parès wrote:
Hello Café,
So is it viable or would the use of multiple infinite lists kill the performances?
Sounds perfectly reasonable to me. I don't see any reason why using multiple infinite lists would have anything to do with the performance of your program -- unless you do something silly like try to compute their length. =)
-Brent
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Wed, Dec 15, 2010 at 06:38:04PM +0100, Yves Parès wrote:
try to compute their length
Yes ^^, that's silly.
I don't see any reason why using multiple infinite lists would have anything to do with the performance
That's comforting. Well, it seems to be a very simple, haskellish and elegant solution, so basic pragmatism -- with an slice of pessimism -- tells it was too good too be true ^^.
Premature pessimism is the root of all procrastination. -Brent

It sounds like a good fit for your problem as stated. One thing to note is that Haskell will give you great abstractions for very strong amounts of code, as long as what you want to do is a good fit for the abstraction. Haskell makes it quite hard to fit a square peg into a round hole, so if one day you decide you need an agent that generates random numbers, you can either do dangerous stuff with unsafeInterleaveIO or you'll need to find a more flexible abstraction. Cheers, Edward

if one day you decide you need an agent that generates random numbers
I could say that my agents now run in a certain monad, I just would have to
transform my basic agents to :
agent1 = liftM . fmap (*2)
(or even agen1 = fmap . fmap (*2), however it is less readable IMO)
Thanks for your comments.
2010/12/15 Edward Z. Yang
It sounds like a good fit for your problem as stated. One thing to note is that Haskell will give you great abstractions for very strong amounts of code, as long as what you want to do is a good fit for the abstraction. Haskell makes it quite hard to fit a square peg into a round hole, so if one day you decide you need an agent that generates random numbers, you can either do dangerous stuff with unsafeInterleaveIO or you'll need to find a more flexible abstraction.
Cheers, Edward

Excerpts from Yves Parès's message of Wed Dec 15 13:28:11 -0500 2010:
if one day you decide you need an agent that generates random numbers
I could say that my agents now run in a certain monad, I just would have to transform my basic agents to : agent1 = liftM . fmap (*2)
(or even agen1 = fmap . fmap (*2), however it is less readable IMO)
Yes, it's one of the really great things about Haskell. :-) But since implementing functionality takes so much less code in Haskell than in many other languages, don't be shy to rewrite as necessary. Edward

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?

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
participants (3)
-
Brent Yorgey
-
Edward Z. Yang
-
Yves Parès