{-# LANGUAGE TemplateHaskell , FlexibleInstances, UndecidableInstances, OverlappingInstances, MultiParamTypeClasses, GeneralizedNewtypeDeriving, DeriveDataTypeable, TypeFamilies #-} module StateVersions.AppState1 where import Happstack.State import Control.Monad import Control.Monad.Reader import Control.Monad.State import Data.Typeable import Data.Data newtype AppState = AppState Int deriving (Read, Show, Typeable, Data) instance Version AppState -- Now, I've said that Version is important for migrations -- but the nice thing is that you don't have to plan in advance -- that you may be migrating your state. You can just use the -- default instance of Version for the very first application -- state you define. It's only future versions that need -- anything other than the default instance for Version. $(deriveSerialize ''AppState) instance Component AppState where type Dependencies AppState = End -- no dependencies initialValue = AppState 0 askVal :: Query AppState Int askVal = do AppState i <- ask return i incVal :: Update AppState () incVal = do AppState i <- get put $ AppState (i+1) $(mkMethods ''AppState ['askVal,'incVal])