| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Graphula.Dependencies
Contents
Synopsis
- class HasDependencies a where
- type Dependencies a
- type KeySource a :: KeySourceType
- dependsOn :: a -> Dependencies a -> a
- newtype Only a = Only {
- fromOnly :: a
- only :: a -> Only a
- data KeySourceType
- class (GenerateKeyInternal (KeySource a) a, KeyConstraint (KeySource a) a) => GenerateKey a
- generateKey :: (GenerateKeyInternal s a, KeyConstraint s a) => Gen (Maybe (Key a))
Documentation
class HasDependencies a where Source #
Minimal complete definition
Nothing
Associated Types
type Dependencies a Source #
A data type declaring the model's dependencies
Models with no dependencies can declare an empty instance,
instance HasDependencies School
Models with one dependency must use the Only 1-tuple constructor,
instance HasDependencies Teacher where
type Dependencies Teacher = Only SchoolId
Models with multiple dependencies use tuple syntax,
instance HasDependencies Course where
type Dependencies Course = (SchoolId, TeacherId)
type Dependencies _a = ()
type KeySource a :: KeySourceType Source #
Specify the method for resolving a node's key
This can be
'SourceDefault -- automatically generate keys from the database 'SourceArbitrary -- automatically generate keys using'SourceExternal -- explicitly pass a key usingArbitrarynodeKeyed
Most types will use SourceDefault or SourceArbitrary. Only use
SourceExternal if the key for a value is always defined externally.
type KeySource _a = 'SourceDefault
Methods
dependsOn :: a -> Dependencies a -> a Source #
Assign values from the Dependencies collection to a value
This must be an idempotent operation. Law:
(\x d -> x `dependsOn` d `dependsOn` d) = dependsOn
The default, Generic-based implementation will assign values by the order
of the fields in the model's type.
default dependsOn :: (HasEot a, HasEot (Dependencies a), GHasDependencies (Proxy a) (Proxy (Dependencies a)) (Eot a) (Eot (Dependencies a))) => a -> Dependencies a -> a Source #
For entities that only have singular Dependencies
Instances
| Functor Only Source # | |
| Foldable Only Source # | |
Defined in Graphula.Dependencies Methods fold :: Monoid m => Only m -> m # foldMap :: Monoid m => (a -> m) -> Only a -> m # foldMap' :: Monoid m => (a -> m) -> Only a -> m # foldr :: (a -> b -> b) -> b -> Only a -> b # foldr' :: (a -> b -> b) -> b -> Only a -> b # foldl :: (b -> a -> b) -> b -> Only a -> b # foldl' :: (b -> a -> b) -> b -> Only a -> b # foldr1 :: (a -> a -> a) -> Only a -> a # foldl1 :: (a -> a -> a) -> Only a -> a # elem :: Eq a => a -> Only a -> Bool # maximum :: Ord a => Only a -> a # | |
| Traversable Only Source # | |
| Eq a => Eq (Only a) Source # | |
| Ord a => Ord (Only a) Source # | |
| Show a => Show (Only a) Source # | |
| Generic (Only a) Source # | |
| type Rep (Only a) Source # | |
Defined in Graphula.Dependencies | |
| type Keys (Only (Entity a)) Source # | |
Non-serial keys
data KeySourceType Source #
Constructors
| SourceDefault | Generate keys using the database's |
| SourceArbitrary | |
| SourceExternal | Always explicitly pass an external key See |
class (GenerateKeyInternal (KeySource a) a, KeyConstraint (KeySource a) a) => GenerateKey a Source #
Abstract constraint that some a can generate a key
This is part of ensuring better error messages.
Instances
| (GenerateKeyInternal (KeySource a) a, KeyConstraint (KeySource a) a) => GenerateKey a Source # | |
Defined in Graphula.Dependencies | |