freckle-app-1.4.0.0: Haskell application toolkit used at Freckle
Safe HaskellNone
LanguageHaskell2010

Freckle.App

Description

Micro-framework for building a non-web application

This is a version of the ReaderT Design Pattern.

https://www.fpcomplete.com/blog/2017/06/readert-design-pattern

Basic Usage

Start by defining a type to hold your global application state:

data App = App
  { appDryRun :: Bool
  , appLogger :: Logger
  }

This type can be as complex or simple as you want. It might hold a separate Config attribute or may keep everything as one level of properties. It could even hold an IORef if you need mutable application state.

The only requirements are HasLogger:

instance HasLogger App where
  loggerL = lens appLogger $ \x y -> x { appLogger = y }

and a way to build a value:

loadApp :: IO App

It's likely you'll want to use Freckle.App.Env to load your App:

import qualified Blammo.Logger.LogSettings.Env as LoggerEnv
import qualified Freckle.App.Env as Env

loadApp = Env.parse id $ App
  <$> Env.switch "DRY_RUN" mempty
  <*> LoggerEnv.parser

Though not required, a type synonym can make things throughout your application a bit more readable:

type AppM = ReaderT App (LoggingT IO)

Now you have application-specific actions that can do IO, log, and access your state:

myAppAction :: AppM ()
myAppAction = do
  isDryRun <- asks appDryRun

  if isDryRun
    then logWarn "Skipping due to dry-run"
    else liftIO $ fireTheMissles

These actions can be (composed of course, or) invoked by a main that handles the reader context and evaluating the logging action.

main :: IO ()
main = do
  app <- loadApp
  runApp app $ do
    myAppAction
    myOtherAppAction

Database

Adding Database access requires an instance of HasSqlPool on your App type. Most often, this will be easiest if you indeed separate a Config attribute:

data Config = Config
  { configDbPoolSize :: Int
  , configLogSettings :: LogSettings
  }

So you can isolate Env-related concerns

loadConfig :: IO Config
loadConfig = Env.parse id $ Config
  <$> Env.var Env.auto "PGPOOLSIZE" (Env.def 1)
  <*> LoggerEnv.parser

from the runtime application state:

data App = App
  { appConfig :: Config
  , appLogger :: Logger
  , appSqlPool :: SqlPool
  }

instance HasLogger App where
  loggerL = appLogger $ \x y -> x { appLogger = y }

instance HasSqlPool App where
  getSqlPool = appSqlPool

The Freckle.App.Database module provides makePostgresPool for building a Pool given this (limited) config data:

loadApp :: IO App
loadApp = do
  appConfig{..} <- loadConfig
  appLogger <- newLogger configLoggerSettings
  appSqlPool <- runLoggerLoggingT appLogger $ makePostgresPool configDbPoolSize
  pure App{..}

Note: the actual database connection parameters (host, user, etc) are (currently) parsed from conventional environment variables by the underlying driver directly. Our application configuration is only involved in declaring the pool size.

This unlocks runDB for your application:

myAppAction :: AppM [Entity Something]
myAppAction = runDB $ selectList [] []

Testing

Freckle.App.Test exposes an AppExample type for examples in a SpecWith App spec. The can be run by giving your loadApp function to Hspec's before.

Our Test module also exposes runAppTest for running AppM actions and lifted expectations for use within such an example.

spec :: Spec
spec = before loadApp $ do
  describe "myAppAction" $ do
    it "works" $ do
      result <- runAppTest myAppAction
      result `shouldBe` "as expected"

If your application makes use of the database, a few things will have to be different:

First, we want to have a specialized runDB in tests to avoid excessive annotations because of the generalized type of runDB itself:

import Database.Persist.Sql
import qualified Freckle.App.Database as DB

runDB :: SqlPersistM IO a -> AppExample App a
runDB = DB.runDB

Second, we'll probably want a conventional withApp function so that we can truncate tables as part of spec setup:

import Freckle.App.Test hiding (withApp)
import Test.Hspec

withApp :: SpecWith App -> Spec
withApp = withAppSql truncateTables loadApp

And now you can write specs that also use the database:

spec :: Spec
spec = withApp $ do
  describe "myAppAction" $ do
    it "works" . withGraph runDB do
      nodeWith -- ...
      nodeWith -- ...
      nodeWith -- ...

      result <- lift $ runAppTest myAppAction
      result `shouldBe` "as expected"

Documentation

runApp :: HasLogger app => app -> ReaderT app (LoggingT IO) a -> IO a Source #