Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
All types and functions exported from this module are for advanced usage only. They are needed for stackage-server integration with pantry and some are needed for stack testing.
Synopsis
- mkSafeFilePath :: Text -> Maybe SafeFilePath
- unSafeFilePath :: SafeFilePath -> Text
- packageTreeKey :: Package -> TreeKey
- data Storage = Storage {
- withStorage_ :: forall env a. HasLogFunc env => ReaderT SqlBackend (RIO env) a -> RIO env a
- withWriteLock_ :: forall env a. HasLogFunc env => RIO env a -> RIO env a
- data PantryConfig = PantryConfig {
- pcPackageIndex :: !PackageIndexConfig
- pcHpackExecutable :: !HpackExecutable
- pcRootDir :: !(Path Abs Dir)
- pcStorage :: !Storage
- pcUpdateRef :: !(MVar Bool)
- pcParsedCabalFilesRawImmutable :: !(IORef (Map RawPackageLocationImmutable GenericPackageDescription))
- pcParsedCabalFilesMutable :: !(IORef (Map (Path Abs Dir) (PrintWarnings -> IO GenericPackageDescription, PackageName, Path Abs File)))
- pcConnectionCount :: !Int
- pcCasaConfig :: !(Maybe (CasaRepoPrefix, Int))
- pcSnapshotLocation :: SnapName -> RawSnapshotLocation
- newtype PackageNameP = PackageNameP {}
- newtype VersionP = VersionP {}
- newtype ModuleNameP = ModuleNameP {}
- data SafeFilePath
- data family Unique record
- data family EntityField record :: Type -> Type
- data family Key record
- type ModuleNameId = Key ModuleName
- type TreeEntryId = Key TreeEntry
- type TreeId = Key Tree
- data Tree = Tree {
- treeKey :: !BlobId
- treeCabal :: !(Maybe BlobId)
- treeCabalType :: !FileType
- treeName :: !PackageNameId
- treeVersion :: !VersionId
- type HackageCabalId = Key HackageCabal
- type VersionId = Key Version
- data Version
- type PackageNameId = Key PackageName
- data PackageName
- type BlobId = Key Blob
- migrateAll :: Migration
- getPackageNameById :: PackageNameId -> ReaderT SqlBackend (RIO env) (Maybe PackageName)
- getPackageNameId :: PackageName -> ReaderT SqlBackend (RIO env) PackageNameId
- getVersionId :: Version -> ReaderT SqlBackend (RIO env) VersionId
- storeBlob :: ByteString -> ReaderT SqlBackend (RIO env) (BlobId, BlobKey)
- loadBlobById :: BlobId -> ReaderT SqlBackend (RIO env) ByteString
- allBlobsSource :: HasResourceMap env => Maybe BlobId -> ConduitT () (BlobId, ByteString) (ReaderT SqlBackend (RIO env)) ()
- allHackageCabalRawPackageLocations :: HasResourceMap env => Maybe HackageCabalId -> ReaderT SqlBackend (RIO env) (Map HackageCabalId RawPackageLocationImmutable)
- allBlobsCount :: Maybe BlobId -> ReaderT SqlBackend (RIO env) Int
- allHackageCabalCount :: Maybe HackageCabalId -> ReaderT SqlBackend (RIO env) Int
- getBlobKey :: BlobId -> ReaderT SqlBackend (RIO env) BlobKey
- getTreeForKey :: TreeKey -> ReaderT SqlBackend (RIO env) (Maybe (Entity Tree))
- data HackageTarballResult = HackageTarballResult {}
- forceUpdateHackageIndex :: (HasPantryConfig env, HasLogFunc env) => Maybe Utf8Builder -> RIO env DidUpdateOccur
- getHackageTarball :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => PackageIdentifierRevision -> Maybe TreeKey -> RIO env HackageTarballResult
Documentation
mkSafeFilePath :: Text -> Maybe SafeFilePath #
unSafeFilePath :: SafeFilePath -> Text #
packageTreeKey :: Package -> TreeKey #
The TreeKey
containing this package.
This is a hash of the binary representation of packageTree
.
Since: 0.1.0.0
Represents a SQL database connection.
Storage | |
|
data PantryConfig #
Configuration value used by the entire pantry package. Create one using
withPantryConfig
or withPantryConfig'
. See also PantryApp
for a
convenience approach to using pantry.
Since: 0.1.0.0
PantryConfig | |
|
newtype PackageNameP #
Instances
Instances
FromJSON VersionP | |
ToJSON VersionP | |
Defined in Pantry.Types | |
Read VersionP | |
Show VersionP | |
NFData VersionP | |
Defined in Pantry.Types | |
Eq VersionP | |
Ord VersionP | |
Defined in Pantry.Types | |
PersistField VersionP | |
Defined in Pantry.Types | |
PersistFieldSql VersionP | |
Display VersionP | |
Defined in Pantry.Types display :: VersionP -> Utf8Builder # textDisplay :: VersionP -> Text # | |
SymbolToField "version" Version VersionP Source # | |
Defined in Pantry.Storage |
newtype ModuleNameP #
Instances
Show ModuleNameP | |
Defined in Pantry.Types showsPrec :: Int -> ModuleNameP -> ShowS # show :: ModuleNameP -> String # showList :: [ModuleNameP] -> ShowS # | |
NFData ModuleNameP | |
Defined in Pantry.Types rnf :: ModuleNameP -> () # | |
Eq ModuleNameP | |
Defined in Pantry.Types (==) :: ModuleNameP -> ModuleNameP -> Bool # (/=) :: ModuleNameP -> ModuleNameP -> Bool # | |
Ord ModuleNameP | |
Defined in Pantry.Types compare :: ModuleNameP -> ModuleNameP -> Ordering # (<) :: ModuleNameP -> ModuleNameP -> Bool # (<=) :: ModuleNameP -> ModuleNameP -> Bool # (>) :: ModuleNameP -> ModuleNameP -> Bool # (>=) :: ModuleNameP -> ModuleNameP -> Bool # max :: ModuleNameP -> ModuleNameP -> ModuleNameP # min :: ModuleNameP -> ModuleNameP -> ModuleNameP # | |
PersistField ModuleNameP | |
Defined in Pantry.Types | |
PersistFieldSql ModuleNameP | |
Defined in Pantry.Types sqlType :: Proxy ModuleNameP -> SqlType # | |
Display ModuleNameP | |
Defined in Pantry.Types display :: ModuleNameP -> Utf8Builder # textDisplay :: ModuleNameP -> Text # |
data SafeFilePath #
Instances
Show SafeFilePath | |
Defined in Pantry.Types showsPrec :: Int -> SafeFilePath -> ShowS # show :: SafeFilePath -> String # showList :: [SafeFilePath] -> ShowS # | |
Eq SafeFilePath | |
Defined in Pantry.Types (==) :: SafeFilePath -> SafeFilePath -> Bool # (/=) :: SafeFilePath -> SafeFilePath -> Bool # | |
Ord SafeFilePath | |
Defined in Pantry.Types compare :: SafeFilePath -> SafeFilePath -> Ordering # (<) :: SafeFilePath -> SafeFilePath -> Bool # (<=) :: SafeFilePath -> SafeFilePath -> Bool # (>) :: SafeFilePath -> SafeFilePath -> Bool # (>=) :: SafeFilePath -> SafeFilePath -> Bool # max :: SafeFilePath -> SafeFilePath -> SafeFilePath # min :: SafeFilePath -> SafeFilePath -> SafeFilePath # | |
PersistField SafeFilePath | |
Defined in Pantry.Types | |
PersistFieldSql SafeFilePath | |
Defined in Pantry.Types sqlType :: Proxy SafeFilePath -> SqlType # | |
Display SafeFilePath | |
Defined in Pantry.Types display :: SafeFilePath -> Utf8Builder # textDisplay :: SafeFilePath -> Text # |
Unique keys besides the Key
.
Instances
data Unique PackageName Source # | |
Defined in Pantry.Storage | |
data Unique Tree Source # | |
Defined in Pantry.Storage | |
data Unique Version Source # | |
Defined in Pantry.Storage |
data family EntityField record :: Type -> Type #
An EntityField
is parameterised by the Haskell record it belongs to
and the additional type of that field.
As of persistent-2.11.0.0
, it's possible to use the OverloadedLabels
language extension to refer to EntityField
values polymorphically. See
the documentation on SymbolToField
for more information.
Instances
SymbolToField sym rec typ => IsLabel sym (EntityField rec typ) | This instance delegates to Since: persistent-2.11.0.0 |
Defined in Database.Persist.Class.PersistEntity fromLabel :: EntityField rec typ # | |
data EntityField PackageName typ Source # | |
Defined in Pantry.Storage data EntityField PackageName typ
| |
data EntityField Tree typ Source # | |
Defined in Pantry.Storage data EntityField Tree typ
| |
data EntityField Version typ Source # | |
Defined in Pantry.Storage |
By default, a backend will automatically generate the key Instead you can specify a Primary key made up of unique values.
Instances
type ModuleNameId = Key ModuleName Source #
type TreeEntryId = Key TreeEntry Source #
Tree | |
|
Instances
type HackageCabalId = Key HackageCabal Source #
Instances
type PackageNameId = Key PackageName Source #
data PackageName Source #
Instances
getPackageNameById :: PackageNameId -> ReaderT SqlBackend (RIO env) (Maybe PackageName) Source #
getPackageNameId :: PackageName -> ReaderT SqlBackend (RIO env) PackageNameId Source #
getVersionId :: Version -> ReaderT SqlBackend (RIO env) VersionId Source #
storeBlob :: ByteString -> ReaderT SqlBackend (RIO env) (BlobId, BlobKey) Source #
loadBlobById :: BlobId -> ReaderT SqlBackend (RIO env) ByteString Source #
:: HasResourceMap env | |
=> Maybe BlobId | For some x, yield blob whose id>x. |
-> ConduitT () (BlobId, ByteString) (ReaderT SqlBackend (RIO env)) () |
allHackageCabalRawPackageLocations Source #
:: HasResourceMap env | |
=> Maybe HackageCabalId | For some x, yield cabals whose id>x. |
-> ReaderT SqlBackend (RIO env) (Map HackageCabalId RawPackageLocationImmutable) |
Pull all hackage cabal entries from the database as
RawPackageLocationImmutable
. We do a manual join rather than dropping to
raw SQL, and Esqueleto would add more deps.
allBlobsCount :: Maybe BlobId -> ReaderT SqlBackend (RIO env) Int Source #
allHackageCabalCount :: Maybe HackageCabalId -> ReaderT SqlBackend (RIO env) Int Source #
getBlobKey :: BlobId -> ReaderT SqlBackend (RIO env) BlobKey Source #
getTreeForKey :: TreeKey -> ReaderT SqlBackend (RIO env) (Maybe (Entity Tree)) Source #
data HackageTarballResult Source #
Information returned by getHackageTarball
Since: 0.1.0.0
HackageTarballResult | |
|
forceUpdateHackageIndex :: (HasPantryConfig env, HasLogFunc env) => Maybe Utf8Builder -> RIO env DidUpdateOccur Source #
Same as updateHackageIndex
, but force the database update even if hackage
security tells that there is no change. This can be useful in order to make
sure the database is in sync with the locally downloaded tarball
Since: 0.1.0.0
getHackageTarball :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => PackageIdentifierRevision -> Maybe TreeKey -> RIO env HackageTarballResult Source #