| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
System.Nix.Store.DB.Schema
Documentation
type DerivationOutputId = Key DerivationOutput Source #
data DerivationOutput Source #
Constructors
| DerivationOutput | |
Fields | |
Instances
Constructors
| Ref | |
Fields | |
Instances
| Show Ref Source # | |||||||||||||||||
| Eq Ref Source # | |||||||||||||||||
| Ord Ref Source # | |||||||||||||||||
| PersistEntity Ref Source # | |||||||||||||||||
Defined in System.Nix.Store.DB.Schema Associated Types
Methods keyToValues :: Key Ref -> [PersistValue] # keyFromValues :: [PersistValue] -> Either Text (Key Ref) # persistIdField :: EntityField Ref (Key Ref) # entityDef :: proxy Ref -> EntityDef # persistFieldDef :: EntityField Ref typ -> FieldDef # toPersistFields :: Ref -> [PersistValue] # fromPersistValues :: [PersistValue] -> Either Text Ref # tabulateEntityA :: Applicative f => (forall a. EntityField Ref a -> f a) -> f (Entity Ref) # tabulateEntityApply :: Apply f => (forall a. EntityField Ref a -> f a) -> f (Entity Ref) # persistUniqueKeys :: Ref -> [Unique Ref] # persistUniqueToFieldNames :: Unique Ref -> NonEmpty (FieldNameHS, FieldNameDB) # persistUniqueToValues :: Unique Ref -> [PersistValue] # fieldLens :: EntityField Ref field -> forall (f :: Type -> Type). Functor f => (field -> f field) -> Entity Ref -> f (Entity Ref) # | |||||||||||||||||
| SafeToInsert Ref Source # | |||||||||||||||||
Defined in System.Nix.Store.DB.Schema | |||||||||||||||||
| PersistField Ref Source # | |||||||||||||||||
Defined in System.Nix.Store.DB.Schema | |||||||||||||||||
| AtLeastOneUniqueKey Ref Source # | |||||||||||||||||
Defined in System.Nix.Store.DB.Schema | |||||||||||||||||
| OnlyOneUniqueKey Ref Source # | |||||||||||||||||
Defined in System.Nix.Store.DB.Schema Methods onlyUniqueP :: Ref -> Unique Ref # | |||||||||||||||||
| PersistFieldSql Ref Source # | |||||||||||||||||
| SymbolToField "reference" Ref ValidPathId Source # | |||||||||||||||||
Defined in System.Nix.Store.DB.Schema Methods | |||||||||||||||||
| SymbolToField "referrer" Ref ValidPathId Source # | |||||||||||||||||
Defined in System.Nix.Store.DB.Schema Methods | |||||||||||||||||
| SymbolToField "id" Ref (Key Ref) Source # | |||||||||||||||||
Defined in System.Nix.Store.DB.Schema Methods symbolToField :: EntityField Ref (Key Ref) # | |||||||||||||||||
| FromJSON (Key Ref) Source # | |||||||||||||||||
| ToJSON (Key Ref) Source # | |||||||||||||||||
| Generic (Key Ref) Source # | |||||||||||||||||
Defined in System.Nix.Store.DB.Schema Associated Types
| |||||||||||||||||
| Read (Key Ref) Source # | |||||||||||||||||
| Show (Key Ref) Source # | |||||||||||||||||
| Eq (Key Ref) Source # | |||||||||||||||||
| Ord (Key Ref) Source # | |||||||||||||||||
Defined in System.Nix.Store.DB.Schema | |||||||||||||||||
| PersistField (Key Ref) Source # | |||||||||||||||||
Defined in System.Nix.Store.DB.Schema Methods toPersistValue :: Key Ref -> PersistValue # fromPersistValue :: PersistValue -> Either Text (Key Ref) # | |||||||||||||||||
| PersistFieldSql (Key Ref) Source # | |||||||||||||||||
| data EntityField Ref typ Source # | |||||||||||||||||
Defined in System.Nix.Store.DB.Schema data EntityField Ref typ
| |||||||||||||||||
| data Key Ref Source # | |||||||||||||||||
Defined in System.Nix.Store.DB.Schema | |||||||||||||||||
| type PersistEntityBackend Ref Source # | |||||||||||||||||
Defined in System.Nix.Store.DB.Schema | |||||||||||||||||
| data Unique Ref Source # | |||||||||||||||||
Defined in System.Nix.Store.DB.Schema | |||||||||||||||||
| type Rep (Key Ref) Source # | |||||||||||||||||
Defined in System.Nix.Store.DB.Schema type Rep (Key Ref) = D1 ('MetaData "Key" "System.Nix.Store.DB.Schema" "hnix-store-db-0.1.0.1-EiJLhPHchq37h8iVlIOneJ" 'False) (C1 ('MetaCons "RefKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "refKeyreferrer") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ValidPathId) :*: S1 ('MetaSel ('Just "refKeyreference") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ValidPathId))) | |||||||||||||||||
type ValidPathId = Key ValidPath Source #
Constructors
| ValidPath | |
Fields
| |
Instances
| Show ValidPath Source # | |||||||||||||||||
| Eq ValidPath Source # | |||||||||||||||||
| Ord ValidPath Source # | |||||||||||||||||
| PersistEntity ValidPath Source # | |||||||||||||||||
Defined in System.Nix.Store.DB.Schema Associated Types
Methods keyToValues :: Key ValidPath -> [PersistValue] # keyFromValues :: [PersistValue] -> Either Text (Key ValidPath) # persistIdField :: EntityField ValidPath (Key ValidPath) # entityDef :: proxy ValidPath -> EntityDef # persistFieldDef :: EntityField ValidPath typ -> FieldDef # toPersistFields :: ValidPath -> [PersistValue] # fromPersistValues :: [PersistValue] -> Either Text ValidPath # tabulateEntityA :: Applicative f => (forall a. EntityField ValidPath a -> f a) -> f (Entity ValidPath) # tabulateEntityApply :: Apply f => (forall a. EntityField ValidPath a -> f a) -> f (Entity ValidPath) # persistUniqueKeys :: ValidPath -> [Unique ValidPath] # persistUniqueToFieldNames :: Unique ValidPath -> NonEmpty (FieldNameHS, FieldNameDB) # persistUniqueToValues :: Unique ValidPath -> [PersistValue] # fieldLens :: EntityField ValidPath field -> forall (f :: Type -> Type). Functor f => (field -> f field) -> Entity ValidPath -> f (Entity ValidPath) # | |||||||||||||||||
| SafeToInsert ValidPath Source # | |||||||||||||||||
Defined in System.Nix.Store.DB.Schema | |||||||||||||||||
| PersistField ValidPath Source # | |||||||||||||||||
Defined in System.Nix.Store.DB.Schema Methods toPersistValue :: ValidPath -> PersistValue # | |||||||||||||||||
| (TypeError (NoUniqueKeysError ValidPath) :: Constraint) => AtLeastOneUniqueKey ValidPath Source # | |||||||||||||||||
Defined in System.Nix.Store.DB.Schema | |||||||||||||||||
| (TypeError (NoUniqueKeysError ValidPath) :: Constraint) => OnlyOneUniqueKey ValidPath Source # | |||||||||||||||||
Defined in System.Nix.Store.DB.Schema Methods onlyUniqueP :: ValidPath -> Unique ValidPath # | |||||||||||||||||
| PersistFieldSql ValidPath Source # | |||||||||||||||||
| ToBackendKey SqlBackend ValidPath Source # | |||||||||||||||||
Defined in System.Nix.Store.DB.Schema Methods | |||||||||||||||||
| SymbolToField "drv" DerivationOutput ValidPathId Source # | |||||||||||||||||
Defined in System.Nix.Store.DB.Schema Methods | |||||||||||||||||
| SymbolToField "hash" ValidPath Text Source # | |||||||||||||||||
Defined in System.Nix.Store.DB.Schema Methods | |||||||||||||||||
| SymbolToField "narBytes" ValidPath Word64 Source # | |||||||||||||||||
Defined in System.Nix.Store.DB.Schema Methods | |||||||||||||||||
| SymbolToField "path" ValidPath StorePath Source # | |||||||||||||||||
Defined in System.Nix.Store.DB.Schema Methods | |||||||||||||||||
| SymbolToField "reference" Ref ValidPathId Source # | |||||||||||||||||
Defined in System.Nix.Store.DB.Schema Methods | |||||||||||||||||
| SymbolToField "referrer" Ref ValidPathId Source # | |||||||||||||||||
Defined in System.Nix.Store.DB.Schema Methods | |||||||||||||||||
| SymbolToField "regTime" ValidPath NixUTCTime Source # | |||||||||||||||||
Defined in System.Nix.Store.DB.Schema Methods | |||||||||||||||||
| SymbolToField "ca" ValidPath (Maybe ContentAddress) Source # | |||||||||||||||||
Defined in System.Nix.Store.DB.Schema Methods symbolToField :: EntityField ValidPath (Maybe ContentAddress) # | |||||||||||||||||
| SymbolToField "deriver" ValidPath (Maybe StorePath) Source # | |||||||||||||||||
Defined in System.Nix.Store.DB.Schema Methods | |||||||||||||||||
| SymbolToField "id" ValidPath (Key ValidPath) Source # | |||||||||||||||||
Defined in System.Nix.Store.DB.Schema Methods | |||||||||||||||||
| SymbolToField "sigs" ValidPath (Maybe Text) Source # | |||||||||||||||||
Defined in System.Nix.Store.DB.Schema Methods | |||||||||||||||||
| SymbolToField "ultimate" ValidPath (Maybe StorePathTrust) Source # | |||||||||||||||||
Defined in System.Nix.Store.DB.Schema Methods symbolToField :: EntityField ValidPath (Maybe StorePathTrust) # | |||||||||||||||||
| FromJSON (Key ValidPath) Source # | |||||||||||||||||
| ToJSON (Key ValidPath) Source # | |||||||||||||||||
| Read (Key ValidPath) Source # | |||||||||||||||||
| Show (Key ValidPath) Source # | |||||||||||||||||
| Eq (Key ValidPath) Source # | |||||||||||||||||
| Ord (Key ValidPath) Source # | |||||||||||||||||
Defined in System.Nix.Store.DB.Schema Methods compare :: Key ValidPath -> Key ValidPath -> Ordering # (<) :: Key ValidPath -> Key ValidPath -> Bool # (<=) :: Key ValidPath -> Key ValidPath -> Bool # (>) :: Key ValidPath -> Key ValidPath -> Bool # (>=) :: Key ValidPath -> Key ValidPath -> Bool # | |||||||||||||||||
| FromHttpApiData (Key ValidPath) Source # | |||||||||||||||||
Defined in System.Nix.Store.DB.Schema | |||||||||||||||||
| ToHttpApiData (Key ValidPath) Source # | |||||||||||||||||
Defined in System.Nix.Store.DB.Schema Methods toUrlPiece :: Key ValidPath -> Text # toEncodedUrlPiece :: Key ValidPath -> Builder # toHeader :: Key ValidPath -> ByteString # toQueryParam :: Key ValidPath -> Text # toEncodedQueryParam :: Key ValidPath -> Builder # | |||||||||||||||||
| PathPiece (Key ValidPath) Source # | |||||||||||||||||
Defined in System.Nix.Store.DB.Schema | |||||||||||||||||
| PersistField (Key ValidPath) Source # | |||||||||||||||||
Defined in System.Nix.Store.DB.Schema Methods toPersistValue :: Key ValidPath -> PersistValue # fromPersistValue :: PersistValue -> Either Text (Key ValidPath) # | |||||||||||||||||
| PersistFieldSql (Key ValidPath) Source # | |||||||||||||||||
| data EntityField ValidPath typ Source # | |||||||||||||||||
Defined in System.Nix.Store.DB.Schema data EntityField ValidPath typ
| |||||||||||||||||
| newtype Key ValidPath Source # | |||||||||||||||||
Defined in System.Nix.Store.DB.Schema | |||||||||||||||||
| type PersistEntityBackend ValidPath Source # | |||||||||||||||||
Defined in System.Nix.Store.DB.Schema | |||||||||||||||||
| data Unique ValidPath Source # | |||||||||||||||||
Defined in System.Nix.Store.DB.Schema | |||||||||||||||||