graphula-2.0.0.5: A declarative library for describing dependencies between data
Safe HaskellNone
LanguageHaskell2010

Graphula.Internal

Synopsis

Documentation

class MonadGraphulaBackend m where Source #

Associated Types

type Logging m :: Type -> Constraint Source #

A constraint provided to log details of the graph to some form of persistence. This is used by runGraphulaLogged to store graph nodes as Shown Text values

Methods

askGen :: m (IORef QCGen) Source #

logNode :: Logging m a => a -> m () Source #

Instances

Instances details
(MonadGraphulaBackend m, MonadIO m) => MonadGraphulaBackend (GraphulaLoggedT m) Source # 
Instance details

Defined in Graphula

Associated Types

type Logging (GraphulaLoggedT m) :: Type -> Constraint Source #

MonadIO m => MonadGraphulaBackend (GraphulaT n m) Source # 
Instance details

Defined in Graphula

Associated Types

type Logging (GraphulaT n m) :: Type -> Constraint Source #

Methods

askGen :: GraphulaT n m (IORef QCGen) Source #

logNode :: Logging (GraphulaT n m) a => a -> GraphulaT n m () Source #

class GHasDependencies nodeTyProxy depsTyProxy node deps where Source #

Methods

genericDependsOn :: nodeTyProxy -> depsTyProxy -> node -> deps -> node Source #

Instances

Instances details
(TypeError ('Text "Use \8216()\8217 instead of \8216Void\8217 for datatypes with no dependencies in" :$$: DependenciesTypeInstance nodeTy depsTy) :: Constraint) => GHasDependencies (Proxy nodeTy) (Proxy depsTy) node Void Source # 
Instance details

Defined in Graphula.Internal

Methods

genericDependsOn :: Proxy nodeTy -> Proxy depsTy -> node -> Void -> node Source #

(TypeError ('Text "A datatype with no constructors can't use the dependencies in" :$$: DependenciesTypeInstance nodeTy depsTy) :: Constraint) => GHasDependencies (Proxy nodeTy) (Proxy depsTy) Void (Either deps rest) Source # 
Instance details

Defined in Graphula.Internal

Methods

genericDependsOn :: Proxy nodeTy -> Proxy depsTy -> Void -> Either deps rest -> Void Source #

GHasDependencies (Proxy nodeTy) (Proxy depsTy) Void (Either () Void) Source # 
Instance details

Defined in Graphula.Internal

Methods

genericDependsOn :: Proxy nodeTy -> Proxy depsTy -> Void -> Either () Void -> Void Source #

(TypeError ('Text "Cannot automatically find dependencies for sum type or use a sum type as a dependency in" :$$: DependenciesTypeInstance nodeTy depsTy) :: Constraint) => GHasDependencies (Proxy nodeTy) (Proxy depsTy) (Either left1 (Either right1 rest1)) (Either left2 (Either right2 rest2)) Source # 
Instance details

Defined in Graphula.Internal

Methods

genericDependsOn :: Proxy nodeTy -> Proxy depsTy -> Either left1 (Either right1 rest1) -> Either left2 (Either right2 rest2) -> Either left1 (Either right1 rest1) Source #

(TypeError ('Text "Cannot automatically use a sum type as dependencies in" :$$: DependenciesTypeInstance nodeTy depsTy) :: Constraint) => GHasDependencies (Proxy nodeTy) (Proxy depsTy) (Either node Void) (Either left (Either right rest)) Source # 
Instance details

Defined in Graphula.Internal

Methods

genericDependsOn :: Proxy nodeTy -> Proxy depsTy -> Either node Void -> Either left (Either right rest) -> Either node Void Source #

(TypeError ('Text "Cannot automatically find dependencies for sum type in" :$$: DependenciesTypeInstance nodeTy depsTy) :: Constraint) => GHasDependencies (Proxy nodeTy) (Proxy depsTy) (Either left (Either right rest)) (Either deps Void) Source # 
Instance details

Defined in Graphula.Internal

Methods

genericDependsOn :: Proxy nodeTy -> Proxy depsTy -> Either left (Either right rest) -> Either deps Void -> Either left (Either right rest) Source #

(FindMatches nodeTy depsTy node deps ~ fields, GHasDependenciesRecursive (Proxy fields) node deps) => GHasDependencies (Proxy nodeTy) (Proxy depsTy) (Either node Void) (Either deps Void) Source # 
Instance details

Defined in Graphula.Internal

Methods

genericDependsOn :: Proxy nodeTy -> Proxy depsTy -> Either node Void -> Either deps Void -> Either node Void Source #

data KeySourceType Source #

Constructors

SourceDefault

Generate keys using the database's DEFAULT strategy

SourceArbitrary

Generate keys using the Arbitrary instance for the Key

SourceExternal

Always explicitly pass an external key

class GenerateKeyInternal (s :: KeySourceType) a where Source #

Handle key generation for SourceDefault and SourceArbitrary

Ths could be a single-parameter class, but carrying the a around lets us give a better error message when node is called instead of nodeKeyed.

Associated Types

type KeyConstraint s a :: Constraint Source #

Methods

generateKey :: KeyConstraint s a => Gen (Maybe (Key a)) Source #

Instances

Instances details
GenerateKeyInternal 'SourceDefault a Source # 
Instance details

Defined in Graphula.Internal

Associated Types

type KeyConstraint 'SourceDefault a Source #

Methods

generateKey :: Gen (Maybe (Key a)) Source #

GenerateKeyInternal 'SourceArbitrary a Source # 
Instance details

Defined in Graphula.Internal

Associated Types

type KeyConstraint 'SourceArbitrary a Source #

Methods

generateKey :: Gen (Maybe (Key a)) Source #

(TypeError ((((((((((('Text "Cannot generate a value of type " :<>: Quote ('ShowType a)) :<>: 'Text " using ") :<>: Quote ('Text "node")) :<>: 'Text " since") :$$: 'Text "") :$$: (('Text " instance HasDependencies " :<>: 'ShowType a) :<>: 'Text " where")) :$$: (((('Text " " :<>: 'Text "type KeySource ") :<>: 'ShowType a) :<>: 'Text " = ") :<>: 'ShowType 'SourceExternal)) :$$: 'Text "") :$$: 'Text "Possible fixes include:") :$$: ((('Text "\8226 Use " :<>: Quote ('Text "nodeKeyed")) :<>: 'Text " instead of ") :<>: Quote ('Text "node"))) :$$: ((((('Text "\8226 Change " :<>: Quote ('Text "KeySource " :<>: 'ShowType a)) :<>: 'Text " to ") :<>: 'Text "'SourceDefault") :<>: 'Text " or ") :<>: 'Text "'SourceArbitrary")) :: Constraint) => GenerateKeyInternal 'SourceExternal a Source #

Explicit instance for SourceExternal to give an actionable error message

Rendered:

Cannot generate a value of type ‘X’ using ‘node’ since

  instance HasDependencies X where
    type KeySource X = 'SourceExternal

Possible fixes include:
• Use ‘nodeKeyed’ instead of ‘node’
• Change ‘KeySource X’ to 'SourceDefault or 'SourceArbitrary
Instance details

Defined in Graphula.Internal

Associated Types

type KeyConstraint 'SourceExternal a Source #

Methods

generateKey :: Gen (Maybe (Key a)) Source #

class NoConstraint a Source #

Graphula accepts constraints for various uses. Frontends do not always utilize these constraints. NoConstraint is a universal class that all types inhabit. It has no behavior and no additional constraints.

Instances

Instances details
NoConstraint a Source # 
Instance details

Defined in Graphula.Internal