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

Freckle.App.Test

Synopsis

Documentation

data AppExample app a Source #

An Hspec example over some App value

Instances

Instances details
MonadReader app (AppExample app) Source # 
Instance details

Defined in Freckle.App.Test

Methods

ask :: AppExample app app #

local :: (app -> app) -> AppExample app a -> AppExample app a #

reader :: (app -> a) -> AppExample app a #

MonadBase IO (AppExample app) Source # 
Instance details

Defined in Freckle.App.Test

Methods

liftBase :: IO α -> AppExample app α #

MonadBaseControl IO (AppExample app) Source # 
Instance details

Defined in Freckle.App.Test

Associated Types

type StM (AppExample app) a #

Methods

liftBaseWith :: (RunInBase (AppExample app) IO -> IO a) -> AppExample app a #

restoreM :: StM (AppExample app) a -> AppExample app a #

Monad (AppExample app) Source # 
Instance details

Defined in Freckle.App.Test

Methods

(>>=) :: AppExample app a -> (a -> AppExample app b) -> AppExample app b #

(>>) :: AppExample app a -> AppExample app b -> AppExample app b #

return :: a -> AppExample app a #

Functor (AppExample app) Source # 
Instance details

Defined in Freckle.App.Test

Methods

fmap :: (a -> b) -> AppExample app a -> AppExample app b #

(<$) :: a -> AppExample app b -> AppExample app a #

MonadFail (AppExample app) Source # 
Instance details

Defined in Freckle.App.Test

Methods

fail :: String -> AppExample app a #

Applicative (AppExample app) Source # 
Instance details

Defined in Freckle.App.Test

Methods

pure :: a -> AppExample app a #

(<*>) :: AppExample app (a -> b) -> AppExample app a -> AppExample app b #

liftA2 :: (a -> b -> c) -> AppExample app a -> AppExample app b -> AppExample app c #

(*>) :: AppExample app a -> AppExample app b -> AppExample app b #

(<*) :: AppExample app a -> AppExample app b -> AppExample app a #

MonadIO (AppExample app) Source # 
Instance details

Defined in Freckle.App.Test

Methods

liftIO :: IO a -> AppExample app a #

MonadRandom (AppExample app) Source # 
Instance details

Defined in Freckle.App.Test

Methods

getRandomR :: Random a => (a, a) -> AppExample app a #

getRandom :: Random a => AppExample app a #

getRandomRs :: Random a => (a, a) -> AppExample app [a] #

getRandoms :: Random a => AppExample app [a] #

MonadUnliftIO (AppExample app) Source # 
Instance details

Defined in Freckle.App.Test

Methods

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

PrimMonad (AppExample app) Source # 
Instance details

Defined in Freckle.App.Test

Associated Types

type PrimState (AppExample app) #

Methods

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

MonadThrow (AppExample app) Source # 
Instance details

Defined in Freckle.App.Test

Methods

throwM :: Exception e => e -> AppExample app a #

MonadCatch (AppExample app) Source # 
Instance details

Defined in Freckle.App.Test

Methods

catch :: Exception e => AppExample app a -> (e -> AppExample app a) -> AppExample app a #

MonadLogger (AppExample app) Source # 
Instance details

Defined in Freckle.App.Test

Methods

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

Example (AppExample app a) Source # 
Instance details

Defined in Freckle.App.Test

Associated Types

type Arg (AppExample app a) #

Methods

evaluateExample :: AppExample app a -> Params -> (ActionWith (Arg (AppExample app a)) -> IO ()) -> ProgressCallback -> IO Result #

type PrimState (AppExample app) Source # 
Instance details

Defined in Freckle.App.Test

type StM (AppExample app) a Source # 
Instance details

Defined in Freckle.App.Test

type StM (AppExample app) a = StM (NoLoggingT (ReaderT app IO)) a
type Arg (AppExample app a) Source # 
Instance details

Defined in Freckle.App.Test

type Arg (AppExample app a) = app

withApp :: IO app -> SpecWith app -> Spec Source #

Spec before helper

