[Haskell-cafe] Inverse of HaskellDB

Jeremy Shaw jeremy at n-heptane.com
Thu Sep 30 14:07:28 EDT 2010


On Wed, Sep 29, 2010 at 5:21 AM, Michael Snoyman <michael at snoyman.com> wrote:
> I think this approach is not possible without involving some fairly
> ugly unsafeInterleaveIO/unsafePerformIO calls. A simple example using
> a common web programming example: support I have a multi-user blog
> site, where each user can have multiple entries. I would model this
> using standard Haskell datatypes as:
>
> data Entry = Entry { title :: String, content :: String }
> data Blogger = Blogger { name :: String, entries :: [Entry] }
>
> Obviously we'll need some kind of blogger loading function:
>
> getBloggerByName :: String -> IO Blogger

That is pretty close to how it would look using happstack-state. Here
is a complete, runnable example which defines the types, a query,
creates/initializes the database, performs the query, and prints the
results.

> {-# LANGUAGE DeriveDataTypeable, FlexibleContexts, MultiParamTypeClasses, TemplateHaskell, TypeSynonymInstances, TypeFamilies #-}
> module Main where
>
> import Control.Exception (bracket)
> import Control.Monad.Reader (ask)
> import Data.Data
> import Happstack.Data
> import Happstack.Data.IxSet
> import Happstack.State

A simple type to identify a particular blogger:

> newtype Blogger = Blogger { name :: String }
>     deriving (Eq, Ord, Read, Show, Data, Typeable)
> $(deriveSerialize ''Blogger)
> instance Version Blogger

The deriveSerialize instance automatically creates the instances for
serializing and deserializing to/from a binary representation for
storage, transmission, etc.

The Version instance is used for migration when the data type changes.
(Since there is no previous version of this type to migrate from, we
don't have to specify anything).

We create a similar type for the title of the blog post:

> newtype Title = Title { unTitle :: String }
>     deriving (Eq, Ord, Read, Show, Data, Typeable)
> $(deriveSerialize ''Title)
> instance Version Title

And a simple record which actually contains a blog post:

> data Entry =
>     Entry { title   :: Title
>           , blogger :: Blogger
>           , content :: String
>           }
>     deriving (Eq, Ord, Read, Show, Data, Typeable)
> $(deriveSerialize ''Entry)
> instance Version Entry

Obviously, it could be expanded to support tags, posted date, whether
or not in is published, etc. Next we create an IxSet which holds all
the Entries that have been posted:

> $(inferIxSet "Entries" ''Entry 'noCalcs [''Blogger, ''Title])

An IxSet is a bit like a normal Set, except it has indexes, which you
can use for performing queries. In this case, we use Blogger and Title
as indexes.

Next we define a component that actually stores the Entries:

> instance Component Entries where
>     type Dependencies Entries = End
>     initialValue = fromList [ Entry { title   = Title "10 Reasons you should use Happstack."
>                                     , blogger = Blogger "stepcut"
>                                     , content = "..."
>                                     }
>                             , Entry { title   = Title "Persistence made easy!"
>                                     , blogger = Blogger "Jeremy Shaw"
>                                     , content = "..."
>                                     }
>                             ]

This component is prepopulated with 2 entries. Now we want to define a
query which retrieves all the entries by a particular Blogger:

> getEntriesByBlogger :: Blogger -> Query Entries Entries
> getEntriesByBlogger blogger =
>     do e <- ask
>        return (e @= blogger)

The Query monad is essentially a specialized version of the Reader
monad. So we use 'ask' to get the Entries from the Entries
component. (@=) is an IxSet function which selects all the Entries with
the specified blogger.

Next we 'register' all the functions we want to use as queries for the
Entries Component:

> $(mkMethods ''Entries ['getEntriesByBlogger])

And finally, here is a main function which initializes the transaction
system, performs a query, prints the results, and shuts the
transaction system down:

> main :: IO ()
> main =
>     bracket (startSystemState (Proxy :: Proxy Entries)) shutdownSystem $ \_ ->
>         do postsByStepcut <- query (GetEntriesByBlogger (Blogger "stepcut"))
>            print postsByStepcut

Note that there is no outside or additional configuration which needs
to be done. If you have the happstack-state libraries installed on
your system, then you can simply run this program. You do not need to
configure or initialize any external database system.

The queries and updates are thread-safe, ACID-transactions. You can
use almost any Haskell datatype declared using the normal Haskell
syntax. Basically, if you could write a pair of Read/Show instances
for the type, then you can probably use it directly with
happstack-state. So that means the type can not have functions,
existentials, and a few other things. But Trees, etc, are no problem.

The queries and updates are just straight-forward functions in the
Reader and State monads. So, there is no special query language or DSL
that you need to learn. You have the full, expressive power of Haskell
at your disposal.

- jeremy


More information about the Haskell-Cafe mailing list