[macid updates and queries, and floundering in ghci thomashartman1@gmail.com**20081002204354] hunk ./src/AppStateSetBased.hs 11 -import Control.Monad.Reader +import Control.Monad (liftM) +import Control.Monad.Reader (ask) hunk ./src/Controller.hs 143 - return $ tutlayoutU rglobs [] "home" + return $ tutlayoutU rglobs [] "dummydatainitialized" hunk ./src/Main.hs 24 - startSystemState entryPoint -- start the HAppS state system + startSystemState (Proxy :: Proxy AppState) -- start the HAppS state system hunk ./src/Main.hs 29 - where entryPoint :: Proxy AppState - entryPoint = Proxy hunk ./src/SerializeableUsers.hs 26 --- Users should also have Maybe a consultant profile, Maybe [list of jobs they want done] + addfile ./templates/dummydatainitialized.st hunk ./templates/dummydatainitialized.st 1 - +
Dummy data initialized. You should now have consultants +and jobs stored in your macid state. + +
Go back to macid dummy data? addfile ./templates/ghciflounderingaskdatastore.st hunk ./templates/ghciflounderingaskdatastore.st 1 - +
*Main> :i askDatastore
+
askDatastore :: Query AppState (Data.Set.Set User)
+
-- Defined at src/AppStateSetBased.hs:43:0-11
+
+
*Main> :i Query
+
type Query state =
+
Ev (Control.Monad.Reader.ReaderT state GHC.Conc.STM)
+
-- Defined in HAppS-State-0.9.2.1:HAppS.State.Types
+
+
data StateStuff.Method st where
+
...
+
Query :: forall st ev res.
+
(QueryEvent ev res) =>
+
(ev -> Query st res) -> StateStuff.Method st
+
-- Defined in HAppS.State.ComponentSystem
+
+
*Main> :t askDatastore :: Ev (Control.Monad.Reader.ReaderT AppState GHC.Conc.STM) (Data.Set.Set User)
+
askDatastore :: Ev (Control.Monad.Reader.ReaderT AppState GHC.Conc.STM) (Data.Set.Set User) :: Ev
+
(Control.Monad.Reader.ReaderT
+
AppState
+
GHC.Conc.STM)
+
(Data.Set.Set User)
+
*Main>
+
+
+
No type errors -- it works.
+ Now, click this link.
+
+ If everything worked right, you should now have two users and a
+ couple hundred jobs worth of test data
+ displaying in your jobs site.
+
+ What just happened?
addfile ./templates/macidupdatesandqueries.st
hunk ./templates/macidupdatesandqueries.st 1
-
+ Clicking initializedummydata passed off control to
+ spAddDummyData in Controller.hs. Keep that .hs file open in another window,
+ scrolled down to spAddDummyData, to follow along.
+
+ In spAddDummyData, pay particular attention to these two statements
+
+ There's a lot of type hackery and template haskell machinery behind those two lines.
+ But operationally, here's what is happening.
+
+ spAddDummyData queried the macid state, and checked whether the datastore, which is a set of users, is the empty set.
+ If it's the empty set, there is no existing data and the dummy data can be added safely, and then
+ a "dummy data success" page gets displayed. Otherwise no update happens and you get an error page.
+
+ The macid state of our job board is defined in AppStateSetBased,
+ in the AppState data declaration. As you may recall, we have seen AppState before, in runserver,
+ in our lesson on the main module.
+ AppState's use in startSystemState, in Main.hs, is what makes it the primary state component of our web app.
+
+ From AppStateSetBased.hs
+ (for optimal learning, open this file in another window):
+
+
+ -- Think of appdatastore as the database in a traditional web app.
+ This is the pattern for a data declaration for data that will be used by the macid state system.
+
+ AppState depends on the User and Sessions data types. The User data type in turn depends
+ on the Job and ConsultantProfile data types. Each of these data declarations follows this same pattern,
+ which you should verify for yourself by reading their data declarations in
+ SerializeableUsers.hs and
+ SerializeableSessions.hs.
+ As long as each subcomponent has been declared in the right way, components depending upon them can
+ be derived more of less hassle-free.
+
+ Because AppState is the top-level component, in addition to Read / Show / Serializeable / Version,
+ it is also an instance of Method and Component.
+
+ The Component instance just defines an initial value for macid: no users, no sessions.
+
+ The Method instance is a template haskell declaration that generates data declarations that can be used
+ as arguments to either query or update within a server part.
+
+ In the dummy data insertion above, we saw an example of this, with
+ query AskDatastore and update InitializeDummyData.
+
+ AskDatastore and InitializeDummyData are generated with template haskell, based on the definitions of
+ askDatastore and initializeDummyData, in AppStateSetBased.
+
+ If you do
+
+ *Main> :browse AppStateSetBased
+
+ you'll see a number of function/datatype pairs defined via template haskell, where the datatype has the
+ same name as the function, except it is upper-cased. askDatastore / AskDatastore, getUser / GetUser,
+ changePassword / ChangePassword, and so on. In every case, the upper-cased datatype is generated by
+ template haskell, whereas the lowercase function is a normal function.
+
+ Think of query actions as the macid equivalent of a select statement in sql, and update as the equivalent
+ of update/delete.
+
+ The functions that query actions are based on are in MonadReader.
+ askDatastore puts itself into MonadReader by its use of ask. This is a bit obfuscated by type systems
+ and the complicated types, but if you flounder around enough in ghci you can
+ fit askDatastore into a concrete type that makes this explicit.
+
+ The functions that update actions are based on are in MonadState.
+ InitializeDataStore puts itself into MonadState by the use of modify in a function that it depends on.
+
+ Alhough it is obvious that AskDatastore is a query action from its name,
+ you can't tell that it's a query action by asking ghci -- only that it is part of the macid system.
+
+ *Main> :i AskDatastore
+ However, if you ask ghci about askDatastore, upon which you know AskDatastore is based --
+ because of the lowercase -- you can confirm that it is a query.
+
+ *Main> :i askDatastore
+ The same goes for InitializeDummyData.
+
+ So remember, if you are reading some happs code and come across a macid action and aren't certain
+ whether it's a query or an update, a quick way to find out is to ask ghci for information about
+ the lowercase function it's based on.
+
+ Macid is one of the most powerful features of HApps, but I found it hard to learn.
+ There are a lot of types, and those signatures can get cryptic.
+ It took me a while to get as comfortable with the macid way of doing things as I was with sql.
+ But when I finally got it I was glad I made the effort.
+ I really feel that this is a much more powerful, straightforward way of
+ laying out a web app's functionality, and that I will win back the invested time
+ with more rapid development of future websites.
+
+ To get comfortable with macid
+
+ Macid is a bit complicated, and those type signatures can get cryptic.
+
+
+
+ What makes some of these generated data declarations.....
+
+ *Main> :i query
+ This may seem slightly less cryptic if you specify the concrete type in this specific instance as follows.
+
+ :t query :: AskDatastore -> WebT IO (Data.Set.Set User)
+ Still pretty cryptic though -- and how did I figure out that concrete type in the first place?
+
+ For now, just take the concrete type as an article of faith, or read
+ tk happs type floundering in ghci if you really must know.
+ Let's do a couple of ghci info queries.
+
+
+
+
+
+
+
+
+ Now loook at AppStateSetBased in yet another window.
+ Notice that there is no actual definition of AskDatastore.
+ This data type is derived by template haskell, and it is based on the askDatastore function, which
+ is a normal function.
+
+ askDatastore :: Query AppState (S.Set User)
+ The next thing to notice is that there are two kinds of template haskell definitions going on: queries, and updates.
+ We have already seen an example of a query: askDatastore/AskDatastore. If you look at the code in
+ spAddDummyData, and understand that this is a query,
+
+
+ Now let's look at an update which is used in spAddDummyData: initializeDummyData/InitializeDummydata.
+
+ *Main> :i InitializeDummyData
+ If you compare the information about
+
+!$
hunk ./templates/mainfunction.st 3
- Have a look at main function at the core of this web application. Have a look at Main.hs module at the core of this web application. Two bits of code that should jump out at you as being important are "entrypoint :: Proxy AppState"
- and "controller". Two bits of code that should jump out at you as being important are
hunk ./templates/mainfunction.st 7
- The entrypoint function has to do with the HAppS state system, and we'll pospone learning about it for later. We'll pospone learning about the HAppS state system (the first line) for later.
Think of it like this: askDatastore is a macid event that reads a value.
+
hunk ./templates/maciddummydata.st 11
- as described earler. Now, click this link.
+ as described earler.
hunk ./templates/maciddummydata.st 13
+Macid updates and queries
+
+
+
+
+
-- Data there gets stored permanently
+
-- Data in appsessions is stored permanently too, but we don't care as much about its persistence,
+
-- it's just to keep track of who is logged in at a point in time.
+
data AppState = AppState {
+
appsessions :: Sessions SessionData,
+
appdatastore :: S.Set User
+
deriving (Show,Read,Typeable,Data)
+
instance Version AppState
+
\$(deriveSerialize ''AppState)
+
+
+
+
+
+
data AskDatastore = AskDatastore
+
-- Defined at src/AppStateSetBased.hs:(178,2)-(191,27)
+
instance Serialize AskDatastore
+
-- Defined at src/AppStateSetBased.hs:(178,2)-(191,27)
+
instance Version AskDatastore
+
-- Defined at src/AppStateSetBased.hs:(178,2)-(191,27)
+
+
askDatastore :: Query AppState (Data.Set.Set User)
+
+
+
+
+$!
+
+
query :: (Control.Monad.Trans.MonadIO m, QueryEvent ev res) => ev -> m res
+
-- Defined in HAppS.State.Transaction
+
+
query :: AskDatastore -> WebT IO (Data.Set.Set User) :: AskDatastore -> WebT IO (Data.Set.Set User)
+
+
*Main> :i AskDatastore
+
data AskDatastore = AskDatastore
+
-- Defined at src/AppStateSetBased.hs:(177,2)-(190,27)
+
instance Serialize AskDatastore
+
-- Defined at src/AppStateSetBased.hs:(177,2)-(190,27)
+
instance Version AskDatastore
+
-- Defined at src/AppStateSetBased.hs:(177,2)-(190,27)
+
*Main> :i askDatastore
+
askDatastore :: Query AppState (Data.Set.Set User)
+
-- Defined at src/AppStateSetBased.hs:42:0-11
+
+
askDatastore = do
+
(s :: AppState ) <- ask
+
return . appdatastore \$ s
+
+
+
+
data InitializeDummyData = InitializeDummyData
+
-- Defined at src/AppStateSetBased.hs:(177,2)-(190,27)
+
instance Serialize InitializeDummyData
+
-- Defined at src/AppStateSetBased.hs:(177,2)-(190,27)
+
instance Version InitializeDummyData
+
-- Defined at src/AppStateSetBased.hs:(177,2)-(190,27)
+
instance (Serialize InitializeDummyData, Serialize ()) =>
+
UpdateEvent InitializeDummyData ()
+
-- Defined at src/AppStateSetBased.hs:(177,2)-(190,27)
+
*Main> :i initializeDummyData
+
initializeDummyData :: Update AppState ()
+
-- Defined at src/AppStateSetBased.hs:169:0-18
+
+
+
+
+
+