Safe Haskell | None |
---|---|
Language | GHC2021 |
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
if you need mutable application state.IORef
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.
). See its
docs for all the constraints it satisfies.MonadReader
app
Database
import Freckle.App.Database import Freckle.App.OpenTelemetry
Adding Database access requires a few more instances on your App
type:
: so we can, you know, talk to a DBHasSqlPool
: to satisfyHasTracer
so we can traceMonadTracer
runDB
: so we can manage connection count metricsHasStatsClient
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
for
building a Pool given this (limited) config data:makePostgresPool
loadApp :: (App -> IO a) -> IO a loadApp f = do appConfig{..} <- loadConfig withLogger configLoggerSettings $ \appLogger -> appSqlPool <- runWithLogger appLogger $ makePostgresPool configDbPoolSize withTracerProvider $ \tracerProvider -> do withStatsClient configStatsSettings $ \appStatsClient -> do let appTracer = makeTracer tracerProvider "my-app" tracerOptions f App{..}
This unlocks
for your application:runDB
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
type for examples in a
AppExample
spec. The can be run by giving your SpecWith
ApploadApp
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
- runApp :: (forall b. (app -> IO b) -> IO b) -> AppT app IO a -> IO a
- setLineBuffering :: MonadIO m => m ()
- newtype AppT app (m :: Type -> Type) a = AppT {}
- runAppT :: MonadUnliftIO m => AppT app m a -> app -> m a
- class (MonadLogger m, MonadIO m) => MonadLoggerIO (m :: Type -> Type)
- class Monad m => MonadLogger (m :: Type -> Type)
- module Control.Monad.Reader
Documentation
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 :: Type -> Type) a Source #
Instances
runAppT :: MonadUnliftIO m => AppT app m a -> app -> m a Source #
Re-exports
class (MonadLogger m, MonadIO m) => MonadLoggerIO (m :: Type -> Type) #
An extension of MonadLogger
for the common case where the logging action
is a simple IO
action. The advantage of using this typeclass is that the
logging function itself can be extracted as a first-class value, which can
make it easier to manipulate monad transformer stacks, as an example.
Since: monad-logger-0.3.10
Instances
class Monad m => MonadLogger (m :: Type -> Type) #
A Monad
which has the ability to log messages in some manner.
Instances
module Control.Monad.Reader