spec :: Spec
spec = withApp loadApp $ do

Reads .env.test, then .env, then loads the application. Examples within this spec can use runAppTest (and runDB, if the app HasSqlPool).

withAppSql :: HasSqlPool app => SqlPersistT IO a -> IO app -> SpecWith app -> Spec Source #

withApp, with custom DB Pool initialization

Runs the given function on the pool before every spec item. For example, to truncate tables.

runAppTest :: ReaderT app (LoggingT IO) a -> AppExample app a Source #

Run an action with the test App

Like runApp, but without exception handling or logging

type HasCallStack = ?callStack :: CallStack #

Request a CallStack.

NOTE: The implicit parameter ?callStack :: CallStack is an implementation detail and should not be considered part of the CallStack API, we may decide to change the implementation in the future.

Since: base-4.9.0.0

example :: Expectation -> Expectation #

example is a type restricted version of id. It can be used to get better error messages on type mismatches.

Compare e.g.

it "exposes some behavior" $ example $ do
  putStrLn

with

it "exposes some behavior" $ do
  putStrLn

type Spec = SpecWith () #

beforeWith :: (b -> IO a) -> SpecWith a -> SpecWith b #

Run a custom action before every spec item.

beforeAll :: HasCallStack => IO a -> SpecWith a -> Spec #

Run a custom action before the first spec item.

describe :: HasCallStack => String -> SpecWith a -> SpecWith a #

The describe function combines a list of specs into a larger spec.

context :: HasCallStack => String -> SpecWith a -> SpecWith a #

context is an alias for describe.

it :: (HasCallStack, Example a) => String -> a -> SpecWith (Arg a) #

The it function creates a spec item.

A spec item consists of:

  • a textual description of a desired behavior
  • an example for that behavior
describe "absolute" $ do
  it "returns a positive number when given a negative number" $
    absolute (-1) == 1

xit :: (HasCallStack, Example a) => String -> a -> SpecWith (Arg a) #

Changing it to xit marks the corresponding spec item as pending.

This can be used to temporarily disable a spec item.

fit :: (HasCallStack, Example a) => String -> a -> SpecWith (Arg a) #

fit is an alias for fmap focus . it

shouldNotReturn :: (HasCallStack, MonadIO m, Show a, Eq a) => m a -> a -> m () infix 1 #

action `shouldNotReturn` notExpected sets the expectation that action does not return notExpected.

shouldNotContain :: (HasCallStack, MonadIO m, Show a, Eq a) => [a] -> [a] -> m () infix 1 #

list `shouldNotContain` sublist sets the expectation that sublist is not contained anywhere in list.

shouldNotSatisfy :: (HasCallStack, MonadIO m, Show a) => a -> (a -> Bool) -> m () infix 1 #

v `shouldNotSatisfy` p sets the expectation that p v is False.

shouldNotBe :: (HasCallStack, MonadIO m, Show a, Eq a) => a -> a -> m () infix 1 #

actual `shouldNotBe` notExpected sets the expectation that actual is not equal to notExpected

shouldReturn :: (HasCallStack, MonadIO m, Show a, Eq a) => m a -> a -> m () infix 1 #

action `shouldReturn` expected sets the expectation that action returns expected.

shouldMatchList :: (HasCallStack, MonadIO m, Show a, Eq a) => [a] -> [a] -> m () infix 1 #

xs `shouldMatchList` ys sets the expectation that xs has the same elements that ys has, possibly in another order

shouldContain :: (HasCallStack, MonadIO m, Show a, Eq a) => [a] -> [a] -> m () infix 1 #

list `shouldContain` sublist sets the expectation that sublist is contained, wholly and intact, anywhere in list.

shouldEndWith :: (HasCallStack, MonadIO m, Show a, Eq a) => [a] -> [a] -> m () infix 1 #

list `shouldEndWith` suffix sets the expectation that list ends with suffix,

shouldStartWith :: (HasCallStack, MonadIO m, Show a, Eq a) => [a] -> [a] -> m () infix 1 #

list `shouldStartWith` prefix sets the expectation that list starts with prefix,

