graphula: A simple interface for generating persistent data and linking its dependencies

[ library, mit, network ] [ Propose Tags ]

Please see README.md


[Skip to Readme]

Flags

Automatic Flags
NameDescriptionDefault
persistent-template

Include dependency on persistent-template

Disabled

Use -f <flag> to enable a flag, or -f -<flag> to disable that flag. More info

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.11.1.0 && <5), containers (>=0.5.11.0), directory (>=1.3.1.5), generics-eot (>=0.4), HUnit (>=1.6.0.0), mtl (>=2.2.2), persistent (>=2.8.2), QuickCheck (>=2.11.3), random (>=1.1), semigroups (>=0.18.5), temporary (>=1.3), text (>=1.2.3.1), unliftio (>=0.2.9.0), unliftio-core (>=0.1.2.0) [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 2023-12-13T20:33:52Z
Distributions LTSHaskell:2.1.0.0, Stackage:2.1.0.0
Downloads 1558 total (40 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2023-12-13 [all 1 reports]

Readme for graphula-2.1.0.0

[back to package description]

Graphula

Hackage Stackage Nightly Stackage LTS CI

Graphula is a simple interface for generating persistent data and linking its dependencies. We use this interface to generate fixtures for automated testing.

Arbitrary Data

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

share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persistLowerCase|
School
  name String
  deriving Show Eq Generic

Teacher
  schoolId SchoolId
  name String
  deriving Show Eq Generic

Course
  schoolId SchoolId
  teacherId TeacherId
  name String
  deriving Show Eq Generic

Student
  name String
  deriving Show Eq Generic

Question
  content String
  deriving Show Eq Generic

Answer
  questionId QuestionId
  studentId StudentId
  yes Bool
  UniqueAnswer questionId studentId
  deriving Show Eq Generic
|]

instance Arbitrary School where
  arbitrary = genericArbitrary

instance Arbitrary Teacher where
  arbitrary = genericArbitrary

instance Arbitrary Course where
  arbitrary = genericArbitrary

instance Arbitrary Student where
  arbitrary = genericArbitrary

instance Arbitrary Question where
  arbitrary = genericArbitrary

instance Arbitrary Answer where
  arbitrary = genericArbitrary

Dependencies

We declare dependencies via the HasDependencies typeclass and its associated type Dependencies. If a model does not have any dependencies, we only need to declare an empty instance.

instance HasDependencies School

instance HasDependencies Student

instance HasDependencies Question

For single-dependency models, we use the Only type.

instance HasDependencies Teacher where
  type Dependencies Teacher = Only SchoolId

Multi-dependency models use tuples. Declare these dependencies in the order they appear in the model's type definition. HasDependencies leverages generic programming to inject dependencies for you.

instance HasDependencies Course where
  type Dependencies Course = (SchoolId, TeacherId)

instance HasDependencies Answer where
  type Dependencies Answer = (QuestionId, StudentId)

Logging failures

runGraphulaLogged will dump generated data to a temporary file. Or runGraphulaLoggedWithFileT can be used to pass an explicit path.

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

    failingGraph :: IO ()
    failingGraph = runGraphulaT Nothing runDB . runGraphulaLoggedWithFileT logFile $ do
      student <- node @Student () mempty
      question <- node @Question () mempty
      answer <- node @Answer
        (entityKey question, entityKey student)
        $ edit $ \a -> a { answerYes = True }

      -- Test failures will cause the graph to be logged (not any exception)
      liftIO $ answerYes (entityVal answer) `shouldBe` False

  failingGraph `shouldThrow` anyException

  n <- lines <$> readFile logFile
  n `shouldSatisfy` (not . null)

Running It

simpleSpec :: IO ()
simpleSpec =
  runGraphulaT Nothing runDB $ do
    school <- node @School () mempty
    teacher <- node @Teacher (Only $ entityKey school) mempty
    course <- node @Course (entityKey school, entityKey teacher) mempty
    student <- node @Student () $ edit $ \s -> s { studentName = "Pat" }
    question <- node @Question () mempty
    answer <- node @Answer
      (entityKey question, entityKey student)
      $ edit $ \a -> a { answerYes = True }

    liftIO $ do
      -- Typically, you would run some other function like "fetch correct
      -- answers at school" and assert you found the correct answers you
      -- generated. In this example we just assert some things about the data
      -- directly:
      teacherSchoolId (entityVal teacher) `shouldBe` entityKey school
      courseTeacherId (entityVal course) `shouldBe` entityKey teacher
      answerYes (entityVal answer) `shouldBe` True