
dear haskellers -- this email is an (il)literate haskell file. suppose i have class of computations a -> State s b. for concreteness, let's say i'm writing a library of on-line statistical summary functions, like
{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances #-}
module Foo where
import Control.Monad import Control.Monad.State import Control.Monad.State.Class
data RunningAverageState = S Double Int
runningAverage :: Double -> State RunningAverageState Double runningAverage v = do S sum count <- get let nsum = sum + v ncount = count + 1 put $ S nsum ncount return $ nsum / (fromIntegral ncount)
test = take 10 $ evalState (mapM runningAverage [1..]) $ S 0 0
test -> [1.0,1.5,2.0,2.5,3.0,3.5,4.0,4.5,5.0,5.5] here "on-line" means that we may be taking data from an intermittant external source, e.g. a data generator IO [Double], say, and want to be able to feed the summarizer datum one-by-one, and produce intermediate summaries. also we may want to be able to serialize our computation state (with Data.Binary, say) so that we can resume data collection and summarization later. naturally i want to create some common higher order operations on these primitives, like applying them to a stream of data, or combining them in some way. it seems that one would want some kind of type class to define a common interface to them.
class (MonadState s m) => Summarizer s m | m -> s where initialState :: s runOne :: Double -> m Double
where initialize puts some intial state into the system, and runOne collects and summarizes the next piece of data. an instance for runningAverage would look like
instance Summarizer RunningAverageState (State RunningAverageState) where initialState = S 0 0 runOne = runningAverage
but how would i use this, e.g.
--summarizeMany vs = last $ evalState (mapM runOne vs) initialState
does not compile. 1) what am i doing wrong? what are the right type class and instance declarations? 2) is there a better way of expressing this kind of "on-line" calculation, perhaps in pure (non-monadic) functions? best, ben

Am Freitag 18 September 2009 16:38:19 schrieb Ben:
instance Summarizer RunningAverageState (State RunningAverageState) where initialState = S 0 0 runOne = runningAverage
but how would i use this, e.g.
--summarizeMany vs = last $ evalState (mapM runOne vs) initialState
does not compile.
No, summarizeMany would have the type (Summarizer m s) => [Double] -> Double which is ambiguous. You would have to make m somehow accessible (dummy argument?).
1) what am i doing wrong? what are the right type class and instance declarations?
2) is there a better way of expressing this kind of "on-line" calculation, perhaps in pure (non-monadic) functions?
Perhaps scanl ?

On Fri, Sep 18, 2009 at 8:28 AM, Daniel Fischer
No, summarizeMany would have the type
(Summarizer m s) => [Double] -> Double
which is ambiguous. You would have to make m somehow accessible (dummy argument?).
yes, i realize the type is ambiguous, ghc even says so in the error message. but a dummy argument doesn't seem very elegant.
2) is there a better way of expressing this kind of "on-line" calculation, perhaps in pure (non-monadic) functions?
Perhaps scanl ?
i originally was using mapAccumL (i need the final result of the state) but it seemed like i was missing the point of the State monad. i guess that is a matter of opinion? b
participants (2)
-
Ben
-
Daniel Fischer