Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Graphula.Node
Contents
Synopsis
- node :: forall a m. (MonadGraphula m, Logging m a, Arbitrary a, HasDependencies a, GenerateKey a, PersistEntityBackend a ~ SqlBackend, PersistEntity a, Typeable a) => Dependencies a -> NodeOptions a -> m (Entity a)
- nodeKeyed :: forall a m. (MonadGraphula m, Logging m a, Arbitrary a, HasDependencies a, PersistEntityBackend a ~ SqlBackend, PersistEntity a, Typeable a) => Key a -> Dependencies a -> NodeOptions a -> m (Entity a)
- data NodeOptions a
- edit :: (a -> a) -> NodeOptions a
- ensure :: (a -> Bool) -> NodeOptions a
- data GenerationFailure
Generating
node :: forall a m. (MonadGraphula m, Logging m a, Arbitrary a, HasDependencies a, GenerateKey a, PersistEntityBackend a ~ SqlBackend, PersistEntity a, Typeable a) => Dependencies a -> NodeOptions a -> m (Entity a) Source #
Generate a node with a default (Arbitrary or database-provided) key
a <- node @A () mempty
nodeKeyed :: forall a m. (MonadGraphula m, Logging m a, Arbitrary a, HasDependencies a, PersistEntityBackend a ~ SqlBackend, PersistEntity a, Typeable a) => Key a -> Dependencies a -> NodeOptions a -> m (Entity a) Source #
Generate a node with an explictly-given key
let someKey = UUID.fromString "..." a <- nodeKeyed @A someKey () mempty
NodeOptions
data NodeOptions a Source #
Options for generating an individual node
NodeOptions
can be created and combined with the Monoidal operations (<>)
and mempty
.
a1 <- node @A () mempty a2 <- node @A () $ edit $ \a -> a { someField = True } a3 <- node @A () $ ensure $ (== True) . someField
The Semigroup orders the operations from right to left. For example,
first performs edit
z <> ensure
y <> edit
x
, then fails if
the value does not satisfy assertion edit
xy
, then performs
.edit
z
Instances
Monoid (NodeOptions a) Source # | |
Defined in Graphula.Node Methods mempty :: NodeOptions a # mappend :: NodeOptions a -> NodeOptions a -> NodeOptions a # mconcat :: [NodeOptions a] -> NodeOptions a # | |
Semigroup (NodeOptions a) Source # | |
Defined in Graphula.Node Methods (<>) :: NodeOptions a -> NodeOptions a -> NodeOptions a # sconcat :: NonEmpty (NodeOptions a) -> NodeOptions a # stimes :: Integral b => b -> NodeOptions a -> NodeOptions a # | |
Generic (NodeOptions a) Source # | |
Defined in Graphula.Node Associated Types type Rep (NodeOptions a) :: Type -> Type # Methods from :: NodeOptions a -> Rep (NodeOptions a) x # to :: Rep (NodeOptions a) x -> NodeOptions a # | |
type Rep (NodeOptions a) Source # | |
Defined in Graphula.Node |
edit :: (a -> a) -> NodeOptions a Source #
Modify the node after it's been generated
a <- node @A () $ edit $ \a -> a { someField = True }
ensure :: (a -> Bool) -> NodeOptions a Source #
Require a node to satisfy the specified predicate
a <- node @A () $ ensure $ (== True) . someField
N.B. ensuring a condition that is infrequently met can be innefficient.
Exceptions
data GenerationFailure Source #
Constructors
GenerationFailureMaxAttemptsToConstrain TypeRep | Could not satisfy constraints defined using |
GenerationFailureMaxAttemptsToInsert TypeRep | Could not satisfy database constraints on |
Instances
Exception GenerationFailure Source # | |
Defined in Graphula.Node Methods toException :: GenerationFailure -> SomeException # | |
Show GenerationFailure Source # | |
Defined in Graphula.Node Methods showsPrec :: Int -> GenerationFailure -> ShowS # show :: GenerationFailure -> String # showList :: [GenerationFailure] -> ShowS # | |
Eq GenerationFailure Source # | |
Defined in Graphula.Node Methods (==) :: GenerationFailure -> GenerationFailure -> Bool # (/=) :: GenerationFailure -> GenerationFailure -> Bool # |