graphula: A declarative library for describing dependencies between data

[ library, mit, network ] [ Propose Tags ]

Please see README.md


[Skip to Readme]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 2.0.0.1, 2.0.0.2, 2.0.0.3, 2.0.0.4, 2.0.0.5, 2.0.1.0, 2.0.1.1, 2.0.2.1, 2.0.2.2, 2.1.0.0
Change log CHANGELOG.md
Dependencies base (>=4.14.1.0 && <5), containers (>=0.6.2.1), directory (>=1.3.6.0), generics-eot (>=0.4.0.1), HUnit (>=1.6.1.0), mtl (>=2.2.2), persistent (>=2.11.0.4), QuickCheck (>=2.14.2), random (>=1.1), semigroups (>=0.19.1), temporary (>=1.3), text (>=1.2.4.1), transformers (>=0.5.6.2), unliftio (>=0.2.14), unliftio-core (>=0.2.0.1) [details]
License MIT
Author
Maintainer Freckle Education
Category Network
Home page https://github.com/freckle/graphula#readme
Bug tracker https://github.com/freckle/graphula/issues
Source repo head: git clone https://github.com/freckle/graphula
Uploaded by PatrickBrisbin at 2021-05-17T13:06:04Z
Distributions LTSHaskell:2.1.0.0, Stackage:2.1.0.0
Downloads 1532 total (38 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2021-05-17 [all 1 reports]

Readme for graphula-2.0.0.5

[back to package description]

Graphula Core

Graphula is a simple interface for generating persistent data and linking its dependencies. We use this interface to generate fixtures for automated testing. The interface is extensible and supports pluggable front-ends.

Arbitrary Data

Graphula utilizes QuickCheck to generate random data. We need to declare Arbitrary instances for our types.

share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persistLowerCase|
A
  a String
  b Int
  deriving Show Eq Generic

B
  a AId
  b String
  deriving Show Eq Generic

C
  a AId
  b BId
  c String
  deriving Show Eq Generic

D
  Id UUIDKey
  a Int
  b String
  deriving Show Eq Generic

E
  Id DId sqltype=uuid
  a String
  deriving Show Eq Generic

F
  a Bool
  UniqueFA a
  deriving Show Eq Generic
|]

instance Arbitrary A where
  arbitrary = A <$> arbitrary <*> arbitrary

instance Arbitrary B where
  arbitrary = B <$> arbitrary <*> arbitrary

instance Arbitrary C where
  arbitrary = C <$> arbitrary <*> arbitrary <*> arbitrary

instance Arbitrary D where
  arbitrary = D <$> arbitrary <*> arbitrary

instance Arbitrary E where
  arbitrary = E <$> arbitrary

instance Arbitrary F where
  arbitrary = F <$> arbitrary

Dependencies

We declare dependencies via the HasDependencies typeclass and its associated type Dependencies.

By default a type does not have any dependencies. We only need to declare an empty instance.

instance HasDependencies A
instance HasDependencies F

For single dependencies we use the Only type.

instance HasDependencies B where
  type Dependencies B = Only AId

Groups of dependencies use tuples. Declare these dependencies in the order they appear in the type. HasDependencies leverages generic programming to inject dependencies for you.

instance HasDependencies C where
  type Dependencies C = (AId, BId)

Non Sequential Keys

Graphula supports non-sequential keys with the KeySource associated type. To generate a key using its Arbitrary instance, use 'SourceArbitrary. Non-serial keys will need to also derive an overlapping Arbitrary instance.

instance HasDependencies D where
  type KeySource D = 'SourceArbitrary

deriving newtype instance {-# OVERLAPPING #-} Arbitrary (Key D)

You can also elect to always specify an external key using 'SourceExternal. This means that this type cannot be constructed with node; use nodeKeyed instead.

instance HasDependencies E where
  type KeySource E = 'SourceExternal

By default, HasDependencies instances use type KeySource _ = 'SourceDefault, which means that graphula will expect the database to provide a key.

Serialization

Graphula allows logging of graphs via runGraphulaLogged. Graphula dumps graphs to a temp file on test failure.

loggingSpec :: IO ()
loggingSpec = do
  let
    logFile :: FilePath
    logFile = "test.graphula"

    -- We'd typically use `runGraphulaLogged` which utilizes a temp file.
    failingGraph :: IO ()
    failingGraph = runGraphulaT Nothing runDB . runGraphulaLoggedWithFileT logFile $ do
      Entity _ a <- node @A () $ edit $ \n ->
        n {aA = "success"}
      liftIO $ aA a `shouldBe` "failed"

  failingGraph
    `shouldThrow` anyException

  n <- lines <$> readFile "test.graphula"
  n `shouldSatisfy` (not . null)

Running It

simpleSpec :: IO ()
simpleSpec =
  runGraphulaT Nothing runDB $ do
    -- Type application is not necessary, but recommended for clarity.
    Entity aId _ <- node @A () mempty
    Entity bId b <- node @B (only aId) mempty
    Entity _ c <- node @C (aId, bId) $ edit $ \n -> n { cC = "edited" }
    Entity dId _ <- node @D () mempty
    Entity eId _ <- nodeKeyed @E (EKey dId) () mempty

    -- Do something with your data
    liftIO $ do
      cC c `shouldBe` "edited"
      cA c `shouldBe` bA b
      unEKey eId `shouldBe` dId

runGraphulaT carries frontend instructions. If we'd like to override them we need to declare our own frontend.

For example, a front-end that always fails to insert.

newtype GraphulaFailT m a = GraphulaFailT { runGraphulaFailT :: m a }
  deriving newtype (Functor, Applicative, Monad, MonadIO, MonadGraphulaBackend)

instance MonadGraphulaFrontend (GraphulaFailT m) where
  insert _ _ = pure Nothing
  remove = const (pure ())

insertionFailureSpec :: IO ()
insertionFailureSpec = do
  let
    failingGraph :: IO ()
    failingGraph =  runGraphulaT Nothing runDB . runGraphulaFailT $ do
      Entity _ _ <- node @A () mempty
      pure ()
  failingGraph
    `shouldThrow` (== (GenerationFailureMaxAttemptsToInsert (typeRep $ Proxy @A)))

Note that graphula can fail naturally if we define a graph that violates unique constraints in the database:

constraintFailureSpec :: IO ()
constraintFailureSpec = do
  let
    failingGraph :: IO ()
    failingGraph =  runGraphulaT Nothing runDB $
      replicateM_ 3 $ node @F () mempty
  failingGraph
    `shouldThrow` (== (GenerationFailureMaxAttemptsToInsert (typeRep $ Proxy @F)))

or if we define a graph with an unsatisfiable predicates:

ensureFailureSpec :: IO ()
ensureFailureSpec = do
  let
    failingGraph :: IO ()
    failingGraph =  runGraphulaT Nothing runDB $ do
      Entity _ _ <- node @A () $ ensure $ \a -> a /= a
      pure ()
  failingGraph
    `shouldThrow` (== (GenerationFailureMaxAttemptsToConstrain (typeRep $ Proxy @A)))