Friday, August 30, 2013

MFlow using persistent with sqlite backend

There are excellent libraries that I want to make interoperable with MFlow one of them is Persistent. It allows to define backend-independent data layers. In the previous post I mentioned an example of direct integration of TCache -the cache of MFlow- with Amazon web services. In this example I will show how MFlow and Persistent directly interact. 

Since in this case, the database is a in memory instance of sqlite, It does not make sense to cache data. But since Persistent can interact with remote SQL and nonSQL databases, I need to integrate TCache with Persistent for caching in the near future.

But first, this example illustrates the use of MFlow with Persistent. The example is at:


The code is taken from http://www.yesodweb.com/book/persistent by modifying the first example and making some guesses by looking at the prostgresSQL version , both are console-oriented programs.

Note how little additions are necessary to change a console application of the sample to a MFlow application.

The example has a navigation of four pages and you can go forward and backward. While the flow looks like an ordinary imperative program, yo can go back and fort and to introduce any bookmark without producing navigation errors.

Additionally you can press the back button, change the form input and see how the responses match the register values. 


This is the code:

{-# LANGUAGE EmptyDataDecls    #-}
{-# LANGUAGE FlexibleContexts  #-}
{-# LANGUAGE GADTs             #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes       #-}
{-# LANGUAGE TemplateHaskell   #-}
{-# LANGUAGE TypeFamilies      #-}
{-# LANGUAGE NoMonomorphismRestriction #-}

module MFlowPersistent

where

import           MFlow.Wai.Blaze.Html.All
import           Control.Monad.IO.Class  (liftIO)
import           Database.Persist
import           Database.Persist.Sqlite
import           Database.Persist.TH

import           System.IO.Unsafe

import           Menu



share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persistLowerCase|
Person
    name String
    age Int Maybe
    deriving Show
BlogPost
    title String
    authorId PersonId
    deriving Show
|]

-- Uncomment this to run the example alone
--main= do
--  migratesqlite
--  runNavigation "" . transientNav $ mFlowPersistent
-- 
--askm= ask 

  
pool= unsafePerformIO $ createSqlitePool ":memory:" 10

runSQL sql= liftIO $  runSqlPersistMPool sql pool

migratesqlite= runSQL $ runMigration migrateAll

mFlowPersistent ∷  FlowM Html IO ()
mFlowPersistent = do
    (name, age) ← askm $ (,) 
                         <$> getString Nothing <! hint "your name" 
                         <++ br
                         <*> getInt    Nothing <! hint "your age"
                         <** br
                         ++> submitButton "enter"
                         
    userId ←  runSQL  $ insert $ Person name $ Just age

    post ←  askm $ getString Nothing <! hint "your post" <** submitButton "enter"
    runSQL  $ insert $ BlogPost post userId

    oneUserPost ←  runSQL  $ selectList [BlogPostAuthorId ==. userId] [LimitTo 1]

    askm $   b << show (oneUserPost ∷  [Entity BlogPost]) 
         ++> br 
         ++> wlink () << b  "click here"

    user ←  runSQL  $ get userId

    askm $   b << show (user ∷  Maybe Person) 
         ++> br ++> wlink ()  << b  "click here"
    where
    hint h=  [("placeholder",h)]

No comments: