Intro to HAppS-State
Update: A demo of the finished application is now available. See this post for more information.
This post is written in literate haskell, so it should compile as-is in a .lhs file.
In my last article on HAppS, I gave a brief introduction to working with the HAppS web server to serve a basic user login/registration page and handle the form submission. In this article we are going to develop the framework for basic session management. The example file AllIn.hs in the HAppS source tree is very similar to this. I have made a few changes to demonstrate some different cases that one might encounter. So without further ado, we'll start with our standard import statements.
> {-# OPTIONS -fglasgow-exts #-}
> {-# LANGUAGE TemplateHaskell , FlexibleInstances,
>              UndecidableInstances, OverlappingInstances,
>              MultiParamTypeClasses, GeneralizedNewtypeDeriving #-}
> 
> module Session where
> 
> import qualified Data.Map as M
> import Control.Monad
> import Control.Monad.Reader
> import Control.Monad.State (modify,put,get,gets)
> import Data.Generics hiding ((:+:))
> import HAppS.Server
> import HAppS.State
> import HAppS.Data
The first thing to do is create some data structures to store the session in HAppS state. We need some type of session key to store in the browser cookie. For now we'll make it a simple Integer. Later it might be good to make it a larger (128 bits or more) cryptographically secure random number.
> type SessionKey = Integer
For this simple example, we'll only need to store the username on the server. We could make a simple type alias like we did for the session key, but I'll make it a data type to show how a more complex implementation might work.
> data SessionData = SessionData {
>   sesUser :: String
> } deriving (Read,Show,Eq,Typeable,Data)
Now we need a map so that we can look up the session data when we get the session key from the browser cookie. I'll make this a generic data type so any type of data can be used as the value.
> data Sessions a = Sessions {unsession::M.Map SessionKey a}
>   deriving (Read,Show,Eq,Typeable,Data)
Since we're doing an authentication framework, we have to store the user's password (in a real system it would be a salted hash) and other user information. This could have been stored in the SessionData type. But there may be times when it's not convenient to look up a user by their session key, so we're going to make another data type to hold all the individual information for each user. Right now it will just be the username and password.
> data User = User {
>   username :: String,
>   password :: String
> } deriving (Show,Read,Typeable,Data)
Next we will make a state data structure to hold all of our HAppS state. To store data in HAppS state, your top-level data type (or types) must be an instance of the Component type class. To simplify things we'll make only the top level state type an instance of Component. You could just as easily separate the session data and the user data into separate components. Components give you transactions and persistence. If you want those assurances you can encapsulate stuff with a component. So if you want transactional updates to your user data separately from the session data, you might want to make them separate instances. But I'll leave those details for another post.
> data State = State {
>   sessions :: Sessions SessionData,
>   users :: M.Map String User
> } deriving (Show,Read,Typeable,Data)
Before we make state an instance of Component, there are some other things that have to be done first. State and our other complex data types created thus far must be instances of Serialize and Version. And they must be declared in the right order. The lowest-level data first. The Version instance is trivial. HAppS provides some TemplateHaskell code to create Serialize instances for you.
> instance Version SessionData > instance Version (Sessions a) > > $(deriveSerialize ''SessionData) > $(deriveSerialize ''Sessions) > > instance Version State > instance Version User > > $(deriveSerialize ''User) > $(deriveSerialize ''State) > > instance Component State where > type Dependencies State = End > initialValue = State (Sessions M.empty) M.empty
The Component instantiation requires you to specify dependencies and some initial value for the state. Since we don't have any other components, a simple End will work for the dependencies. An empty map will be our initial value.
If you did have other dependencies, they would be specified something like this:
type Dependencies State = Sessions SessionData :+:
                          Users :+:
                          End
If you leave out the 8 lines deriving Version and Serialize, you'll get a compiler error that looks something like the following:
No instances for (Data.Generics.SYB.WithClass.Basics.Data
                    NormalizeD State,
                  Default State,
                  Data.Generics.SYB.WithClass.Basics.Data XmlD State)
  arising from the superclasses of an instance declaration
               at Session.lhs:102:2
Possible fix:
  add an instance declaration for
  (Data.Generics.SYB.WithClass.Basics.Data NormalizeD State,
   Default State,
   Data.Generics.SYB.WithClass.Basics.Data XmlD State)
In the instance declaration for `Component State'
Unfortunately this isn't a very helpful message. For now, HAppS defaults to use XML for its serialization. From what I understand, that may change in the future. For now, if you see an error like this, check that you have made everything an instance of Serialize.
This example demonstrated the first steps to getting data into HAppS state. In the next post we'll look at how to access and manipulate the state.
Comments
Could you post a demo link?
What about scalability?
Does HAppS support data/process clustering?. If so Do the state is shared among the machines? . If not. How HappS can scale?