freckle-app-1.15.2.0: Haskell application toolkit used at Freckle
Safe HaskellSafe-Inferred
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 bracketed function for building and using a value:

loadApp :: (App -> m a) -> m a
loadApp f = do
  app <- -- ...
  f 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 f = do
  app <- Env.parse id $ App
    <$> Env.switch "DRY_RUN" mempty
    <*> LoggerEnv.parser

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

myAppAction :: (MonadIO m, MonadLogger m, MonadReader App env) => m ()
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
  runApp loadApp $ do
    myAppAction
    myOtherAppAction

AppT

Functions like myAppAction will be run in the concrete stack AppT, but you should prefer using using constraints (e.g. MonadReader app). See its docs for all the constraints it satisfies.

Database

import Freckle.App.Database
import Freckle.App.OpenTelemetry

Adding Database access requires a few more instances on your App type:

Most often, this will be easiest if you indeed separate a Config attribute:

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

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
  <*> envParseStatsSettings

from the runtime application state:

data App = App
  { appConfig :: Config
  , appLogger :: Logger
  , appSqlPool :: SqlPool
  , appTracer :: Tracer
  , appStatsClient :: StatsClient
  }

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

instance HasSqlPool App where
  getSqlPool = appSqlPool

instance HasTracer App where
  tracerL = lens appTracer $ \x y -> x { appTracer = y }

instance HasStatsClient App where
  statsClientL = lens appStatsClient $ \x y -> x { appStatsClient = y }

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

loadApp :: (App -> IO a) -> IO a
loadApp f = do
  appConfig{..} <- loadConfig
  appLogger <- newLogger configLoggerSettings
  appSqlPool <- runLoggerLoggingT appLogger $ makePostgresPool configDbPoolSize
  withTracerProvider $ \tracerProvider -> do
    withStatsClient configStatsSettings $ \appStatsClient -> do
      let appTracer = makeTracer tracerProvider "my-app" tracerOptions
      f App{..}

This unlocks runDB for your application:

