{-# LANGUAGE TemplateHaskell , FlexibleInstances, UndecidableInstances, OverlappingInstances, MultiParamTypeClasses, GeneralizedNewtypeDeriving, DeriveDataTypeable, TypeFamilies #-} module StateVersions.AppState2 where import Happstack.State import Control.Monad import Control.Monad.Reader import Control.Monad.State import Data.Typeable import Data.Data import qualified StateVersions.AppState1 as Old newtype AppState = AppState (Int,Int) deriving (Read, Show, Typeable, Data) $(deriveSerialize ''AppState) -- We need to make our Migrate instance between the two states. -- As you can see, Migrate needs to be defined as Migrate Old New. -- In this case, we do a very simple migration and just convert -- the singleton to the first element of the tuple. instance Migrate Old.AppState AppState where migrate (Old.AppState i) = AppState (i,0) -- instance Version AppState where mode = extension 1 (Proxy :: Proxy Old.AppState) -- extension is the preferred way to create the version instance -- for your migration. You just need to provide it with the number -- of the version and a Proxy corresponding to the directly previous -- state. Since the version in the default instance starts with a -- version number of 0, we choose 1 as the version. instance Component AppState where type Dependencies AppState = End -- no dependencies initialValue = AppState (0,0) incVal :: Update AppState () incVal = do AppState (i,j) <- get put $ AppState (i+1,j+1) askVal :: Query AppState (Int,Int) askVal = do AppState p <- ask return p $(mkMethods ''AppState ['askVal, 'incVal])