shouldSatisfy :: (HasCallStack, MonadIO m, Show a) => a -> (a -> Bool) -> m () infix 1 #

v `shouldSatisfy` p sets the expectation that p v is True.

shouldBe :: (HasCallStack, MonadIO m, Show a, Eq a) => a -> a -> m () infix 1 #

actual `shouldBe` expected sets the expectation that actual is equal to expected.

data Pool a #

Striped resource pool based on Control.Concurrent.QSem.

The number of stripes is arranged to be equal to the number of capabilities so that they never compete over access to the same stripe. This results in a very good performance in a multi-threaded environment.

Instances

Instances details
HasSqlPool SqlPool Source # 
Instance details

Defined in Freckle.App.Database

createPool :: IO a -> (a -> IO ()) -> Int -> NominalDiffTime -> Int -> IO (Pool a) #

Provided for compatibility with resource-pool < 0.3.

Use newPool instead.

takeResource :: Pool a -> IO (a, LocalPool a) #

Take a resource from the pool, following the same results as withResource.

Note: this function returns both a resource and the LocalPool it came from so that it may either be destroyed (via destroyResource) or returned to the pool (via putResource).

withResource :: Pool a -> (a -> IO r) -> IO r #

Take a resource from the pool, perform an action with it and return it to the pool afterwards.

  • If the pool has an idle resource available, it is used immediately.
  • Otherwise, if the maximum number of resources has not yet been reached, a new resource is created and used.
  • If the maximum number of resources has been reached, this function blocks until a resource becomes available.

If the action throws an exception of any type, the resource is destroyed and not returned to the pool.

It probably goes without saying that you should never manually destroy a pooled resource, as doing so will almost certainly cause a subsequent user (who expects the resource to be valid) to throw an exception.

destroyAllResources :: Pool a -> IO () #

Destroy all resources in all stripes in the pool.

Note that this will ignore any exceptions in the destroy function.

This function is useful when you detect that all resources in the pool are broken. For example after a database has been restarted all connections opened before the restart will be broken. In that case it's better to close those connections so that takeResource won't take a broken connection from the pool but will open a new connection instead.

Another use-case for this function is that when you know you are done with the pool you can destroy all idle resources immediately instead of waiting on the garbage collector to destroy them, thus freeing up those resources sooner.

putResource :: LocalPool a -> a -> IO () #

Return a resource to the given LocalPool.

destroyResource :: Pool a -> LocalPool a -> a -> IO () #

Destroy a resource.

Note that this will ignore any exceptions in the destroy function.

newPool :: PoolConfig a -> IO (Pool a) #

Create a new striped resource pool.

The number of stripes is equal to the number of capabilities.

Note: although the runtime system will destroy all idle resources when the pool is garbage collected, it's recommended to manually call destroyAllResources when you're done with the pool so that the resources are freed up as soon as possible.

data LocalPool a #

A single, capability-local pool.

data PoolConfig a #

Configuration of a Pool.

Constructors

PoolConfig 

Fields

  • createResource :: !(IO a)

    The action that creates a new resource.

  • freeResource :: !(a -> IO ())

    The action that destroys an existing resource.

  • poolCacheTTL :: !Double

    The amount of seconds for which an unused resource is kept around. The smallest acceptable value is 0.5.

    Note: the elapsed time before destroying a resource may be a little longer than requested, as the collector thread wakes at 1-second intervals.

  • poolMaxResources :: !Int

    The maximum number of resources to keep open across all stripes. The smallest acceptable value is 1.

    Note: for each stripe the number of resources is divided by the number of capabilities and rounded up. Therefore the pool might end up creating up to N - 1 resources more in total than specified, where N is the number of capabilities.

class HasSqlPool app where Source #

Methods

getSqlPool :: app -> SqlPool Source #

Instances

Instances details
HasSqlPool SqlPool Source # 
Instance details

Defined in Freckle.App.Database

runDB :: (HasSqlPool app, MonadUnliftIO m, MonadReader app m) => SqlPersistT m a -> m a Source #