myAppAction
  :: ( MonadUnliftIO m
     , MonadTracer m
     , MonadReader env m
     , HasSqlPool env
     , HasStatsClient env
     )
  => SqlPersistT m [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 aroundAll.

Using MTL-style constraints (i.e. MonadReader) means you can use your actions directly in expectations, but you may need some type annotations:

spec :: Spec
spec = aroundAll loadApp $ do
  describe "myAppAction" $ do
    it "works" $ do
      result <- myAppAction :: AppExample App Text
      result `shouldBe` "as expected"

If your App type has the required instances, you can use runDB in your specs too:

spec :: Spec
spec = aroundAll loadApp $ do
  describe "myQuery" $ do
    it "works" $ do
      result <- runDB myQuery :: AppExample App Text
      result `shouldBe` "as expected"
Synopsis

Documentation

runApp :: HasLogger app => (forall b. (app -> IO b) -> IO b) -> AppT app IO a -> IO a Source #

setLineBuffering :: MonadIO m => m () Source #

Ensure output is streamed if in a Docker container

runApp calls this for you, but it may be useful if you're running the app some other way.

Concrete transformer stack

newtype AppT app m a Source #

Constructors

AppT 

Fields

Instances

Instances details
Monad m => MonadReader app (AppT app m) Source # 
Instance details

Defined in Freckle.App

Methods

ask :: AppT app m app #

local :: (app -> app) -> AppT app m a -> AppT app m a #

reader :: (app -> a) -> AppT app m a #

MonadIO m => MonadIO (AppT app m) Source # 
Instance details

Defined in Freckle.App

Methods

liftIO :: IO a -> AppT app m a #

Applicative m => Applicative (AppT app m) Source # 
Instance details

Defined in Freckle.App

Methods

pure :: a -> AppT app m a #

(<*>) :: AppT app m (a -> b) -> AppT app m a -> AppT app m b #

liftA2 :: (a -> b -> c) -> AppT app m a -> AppT app m b -> AppT app m c #

(*>) :: AppT app m a -> AppT app m b -> AppT app m b #

(<*) :: AppT app m a -> AppT app m b -> AppT app m a #

Functor m => Functor (AppT app m) Source # 
Instance details

Defined in Freckle.App

Methods

fmap :: (a -> b) -> AppT app m a -> AppT app m b #

(<$) :: a -> AppT app m b -> AppT app m a #

Monad m => Monad (AppT app m) Source # 
Instance details

Defined in Freckle.App

Methods

(>>=) :: AppT app m a -> (a -> AppT app m b) -> AppT app m b #

(>>) :: AppT app m a -> AppT app m b -> AppT app m b #

return :: a -> AppT app m a #

MonadCatch m => MonadCatch (AppT app m) Source # 
Instance details

Defined in Freckle.App

Methods

catch :: (HasCallStack, Exception e) => AppT app m a -> (e -> AppT app m a) -> AppT app m a #

MonadMask m => MonadMask (AppT app m) Source # 
Instance details

Defined in Freckle.App

Methods

mask :: HasCallStack => ((forall a. AppT app m a -> AppT app m a) -> AppT app m b) -> AppT app m b #

uninterruptibleMask :: HasCallStack => ((forall a. AppT app m a -> AppT app m a) -> AppT app m b) -> AppT app m b #

generalBracket :: HasCallStack => AppT app m a -> (a -> ExitCase b -> AppT app m c) -> (a -> AppT app m b) -> AppT app m (b, c) #

MonadThrow m => MonadThrow (AppT app m) Source # 
Instance details

Defined in Freckle.App

Methods

throwM :: (HasCallStack, Exception e) => e -> AppT app m a #

Applicative m => MonadTracer (AppT app m) Source # 
Instance details

Defined in Freckle.App

MonadIO m => MonadHttp (AppT app m) Source # 
Instance details

Defined in Freckle.App

(Monad m, HasTracer app) => MonadTracer (AppT app m) Source # 
Instance details

Defined in Freckle.App

Methods

getTracer :: AppT app m Tracer #

MonadIO m => MonadLogger (AppT app m) Source # 
Instance details

Defined in Freckle.App

Methods

monadLoggerLog :: ToLogStr msg => Loc -> LogSource -> LogLevel -> msg -> AppT app m () #

MonadIO m => MonadLoggerIO (AppT app m) Source # 
Instance details

Defined in Freckle.App

Methods

askLoggerIO :: AppT app m (Loc -> LogSource -> LogLevel -> LogStr -> IO ()) #

PrimMonad m => PrimMonad (AppT app m) Source # 
Instance details

Defined in Freckle.App

Associated Types

type PrimState (AppT app m) #

Methods

primitive :: (State# (PrimState (AppT app m)) -> (# State# (PrimState (AppT app m)), a #)) -> AppT app m a #

MonadIO m => MonadResource (AppT app m) Source # 
Instance details

Defined in Freckle.App

Methods

liftResourceT :: ResourceT IO a -> AppT app m a #

MonadUnliftIO m => MonadUnliftIO (AppT app m) Source # 
Instance details

Defined in Freckle.App

Methods

withRunInIO :: ((forall a. AppT app m a -> IO a) -> IO b) -> AppT app m b #

(MonadUnliftIO m, HasSqlPool app, HasStatsClient app, HasTracer app) => MonadSqlTx (ReaderT SqlBackend (AppT app m)) (AppT app m) Source # 
Instance details

Defined in Freckle.App

Methods

runSqlTx :: HasCallStack => ReaderT SqlBackend (AppT app m) a -> AppT app m a Source #

type PrimState (AppT app m) Source # 
Instance details

Defined in Freckle.App

type PrimState (AppT app m) = PrimState m

runAppT :: (MonadUnliftIO m, HasLogger app) => AppT app m a -> app -> m a Source #

Re-exports