
8 Oct
2003
8 Oct
'03
4:40 p.m.
Jan-Willem Maessenwrites: > Tomasz Zielonka wrote: > [...] > > data Stat i o = -- aggregate function taking i's on input and producing o > > forall s. Stat > > s -- init > > (s -> i -> s) -- update > > (s -> o) -- result > [...] > * But it bugs me that an awful lot of examples of existential typing > could be obtained simply by currying / lazy evaluation. In this > case, however, the "update" function lets us absorb additional input > as in the subsequent message (which I've now accidentally deleted): I'm not convinced that existentials are needed here. mike import Prelude hiding ( sum ) data Stat i o = Stat { update :: i -> Stat i o , result :: o } runStat :: Stat i o -> [i] -> o runStat stat = result . foldl update stat stateStat :: (s -> i -> s) -> (s -> o) -> s -> Stat i o stateStat updateF resultF initState = Stat { update = \i -> stateStat updateF resultF (updateF initState i) , result = resultF initState } instance Functor (Stat a) where fmap f st = Stat { update = fmap f . update st, result = f (result st) } avg :: Fractional n => Stat n n avg = fmap (\(s,c) -> if c /= 0 then s/c else 0) (pair sum count) fold :: (a -> b -> a) -> a -> Stat b a fold f = stateStat f id count :: Num n => Stat a n count = fold (\s _ -> s+1) 0 sum :: Num n => Stat n n sum = fold (+) 0 pair :: Stat a b -> Stat a c -> Stat a (b,c) pair (Stat upd1 res1) (Stat upd2 res2) = Stat (\i -> pair (upd1 i) (upd2 i)) (res1, res2) main = error "no main"