adhoc-fixtures-0.1.0.1: Manage fine grained fixtures
CopyrightGautier DI FOLCO
LicenseISC
MaintainerGautier DI FOLCO <gautier.difolco@gmail.com>
StabilityUnstable
Portabilitynot portable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Fixtures.Adhoc

Description

Fixtures builder and runner

Example:

boxFixture ::
  HasFixture items "tracker" Tracker =>
  BuilderWith items IO "box" Box
boxFixture =
  buildWithClean
  (\prev -> let box = Box 42 "box00" in addId box.boxKey box.boxId prev.tracker >> return box)
  (\prev box -> rmId box.boxKey prev.tracker)
Synopsis

Documentation

data Builder m items Source #

Fixture builder (should be used directly with care)

Constructors

Builder 

Fields

type BuilderWith items m (name :: Symbol) a = HasNotField name items => Builder m items -> Builder m (Field name a ': items) Source #

Builder relying on other builder(s)

type HasFixture items (name :: Symbol) a = HasField name (Record items) a Source #

Helper around HasRecord

buildWith :: forall (name :: Symbol) a m items. (Monad m, HasNotField name items) => (Record items -> m a) -> BuilderWith items m name a Source #

Simple builder, no clean operation

buildWithClean :: forall (name :: Symbol) a m items. (Monad m, HasNotField name items) => (Record items -> m a) -> (Record items -> a -> m ()) -> BuilderWith items m name a Source #

Builder with cleaning operation

build :: forall (name :: Symbol) a m items. (Monad m, HasNotField name items) => m a -> BuilderWith items m name a Source #

Simple builder without dependency, no clean operation

buildClean :: forall (name :: Symbol) a m items. (Monad m, HasNotField name items) => m a -> (a -> m ()) -> BuilderWith items m name a Source #

Builder without dependency with cleaning operation

nullBuilder :: Monad m => Builder m '[] Source #

Base builder

pureBuilder :: Monad m => Record items -> Builder m items Source #

Pure builder

(&:) :: HasNotField name items => BuilderWith items m name a -> Builder m items -> Builder m (Field name a ': items) infixr 5 Source #

Chain builders

(&>) :: (HasNotField name items, Monad m) => BuilderWith items m name a -> Record items -> Builder m (Field name a ': items) infixr 5 Source #

Nest builders

runWithFixtures :: MonadMask m => Builder m items -> (Record items -> m a) -> m a Source #

Run fixtures with clean up (bracket)

createFixtures :: Monad m => Builder m items -> (Record items -> m a) -> m a Source #

Create fixtures (no clean up)