[Haskell-cafe] Help wanted: Lazy multiway zipper with mismached intervals

Robin Green greenrd at greenrd.org
Mon Sep 26 14:28:42 EDT 2005


On Monday 26 September 2005 17:14, Rene de Visser wrote:
> Hello,
>
> I need to zip together multiple lists.
>
> The lists are sorted by date, and each entry in the list represents data
> for a time interval.
> The time intervals between the lists may be missmatched from each other.

Is this the sort of thing you want?

module Main where

data Event = Event { time :: Int, what :: String } deriving (Eq, Show)

zipToMaybes :: [Event] -> [Event] -> [(Maybe Event, Maybe Event)]
zipToMaybes [] [] = []
zipToMaybes [] (h:t) = ((Nothing, Just h):(zipToMaybes [] t))
zipToMaybes (h:t) [] = ((Just h, Nothing):(zipToMaybes t []))
zipToMaybes (ha:ta) (hb:tb)
	| (time ha) == (time hb)  = ((Just ha, Just hb):(zipToMaybes ta tb))
	| (time ha) < (time hb)   = ((Just ha, Nothing):(zipToMaybes ta (hb:tb)))
	| otherwise               = ((Nothing, Just hb):(zipToMaybes (ha:ta) tb))

main = interact $ const $ show $ zipToMaybes [Event 0 "Got up", Event 1 "Had 
breakfast", Event 3 "Went to work"] [Event 0 "Got up", Event 2 "Went to 
work"]



More information about the Haskell-Cafe mailing list