Safe Haskell | None |
---|---|
Language | GHC2021 |
Stack.Prelude
Synopsis
- withSystemTempDir :: MonadUnliftIO m => String -> (Path Abs Dir -> m a) -> m a
- withKeepSystemTempDir :: MonadUnliftIO m => String -> (Path Abs Dir -> m a) -> m a
- sinkProcessStderrStdout :: forall e o env. (HasProcessContext env, HasLogFunc env, HasCallStack) => String -> [String] -> ConduitM ByteString Void (RIO env) e -> ConduitM ByteString Void (RIO env) o -> RIO env (e, o)
- sinkProcessStdout :: (HasProcessContext env, HasLogFunc env, HasCallStack) => String -> [String] -> ConduitM ByteString Void (RIO env) a -> RIO env a
- logProcessStderrStdout :: (HasCallStack, HasProcessContext env, HasLogFunc env) => ProcessConfig stdin stdoutIgnored stderrIgnored -> RIO env ()
- readProcessNull :: (HasProcessContext env, HasLogFunc env, HasCallStack) => String -> [String] -> RIO env ()
- withProcessContext :: HasProcessContext env => ProcessContext -> RIO env a -> RIO env a
- stripCR :: Text -> Text
- prompt :: MonadIO m => Text -> m Text
- promptPassword :: MonadIO m => Text -> m Text
- promptBool :: MonadIO m => Text -> m Bool
- newtype FirstTrue = FirstTrue {}
- fromFirstTrue :: FirstTrue -> Bool
- defaultFirstTrue :: FirstTrue -> Bool
- newtype FirstFalse = FirstFalse {
- firstFalse :: Maybe Bool
- fromFirstFalse :: FirstFalse -> Bool
- defaultFirstFalse :: FirstFalse -> Bool
- writeBinaryFileAtomic :: MonadIO m => Path absrel File -> Builder -> m ()
- bugReport :: String -> String -> String
- bugPrettyReport :: String -> StyleDoc -> StyleDoc
- blankLine :: StyleDoc
- putUtf8Builder :: MonadIO m => Utf8Builder -> m ()
- putBuilder :: MonadIO m => Builder -> m ()
- ppException :: SomeException -> StyleDoc
- prettyThrowIO :: (Exception e, MonadIO m, Pretty e) => e -> m a
- prettyThrowM :: (Exception e, MonadThrow m, Pretty e) => e -> m a
- mcons :: Maybe a -> [a] -> [a]
- data MungedPackageId = MungedPackageId {}
- data MungedPackageName = MungedPackageName !PackageName !LibraryName
- data LibraryName
- module RIO
- data Version
- data Path b t
- newtype First a = First {}
- data PackageName
- data PackageIdentifier = PackageIdentifier {}
- newtype Any = Any {}
- data RepoType
- data Repo = Repo {
- repoUrl :: !Text
- repoCommit :: !Text
- repoType :: !RepoType
- repoSubdir :: !Text
- data FlagName
- toFilePath :: Path b t -> FilePath
- newtype Sum a = Sum {
- getSum :: a
- newtype Endo a = Endo {
- appEndo :: a -> a
- parseVersion :: String -> Maybe Version
- newtype FileSize = FileSize Word
- data BlobKey = BlobKey !SHA256 !FileSize
- type ConduitM = ConduitT
- (.|) :: forall (m :: Type -> Type) a b c r. Monad m => ConduitT a b m () -> ConduitT b c m r -> ConduitT a c m r
- runConduit :: Monad m => ConduitT () Void m r -> m r
- data SHA256
- data File
- data Snapshot = Snapshot {}
- data Force
- data GlobalHintsLocation
- = GHLUrl !Text
- | GHLFilePath !(ResolvedPath File)
- newtype SnapshotCacheHash = SnapshotCacheHash {}
- data SnapshotLayer = SnapshotLayer {
- slParent :: !SnapshotLocation
- slCompiler :: !(Maybe WantedCompiler)
- slLocations :: ![PackageLocationImmutable]
- slDropPackages :: !(Set PackageName)
- slFlags :: !(Map PackageName (Map FlagName Bool))
- slHidden :: !(Map PackageName Bool)
- slGhcOptions :: !(Map PackageName [Text])
- slPublishTime :: !(Maybe UTCTime)
- data RawSnapshotLayer = RawSnapshotLayer {
- rslParent :: !RawSnapshotLocation
- rslCompiler :: !(Maybe WantedCompiler)
- rslLocations :: ![RawPackageLocationImmutable]
- rslDropPackages :: !(Set PackageName)
- rslFlags :: !(Map PackageName (Map FlagName Bool))
- rslHidden :: !(Map PackageName Bool)
- rslGhcOptions :: !(Map PackageName [Text])
- rslPublishTime :: !(Maybe UTCTime)
- data SnapshotPackage = SnapshotPackage {
- spLocation :: !PackageLocationImmutable
- spFlags :: !(Map FlagName Bool)
- spHidden :: !Bool
- spGhcOptions :: ![Text]
- data RawSnapshotPackage = RawSnapshotPackage {
- rspLocation :: !RawPackageLocationImmutable
- rspFlags :: !(Map FlagName Bool)
- rspHidden :: !Bool
- rspGhcOptions :: ![Text]
- data RawSnapshot = RawSnapshot {
- rsCompiler :: !WantedCompiler
- rsPackages :: !(Map PackageName RawSnapshotPackage)
- rsDrop :: !(Set PackageName)
- data SnapshotLocation
- = SLCompiler !WantedCompiler
- | SLUrl !Text !BlobKey
- | SLFilePath !(ResolvedPath File)
- data RawSnapshotLocation
- = RSLCompiler !WantedCompiler
- | RSLUrl !Text !(Maybe BlobKey)
- | RSLFilePath !(ResolvedPath File)
- | RSLSynonym !SnapName
- data SnapName
- data WantedCompiler
- data HpackExecutable
- newtype CabalString a = CabalString {
- unCabalString :: a
- data ArchiveLocation
- = ALUrl !Text
- | ALFilePath !(ResolvedPath File)
- newtype RelFilePath = RelFilePath Text
- data PackageMetadata = PackageMetadata {
- pmIdent :: !PackageIdentifier
- pmTreeKey :: !TreeKey
- data RawPackageMetadata = RawPackageMetadata {
- rpmName :: !(Maybe PackageName)
- rpmVersion :: !(Maybe Version)
- rpmTreeKey :: !(Maybe TreeKey)
- newtype TreeKey = TreeKey BlobKey
- data SafeFilePath
- data FuzzyResults
- data PantryException
- = PackageIdentifierRevisionParseFail !Text
- | InvalidCabalFile !(Either RawPackageLocationImmutable (Path Abs File)) !(Maybe Version) ![PError] ![PWarning]
- | TreeWithoutCabalFile !RawPackageLocationImmutable
- | TreeWithMultipleCabalFiles !RawPackageLocationImmutable ![SafeFilePath]
- | MismatchedCabalName !(Path Abs File) !PackageName
- | NoLocalPackageDirFound !(Path Abs Dir)
- | NoCabalFileFound !(Path Abs Dir)
- | MultipleCabalFilesFound !(Path Abs Dir) ![Path Abs File]
- | InvalidWantedCompiler !Text
- | InvalidSnapshotLocation !(Path Abs Dir) !Text
- | InvalidOverrideCompiler !WantedCompiler !WantedCompiler
- | InvalidFilePathSnapshot !Text
- | InvalidSnapshot !RawSnapshotLocation !SomeException
- | InvalidGlobalHintsLocation !(Path Abs Dir) !Text
- | InvalidFilePathGlobalHints !Text
- | MismatchedPackageMetadata !RawPackageLocationImmutable !RawPackageMetadata !(Maybe TreeKey) !PackageIdentifier
- | Non200ResponseStatus !Status
- | InvalidBlobKey !(Mismatch BlobKey)
- | Couldn'tParseSnapshot !RawSnapshotLocation !String
- | WrongCabalFileName !RawPackageLocationImmutable !SafeFilePath !PackageName
- | DownloadInvalidSHA256 !Text !(Mismatch SHA256)
- | DownloadInvalidSize !Text !(Mismatch FileSize)
- | DownloadTooLarge !Text !(Mismatch FileSize)
- | LocalNoArchiveFileFound !(Path Abs File)
- | LocalInvalidSHA256 !(Path Abs File) !(Mismatch SHA256)
- | LocalInvalidSize !(Path Abs File) !(Mismatch FileSize)
- | UnknownArchiveType !ArchiveLocation
- | InvalidTarFileType !ArchiveLocation !FilePath !FileType
- | UnsupportedTarball !ArchiveLocation !Text
- | NoHackageCryptographicHash !PackageIdentifier
- | FailedToCloneRepo !SimpleRepo
- | TreeReferencesMissingBlob !RawPackageLocationImmutable !SafeFilePath !BlobKey
- | CompletePackageMetadataMismatch !RawPackageLocationImmutable !PackageMetadata
- | CRC32Mismatch !ArchiveLocation !FilePath !(Mismatch Word32)
- | UnknownHackagePackage !PackageIdentifierRevision !FuzzyResults
- | CannotCompleteRepoNonSHA1 !Repo
- | MutablePackageLocationFromUrl !Text
- | MismatchedCabalFileForHackage !PackageIdentifierRevision !(Mismatch PackageIdentifier)
- | PackageNameParseFail !Text
- | PackageVersionParseFail !Text
- | InvalidCabalFilePath !(Path Abs File)
- | DuplicatePackageNames !Utf8Builder ![(PackageName, [RawPackageLocationImmutable])]
- | MigrationFailure !Text !(Path Abs File) !SomeException
- | NoCasaConfig
- | InvalidTreeFromCasa !BlobKey !ByteString
- | ParseSnapNameException !Text
- | HpackLibraryException !(Path Abs File) !String
- | HpackExeException !FilePath !(Path Abs Dir) !SomeException
- data Mismatch a = Mismatch {
- mismatchExpected :: !a
- mismatchActual :: !a
- data PackageIdentifierRevision = PackageIdentifierRevision !PackageName !Version !CabalFileInfo
- data CabalFileInfo
- class HasPantryConfig env where
- pantryConfigL :: Lens' env PantryConfig
- data HackageSecurityConfig = HackageSecurityConfig {
- hscKeyIds :: ![Text]
- hscKeyThreshold :: !Int
- hscIgnoreExpiry :: !Bool
- data PackageIndexConfig = PackageIndexConfig {}
- data SimpleRepo = SimpleRepo {}
- data Archive = Archive {}
- data RawArchive = RawArchive {
- raLocation :: !ArchiveLocation
- raHash :: !(Maybe SHA256)
- raSize :: !(Maybe FileSize)
- raSubdir :: !Text
- data PackageLocationImmutable
- data RawPackageLocationImmutable
- data PackageLocation
- data RawPackageLocation
- data ResolvedPath t = ResolvedPath {
- resolvedRelative :: !RelFilePath
- resolvedAbsolute :: !(Path Abs t)
- data Unresolved a
- data PrintWarnings
- data PantryConfig
- newtype Revision = Revision Word
- snapshotLocation :: HasPantryConfig env => SnapName -> RIO env RawSnapshotLocation
- resolvePaths :: MonadIO m => Maybe (Path Abs Dir) -> Unresolved a -> m a
- toRawPL :: PackageLocation -> RawPackageLocation
- defaultHackageSecurityConfig :: HackageSecurityConfig
- parseHackageText :: Text -> Either PantryException (PackageIdentifier, BlobKey)
- parsePackageIdentifierRevision :: Text -> Either PantryException PackageIdentifierRevision
- mkSafeFilePath :: Text -> Maybe SafeFilePath
- parsePackageIdentifier :: String -> Maybe PackageIdentifier
- parsePackageName :: String -> Maybe PackageName
- parsePackageNameThrowing :: MonadThrow m => String -> m PackageName
- parseVersionThrowing :: MonadThrow m => String -> m Version
- parseFlagName :: String -> Maybe FlagName
- packageNameString :: PackageName -> String
- packageIdentifierString :: PackageIdentifier -> String
- versionString :: Version -> String
- flagNameString :: FlagName -> String
- moduleNameString :: ModuleName -> String
- toCabalStringMap :: Map a v -> Map (CabalString a) v
- unCabalStringMap :: Map (CabalString a) v -> Map a v
- parseWantedCompiler :: Text -> Either PantryException WantedCompiler
- parseRawSnapshotLocation :: Text -> Unresolved RawSnapshotLocation
- defaultSnapshotLocation :: SnapName -> RawSnapshotLocation
- defaultGlobalHintsLocation :: WantedCompiler -> GlobalHintsLocation
- parseSnapName :: MonadThrow m => Text -> m SnapName
- toRawSL :: SnapshotLocation -> RawSnapshotLocation
- toRawSnapshotLayer :: SnapshotLayer -> RawSnapshotLayer
- warnMissingCabalFile :: HasLogFunc env => RawPackageLocationImmutable -> RIO env ()
- data RequireHackageIndex
- data UsePreferredVersions
- data DidUpdateOccur
- hackageIndexTarballL :: HasPantryConfig env => SimpleGetter env (Path Abs File)
- updateHackageIndex :: (HasPantryConfig env, HasLogFunc env) => Maybe Utf8Builder -> RIO env DidUpdateOccur
- getHackageTypoCorrections :: (HasPantryConfig env, HasLogFunc env) => PackageName -> RIO env [PackageName]
- getHackagePackageVersions :: (HasPantryConfig env, HasLogFunc env) => RequireHackageIndex -> UsePreferredVersions -> PackageName -> RIO env (Map Version (Map Revision BlobKey))
- fetchReposRaw :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => [(Repo, RawPackageMetadata)] -> RIO env ()
- fetchRepos :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => [(Repo, PackageMetadata)] -> RIO env ()
- withRepo :: (HasLogFunc env, HasProcessContext env) => SimpleRepo -> RIO env a -> RIO env a
- data PantryApp
- data AddPackagesConfig = AddPackagesConfig {
- apcDrop :: !(Set PackageName)
- apcFlags :: !(Map PackageName (Map FlagName Bool))
- apcHiddens :: !(Map PackageName Bool)
- apcGhcOptions :: !(Map PackageName [Text])
- data CompletedSL = CompletedSL !RawSnapshotLocation !SnapshotLocation
- data CompletedPLI = CompletedPLI !RawPackageLocationImmutable !PackageLocationImmutable
- data CompletePackageLocation = CompletePackageLocation {}
- withPantryConfig :: HasLogFunc env => Path Abs Dir -> PackageIndexConfig -> HpackExecutable -> Int -> CasaRepoPrefix -> Int -> (SnapName -> RawSnapshotLocation) -> (WantedCompiler -> GlobalHintsLocation) -> (PantryConfig -> RIO env a) -> RIO env a
- withPantryConfig' :: HasLogFunc env => Path Abs Dir -> PackageIndexConfig -> HpackExecutable -> Force -> Int -> Maybe (CasaRepoPrefix, Int) -> (SnapName -> RawSnapshotLocation) -> (WantedCompiler -> GlobalHintsLocation) -> (PantryConfig -> RIO env a) -> RIO env a
- defaultCasaRepoPrefix :: CasaRepoPrefix
- defaultCasaMaxPerRequest :: Int
- defaultPackageIndexConfig :: PackageIndexConfig
- defaultDownloadPrefix :: Text
- getLatestHackageVersion :: (HasPantryConfig env, HasLogFunc env) => RequireHackageIndex -> PackageName -> UsePreferredVersions -> RIO env (Maybe PackageIdentifierRevision)
- getLatestHackageLocation :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => RequireHackageIndex -> PackageName -> UsePreferredVersions -> RIO env (Maybe PackageLocationImmutable)
- getLatestHackageRevision :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => RequireHackageIndex -> PackageName -> Version -> RIO env (Maybe (Revision, BlobKey, TreeKey))
- fetchPackages :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env, Foldable f) => f PackageLocationImmutable -> RIO env ()
- unpackPackageLocationRaw :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => Path Abs Dir -> RawPackageLocationImmutable -> RIO env ()
- unpackPackageLocation :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => Path Abs Dir -> PackageLocationImmutable -> RIO env ()
- loadCabalFileImmutable :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => PackageLocationImmutable -> RIO env GenericPackageDescription
- loadCabalFileRawImmutable :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => RawPackageLocationImmutable -> RIO env GenericPackageDescription
- loadCabalFileRaw :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => Maybe Text -> RawPackageLocation -> RIO env GenericPackageDescription
- loadCabalFile :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => Maybe Text -> PackageLocation -> RIO env GenericPackageDescription
- loadCabalFilePath :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => Maybe Text -> Path Abs Dir -> RIO env (PrintWarnings -> IO GenericPackageDescription, PackageName, Path Abs File)
- findOrGenerateCabalFile :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => Maybe Text -> Path Abs Dir -> RIO env (PackageName, Path Abs File)
- gpdPackageIdentifier :: GenericPackageDescription -> PackageIdentifier
- gpdPackageName :: GenericPackageDescription -> PackageName
- gpdVersion :: GenericPackageDescription -> Version
- loadPackage :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => PackageLocationImmutable -> RIO env Package
- loadPackageRaw :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => RawPackageLocationImmutable -> RIO env Package
- tryLoadPackageRawViaCasa :: (HasLogFunc env, HasPantryConfig env, HasProcessContext env) => RawPackageLocationImmutable -> TreeKey -> RIO env (Maybe Package)
- completePackageLocation :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => RawPackageLocationImmutable -> RIO env CompletePackageLocation
- completeSnapshotLocation :: (HasPantryConfig env, HasLogFunc env) => RawSnapshotLocation -> RIO env SnapshotLocation
- loadAndCompleteSnapshot :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => SnapshotLocation -> Map RawSnapshotLocation SnapshotLocation -> Map RawPackageLocationImmutable PackageLocationImmutable -> RIO env (Snapshot, [CompletedSL], [CompletedPLI])
- loadAndCompleteSnapshot' :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => Bool -> SnapshotLocation -> Map RawSnapshotLocation SnapshotLocation -> Map RawPackageLocationImmutable PackageLocationImmutable -> RIO env (Snapshot, [CompletedSL], [CompletedPLI])
- loadAndCompleteSnapshotRaw :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => RawSnapshotLocation -> Map RawSnapshotLocation SnapshotLocation -> Map RawPackageLocationImmutable PackageLocationImmutable -> RIO env (Snapshot, [CompletedSL], [CompletedPLI])
- loadAndCompleteSnapshotRaw' :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => Bool -> RawSnapshotLocation -> Map RawSnapshotLocation SnapshotLocation -> Map RawPackageLocationImmutable PackageLocationImmutable -> RIO env (Snapshot, [CompletedSL], [CompletedPLI])
- addPackagesToSnapshot :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => Utf8Builder -> [RawPackageLocationImmutable] -> AddPackagesConfig -> Map PackageName RawSnapshotPackage -> RIO env (Map PackageName RawSnapshotPackage, AddPackagesConfig)
- loadRawSnapshotLayer :: (HasPantryConfig env, HasLogFunc env) => RawSnapshotLocation -> RIO env (Either WantedCompiler (RawSnapshotLayer, CompletedSL))
- loadSnapshotLayer :: (HasPantryConfig env, HasLogFunc env) => SnapshotLocation -> RIO env (Either WantedCompiler RawSnapshotLayer)
- getPackageLocationName :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => RawPackageLocationImmutable -> RIO env PackageName
- packageLocationIdent :: PackageLocationImmutable -> PackageIdentifier
- packageLocationVersion :: PackageLocationImmutable -> Version
- getRawPackageLocationIdent :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => RawPackageLocationImmutable -> RIO env PackageIdentifier
- getRawPackageLocationTreeKey :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => RawPackageLocationImmutable -> RIO env TreeKey
- getPackageLocationTreeKey :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => PackageLocationImmutable -> RIO env TreeKey
- hpackExecutableL :: Lens' PantryConfig HpackExecutable
- hpackForceL :: Lens' PantryConfig Force
- runPantryApp :: MonadIO m => RIO PantryApp a -> m a
- runPantryAppWith :: MonadIO m => Int -> CasaRepoPrefix -> Int -> RIO PantryApp a -> m a
- runPantryAppClean :: MonadIO m => RIO PantryApp a -> m a
- loadGlobalHints :: (HasTerm env, HasPantryConfig env) => WantedCompiler -> RIO env (Maybe (Map PackageName Version))
- partitionReplacedDependencies :: Ord id => Map PackageName a -> (a -> PackageName) -> (a -> id) -> (a -> [id]) -> Set PackageName -> (Map PackageName [PackageName], Map PackageName a)
- withSnapshotCache :: (HasPantryConfig env, HasLogFunc env) => SnapshotCacheHash -> RIO env (Map PackageName (Set ModuleName)) -> ((ModuleName -> RIO env [PackageName]) -> RIO env a) -> RIO env a
- data Abs
- data Rel
- data Dir
- ensureFileDurable :: MonadIO m => FilePath -> m ()
- writeBinaryFileDurable :: MonadIO m => FilePath -> ByteString -> m ()
- writeBinaryFileDurableAtomic :: MonadIO m => FilePath -> ByteString -> m ()
- withBinaryFileDurable :: MonadUnliftIO m => FilePath -> IOMode -> (Handle -> m r) -> m r
- withBinaryFileDurableAtomic :: MonadUnliftIO m => FilePath -> IOMode -> (Handle -> m r) -> m r
- withBinaryFileAtomic :: MonadUnliftIO m => FilePath -> IOMode -> (Handle -> m r) -> m r
- writeBinaryFile :: MonadIO m => FilePath -> ByteString -> m ()
- class HasStylesUpdate env where
- stylesUpdateL :: Lens' env StylesUpdate
- class (HasLogFunc env, HasStylesUpdate env) => HasTerm env where
- class Pretty a where
- data PrettyException = (Exception e, Pretty e) => PrettyException e
- newtype PrettyRawSnapshotLocation = PrettyRawSnapshotLocation RawSnapshotLocation
- data StyleDoc
- data Style
- type StyleSpec = (Text, [SGR])
- newtype StylesUpdate = StylesUpdate {
- stylesUpdate :: [(Style, StyleSpec)]
- (<+>) :: StyleDoc -> StyleDoc -> StyleDoc
- align :: StyleDoc -> StyleDoc
- bulletedList :: [StyleDoc] -> StyleDoc
- debugBracket :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m, MonadUnliftIO m) => StyleDoc -> m a -> m a
- defaultStyles :: Styles
- displayWithColor :: (HasTerm env, Pretty a, MonadReader env m, HasCallStack) => a -> m Utf8Builder
- encloseSep :: StyleDoc -> StyleDoc -> StyleDoc -> [StyleDoc] -> StyleDoc
- fill :: Int -> StyleDoc -> StyleDoc
- fillSep :: [StyleDoc] -> StyleDoc
- foldr' :: Foldable t => (a -> b -> b) -> b -> t a -> b
- fromPackageId :: IsString a => PackageIdentifier -> a
- fromPackageName :: IsString a => PackageName -> a
- flow :: String -> StyleDoc
- hang :: Int -> StyleDoc -> StyleDoc
- hcat :: [StyleDoc] -> StyleDoc
- hsep :: [StyleDoc] -> StyleDoc
- indent :: Int -> StyleDoc -> StyleDoc
- line :: StyleDoc
- logLevelToStyle :: LogLevel -> Style
- mkNarrativeList :: Pretty a => Maybe Style -> Bool -> [a] -> [StyleDoc]
- parens :: StyleDoc -> StyleDoc
- parseStylesUpdateFromString :: String -> StylesUpdate
- prettyDebug :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => StyleDoc -> m ()
- prettyDebugL :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => [StyleDoc] -> m ()
- prettyError :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => StyleDoc -> m ()
- prettyErrorL :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => [StyleDoc] -> m ()
- prettyGeneric :: (HasTerm env, HasCallStack, Pretty b, MonadReader env m, MonadIO m) => LogLevel -> b -> m ()
- prettyInfo :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => StyleDoc -> m ()
- prettyInfoL :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => [StyleDoc] -> m ()
- prettyInfoS :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => String -> m ()
- prettyNote :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => StyleDoc -> m ()
- prettyNoteL :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => [StyleDoc] -> m ()
- prettyNoteS :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => String -> m ()
- prettyWarn :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => StyleDoc -> m ()
- prettyWarnL :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => [StyleDoc] -> m ()
- prettyWarnNoIndent :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => StyleDoc -> m ()
- prettyWarnS :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => String -> m ()
- punctuate :: StyleDoc -> [StyleDoc] -> [StyleDoc]
- sep :: [StyleDoc] -> StyleDoc
- softbreak :: StyleDoc
- softline :: StyleDoc
- spacedBulletedList :: [StyleDoc] -> StyleDoc
- string :: String -> StyleDoc
- style :: Style -> StyleDoc -> StyleDoc
- vsep :: [StyleDoc] -> StyleDoc
Documentation
withSystemTempDir :: MonadUnliftIO m => String -> (Path Abs Dir -> m a) -> m a Source #
Path version
withKeepSystemTempDir :: MonadUnliftIO m => String -> (Path Abs Dir -> m a) -> m a Source #
Like withSystemTempDir
, but the temporary directory is not deleted.
sinkProcessStderrStdout Source #
Arguments
:: forall e o env. (HasProcessContext env, HasLogFunc env, HasCallStack) | |
=> String | Command |
-> [String] | Command line arguments |
-> ConduitM ByteString Void (RIO env) e | Sink for stderr |
-> ConduitM ByteString Void (RIO env) o | Sink for stdout |
-> RIO env (e, o) |
Consume the stdout and stderr of a process feeding strict ByteString
s to
the consumers.
Throws a ReadProcessException
if unsuccessful in launching, or
ExitCodeException
if the process itself fails.
Arguments
:: (HasProcessContext env, HasLogFunc env, HasCallStack) | |
=> String | Command |
-> [String] | Command line arguments |
-> ConduitM ByteString Void (RIO env) a | Sink for stdout |
-> RIO env a |
Consume the stdout of a process feeding strict ByteString
s to a consumer.
If the process fails, spits out stdout and stderr as error log
level. Should not be used for long-running processes or ones with
lots of output; for that use sinkProcessStderrStdout
.
Throws a ReadProcessException
if unsuccessful.
logProcessStderrStdout :: (HasCallStack, HasProcessContext env, HasLogFunc env) => ProcessConfig stdin stdoutIgnored stderrIgnored -> RIO env () Source #
Arguments
:: (HasProcessContext env, HasLogFunc env, HasCallStack) | |
=> String | Command |
-> [String] | Command line arguments |
-> RIO env () |
Read from the process, ignoring any output.
Throws a ReadProcessException
exception if the process fails.
withProcessContext :: HasProcessContext env => ProcessContext -> RIO env a -> RIO env a Source #
Use the new ProcessContext
, but retain the working directory
from the parent environment.
prompt :: MonadIO m => Text -> m Text Source #
Prompt the user by sending text to stdout, and taking a line of input from stdin.
promptPassword :: MonadIO m => Text -> m Text Source #
Prompt the user by sending text to stdout, and collecting a line of input from stdin. While taking input from stdin, input echoing is disabled, to hide passwords.
Based on code from cabal-install, Distribution.Client.Upload
promptBool :: MonadIO m => Text -> m Bool Source #
Prompt the user by sending text to stdout, and collecting a line of input from stdin. If something other than "y" or "n" is entered, then print a message indicating that "y" or "n" is expected, and ask again.
Like First Bool
, but the default is True
.
Instances
Monoid FirstTrue Source # | |
Semigroup FirstTrue Source # | |
Show FirstTrue Source # | |
Eq FirstTrue Source # | |
Ord FirstTrue Source # | |
defaultFirstTrue :: FirstTrue -> Bool Source #
Helper for filling in default values
newtype FirstFalse Source #
Like First Bool
, but the default is False
.
Constructors
FirstFalse | |
Fields
|
Instances
Monoid FirstFalse Source # | |
Defined in Stack.Prelude Methods mempty :: FirstFalse # mappend :: FirstFalse -> FirstFalse -> FirstFalse # mconcat :: [FirstFalse] -> FirstFalse # | |
Semigroup FirstFalse Source # | |
Defined in Stack.Prelude Methods (<>) :: FirstFalse -> FirstFalse -> FirstFalse # sconcat :: NonEmpty FirstFalse -> FirstFalse # stimes :: Integral b => b -> FirstFalse -> FirstFalse # | |
Show FirstFalse Source # | |
Defined in Stack.Prelude Methods showsPrec :: Int -> FirstFalse -> ShowS # show :: FirstFalse -> String # showList :: [FirstFalse] -> ShowS # | |
Eq FirstFalse Source # | |
Defined in Stack.Prelude | |
Ord FirstFalse Source # | |
Defined in Stack.Prelude Methods compare :: FirstFalse -> FirstFalse -> Ordering # (<) :: FirstFalse -> FirstFalse -> Bool # (<=) :: FirstFalse -> FirstFalse -> Bool # (>) :: FirstFalse -> FirstFalse -> Bool # (>=) :: FirstFalse -> FirstFalse -> Bool # max :: FirstFalse -> FirstFalse -> FirstFalse # min :: FirstFalse -> FirstFalse -> FirstFalse # |
fromFirstFalse :: FirstFalse -> Bool Source #
defaultFirstFalse :: FirstFalse -> Bool Source #
Helper for filling in default values
writeBinaryFileAtomic :: MonadIO m => Path absrel File -> Builder -> m () Source #
Write a Builder
to a file and atomically rename.
putUtf8Builder :: MonadIO m => Utf8Builder -> m () Source #
Write a Utf8Builder
to the standard output stream.
ppException :: SomeException -> StyleDoc #
Provide the prettiest available information about an exception.
prettyThrowIO :: (Exception e, MonadIO m, Pretty e) => e -> m a #
Synchronously throw the given exception as a PrettyException
.
prettyThrowM :: (Exception e, MonadThrow m, Pretty e) => e -> m a #
Throw the given exception as a PrettyException
, when the action is run in
the monad m
.
data MungedPackageId #
A simple pair of a MungedPackageName
and Version
. MungedPackageName
is to
MungedPackageId
as PackageName
is to PackageId
. See MungedPackageName
for more
info.
Constructors
MungedPackageId | |
Fields
|
Instances
HasMungedPackageId MungedPackageId | |||||
Defined in Distribution.Package Methods | |||||
Parsec MungedPackageId |
| ||||
Defined in Distribution.Types.MungedPackageId Methods parsec :: CabalParsing m => m MungedPackageId # | |||||
Pretty MungedPackageId |
| ||||
Defined in Distribution.Types.MungedPackageId Methods pretty :: MungedPackageId -> Doc # prettyVersioned :: CabalSpecVersion -> MungedPackageId -> Doc # | |||||
Structured MungedPackageId | |||||
Defined in Distribution.Types.MungedPackageId Methods structure :: Proxy MungedPackageId -> Structure # structureHash' :: Tagged MungedPackageId MD5 | |||||
Data MungedPackageId | |||||
Defined in Distribution.Types.MungedPackageId Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MungedPackageId -> c MungedPackageId # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MungedPackageId # toConstr :: MungedPackageId -> Constr # dataTypeOf :: MungedPackageId -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MungedPackageId) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MungedPackageId) # gmapT :: (forall b. Data b => b -> b) -> MungedPackageId -> MungedPackageId # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MungedPackageId -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MungedPackageId -> r # gmapQ :: (forall d. Data d => d -> u) -> MungedPackageId -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> MungedPackageId -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MungedPackageId -> m MungedPackageId # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MungedPackageId -> m MungedPackageId # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MungedPackageId -> m MungedPackageId # | |||||
Generic MungedPackageId | |||||
Defined in Distribution.Types.MungedPackageId Associated Types
Methods from :: MungedPackageId -> Rep MungedPackageId x # to :: Rep MungedPackageId x -> MungedPackageId # | |||||
Read MungedPackageId | |||||
Defined in Distribution.Types.MungedPackageId Methods readsPrec :: Int -> ReadS MungedPackageId # readList :: ReadS [MungedPackageId] # | |||||
Show MungedPackageId | |||||
Defined in Distribution.Types.MungedPackageId Methods showsPrec :: Int -> MungedPackageId -> ShowS # show :: MungedPackageId -> String # showList :: [MungedPackageId] -> ShowS # | |||||
Binary MungedPackageId | |||||
Defined in Distribution.Types.MungedPackageId Methods put :: MungedPackageId -> Put # get :: Get MungedPackageId # putList :: [MungedPackageId] -> Put # | |||||
NFData MungedPackageId | |||||
Defined in Distribution.Types.MungedPackageId Methods rnf :: MungedPackageId -> () # | |||||
Eq MungedPackageId | |||||
Defined in Distribution.Types.MungedPackageId Methods (==) :: MungedPackageId -> MungedPackageId -> Bool # (/=) :: MungedPackageId -> MungedPackageId -> Bool # | |||||
Ord MungedPackageId | |||||
Defined in Distribution.Types.MungedPackageId Methods compare :: MungedPackageId -> MungedPackageId -> Ordering # (<) :: MungedPackageId -> MungedPackageId -> Bool # (<=) :: MungedPackageId -> MungedPackageId -> Bool # (>) :: MungedPackageId -> MungedPackageId -> Bool # (>=) :: MungedPackageId -> MungedPackageId -> Bool # max :: MungedPackageId -> MungedPackageId -> MungedPackageId # min :: MungedPackageId -> MungedPackageId -> MungedPackageId # | |||||
type Rep MungedPackageId | |||||
Defined in Distribution.Types.MungedPackageId type Rep MungedPackageId = D1 ('MetaData "MungedPackageId" "Distribution.Types.MungedPackageId" "Cabal-syntax-3.10.3.0-dc3a" 'False) (C1 ('MetaCons "MungedPackageId" 'PrefixI 'True) (S1 ('MetaSel ('Just "mungedName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MungedPackageName) :*: S1 ('MetaSel ('Just "mungedVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version))) |
data MungedPackageName #
A combination of a package and component name used in various legacy
interfaces, chiefly bundled with a version as MungedPackageId
. It's generally
better to use a UnitId
to opaquely refer to some compilation/packing unit,
but that doesn't always work, e.g. where a "name" is needed, in which case
this can be used as a fallback.
Use mkMungedPackageName
and unMungedPackageName
to convert from/to a String
.
In 3.0.0.0
representation was changed from opaque (string) to semantic representation.
Since: Cabal-syntax-2.0.0.2
Constructors
MungedPackageName !PackageName !LibraryName |
Instances
Parsec MungedPackageName |
| ||||
Defined in Distribution.Types.MungedPackageName Methods parsec :: CabalParsing m => m MungedPackageName # | |||||
Pretty MungedPackageName | Computes the package name for a library. If this is the public library, it will just be the original package name; otherwise, it will be a munged package name recording the original package name as well as the name of the internal library. A lot of tooling in the Haskell ecosystem assumes that if something
is installed to the package database with the package name We munge into a reserved namespace, "z-", and encode both the component name and the package name of an internal library using the following format: compat-pkg-name ::= "z-" package-name "-z-" library-name where package-name and library-name have "-" ( "z" + ) "-" segments encoded by adding an extra "z". When we have the public library, the compat-pkg-name is just the package-name, no surprises there!
| ||||
Defined in Distribution.Types.MungedPackageName Methods pretty :: MungedPackageName -> Doc # prettyVersioned :: CabalSpecVersion -> MungedPackageName -> Doc # | |||||
Structured MungedPackageName | |||||
Defined in Distribution.Types.MungedPackageName Methods structure :: Proxy MungedPackageName -> Structure # structureHash' :: Tagged MungedPackageName MD5 | |||||
Data MungedPackageName | |||||
Defined in Distribution.Types.MungedPackageName Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MungedPackageName -> c MungedPackageName # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MungedPackageName # toConstr :: MungedPackageName -> Constr # dataTypeOf :: MungedPackageName -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MungedPackageName) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MungedPackageName) # gmapT :: (forall b. Data b => b -> b) -> MungedPackageName -> MungedPackageName # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MungedPackageName -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MungedPackageName -> r # gmapQ :: (forall d. Data d => d -> u) -> MungedPackageName -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> MungedPackageName -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MungedPackageName -> m MungedPackageName # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MungedPackageName -> m MungedPackageName # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MungedPackageName -> m MungedPackageName # | |||||
Generic MungedPackageName | |||||
Defined in Distribution.Types.MungedPackageName Associated Types
Methods from :: MungedPackageName -> Rep MungedPackageName x # to :: Rep MungedPackageName x -> MungedPackageName # | |||||
Read MungedPackageName | |||||
Defined in Distribution.Types.MungedPackageName Methods readsPrec :: Int -> ReadS MungedPackageName # readList :: ReadS [MungedPackageName] # | |||||
Show MungedPackageName | |||||
Defined in Distribution.Types.MungedPackageName Methods showsPrec :: Int -> MungedPackageName -> ShowS # show :: MungedPackageName -> String # showList :: [MungedPackageName] -> ShowS # | |||||
Binary MungedPackageName | |||||
Defined in Distribution.Types.MungedPackageName Methods put :: MungedPackageName -> Put # get :: Get MungedPackageName # putList :: [MungedPackageName] -> Put # | |||||
NFData MungedPackageName | |||||
Defined in Distribution.Types.MungedPackageName Methods rnf :: MungedPackageName -> () # | |||||
Eq MungedPackageName | |||||
Defined in Distribution.Types.MungedPackageName Methods (==) :: MungedPackageName -> MungedPackageName -> Bool # (/=) :: MungedPackageName -> MungedPackageName -> Bool # | |||||
Ord MungedPackageName | |||||
Defined in Distribution.Types.MungedPackageName Methods compare :: MungedPackageName -> MungedPackageName -> Ordering # (<) :: MungedPackageName -> MungedPackageName -> Bool # (<=) :: MungedPackageName -> MungedPackageName -> Bool # (>) :: MungedPackageName -> MungedPackageName -> Bool # (>=) :: MungedPackageName -> MungedPackageName -> Bool # max :: MungedPackageName -> MungedPackageName -> MungedPackageName # min :: MungedPackageName -> MungedPackageName -> MungedPackageName # | |||||
type Rep MungedPackageName | |||||
Defined in Distribution.Types.MungedPackageName type Rep MungedPackageName = D1 ('MetaData "MungedPackageName" "Distribution.Types.MungedPackageName" "Cabal-syntax-3.10.3.0-dc3a" 'False) (C1 ('MetaCons "MungedPackageName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 PackageName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 LibraryName))) |
data LibraryName #
Constructors
LMainLibName | |
LSubLibName UnqualComponentName |
Instances
module RIO
A Version
represents the version of a software entity.
Instances of Eq
and Ord
are provided, which gives exact
equality and lexicographic ordering of the version number
components (i.e. 2.1 > 2.0, 1.2.3 > 1.2.2, etc.).
This type is opaque and distinct from the Version
type in
Data.Version since Cabal-2.0
. The difference extends to the
Binary
instance using a different (and more compact) encoding.
Since: Cabal-syntax-2.0.0.2
Instances
Parsec Version | |||||
Defined in Distribution.Types.Version Methods parsec :: CabalParsing m => m Version # | |||||
Pretty Version | |||||
Defined in Distribution.Types.Version | |||||
Structured Version | |||||
Defined in Distribution.Types.Version | |||||
Data Version | |||||
Defined in Distribution.Types.Version Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Version -> c Version # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Version # toConstr :: Version -> Constr # dataTypeOf :: Version -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Version) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Version) # gmapT :: (forall b. Data b => b -> b) -> Version -> Version # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Version -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Version -> r # gmapQ :: (forall d. Data d => d -> u) -> Version -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Version -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Version -> m Version # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Version -> m Version # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Version -> m Version # | |||||
Generic Version | |||||
Defined in Distribution.Types.Version Associated Types
| |||||
Read Version | |||||
Show Version | |||||
Binary Version | |||||
NFData Version | |||||
Defined in Distribution.Types.Version | |||||
Eq Version | |||||
Ord Version | |||||
Defined in Distribution.Types.Version | |||||
IsCabalString Version | |||||
Defined in Pantry.Types | |||||
type Rep Version | |||||
Defined in Distribution.Types.Version type Rep Version = D1 ('MetaData "Version" "Distribution.Types.Version" "Cabal-syntax-3.10.3.0-dc3a" 'False) (C1 ('MetaCons "PV0" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedUnpack) (Rec0 Word64)) :+: C1 ('MetaCons "PV1" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Int]))) |
Path of some base and type.
The type variables are:
b
— base, the base location of the path; absolute or relative.t
— type, whether file or directory.
Internally is a string. The string can be of two formats only:
- File format:
file.txt
,foo/bar.txt
,/foo/bar.txt
- Directory format:
foo/
,/foo/bar/
All directories end in a trailing separator. There are no duplicate
path separators //
, no ..
, no ./
, no ~/
, etc.
Instances
(Typeable b, Typeable t) => Lift (Path b t :: Type) | |||||
FromJSON (Path Abs Dir) | |||||
FromJSON (Path Abs File) | |||||
FromJSON (Path Rel Dir) | |||||
FromJSON (Path Rel File) | |||||
FromJSONKey (Path Abs Dir) | |||||
Defined in Path.Posix Methods | |||||
FromJSONKey (Path Abs File) | |||||
Defined in Path.Posix Methods | |||||
FromJSONKey (Path Rel Dir) | |||||
Defined in Path.Posix Methods | |||||
FromJSONKey (Path Rel File) | |||||
Defined in Path.Posix Methods | |||||
ToJSON (Path b t) | |||||
ToJSONKey (Path b t) | |||||
Defined in Path.Internal.Posix | |||||
(Data b, Data t) => Data (Path b t) | |||||
Defined in Path.Internal.Posix Methods gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Path b t -> c (Path b t) # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Path b t) # toConstr :: Path b t -> Constr # dataTypeOf :: Path b t -> DataType # dataCast1 :: Typeable t0 => (forall d. Data d => c (t0 d)) -> Maybe (c (Path b t)) # dataCast2 :: Typeable t0 => (forall d e. (Data d, Data e) => c (t0 d e)) -> Maybe (c (Path b t)) # gmapT :: (forall b0. Data b0 => b0 -> b0) -> Path b t -> Path b t # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Path b t -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Path b t -> r # gmapQ :: (forall d. Data d => d -> u) -> Path b t -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Path b t -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Path b t -> m (Path b t) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Path b t -> m (Path b t) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Path b t -> m (Path b t) # | |||||
Generic (Path b t) | |||||
Defined in Path.Internal.Posix Associated Types
| |||||
Show (Path b t) | Same as 'show . Path.toFilePath'. The following property holds: x == y ≡ show x == show y | ||||
NFData (Path b t) | |||||
Defined in Path.Internal.Posix | |||||
Eq (Path b t) | String equality. The following property holds: show x == show y ≡ x == y | ||||
Ord (Path b t) | String ordering. The following property holds: show x `compare` show y ≡ x `compare` y | ||||
Defined in Path.Internal.Posix | |||||
Hashable (Path b t) | |||||
Defined in Path.Internal.Posix | |||||
AnyPath (Path b Dir) | |||||
Defined in Path.IO Methods canonicalizePath :: MonadIO m => Path b Dir -> m (AbsPath (Path b Dir)) # makeAbsolute :: MonadIO m => Path b Dir -> m (AbsPath (Path b Dir)) # makeRelative :: MonadThrow m => Path Abs Dir -> Path b Dir -> m (RelPath (Path b Dir)) # makeRelativeToCurrentDir :: MonadIO m => Path b Dir -> m (RelPath (Path b Dir)) # | |||||
AnyPath (Path b File) | |||||
Defined in Path.IO Methods canonicalizePath :: MonadIO m => Path b File -> m (AbsPath (Path b File)) # makeAbsolute :: MonadIO m => Path b File -> m (AbsPath (Path b File)) # makeRelative :: MonadThrow m => Path Abs Dir -> Path b File -> m (RelPath (Path b File)) # makeRelativeToCurrentDir :: MonadIO m => Path b File -> m (RelPath (Path b File)) # | |||||
Pretty (Path b Dir) | |||||
Pretty (Path b File) | |||||
type Rep (Path b t) | |||||
Defined in Path.Internal.Posix | |||||
type AbsPath (Path b Dir) | |||||
type AbsPath (Path b File) | |||||
type RelPath (Path b Dir) | |||||
type RelPath (Path b File) | |||||
Maybe monoid returning the leftmost non-Nothing
value.
is isomorphic to First
a
, but precedes it
historically.Alt
Maybe
a
Beware that Data.Monoid.
First
is different from
Data.Semigroup.
First
. The former returns the first non-Nothing
,
so Data.Monoid.First Nothing <> x = x
. The latter simply returns the first value,
thus Data.Semigroup.First Nothing <> x = Data.Semigroup.First Nothing
.
Examples
>>>
First (Just "hello") <> First Nothing <> First (Just "world")
First {getFirst = Just "hello"}
>>>
First Nothing <> mempty
First {getFirst = Nothing}
Instances
FromJSON1 First | |||||
Defined in Data.Aeson.Types.FromJSON | |||||
ToJSON1 First | |||||
Defined in Data.Aeson.Types.ToJSON Methods liftToJSON :: (a -> Bool) -> (a -> Value) -> ([a] -> Value) -> First a -> Value # liftToJSONList :: (a -> Bool) -> (a -> Value) -> ([a] -> Value) -> [First a] -> Value # liftToEncoding :: (a -> Bool) -> (a -> Encoding) -> ([a] -> Encoding) -> First a -> Encoding # liftToEncodingList :: (a -> Bool) -> (a -> Encoding) -> ([a] -> Encoding) -> [First a] -> Encoding # liftOmitField :: (a -> Bool) -> First a -> Bool # | |||||
MonadFix First | Since: base-4.8.0.0 | ||||
Defined in Control.Monad.Fix | |||||
MonadZip First | Since: base-4.8.0.0 | ||||
Foldable First | Since: base-4.8.0.0 | ||||
Defined in Data.Foldable Methods fold :: Monoid m => First m -> m # foldMap :: Monoid m => (a -> m) -> First a -> m # foldMap' :: Monoid m => (a -> m) -> First a -> m # foldr :: (a -> b -> b) -> b -> First a -> b # foldr' :: (a -> b -> b) -> b -> First a -> b # foldl :: (b -> a -> b) -> b -> First a -> b # foldl' :: (b -> a -> b) -> b -> First a -> b # foldr1 :: (a -> a -> a) -> First a -> a # foldl1 :: (a -> a -> a) -> First a -> a # elem :: Eq a => a -> First a -> Bool # maximum :: Ord a => First a -> a # minimum :: Ord a => First a -> a # | |||||
Traversable First | Since: base-4.8.0.0 | ||||
Applicative First | Since: base-4.8.0.0 | ||||
Functor First | Since: base-4.8.0.0 | ||||
Monad First | Since: base-4.8.0.0 | ||||
NFData1 First | Since: deepseq-1.4.3.0 | ||||
Defined in Control.DeepSeq | |||||
GFoldable First | |||||
Defined in Generics.Deriving.Foldable Methods gfoldMap :: Monoid m => (a -> m) -> First a -> m # gfold :: Monoid m => First m -> m # gfoldr :: (a -> b -> b) -> b -> First a -> b # gfoldr' :: (a -> b -> b) -> b -> First a -> b # gfoldl :: (a -> b -> a) -> a -> First b -> a # gfoldl' :: (a -> b -> a) -> a -> First b -> a # | |||||
GFunctor First | |||||
Defined in Generics.Deriving.Functor | |||||
GTraversable First | |||||
Generic1 First | |||||
Defined in Data.Monoid Associated Types
| |||||
FromJSON a => FromJSON (First a) | |||||
Defined in Data.Aeson.Types.FromJSON | |||||
ToJSON a => ToJSON (First a) | |||||
Data a => Data (First a) | Since: base-4.8.0.0 | ||||
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> First a -> c (First a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (First a) # toConstr :: First a -> Constr # dataTypeOf :: First a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (First a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (First a)) # gmapT :: (forall b. Data b => b -> b) -> First a -> First a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> First a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> First a -> r # gmapQ :: (forall d. Data d => d -> u) -> First a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> First a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> First a -> m (First a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> First a -> m (First a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> First a -> m (First a) # | |||||
Monoid (First a) | Since: base-2.1 | ||||
Semigroup (First a) | Since: base-4.9.0.0 | ||||
Generic (First a) | |||||
Defined in Data.Monoid Associated Types
| |||||
Read a => Read (First a) | Since: base-2.1 | ||||
Show a => Show (First a) | Since: base-2.1 | ||||
Binary a => Binary (First a) | Since: binary-0.8.4.0 | ||||
NFData a => NFData (First a) | Since: deepseq-1.4.0.0 | ||||
Defined in Control.DeepSeq | |||||
GEnum a => GEnum (First a) | |||||
Defined in Generics.Deriving.Enum | |||||
(GEq a, GEnum a, GIx a) => GIx (First a) | |||||
GEq a => GEq (First a) | |||||
GMonoid (First a) | |||||
GShow a => GShow (First a) | |||||
Eq a => Eq (First a) | Since: base-2.1 | ||||
Ord a => Ord (First a) | Since: base-2.1 | ||||
FromHttpApiData a => FromHttpApiData (First a) | |||||
Defined in Web.Internal.HttpApiData Methods parseUrlPiece :: Text -> Either Text (First a) # parseHeader :: ByteString -> Either Text (First a) # | |||||
ToHttpApiData a => ToHttpApiData (First a) | |||||
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: First a -> Text # toEncodedUrlPiece :: First a -> Builder # toHeader :: First a -> ByteString # toQueryParam :: First a -> Text # toEncodedQueryParam :: First a -> Builder # | |||||
type Rep1 First | Since: base-4.7.0.0 | ||||
Defined in Data.Monoid | |||||
type Rep (First a) | Since: base-4.7.0.0 | ||||
Defined in Data.Monoid |
data PackageName #
A package name.
Use mkPackageName
and unPackageName
to convert from/to a
String
.
This type is opaque since Cabal-2.0
Since: Cabal-syntax-2.0.0.2
Instances
Parsec PackageName | |||||
Defined in Distribution.Types.PackageName Methods parsec :: CabalParsing m => m PackageName # | |||||
Pretty PackageName | |||||
Defined in Distribution.Types.PackageName | |||||
Structured PackageName | |||||
Defined in Distribution.Types.PackageName | |||||
Data PackageName | |||||
Defined in Distribution.Types.PackageName Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PackageName -> c PackageName # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PackageName # toConstr :: PackageName -> Constr # dataTypeOf :: PackageName -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PackageName) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PackageName) # gmapT :: (forall b. Data b => b -> b) -> PackageName -> PackageName # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PackageName -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PackageName -> r # gmapQ :: (forall d. Data d => d -> u) -> PackageName -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PackageName -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PackageName -> m PackageName # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PackageName -> m PackageName # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PackageName -> m PackageName # | |||||
IsString PackageName | Since: Cabal-syntax-2.0.0.2 | ||||
Defined in Distribution.Types.PackageName Methods fromString :: String -> PackageName # | |||||
Generic PackageName | |||||
Defined in Distribution.Types.PackageName Associated Types
| |||||
Read PackageName | |||||
Defined in Distribution.Types.PackageName Methods readsPrec :: Int -> ReadS PackageName # readList :: ReadS [PackageName] # readPrec :: ReadPrec PackageName # readListPrec :: ReadPrec [PackageName] # | |||||
Show PackageName | |||||
Defined in Distribution.Types.PackageName Methods showsPrec :: Int -> PackageName -> ShowS # show :: PackageName -> String # showList :: [PackageName] -> ShowS # | |||||
Binary PackageName | |||||
Defined in Distribution.Types.PackageName | |||||
NFData PackageName | |||||
Defined in Distribution.Types.PackageName Methods rnf :: PackageName -> () # | |||||
Eq PackageName | |||||
Defined in Distribution.Types.PackageName | |||||
Ord PackageName | |||||
Defined in Distribution.Types.PackageName Methods compare :: PackageName -> PackageName -> Ordering # (<) :: PackageName -> PackageName -> Bool # (<=) :: PackageName -> PackageName -> Bool # (>) :: PackageName -> PackageName -> Bool # (>=) :: PackageName -> PackageName -> Bool # max :: PackageName -> PackageName -> PackageName # min :: PackageName -> PackageName -> PackageName # | |||||
IsCabalString PackageName | |||||
Defined in Pantry.Types Methods cabalStringName :: proxy PackageName -> String | |||||
type Rep PackageName | |||||
Defined in Distribution.Types.PackageName type Rep PackageName = D1 ('MetaData "PackageName" "Distribution.Types.PackageName" "Cabal-syntax-3.10.3.0-dc3a" 'True) (C1 ('MetaCons "PackageName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ShortText))) |
data PackageIdentifier #
The name and version of a package.
Constructors
PackageIdentifier | |
Fields
|
Instances
Package PackageIdentifier | |||||
Defined in Distribution.Package Methods | |||||
Parsec PackageIdentifier |
Note: Stricter than
| ||||
Defined in Distribution.Types.PackageId Methods parsec :: CabalParsing m => m PackageIdentifier # | |||||
Pretty PackageIdentifier | |||||
Defined in Distribution.Types.PackageId Methods pretty :: PackageIdentifier -> Doc # prettyVersioned :: CabalSpecVersion -> PackageIdentifier -> Doc # | |||||
Structured PackageIdentifier | |||||
Defined in Distribution.Types.PackageId Methods structure :: Proxy PackageIdentifier -> Structure # structureHash' :: Tagged PackageIdentifier MD5 | |||||
Data PackageIdentifier | |||||
Defined in Distribution.Types.PackageId Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PackageIdentifier -> c PackageIdentifier # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PackageIdentifier # toConstr :: PackageIdentifier -> Constr # dataTypeOf :: PackageIdentifier -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PackageIdentifier) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PackageIdentifier) # gmapT :: (forall b. Data b => b -> b) -> PackageIdentifier -> PackageIdentifier # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PackageIdentifier -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PackageIdentifier -> r # gmapQ :: (forall d. Data d => d -> u) -> PackageIdentifier -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PackageIdentifier -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PackageIdentifier -> m PackageIdentifier # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PackageIdentifier -> m PackageIdentifier # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PackageIdentifier -> m PackageIdentifier # | |||||
Generic PackageIdentifier | |||||
Defined in Distribution.Types.PackageId Associated Types
Methods from :: PackageIdentifier -> Rep PackageIdentifier x # to :: Rep PackageIdentifier x -> PackageIdentifier # | |||||
Read PackageIdentifier | |||||
Defined in Distribution.Types.PackageId Methods readsPrec :: Int -> ReadS PackageIdentifier # readList :: ReadS [PackageIdentifier] # | |||||
Show PackageIdentifier | |||||
Defined in Distribution.Types.PackageId Methods showsPrec :: Int -> PackageIdentifier -> ShowS # show :: PackageIdentifier -> String # showList :: [PackageIdentifier] -> ShowS # | |||||
Binary PackageIdentifier | |||||
Defined in Distribution.Types.PackageId Methods put :: PackageIdentifier -> Put # get :: Get PackageIdentifier # putList :: [PackageIdentifier] -> Put # | |||||
NFData PackageIdentifier | |||||
Defined in Distribution.Types.PackageId Methods rnf :: PackageIdentifier -> () # | |||||
Eq PackageIdentifier | |||||
Defined in Distribution.Types.PackageId Methods (==) :: PackageIdentifier -> PackageIdentifier -> Bool # (/=) :: PackageIdentifier -> PackageIdentifier -> Bool # | |||||
Ord PackageIdentifier | |||||
Defined in Distribution.Types.PackageId Methods compare :: PackageIdentifier -> PackageIdentifier -> Ordering # (<) :: PackageIdentifier -> PackageIdentifier -> Bool # (<=) :: PackageIdentifier -> PackageIdentifier -> Bool # (>) :: PackageIdentifier -> PackageIdentifier -> Bool # (>=) :: PackageIdentifier -> PackageIdentifier -> Bool # max :: PackageIdentifier -> PackageIdentifier -> PackageIdentifier # min :: PackageIdentifier -> PackageIdentifier -> PackageIdentifier # | |||||
IsCabalString PackageIdentifier | |||||
Defined in Pantry.Types Methods cabalStringName :: proxy PackageIdentifier -> String | |||||
type Rep PackageIdentifier | |||||
Defined in Distribution.Types.PackageId type Rep PackageIdentifier = D1 ('MetaData "PackageIdentifier" "Distribution.Types.PackageId" "Cabal-syntax-3.10.3.0-dc3a" 'False) (C1 ('MetaCons "PackageIdentifier" 'PrefixI 'True) (S1 ('MetaSel ('Just "pkgName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PackageName) :*: S1 ('MetaSel ('Just "pkgVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version))) |
Boolean monoid under disjunction (||)
.
Any x <> Any y = Any (x || y)
Examples
>>>
Any True <> mempty <> Any False
Any {getAny = True}
>>>
mconcat (map (\x -> Any (even x)) [2,4,6,7,8])
Any {getAny = True}
>>>
Any False <> mempty
Any {getAny = False}
Instances
FromJSON Any | Since: aeson-2.2.3.0 | ||||
Defined in Data.Aeson.Types.FromJSON | |||||
ToJSON Any | Since: aeson-2.2.3.0 | ||||
Data Any | Since: base-4.8.0.0 | ||||
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Any -> c Any # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Any # dataTypeOf :: Any -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Any) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Any) # gmapT :: (forall b. Data b => b -> b) -> Any -> Any # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Any -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Any -> r # gmapQ :: (forall d. Data d => d -> u) -> Any -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Any -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Any -> m Any # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Any -> m Any # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Any -> m Any # | |||||
Monoid Any | Since: base-2.1 | ||||
Semigroup Any | Since: base-4.9.0.0 | ||||
Bounded Any | Since: base-2.1 | ||||
Generic Any | |||||
Defined in Data.Semigroup.Internal Associated Types
| |||||
Read Any | Since: base-2.1 | ||||
Show Any | Since: base-2.1 | ||||
Binary Any | Since: binary-0.8.4.0 | ||||
NFData Any | Since: deepseq-1.4.0.0 | ||||
Defined in Control.DeepSeq | |||||
GEnum Any | |||||
Defined in Generics.Deriving.Enum | |||||
GIx Any | |||||
GEq Any | |||||
GMonoid Any | |||||
GShow Any | |||||
Eq Any | Since: base-2.1 | ||||
Ord Any | Since: base-2.1 | ||||
FromHttpApiData Any | |||||
Defined in Web.Internal.HttpApiData | |||||
ToHttpApiData Any | |||||
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Any -> Text # toEncodedUrlPiece :: Any -> Builder # toHeader :: Any -> ByteString # toQueryParam :: Any -> Text # toEncodedQueryParam :: Any -> Builder # | |||||
Unbox Any | |||||
Defined in Data.Vector.Unboxed.Base | |||||
Vector Vector Any | |||||
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s Any -> ST s (Vector Any) # basicUnsafeThaw :: Vector Any -> ST s (Mutable Vector s Any) # basicLength :: Vector Any -> Int # basicUnsafeSlice :: Int -> Int -> Vector Any -> Vector Any # basicUnsafeIndexM :: Vector Any -> Int -> Box Any # basicUnsafeCopy :: Mutable Vector s Any -> Vector Any -> ST s () # | |||||
MVector MVector Any | |||||
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s Any -> Int basicUnsafeSlice :: Int -> Int -> MVector s Any -> MVector s Any basicOverlaps :: MVector s Any -> MVector s Any -> Bool basicUnsafeNew :: Int -> ST s (MVector s Any) basicInitialize :: MVector s Any -> ST s () basicUnsafeReplicate :: Int -> Any -> ST s (MVector s Any) basicUnsafeRead :: MVector s Any -> Int -> ST s Any basicUnsafeWrite :: MVector s Any -> Int -> Any -> ST s () basicClear :: MVector s Any -> ST s () basicSet :: MVector s Any -> Any -> ST s () basicUnsafeCopy :: MVector s Any -> MVector s Any -> ST s () basicUnsafeMove :: MVector s Any -> MVector s Any -> ST s () basicUnsafeGrow :: MVector s Any -> Int -> ST s (MVector s Any) | |||||
type Rep Any | Since: base-4.7.0.0 | ||||
Defined in Data.Semigroup.Internal | |||||
newtype Vector Any | |||||
newtype MVector s Any | |||||
Instances
Generic RepoType | |
Defined in Pantry.Types | |
Show RepoType | |
NFData RepoType | |
Defined in Pantry.Types | |
Eq RepoType | |
Ord RepoType | |
Defined in Pantry.Types | |
PersistField RepoType | |
Defined in Pantry.Types Methods toPersistValue :: RepoType -> PersistValue # | |
PersistFieldSql RepoType | |
SymbolToField "type" RepoCache RepoType | |
Defined in Pantry.Storage Methods symbolToField :: EntityField RepoCache RepoType # | |
type Rep RepoType | |
Constructors
Repo | |
Fields
|
Instances
Generic Repo | |||||
Defined in Pantry.Types Associated Types
| |||||
Show Repo | |||||
NFData Repo | |||||
Defined in Pantry.Types | |||||
Eq Repo | |||||
Ord Repo | |||||
Display Repo | |||||
Defined in Pantry.Types | |||||
type Rep Repo | |||||
Defined in Pantry.Types type Rep Repo = D1 ('MetaData "Repo" "Pantry.Types" "pantry-0.10.0-2c6hPrHSjDQ3SnTMTDZv1w-internal" 'False) (C1 ('MetaCons "Repo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "repoUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "repoCommit") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "repoType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RepoType) :*: S1 ('MetaSel ('Just "repoSubdir") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)))) |
A FlagName
is the name of a user-defined configuration flag
Use mkFlagName
and unFlagName
to convert from/to a String
.
This type is opaque since Cabal-2.0
Since: Cabal-syntax-2.0.0.2
Instances
Parsec FlagName | |||||
Defined in Distribution.Types.Flag Methods parsec :: CabalParsing m => m FlagName # | |||||
Pretty FlagName | |||||
Defined in Distribution.Types.Flag | |||||
Structured FlagName | |||||
Defined in Distribution.Types.Flag | |||||
Data FlagName | |||||
Defined in Distribution.Types.Flag Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FlagName -> c FlagName # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FlagName # toConstr :: FlagName -> Constr # dataTypeOf :: FlagName -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FlagName) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FlagName) # gmapT :: (forall b. Data b => b -> b) -> FlagName -> FlagName # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FlagName -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FlagName -> r # gmapQ :: (forall d. Data d => d -> u) -> FlagName -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FlagName -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FlagName -> m FlagName # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FlagName -> m FlagName # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FlagName -> m FlagName # | |||||
IsString FlagName | Since: Cabal-syntax-2.0.0.2 | ||||
Defined in Distribution.Types.Flag Methods fromString :: String -> FlagName # | |||||
Generic FlagName | |||||
Defined in Distribution.Types.Flag Associated Types
| |||||
Read FlagName | |||||
Show FlagName | |||||
Binary FlagName | |||||
NFData FlagName | |||||
Defined in Distribution.Types.Flag | |||||
Eq FlagName | |||||
Ord FlagName | |||||
Defined in Distribution.Types.Flag | |||||
IsCabalString FlagName | |||||
Defined in Pantry.Types | |||||
type Rep FlagName | |||||
Defined in Distribution.Types.Flag |
toFilePath :: Path b t -> FilePath #
Convert to a FilePath
type.
All directories have a trailing slash, so if you want no trailing
slash, you can use dropTrailingPathSeparator
from
the filepath package.
Monoid under addition.
Sum a <> Sum b = Sum (a + b)
Examples
>>>
Sum 1 <> Sum 2 <> mempty
Sum {getSum = 3}
>>>
mconcat [ Sum n | n <- [3 .. 9]]
Sum {getSum = 42}
Instances
FromJSON1 Sum | Since: aeson-2.2.3.0 | ||||
ToJSON1 Sum | Since: aeson-2.2.3.0 | ||||
Defined in Data.Aeson.Types.ToJSON Methods liftToJSON :: (a -> Bool) -> (a -> Value) -> ([a] -> Value) -> Sum a -> Value # liftToJSONList :: (a -> Bool) -> (a -> Value) -> ([a] -> Value) -> [Sum a] -> Value # liftToEncoding :: (a -> Bool) -> (a -> Encoding) -> ([a] -> Encoding) -> Sum a -> Encoding # liftToEncodingList :: (a -> Bool) -> (a -> Encoding) -> ([a] -> Encoding) -> [Sum a] -> Encoding # liftOmitField :: (a -> Bool) -> Sum a -> Bool # | |||||
MonadFix Sum | Since: base-4.8.0.0 | ||||
Defined in Control.Monad.Fix | |||||
MonadZip Sum | Since: base-4.8.0.0 | ||||
Foldable Sum | Since: base-4.8.0.0 | ||||
Defined in Data.Foldable Methods fold :: Monoid m => Sum m -> m # foldMap :: Monoid m => (a -> m) -> Sum a -> m # foldMap' :: Monoid m => (a -> m) -> Sum a -> m # foldr :: (a -> b -> b) -> b -> Sum a -> b # foldr' :: (a -> b -> b) -> b -> Sum a -> b # foldl :: (b -> a -> b) -> b -> Sum a -> b # foldl' :: (b -> a -> b) -> b -> Sum a -> b # foldr1 :: (a -> a -> a) -> Sum a -> a # foldl1 :: (a -> a -> a) -> Sum a -> a # elem :: Eq a => a -> Sum a -> Bool # maximum :: Ord a => Sum a -> a # | |||||
Foldable1 Sum | Since: base-4.18.0.0 | ||||
Defined in Data.Foldable1 Methods fold1 :: Semigroup m => Sum m -> m # foldMap1 :: Semigroup m => (a -> m) -> Sum a -> m # foldMap1' :: Semigroup m => (a -> m) -> Sum a -> m # toNonEmpty :: Sum a -> NonEmpty a # maximum :: Ord a => Sum a -> a # minimum :: Ord a => Sum a -> a # foldrMap1 :: (a -> b) -> (a -> b -> b) -> Sum a -> b # foldlMap1' :: (a -> b) -> (b -> a -> b) -> Sum a -> b # foldlMap1 :: (a -> b) -> (b -> a -> b) -> Sum a -> b # foldrMap1' :: (a -> b) -> (a -> b -> b) -> Sum a -> b # | |||||
Traversable Sum | Since: base-4.8.0.0 | ||||
Applicative Sum | Since: base-4.8.0.0 | ||||
Functor Sum | Since: base-4.8.0.0 | ||||
Monad Sum | Since: base-4.8.0.0 | ||||
NFData1 Sum | Since: deepseq-1.4.3.0 | ||||
Defined in Control.DeepSeq | |||||
GCopoint Sum | |||||
Defined in Generics.Deriving.Copoint | |||||
GFoldable Sum | |||||
Defined in Generics.Deriving.Foldable Methods gfoldMap :: Monoid m => (a -> m) -> Sum a -> m # gfold :: Monoid m => Sum m -> m # gfoldr :: (a -> b -> b) -> b -> Sum a -> b # gfoldr' :: (a -> b -> b) -> b -> Sum a -> b # gfoldl :: (a -> b -> a) -> a -> Sum b -> a # gfoldl' :: (a -> b -> a) -> a -> Sum b -> a # | |||||
GFunctor Sum | |||||
Defined in Generics.Deriving.Functor | |||||
GTraversable Sum | |||||
Generic1 Sum | |||||
Defined in Data.Semigroup.Internal Associated Types
| |||||
Newtype a (Sum a) | |||||
Unbox a => Vector Vector (Sum a) | |||||
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s (Sum a) -> ST s (Vector (Sum a)) # basicUnsafeThaw :: Vector (Sum a) -> ST s (Mutable Vector s (Sum a)) # basicLength :: Vector (Sum a) -> Int # basicUnsafeSlice :: Int -> Int -> Vector (Sum a) -> Vector (Sum a) # basicUnsafeIndexM :: Vector (Sum a) -> Int -> Box (Sum a) # basicUnsafeCopy :: Mutable Vector s (Sum a) -> Vector (Sum a) -> ST s () # | |||||
Unbox a => MVector MVector (Sum a) | |||||
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s (Sum a) -> Int basicUnsafeSlice :: Int -> Int -> MVector s (Sum a) -> MVector s (Sum a) basicOverlaps :: MVector s (Sum a) -> MVector s (Sum a) -> Bool basicUnsafeNew :: Int -> ST s (MVector s (Sum a)) basicInitialize :: MVector s (Sum a) -> ST s () basicUnsafeReplicate :: Int -> Sum a -> ST s (MVector s (Sum a)) basicUnsafeRead :: MVector s (Sum a) -> Int -> ST s (Sum a) basicUnsafeWrite :: MVector s (Sum a) -> Int -> Sum a -> ST s () basicClear :: MVector s (Sum a) -> ST s () basicSet :: MVector s (Sum a) -> Sum a -> ST s () basicUnsafeCopy :: MVector s (Sum a) -> MVector s (Sum a) -> ST s () basicUnsafeMove :: MVector s (Sum a) -> MVector s (Sum a) -> ST s () basicUnsafeGrow :: MVector s (Sum a) -> Int -> ST s (MVector s (Sum a)) | |||||
FromJSON a => FromJSON (Sum a) | Since: aeson-2.2.3.0 | ||||
Defined in Data.Aeson.Types.FromJSON | |||||
ToJSON a => ToJSON (Sum a) | Since: aeson-2.2.3.0 | ||||
Data a => Data (Sum a) | Since: base-4.8.0.0 | ||||
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Sum a -> c (Sum a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Sum a) # dataTypeOf :: Sum a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Sum a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Sum a)) # gmapT :: (forall b. Data b => b -> b) -> Sum a -> Sum a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Sum a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Sum a -> r # gmapQ :: (forall d. Data d => d -> u) -> Sum a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Sum a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Sum a -> m (Sum a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Sum a -> m (Sum a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Sum a -> m (Sum a) # | |||||
Num a => Monoid (Sum a) | Since: base-2.1 | ||||
Num a => Semigroup (Sum a) | Since: base-4.9.0.0 | ||||
Bounded a => Bounded (Sum a) | Since: base-2.1 | ||||
Generic (Sum a) | |||||
Defined in Data.Semigroup.Internal Associated Types
| |||||
Num a => Num (Sum a) | Since: base-4.7.0.0 | ||||
Read a => Read (Sum a) | Since: base-2.1 | ||||
Show a => Show (Sum a) | Since: base-2.1 | ||||
Binary a => Binary (Sum a) | Since: binary-0.8.4.0 | ||||
NFData a => NFData (Sum a) | Since: deepseq-1.4.0.0 | ||||
Defined in Control.DeepSeq | |||||
GEnum a => GEnum (Sum a) | |||||
Defined in Generics.Deriving.Enum | |||||
(GEq a, GEnum a, GIx a) => GIx (Sum a) | |||||
GEq a => GEq (Sum a) | |||||
Num a => GMonoid (Sum a) | |||||
GShow a => GShow (Sum a) | |||||
Eq a => Eq (Sum a) | Since: base-2.1 | ||||
Ord a => Ord (Sum a) | Since: base-2.1 | ||||
FromHttpApiData a => FromHttpApiData (Sum a) | |||||
Defined in Web.Internal.HttpApiData Methods parseUrlPiece :: Text -> Either Text (Sum a) # parseHeader :: ByteString -> Either Text (Sum a) # | |||||
ToHttpApiData a => ToHttpApiData (Sum a) | |||||
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Sum a -> Text # toEncodedUrlPiece :: Sum a -> Builder # toHeader :: Sum a -> ByteString # toQueryParam :: Sum a -> Text # toEncodedQueryParam :: Sum a -> Builder # | |||||
Unbox a => Unbox (Sum a) | |||||
Defined in Data.Vector.Unboxed.Base | |||||
type Rep1 Sum | Since: base-4.7.0.0 | ||||
Defined in Data.Semigroup.Internal | |||||
newtype MVector s (Sum a) | |||||
Defined in Data.Vector.Unboxed.Base | |||||
type Rep (Sum a) | Since: base-4.7.0.0 | ||||
Defined in Data.Semigroup.Internal | |||||
newtype Vector (Sum a) | |||||
Defined in Data.Vector.Unboxed.Base |
The monoid of endomorphisms under composition.
Endo f <> Endo g == Endo (f . g)
Examples
>>>
let computation = Endo ("Hello, " ++) <> Endo (++ "!")
>>>
appEndo computation "Haskell"
"Hello, Haskell!"
>>>
let computation = Endo (*3) <> Endo (+1)
>>>
appEndo computation 1
6
Instances
Monoid (Endo a) | Since: base-2.1 | ||||
Semigroup (Endo a) | Since: base-4.9.0.0 | ||||
Generic (Endo a) | |||||
Defined in Data.Semigroup.Internal Associated Types
| |||||
GMonoid (Endo a) | |||||
Newtype (a -> a) (Endo a) | |||||
type Rep (Endo a) | Since: base-4.7.0.0 | ||||
Defined in Data.Semigroup.Internal |
parseVersion :: String -> Maybe Version #
Instances
FromJSON FileSize | |||||
Defined in Pantry.Types | |||||
ToJSON FileSize | |||||
Generic FileSize | |||||
Defined in Pantry.Types Associated Types
| |||||
Show FileSize | |||||
NFData FileSize | |||||
Defined in Pantry.Types | |||||
Eq FileSize | |||||
Ord FileSize | |||||
Defined in Pantry.Types | |||||
Hashable FileSize | |||||
Defined in Pantry.Types | |||||
PersistField FileSize | |||||
Defined in Pantry.Types Methods toPersistValue :: FileSize -> PersistValue # | |||||
PersistFieldSql FileSize | |||||
Display FileSize | |||||
Defined in Pantry.Types | |||||
SymbolToField "size" ArchiveCache FileSize | |||||
Defined in Pantry.Storage Methods symbolToField :: EntityField ArchiveCache FileSize # | |||||
SymbolToField "size" Blob FileSize | |||||
Defined in Pantry.Storage Methods symbolToField :: EntityField Blob FileSize # | |||||
SymbolToField "size" CacheUpdate FileSize | |||||
Defined in Pantry.Storage Methods symbolToField :: EntityField CacheUpdate FileSize # | |||||
SymbolToField "size" HackageTarball FileSize | |||||
Defined in Pantry.Storage Methods symbolToField :: EntityField HackageTarball FileSize # | |||||
type Rep FileSize | |||||
Defined in Pantry.Types |
Instances
FromJSON BlobKey | |||||
Defined in Pantry.Types | |||||
ToJSON BlobKey | |||||
Generic BlobKey | |||||
Defined in Pantry.Types Associated Types
| |||||
Show BlobKey | |||||
NFData BlobKey | |||||
Defined in Pantry.Types | |||||
Eq BlobKey | |||||
Ord BlobKey | |||||
Display BlobKey | |||||
Defined in Pantry.Types | |||||
type Rep BlobKey | |||||
Defined in Pantry.Types type Rep BlobKey = D1 ('MetaData "BlobKey" "Pantry.Types" "pantry-0.10.0-2c6hPrHSjDQ3SnTMTDZv1w-internal" 'False) (C1 ('MetaCons "BlobKey" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SHA256) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 FileSize))) |
Arguments
:: forall (m :: Type -> Type) a b c r. Monad m | |
=> ConduitT a b m () | upstream |
-> ConduitT b c m r | downstream |
-> ConduitT a c m r |
Combine two Conduit
s together into a new Conduit
(aka fuse
).
Output from the upstream (left) conduit will be fed into the
downstream (right) conduit. Processing will terminate when
downstream (right) returns.
Leftover data returned from the right Conduit
will be discarded.
Equivalent to fuse
and =$=
, however the latter is deprecated and will
be removed in a future version.
Note that, while this operator looks like categorical composition (from Control.Category), there are a few reasons it's different:
- The position of the type parameters to
ConduitT
do not match. We would need to changeConduitT i o m r
toConduitT r m i o
, which would preclude aMonad
orMonadTrans
instance. - The result value from upstream and downstream are allowed to
differ between upstream and downstream. In other words, we would
need the type signature here to look like
ConduitT a b m r -> ConduitT b c m r -> ConduitT a c m r
. - Due to leftovers, we do not have a left identity in Conduit. This
can be achieved with the underlying
Pipe
datatype, but this is not generally recommended. See https://stackoverflow.com/a/15263700.
Since: conduit-1.2.8
runConduit :: Monad m => ConduitT () Void m r -> m r #
Run a pipeline until processing completes.
Since 1.2.1
Instances
FromJSON SHA256 | |||||
Defined in Pantry.SHA256 | |||||
ToJSON SHA256 | |||||
Data SHA256 | |||||
Defined in Pantry.SHA256 Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SHA256 -> c SHA256 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SHA256 # toConstr :: SHA256 -> Constr # dataTypeOf :: SHA256 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SHA256) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SHA256) # gmapT :: (forall b. Data b => b -> b) -> SHA256 -> SHA256 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SHA256 -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SHA256 -> r # gmapQ :: (forall d. Data d => d -> u) -> SHA256 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SHA256 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SHA256 -> m SHA256 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA256 -> m SHA256 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA256 -> m SHA256 # | |||||
Generic SHA256 | |||||
Defined in Pantry.SHA256 Associated Types
| |||||
Show SHA256 | |||||
NFData SHA256 | |||||
Defined in Pantry.SHA256 | |||||
Eq SHA256 | |||||
Ord SHA256 | |||||
Hashable SHA256 | |||||
Defined in Pantry.SHA256 | |||||
PersistField SHA256 | |||||
Defined in Pantry.SHA256 Methods toPersistValue :: SHA256 -> PersistValue # | |||||
PersistFieldSql SHA256 | |||||
Display SHA256 | |||||
Defined in Pantry.SHA256 | |||||
SymbolToField "sha" ArchiveCache SHA256 | |||||
Defined in Pantry.Storage Methods symbolToField :: EntityField ArchiveCache SHA256 # | |||||
SymbolToField "sha" Blob SHA256 | |||||
Defined in Pantry.Storage Methods symbolToField :: EntityField Blob SHA256 # | |||||
SymbolToField "sha" CacheUpdate SHA256 | |||||
Defined in Pantry.Storage Methods symbolToField :: EntityField CacheUpdate SHA256 # | |||||
SymbolToField "sha" HackageTarball SHA256 | |||||
Defined in Pantry.Storage Methods symbolToField :: EntityField HackageTarball SHA256 # | |||||
SymbolToField "sha" SnapshotCache SHA256 | |||||
Defined in Pantry.Storage Methods symbolToField :: EntityField SnapshotCache SHA256 # | |||||
type Rep SHA256 | |||||
Defined in Pantry.SHA256 |
A file path.
Instances
Data File | |
Defined in Path.Posix Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> File -> c File # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c File # dataTypeOf :: File -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c File) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c File) # gmapT :: (forall b. Data b => b -> b) -> File -> File # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> File -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> File -> r # gmapQ :: (forall d. Data d => d -> u) -> File -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> File -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> File -> m File # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> File -> m File # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> File -> m File # | |
FromJSON (SomeBase File) | |
AnyPath (SomeBase File) | Since: path-io-1.8.0 |
Defined in Path.IO Methods canonicalizePath :: MonadIO m => SomeBase File -> m (AbsPath (SomeBase File)) # makeAbsolute :: MonadIO m => SomeBase File -> m (AbsPath (SomeBase File)) # makeRelative :: MonadThrow m => Path Abs Dir -> SomeBase File -> m (RelPath (SomeBase File)) # makeRelativeToCurrentDir :: MonadIO m => SomeBase File -> m (RelPath (SomeBase File)) # | |
Pretty (SomeBase File) | |
FromJSON (Path Abs File) | |
FromJSON (Path Rel File) | |
FromJSONKey (Path Abs File) | |
Defined in Path.Posix Methods | |
FromJSONKey (Path Rel File) | |
Defined in Path.Posix Methods | |
AnyPath (Path b File) | |
Defined in Path.IO Methods canonicalizePath :: MonadIO m => Path b File -> m (AbsPath (Path b File)) # makeAbsolute :: MonadIO m => Path b File -> m (AbsPath (Path b File)) # makeRelative :: MonadThrow m => Path Abs Dir -> Path b File -> m (RelPath (Path b File)) # makeRelativeToCurrentDir :: MonadIO m => Path b File -> m (RelPath (Path b File)) # | |
Pretty (Path b File) | |
type AbsPath (SomeBase File) | |
type RelPath (SomeBase File) | |
type AbsPath (Path b File) | |
type RelPath (Path b File) | |
Constructors
Snapshot | |
Fields |
data GlobalHintsLocation #
Constructors
GHLUrl !Text | |
GHLFilePath !(ResolvedPath File) |
Instances
ToJSON GlobalHintsLocation | |||||
Defined in Pantry.Types Methods toJSON :: GlobalHintsLocation -> Value # toEncoding :: GlobalHintsLocation -> Encoding # toJSONList :: [GlobalHintsLocation] -> Value # toEncodingList :: [GlobalHintsLocation] -> Encoding # omitField :: GlobalHintsLocation -> Bool # | |||||
Generic GlobalHintsLocation | |||||
Defined in Pantry.Types Associated Types
Methods from :: GlobalHintsLocation -> Rep GlobalHintsLocation x # to :: Rep GlobalHintsLocation x -> GlobalHintsLocation # | |||||
Show GlobalHintsLocation | |||||
Defined in Pantry.Types Methods showsPrec :: Int -> GlobalHintsLocation -> ShowS # show :: GlobalHintsLocation -> String # showList :: [GlobalHintsLocation] -> ShowS # | |||||
NFData GlobalHintsLocation | |||||
Defined in Pantry.Types Methods rnf :: GlobalHintsLocation -> () # | |||||
Eq GlobalHintsLocation | |||||
Defined in Pantry.Types Methods (==) :: GlobalHintsLocation -> GlobalHintsLocation -> Bool # (/=) :: GlobalHintsLocation -> GlobalHintsLocation -> Bool # | |||||
Ord GlobalHintsLocation | |||||
Defined in Pantry.Types Methods compare :: GlobalHintsLocation -> GlobalHintsLocation -> Ordering # (<) :: GlobalHintsLocation -> GlobalHintsLocation -> Bool # (<=) :: GlobalHintsLocation -> GlobalHintsLocation -> Bool # (>) :: GlobalHintsLocation -> GlobalHintsLocation -> Bool # (>=) :: GlobalHintsLocation -> GlobalHintsLocation -> Bool # max :: GlobalHintsLocation -> GlobalHintsLocation -> GlobalHintsLocation # min :: GlobalHintsLocation -> GlobalHintsLocation -> GlobalHintsLocation # | |||||
Display GlobalHintsLocation | |||||
Defined in Pantry.Types | |||||
Pretty GlobalHintsLocation | |||||
Defined in Pantry.Types Methods pretty :: GlobalHintsLocation -> StyleDoc # | |||||
FromJSON (WithJSONWarnings (Unresolved GlobalHintsLocation)) | |||||
Defined in Pantry.Types Methods parseJSON :: Value -> Parser (WithJSONWarnings (Unresolved GlobalHintsLocation)) # parseJSONList :: Value -> Parser [WithJSONWarnings (Unresolved GlobalHintsLocation)] # omittedField :: Maybe (WithJSONWarnings (Unresolved GlobalHintsLocation)) # | |||||
type Rep GlobalHintsLocation | |||||
Defined in Pantry.Types type Rep GlobalHintsLocation = D1 ('MetaData "GlobalHintsLocation" "Pantry.Types" "pantry-0.10.0-2c6hPrHSjDQ3SnTMTDZv1w-internal" 'False) (C1 ('MetaCons "GHLUrl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :+: C1 ('MetaCons "GHLFilePath" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ResolvedPath File)))) |
newtype SnapshotCacheHash #
Constructors
SnapshotCacheHash | |
Fields |
Instances
Show SnapshotCacheHash | |
Defined in Pantry.Types Methods showsPrec :: Int -> SnapshotCacheHash -> ShowS # show :: SnapshotCacheHash -> String # showList :: [SnapshotCacheHash] -> ShowS # |
data SnapshotLayer #
Constructors
SnapshotLayer | |
Fields
|
Instances
ToJSON SnapshotLayer | |||||
Defined in Pantry.Types Methods toJSON :: SnapshotLayer -> Value # toEncoding :: SnapshotLayer -> Encoding # toJSONList :: [SnapshotLayer] -> Value # toEncodingList :: [SnapshotLayer] -> Encoding # omitField :: SnapshotLayer -> Bool # | |||||
Generic SnapshotLayer | |||||
Defined in Pantry.Types Associated Types
| |||||
Show SnapshotLayer | |||||
Defined in Pantry.Types Methods showsPrec :: Int -> SnapshotLayer -> ShowS # show :: SnapshotLayer -> String # showList :: [SnapshotLayer] -> ShowS # | |||||
Eq SnapshotLayer | |||||
Defined in Pantry.Types Methods (==) :: SnapshotLayer -> SnapshotLayer -> Bool # (/=) :: SnapshotLayer -> SnapshotLayer -> Bool # | |||||
type Rep SnapshotLayer | |||||
Defined in Pantry.Types type Rep SnapshotLayer = D1 ('MetaData "SnapshotLayer" "Pantry.Types" "pantry-0.10.0-2c6hPrHSjDQ3SnTMTDZv1w-internal" 'False) (C1 ('MetaCons "SnapshotLayer" 'PrefixI 'True) (((S1 ('MetaSel ('Just "slParent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SnapshotLocation) :*: S1 ('MetaSel ('Just "slCompiler") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe WantedCompiler))) :*: (S1 ('MetaSel ('Just "slLocations") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [PackageLocationImmutable]) :*: S1 ('MetaSel ('Just "slDropPackages") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Set PackageName)))) :*: ((S1 ('MetaSel ('Just "slFlags") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map PackageName (Map FlagName Bool))) :*: S1 ('MetaSel ('Just "slHidden") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map PackageName Bool))) :*: (S1 ('MetaSel ('Just "slGhcOptions") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map PackageName [Text])) :*: S1 ('MetaSel ('Just "slPublishTime") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe UTCTime)))))) |
data RawSnapshotLayer #
Constructors
RawSnapshotLayer | |
Fields
|
Instances
ToJSON RawSnapshotLayer | |||||
Defined in Pantry.Types Methods toJSON :: RawSnapshotLayer -> Value # toEncoding :: RawSnapshotLayer -> Encoding # toJSONList :: [RawSnapshotLayer] -> Value # toEncodingList :: [RawSnapshotLayer] -> Encoding # omitField :: RawSnapshotLayer -> Bool # | |||||
Generic RawSnapshotLayer | |||||
Defined in Pantry.Types Associated Types
Methods from :: RawSnapshotLayer -> Rep RawSnapshotLayer x # to :: Rep RawSnapshotLayer x -> RawSnapshotLayer # | |||||
Show RawSnapshotLayer | |||||
Defined in Pantry.Types Methods showsPrec :: Int -> RawSnapshotLayer -> ShowS # show :: RawSnapshotLayer -> String # showList :: [RawSnapshotLayer] -> ShowS # | |||||
NFData RawSnapshotLayer | |||||
Defined in Pantry.Types Methods rnf :: RawSnapshotLayer -> () # | |||||
Eq RawSnapshotLayer | |||||
Defined in Pantry.Types Methods (==) :: RawSnapshotLayer -> RawSnapshotLayer -> Bool # (/=) :: RawSnapshotLayer -> RawSnapshotLayer -> Bool # | |||||
FromJSON (WithJSONWarnings (Unresolved RawSnapshotLayer)) | |||||
Defined in Pantry.Types Methods parseJSON :: Value -> Parser (WithJSONWarnings (Unresolved RawSnapshotLayer)) # parseJSONList :: Value -> Parser [WithJSONWarnings (Unresolved RawSnapshotLayer)] # omittedField :: Maybe (WithJSONWarnings (Unresolved RawSnapshotLayer)) # | |||||
type Rep RawSnapshotLayer | |||||
Defined in Pantry.Types type Rep RawSnapshotLayer = D1 ('MetaData "RawSnapshotLayer" "Pantry.Types" "pantry-0.10.0-2c6hPrHSjDQ3SnTMTDZv1w-internal" 'False) (C1 ('MetaCons "RawSnapshotLayer" 'PrefixI 'True) (((S1 ('MetaSel ('Just "rslParent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RawSnapshotLocation) :*: S1 ('MetaSel ('Just "rslCompiler") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe WantedCompiler))) :*: (S1 ('MetaSel ('Just "rslLocations") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [RawPackageLocationImmutable]) :*: S1 ('MetaSel ('Just "rslDropPackages") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Set PackageName)))) :*: ((S1 ('MetaSel ('Just "rslFlags") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map PackageName (Map FlagName Bool))) :*: S1 ('MetaSel ('Just "rslHidden") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map PackageName Bool))) :*: (S1 ('MetaSel ('Just "rslGhcOptions") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map PackageName [Text])) :*: S1 ('MetaSel ('Just "rslPublishTime") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe UTCTime)))))) |
data SnapshotPackage #
Constructors
SnapshotPackage | |
Fields
|
Instances
Show SnapshotPackage | |
Defined in Pantry.Types Methods showsPrec :: Int -> SnapshotPackage -> ShowS # show :: SnapshotPackage -> String # showList :: [SnapshotPackage] -> ShowS # |
data RawSnapshotPackage #
Constructors
RawSnapshotPackage | |
Fields
|
data RawSnapshot #
Constructors
RawSnapshot | |
Fields
|
data SnapshotLocation #
Constructors
SLCompiler !WantedCompiler | |
SLUrl !Text !BlobKey | |
SLFilePath !(ResolvedPath File) |
Instances
ToJSON SnapshotLocation | |||||
Defined in Pantry.Types Methods toJSON :: SnapshotLocation -> Value # toEncoding :: SnapshotLocation -> Encoding # toJSONList :: [SnapshotLocation] -> Value # toEncodingList :: [SnapshotLocation] -> Encoding # omitField :: SnapshotLocation -> Bool # | |||||
Generic SnapshotLocation | |||||
Defined in Pantry.Types Associated Types
Methods from :: SnapshotLocation -> Rep SnapshotLocation x # to :: Rep SnapshotLocation x -> SnapshotLocation # | |||||
Show SnapshotLocation | |||||
Defined in Pantry.Types Methods showsPrec :: Int -> SnapshotLocation -> ShowS # show :: SnapshotLocation -> String # showList :: [SnapshotLocation] -> ShowS # | |||||
NFData SnapshotLocation | |||||
Defined in Pantry.Types Methods rnf :: SnapshotLocation -> () # | |||||
Eq SnapshotLocation | |||||
Defined in Pantry.Types Methods (==) :: SnapshotLocation -> SnapshotLocation -> Bool # (/=) :: SnapshotLocation -> SnapshotLocation -> Bool # | |||||
Ord SnapshotLocation | |||||
Defined in Pantry.Types Methods compare :: SnapshotLocation -> SnapshotLocation -> Ordering # (<) :: SnapshotLocation -> SnapshotLocation -> Bool # (<=) :: SnapshotLocation -> SnapshotLocation -> Bool # (>) :: SnapshotLocation -> SnapshotLocation -> Bool # (>=) :: SnapshotLocation -> SnapshotLocation -> Bool # max :: SnapshotLocation -> SnapshotLocation -> SnapshotLocation # min :: SnapshotLocation -> SnapshotLocation -> SnapshotLocation # | |||||
Display SnapshotLocation | |||||
Defined in Pantry.Types | |||||
FromJSON (WithJSONWarnings (Unresolved SnapshotLocation)) | |||||
Defined in Pantry.Types Methods parseJSON :: Value -> Parser (WithJSONWarnings (Unresolved SnapshotLocation)) # parseJSONList :: Value -> Parser [WithJSONWarnings (Unresolved SnapshotLocation)] # omittedField :: Maybe (WithJSONWarnings (Unresolved SnapshotLocation)) # | |||||
type Rep SnapshotLocation | |||||
Defined in Pantry.Types type Rep SnapshotLocation = D1 ('MetaData "SnapshotLocation" "Pantry.Types" "pantry-0.10.0-2c6hPrHSjDQ3SnTMTDZv1w-internal" 'False) (C1 ('MetaCons "SLCompiler" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 WantedCompiler)) :+: (C1 ('MetaCons "SLUrl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BlobKey)) :+: C1 ('MetaCons "SLFilePath" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ResolvedPath File))))) |
data RawSnapshotLocation #
Constructors
RSLCompiler !WantedCompiler | |
RSLUrl !Text !(Maybe BlobKey) | |
RSLFilePath !(ResolvedPath File) | |
RSLSynonym !SnapName |
Instances
ToJSON RawSnapshotLocation | |||||
Defined in Pantry.Types Methods toJSON :: RawSnapshotLocation -> Value # toEncoding :: RawSnapshotLocation -> Encoding # toJSONList :: [RawSnapshotLocation] -> Value # toEncodingList :: [RawSnapshotLocation] -> Encoding # omitField :: RawSnapshotLocation -> Bool # | |||||
Generic RawSnapshotLocation | |||||
Defined in Pantry.Types Associated Types
Methods from :: RawSnapshotLocation -> Rep RawSnapshotLocation x # to :: Rep RawSnapshotLocation x -> RawSnapshotLocation # | |||||
Show RawSnapshotLocation | |||||
Defined in Pantry.Types Methods showsPrec :: Int -> RawSnapshotLocation -> ShowS # show :: RawSnapshotLocation -> String # showList :: [RawSnapshotLocation] -> ShowS # | |||||
NFData RawSnapshotLocation | |||||
Defined in Pantry.Types Methods rnf :: RawSnapshotLocation -> () # | |||||
Eq RawSnapshotLocation | |||||
Defined in Pantry.Types Methods (==) :: RawSnapshotLocation -> RawSnapshotLocation -> Bool # (/=) :: RawSnapshotLocation -> RawSnapshotLocation -> Bool # | |||||
Ord RawSnapshotLocation | |||||
Defined in Pantry.Types Methods compare :: RawSnapshotLocation -> RawSnapshotLocation -> Ordering # (<) :: RawSnapshotLocation -> RawSnapshotLocation -> Bool # (<=) :: RawSnapshotLocation -> RawSnapshotLocation -> Bool # (>) :: RawSnapshotLocation -> RawSnapshotLocation -> Bool # (>=) :: RawSnapshotLocation -> RawSnapshotLocation -> Bool # max :: RawSnapshotLocation -> RawSnapshotLocation -> RawSnapshotLocation # min :: RawSnapshotLocation -> RawSnapshotLocation -> RawSnapshotLocation # | |||||
Display RawSnapshotLocation | |||||
Defined in Pantry.Types | |||||
Pretty RawSnapshotLocation | |||||
Defined in Pantry.Types Methods pretty :: RawSnapshotLocation -> StyleDoc # | |||||
FromJSON (WithJSONWarnings (Unresolved RawSnapshotLocation)) | |||||
Defined in Pantry.Types Methods parseJSON :: Value -> Parser (WithJSONWarnings (Unresolved RawSnapshotLocation)) # parseJSONList :: Value -> Parser [WithJSONWarnings (Unresolved RawSnapshotLocation)] # omittedField :: Maybe (WithJSONWarnings (Unresolved RawSnapshotLocation)) # | |||||
type Rep RawSnapshotLocation | |||||
Defined in Pantry.Types type Rep RawSnapshotLocation = D1 ('MetaData "RawSnapshotLocation" "Pantry.Types" "pantry-0.10.0-2c6hPrHSjDQ3SnTMTDZv1w-internal" 'False) ((C1 ('MetaCons "RSLCompiler" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 WantedCompiler)) :+: C1 ('MetaCons "RSLUrl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe BlobKey)))) :+: (C1 ('MetaCons "RSLFilePath" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ResolvedPath File))) :+: C1 ('MetaCons "RSLSynonym" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SnapName)))) |
Instances
ToJSON SnapName | |||||
Generic SnapName | |||||
Defined in Pantry.Types Associated Types
| |||||
Show SnapName | |||||
NFData SnapName | |||||
Defined in Pantry.Types | |||||
Eq SnapName | |||||
Ord SnapName | |||||
Defined in Pantry.Types | |||||
Display SnapName | |||||
Defined in Pantry.Types | |||||
type Rep SnapName | |||||
Defined in Pantry.Types type Rep SnapName = D1 ('MetaData "SnapName" "Pantry.Types" "pantry-0.10.0-2c6hPrHSjDQ3SnTMTDZv1w-internal" 'False) (C1 ('MetaCons "LTS" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Int)) :+: C1 ('MetaCons "Nightly" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Day))) |
data WantedCompiler #
Instances
FromJSON WantedCompiler | |||||
Defined in Pantry.Types Methods parseJSON :: Value -> Parser WantedCompiler # parseJSONList :: Value -> Parser [WantedCompiler] # | |||||
FromJSONKey WantedCompiler | |||||
Defined in Pantry.Types | |||||
ToJSON WantedCompiler | |||||
Defined in Pantry.Types Methods toJSON :: WantedCompiler -> Value # toEncoding :: WantedCompiler -> Encoding # toJSONList :: [WantedCompiler] -> Value # toEncodingList :: [WantedCompiler] -> Encoding # omitField :: WantedCompiler -> Bool # | |||||
Generic WantedCompiler | |||||
Defined in Pantry.Types Associated Types
Methods from :: WantedCompiler -> Rep WantedCompiler x # to :: Rep WantedCompiler x -> WantedCompiler # | |||||
Show WantedCompiler | |||||
Defined in Pantry.Types Methods showsPrec :: Int -> WantedCompiler -> ShowS # show :: WantedCompiler -> String # showList :: [WantedCompiler] -> ShowS # | |||||
NFData WantedCompiler | |||||
Defined in Pantry.Types Methods rnf :: WantedCompiler -> () # | |||||
Eq WantedCompiler | |||||
Defined in Pantry.Types Methods (==) :: WantedCompiler -> WantedCompiler -> Bool # (/=) :: WantedCompiler -> WantedCompiler -> Bool # | |||||
Ord WantedCompiler | |||||
Defined in Pantry.Types Methods compare :: WantedCompiler -> WantedCompiler -> Ordering # (<) :: WantedCompiler -> WantedCompiler -> Bool # (<=) :: WantedCompiler -> WantedCompiler -> Bool # (>) :: WantedCompiler -> WantedCompiler -> Bool # (>=) :: WantedCompiler -> WantedCompiler -> Bool # max :: WantedCompiler -> WantedCompiler -> WantedCompiler # min :: WantedCompiler -> WantedCompiler -> WantedCompiler # | |||||
Display WantedCompiler | |||||
Defined in Pantry.Types | |||||
type Rep WantedCompiler | |||||
Defined in Pantry.Types type Rep WantedCompiler = D1 ('MetaData "WantedCompiler" "Pantry.Types" "pantry-0.10.0-2c6hPrHSjDQ3SnTMTDZv1w-internal" 'False) (C1 ('MetaCons "WCGhc" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Version)) :+: (C1 ('MetaCons "WCGhcGit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :+: C1 ('MetaCons "WCGhcjs" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Version) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Version)))) |
data HpackExecutable #
Constructors
HpackBundled | |
HpackCommand !FilePath |
Instances
Read HpackExecutable | |
Defined in Pantry.Types Methods readsPrec :: Int -> ReadS HpackExecutable # readList :: ReadS [HpackExecutable] # | |
Show HpackExecutable | |
Defined in Pantry.Types Methods showsPrec :: Int -> HpackExecutable -> ShowS # show :: HpackExecutable -> String # showList :: [HpackExecutable] -> ShowS # | |
Eq HpackExecutable | |
Defined in Pantry.Types Methods (==) :: HpackExecutable -> HpackExecutable -> Bool # (/=) :: HpackExecutable -> HpackExecutable -> Bool # | |
Ord HpackExecutable | |
Defined in Pantry.Types Methods compare :: HpackExecutable -> HpackExecutable -> Ordering # (<) :: HpackExecutable -> HpackExecutable -> Bool # (<=) :: HpackExecutable -> HpackExecutable -> Bool # (>) :: HpackExecutable -> HpackExecutable -> Bool # (>=) :: HpackExecutable -> HpackExecutable -> Bool # max :: HpackExecutable -> HpackExecutable -> HpackExecutable # min :: HpackExecutable -> HpackExecutable -> HpackExecutable # |
newtype CabalString a #
Constructors
CabalString | |
Fields
|
Instances
IsCabalString a => FromJSON (CabalString a) | |
Defined in Pantry.Types Methods parseJSON :: Value -> Parser (CabalString a) # parseJSONList :: Value -> Parser [CabalString a] # omittedField :: Maybe (CabalString a) # | |
IsCabalString a => FromJSONKey (CabalString a) | |
Defined in Pantry.Types Methods | |
Pretty a => ToJSON (CabalString a) | |
Defined in Pantry.Types Methods toJSON :: CabalString a -> Value # toEncoding :: CabalString a -> Encoding # toJSONList :: [CabalString a] -> Value # toEncodingList :: [CabalString a] -> Encoding # omitField :: CabalString a -> Bool # | |
Pretty a => ToJSONKey (CabalString a) | |
Defined in Pantry.Types Methods toJSONKey :: ToJSONKeyFunction (CabalString a) # | |
Show a => Show (CabalString a) | |
Defined in Pantry.Types Methods showsPrec :: Int -> CabalString a -> ShowS # show :: CabalString a -> String # showList :: [CabalString a] -> ShowS # | |
Eq a => Eq (CabalString a) | |
Defined in Pantry.Types Methods (==) :: CabalString a -> CabalString a -> Bool # (/=) :: CabalString a -> CabalString a -> Bool # | |
Ord a => Ord (CabalString a) | |
Defined in Pantry.Types Methods compare :: CabalString a -> CabalString a -> Ordering # (<) :: CabalString a -> CabalString a -> Bool # (<=) :: CabalString a -> CabalString a -> Bool # (>) :: CabalString a -> CabalString a -> Bool # (>=) :: CabalString a -> CabalString a -> Bool # max :: CabalString a -> CabalString a -> CabalString a # min :: CabalString a -> CabalString a -> CabalString a # |
data ArchiveLocation #
Constructors
ALUrl !Text | |
ALFilePath !(ResolvedPath File) |
Instances
Generic ArchiveLocation | |||||
Defined in Pantry.Types Associated Types
Methods from :: ArchiveLocation -> Rep ArchiveLocation x # to :: Rep ArchiveLocation x -> ArchiveLocation # | |||||
Show ArchiveLocation | |||||
Defined in Pantry.Types Methods showsPrec :: Int -> ArchiveLocation -> ShowS # show :: ArchiveLocation -> String # showList :: [ArchiveLocation] -> ShowS # | |||||
NFData ArchiveLocation | |||||
Defined in Pantry.Types Methods rnf :: ArchiveLocation -> () # | |||||
Eq ArchiveLocation | |||||
Defined in Pantry.Types Methods (==) :: ArchiveLocation -> ArchiveLocation -> Bool # (/=) :: ArchiveLocation -> ArchiveLocation -> Bool # | |||||
Ord ArchiveLocation | |||||
Defined in Pantry.Types Methods compare :: ArchiveLocation -> ArchiveLocation -> Ordering # (<) :: ArchiveLocation -> ArchiveLocation -> Bool # (<=) :: ArchiveLocation -> ArchiveLocation -> Bool # (>) :: ArchiveLocation -> ArchiveLocation -> Bool # (>=) :: ArchiveLocation -> ArchiveLocation -> Bool # max :: ArchiveLocation -> ArchiveLocation -> ArchiveLocation # min :: ArchiveLocation -> ArchiveLocation -> ArchiveLocation # | |||||
Display ArchiveLocation | |||||
Defined in Pantry.Types | |||||
Pretty ArchiveLocation | |||||
Defined in Pantry.Types Methods pretty :: ArchiveLocation -> StyleDoc # | |||||
type Rep ArchiveLocation | |||||
Defined in Pantry.Types type Rep ArchiveLocation = D1 ('MetaData "ArchiveLocation" "Pantry.Types" "pantry-0.10.0-2c6hPrHSjDQ3SnTMTDZv1w-internal" 'False) (C1 ('MetaCons "ALUrl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :+: C1 ('MetaCons "ALFilePath" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ResolvedPath File)))) |
newtype RelFilePath #
Constructors
RelFilePath Text |
Instances
FromJSON RelFilePath | |||||
Defined in Pantry.Types | |||||
ToJSON RelFilePath | |||||
Defined in Pantry.Types Methods toJSON :: RelFilePath -> Value # toEncoding :: RelFilePath -> Encoding # toJSONList :: [RelFilePath] -> Value # toEncodingList :: [RelFilePath] -> Encoding # omitField :: RelFilePath -> Bool # | |||||
Generic RelFilePath | |||||
Defined in Pantry.Types Associated Types
| |||||
Show RelFilePath | |||||
Defined in Pantry.Types Methods showsPrec :: Int -> RelFilePath -> ShowS # show :: RelFilePath -> String # showList :: [RelFilePath] -> ShowS # | |||||
NFData RelFilePath | |||||
Defined in Pantry.Types Methods rnf :: RelFilePath -> () # | |||||
Eq RelFilePath | |||||
Defined in Pantry.Types | |||||
Ord RelFilePath | |||||
Defined in Pantry.Types Methods compare :: RelFilePath -> RelFilePath -> Ordering # (<) :: RelFilePath -> RelFilePath -> Bool # (<=) :: RelFilePath -> RelFilePath -> Bool # (>) :: RelFilePath -> RelFilePath -> Bool # (>=) :: RelFilePath -> RelFilePath -> Bool # max :: RelFilePath -> RelFilePath -> RelFilePath # min :: RelFilePath -> RelFilePath -> RelFilePath # | |||||
Display RelFilePath | |||||
Defined in Pantry.Types | |||||
type Rep RelFilePath | |||||
Defined in Pantry.Types type Rep RelFilePath = D1 ('MetaData "RelFilePath" "Pantry.Types" "pantry-0.10.0-2c6hPrHSjDQ3SnTMTDZv1w-internal" 'True) (C1 ('MetaCons "RelFilePath" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) |
data PackageMetadata #
Constructors
PackageMetadata | |
Fields
|
Instances
Generic PackageMetadata | |||||
Defined in Pantry.Types Associated Types
Methods from :: PackageMetadata -> Rep PackageMetadata x # to :: Rep PackageMetadata x -> PackageMetadata # | |||||
Show PackageMetadata | |||||
Defined in Pantry.Types Methods showsPrec :: Int -> PackageMetadata -> ShowS # show :: PackageMetadata -> String # showList :: [PackageMetadata] -> ShowS # | |||||
NFData PackageMetadata | |||||
Defined in Pantry.Types Methods rnf :: PackageMetadata -> () # | |||||
Eq PackageMetadata | |||||
Defined in Pantry.Types Methods (==) :: PackageMetadata -> PackageMetadata -> Bool # (/=) :: PackageMetadata -> PackageMetadata -> Bool # | |||||
Ord PackageMetadata | |||||
Defined in Pantry.Types Methods compare :: PackageMetadata -> PackageMetadata -> Ordering # (<) :: PackageMetadata -> PackageMetadata -> Bool # (<=) :: PackageMetadata -> PackageMetadata -> Bool # (>) :: PackageMetadata -> PackageMetadata -> Bool # (>=) :: PackageMetadata -> PackageMetadata -> Bool # max :: PackageMetadata -> PackageMetadata -> PackageMetadata # min :: PackageMetadata -> PackageMetadata -> PackageMetadata # | |||||
Display PackageMetadata | |||||
Defined in Pantry.Types | |||||
type Rep PackageMetadata | |||||
Defined in Pantry.Types type Rep PackageMetadata = D1 ('MetaData "PackageMetadata" "Pantry.Types" "pantry-0.10.0-2c6hPrHSjDQ3SnTMTDZv1w-internal" 'False) (C1 ('MetaCons "PackageMetadata" 'PrefixI 'True) (S1 ('MetaSel ('Just "pmIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PackageIdentifier) :*: S1 ('MetaSel ('Just "pmTreeKey") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TreeKey))) |
data RawPackageMetadata #
Constructors
RawPackageMetadata | |
Fields
|
Instances
Generic RawPackageMetadata | |||||
Defined in Pantry.Types Associated Types
Methods from :: RawPackageMetadata -> Rep RawPackageMetadata x # to :: Rep RawPackageMetadata x -> RawPackageMetadata # | |||||
Show RawPackageMetadata | |||||
Defined in Pantry.Types Methods showsPrec :: Int -> RawPackageMetadata -> ShowS # show :: RawPackageMetadata -> String # showList :: [RawPackageMetadata] -> ShowS # | |||||
NFData RawPackageMetadata | |||||
Defined in Pantry.Types Methods rnf :: RawPackageMetadata -> () # | |||||
Eq RawPackageMetadata | |||||
Defined in Pantry.Types Methods (==) :: RawPackageMetadata -> RawPackageMetadata -> Bool # (/=) :: RawPackageMetadata -> RawPackageMetadata -> Bool # | |||||
Ord RawPackageMetadata | |||||
Defined in Pantry.Types Methods compare :: RawPackageMetadata -> RawPackageMetadata -> Ordering # (<) :: RawPackageMetadata -> RawPackageMetadata -> Bool # (<=) :: RawPackageMetadata -> RawPackageMetadata -> Bool # (>) :: RawPackageMetadata -> RawPackageMetadata -> Bool # (>=) :: RawPackageMetadata -> RawPackageMetadata -> Bool # max :: RawPackageMetadata -> RawPackageMetadata -> RawPackageMetadata # min :: RawPackageMetadata -> RawPackageMetadata -> RawPackageMetadata # | |||||
Display RawPackageMetadata | |||||
Defined in Pantry.Types | |||||
type Rep RawPackageMetadata | |||||
Defined in Pantry.Types type Rep RawPackageMetadata = D1 ('MetaData "RawPackageMetadata" "Pantry.Types" "pantry-0.10.0-2c6hPrHSjDQ3SnTMTDZv1w-internal" 'False) (C1 ('MetaCons "RawPackageMetadata" 'PrefixI 'True) (S1 ('MetaSel ('Just "rpmName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe PackageName)) :*: (S1 ('MetaSel ('Just "rpmVersion") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Version)) :*: S1 ('MetaSel ('Just "rpmTreeKey") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe TreeKey))))) |
Instances
FromJSON TreeKey | |||||
Defined in Pantry.Types | |||||
ToJSON TreeKey | |||||
Generic TreeKey | |||||
Defined in Pantry.Types Associated Types
| |||||
Show TreeKey | |||||
NFData TreeKey | |||||
Defined in Pantry.Types | |||||
Eq TreeKey | |||||
Ord TreeKey | |||||
Display TreeKey | |||||
Defined in Pantry.Types | |||||
type Rep TreeKey | |||||
Defined in Pantry.Types |
data SafeFilePath #
Instances
Show SafeFilePath | |
Defined in Pantry.Types Methods showsPrec :: Int -> SafeFilePath -> ShowS # show :: SafeFilePath -> String # showList :: [SafeFilePath] -> ShowS # | |
Eq SafeFilePath | |
Defined in Pantry.Types | |
Ord SafeFilePath | |
Defined in Pantry.Types Methods 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 Methods toPersistValue :: SafeFilePath -> PersistValue # fromPersistValue :: PersistValue -> Either Text SafeFilePath # | |
PersistFieldSql SafeFilePath | |
Defined in Pantry.Types Methods sqlType :: Proxy SafeFilePath -> SqlType # | |
Display SafeFilePath | |
Defined in Pantry.Types | |
SymbolToField "path" FilePath SafeFilePath | |
Defined in Pantry.Storage Methods symbolToField :: EntityField FilePath SafeFilePath # |
data FuzzyResults #
data PantryException #
Constructors
PackageIdentifierRevisionParseFail !Text | |
InvalidCabalFile !(Either RawPackageLocationImmutable (Path Abs File)) !(Maybe Version) ![PError] ![PWarning] | |
TreeWithoutCabalFile !RawPackageLocationImmutable | |
TreeWithMultipleCabalFiles !RawPackageLocationImmutable ![SafeFilePath] | |
MismatchedCabalName !(Path Abs File) !PackageName | |
NoLocalPackageDirFound !(Path Abs Dir) | |
NoCabalFileFound !(Path Abs Dir) | |
MultipleCabalFilesFound !(Path Abs Dir) ![Path Abs File] | |
InvalidWantedCompiler !Text | |
InvalidSnapshotLocation !(Path Abs Dir) !Text | |
InvalidOverrideCompiler !WantedCompiler !WantedCompiler | |
InvalidFilePathSnapshot !Text | |
InvalidSnapshot !RawSnapshotLocation !SomeException | |
InvalidGlobalHintsLocation !(Path Abs Dir) !Text | |
InvalidFilePathGlobalHints !Text | |
MismatchedPackageMetadata !RawPackageLocationImmutable !RawPackageMetadata !(Maybe TreeKey) !PackageIdentifier | |
Non200ResponseStatus !Status | |
InvalidBlobKey !(Mismatch BlobKey) | |
Couldn'tParseSnapshot !RawSnapshotLocation !String | |
WrongCabalFileName !RawPackageLocationImmutable !SafeFilePath !PackageName | |
DownloadInvalidSHA256 !Text !(Mismatch SHA256) | |
DownloadInvalidSize !Text !(Mismatch FileSize) | |
DownloadTooLarge !Text !(Mismatch FileSize) | |
LocalNoArchiveFileFound !(Path Abs File) | |
LocalInvalidSHA256 !(Path Abs File) !(Mismatch SHA256) | |
LocalInvalidSize !(Path Abs File) !(Mismatch FileSize) | |
UnknownArchiveType !ArchiveLocation | |
InvalidTarFileType !ArchiveLocation !FilePath !FileType | |
UnsupportedTarball !ArchiveLocation !Text | |
NoHackageCryptographicHash !PackageIdentifier | |
FailedToCloneRepo !SimpleRepo | |
TreeReferencesMissingBlob !RawPackageLocationImmutable !SafeFilePath !BlobKey | |
CompletePackageMetadataMismatch !RawPackageLocationImmutable !PackageMetadata | |
CRC32Mismatch !ArchiveLocation !FilePath !(Mismatch Word32) | |
UnknownHackagePackage !PackageIdentifierRevision !FuzzyResults | |
CannotCompleteRepoNonSHA1 !Repo | |
MutablePackageLocationFromUrl !Text | |
MismatchedCabalFileForHackage !PackageIdentifierRevision !(Mismatch PackageIdentifier) | |
PackageNameParseFail !Text | |
PackageVersionParseFail !Text | |
InvalidCabalFilePath !(Path Abs File) | |
DuplicatePackageNames !Utf8Builder ![(PackageName, [RawPackageLocationImmutable])] | |
MigrationFailure !Text !(Path Abs File) !SomeException | |
NoCasaConfig | |
InvalidTreeFromCasa !BlobKey !ByteString | |
ParseSnapNameException !Text | |
HpackLibraryException !(Path Abs File) !String | |
HpackExeException !FilePath !(Path Abs Dir) !SomeException |
Instances
Exception PantryException | |
Defined in Pantry.Types Methods toException :: PantryException -> SomeException # | |
Show PantryException | |
Defined in Pantry.Types Methods showsPrec :: Int -> PantryException -> ShowS # show :: PantryException -> String # showList :: [PantryException] -> ShowS # | |
Display PantryException | |
Defined in Pantry.Types | |
Pretty PantryException | |
Defined in Pantry.Types Methods pretty :: PantryException -> StyleDoc # |
Constructors
Mismatch | |
Fields
|
data PackageIdentifierRevision #
Constructors
PackageIdentifierRevision !PackageName !Version !CabalFileInfo |
Instances
FromJSON PackageIdentifierRevision | |||||
Defined in Pantry.Types Methods parseJSON :: Value -> Parser PackageIdentifierRevision # parseJSONList :: Value -> Parser [PackageIdentifierRevision] # | |||||
ToJSON PackageIdentifierRevision | |||||
Defined in Pantry.Types Methods toJSON :: PackageIdentifierRevision -> Value # toEncoding :: PackageIdentifierRevision -> Encoding # toJSONList :: [PackageIdentifierRevision] -> Value # | |||||
Generic PackageIdentifierRevision | |||||
Defined in Pantry.Types Associated Types
Methods from :: PackageIdentifierRevision -> Rep PackageIdentifierRevision x # to :: Rep PackageIdentifierRevision x -> PackageIdentifierRevision # | |||||
Show PackageIdentifierRevision | |||||
Defined in Pantry.Types Methods showsPrec :: Int -> PackageIdentifierRevision -> ShowS # show :: PackageIdentifierRevision -> String # showList :: [PackageIdentifierRevision] -> ShowS # | |||||
NFData PackageIdentifierRevision | |||||
Defined in Pantry.Types Methods rnf :: PackageIdentifierRevision -> () # | |||||
Eq PackageIdentifierRevision | |||||
Defined in Pantry.Types Methods (==) :: PackageIdentifierRevision -> PackageIdentifierRevision -> Bool # (/=) :: PackageIdentifierRevision -> PackageIdentifierRevision -> Bool # | |||||
Ord PackageIdentifierRevision | |||||
Defined in Pantry.Types Methods compare :: PackageIdentifierRevision -> PackageIdentifierRevision -> Ordering # (<) :: PackageIdentifierRevision -> PackageIdentifierRevision -> Bool # (<=) :: PackageIdentifierRevision -> PackageIdentifierRevision -> Bool # (>) :: PackageIdentifierRevision -> PackageIdentifierRevision -> Bool # (>=) :: PackageIdentifierRevision -> PackageIdentifierRevision -> Bool # max :: PackageIdentifierRevision -> PackageIdentifierRevision -> PackageIdentifierRevision # min :: PackageIdentifierRevision -> PackageIdentifierRevision -> PackageIdentifierRevision # | |||||
Display PackageIdentifierRevision | |||||
Defined in Pantry.Types Methods | |||||
type Rep PackageIdentifierRevision | |||||
Defined in Pantry.Types type Rep PackageIdentifierRevision = D1 ('MetaData "PackageIdentifierRevision" "Pantry.Types" "pantry-0.10.0-2c6hPrHSjDQ3SnTMTDZv1w-internal" 'False) (C1 ('MetaCons "PackageIdentifierRevision" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 PackageName) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Version) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CabalFileInfo)))) |
data CabalFileInfo #
Instances
Generic CabalFileInfo | |||||
Defined in Pantry.Types Associated Types
| |||||
Show CabalFileInfo | |||||
Defined in Pantry.Types Methods showsPrec :: Int -> CabalFileInfo -> ShowS # show :: CabalFileInfo -> String # showList :: [CabalFileInfo] -> ShowS # | |||||
NFData CabalFileInfo | |||||
Defined in Pantry.Types Methods rnf :: CabalFileInfo -> () # | |||||
Eq CabalFileInfo | |||||
Defined in Pantry.Types Methods (==) :: CabalFileInfo -> CabalFileInfo -> Bool # (/=) :: CabalFileInfo -> CabalFileInfo -> Bool # | |||||
Ord CabalFileInfo | |||||
Defined in Pantry.Types Methods compare :: CabalFileInfo -> CabalFileInfo -> Ordering # (<) :: CabalFileInfo -> CabalFileInfo -> Bool # (<=) :: CabalFileInfo -> CabalFileInfo -> Bool # (>) :: CabalFileInfo -> CabalFileInfo -> Bool # (>=) :: CabalFileInfo -> CabalFileInfo -> Bool # max :: CabalFileInfo -> CabalFileInfo -> CabalFileInfo # min :: CabalFileInfo -> CabalFileInfo -> CabalFileInfo # | |||||
Hashable CabalFileInfo | |||||
Defined in Pantry.Types | |||||
Display CabalFileInfo | |||||
Defined in Pantry.Types | |||||
type Rep CabalFileInfo | |||||
Defined in Pantry.Types type Rep CabalFileInfo = D1 ('MetaData "CabalFileInfo" "Pantry.Types" "pantry-0.10.0-2c6hPrHSjDQ3SnTMTDZv1w-internal" 'False) (C1 ('MetaCons "CFILatest" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CFIHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SHA256) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe FileSize))) :+: C1 ('MetaCons "CFIRevision" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Revision)))) |
class HasPantryConfig env where #
Methods
pantryConfigL :: Lens' env PantryConfig #
Instances
HasPantryConfig PantryApp | |
Defined in Pantry Methods | |
HasPantryConfig EnvConfigPathInfo Source # | |
Defined in Stack.Path Methods | |
HasPantryConfig Ctx Source # | |
Defined in Stack.Types.Build.ConstructPlan Methods | |
HasPantryConfig BuildConfig Source # | |
Defined in Stack.Types.BuildConfig Methods | |
HasPantryConfig Config Source # | |
Defined in Stack.Types.Config Methods | |
HasPantryConfig DotConfig Source # | |
Defined in Stack.Types.DotConfig Methods | |
HasPantryConfig EnvConfig Source # | |
Defined in Stack.Types.EnvConfig Methods | |
HasPantryConfig GetPackageFileContext Source # | |
Defined in Stack.Types.PackageFile Methods |
data HackageSecurityConfig #
Constructors
HackageSecurityConfig | |
Fields
|
Instances
Show HackageSecurityConfig | |
Defined in Pantry.Types Methods showsPrec :: Int -> HackageSecurityConfig -> ShowS # show :: HackageSecurityConfig -> String # showList :: [HackageSecurityConfig] -> ShowS # | |
FromJSON (WithJSONWarnings HackageSecurityConfig) | |
Defined in Pantry.Types |
data PackageIndexConfig #
Constructors
PackageIndexConfig | |
Fields |
Instances
Show PackageIndexConfig | |
Defined in Pantry.Types Methods showsPrec :: Int -> PackageIndexConfig -> ShowS # show :: PackageIndexConfig -> String # showList :: [PackageIndexConfig] -> ShowS # | |
FromJSON (WithJSONWarnings PackageIndexConfig) | |
Defined in Pantry.Types Methods parseJSON :: Value -> Parser (WithJSONWarnings PackageIndexConfig) # parseJSONList :: Value -> Parser [WithJSONWarnings PackageIndexConfig] # omittedField :: Maybe (WithJSONWarnings PackageIndexConfig) # |
data SimpleRepo #
Constructors
SimpleRepo | |
Instances
Generic SimpleRepo | |||||
Defined in Pantry.Types Associated Types
| |||||
Show SimpleRepo | |||||
Defined in Pantry.Types Methods showsPrec :: Int -> SimpleRepo -> ShowS # show :: SimpleRepo -> String # showList :: [SimpleRepo] -> ShowS # | |||||
Eq SimpleRepo | |||||
Defined in Pantry.Types | |||||
Ord SimpleRepo | |||||
Defined in Pantry.Types Methods compare :: SimpleRepo -> SimpleRepo -> Ordering # (<) :: SimpleRepo -> SimpleRepo -> Bool # (<=) :: SimpleRepo -> SimpleRepo -> Bool # (>) :: SimpleRepo -> SimpleRepo -> Bool # (>=) :: SimpleRepo -> SimpleRepo -> Bool # max :: SimpleRepo -> SimpleRepo -> SimpleRepo # min :: SimpleRepo -> SimpleRepo -> SimpleRepo # | |||||
Display SimpleRepo | |||||
Defined in Pantry.Types | |||||
type Rep SimpleRepo | |||||
Defined in Pantry.Types type Rep SimpleRepo = D1 ('MetaData "SimpleRepo" "Pantry.Types" "pantry-0.10.0-2c6hPrHSjDQ3SnTMTDZv1w-internal" 'False) (C1 ('MetaCons "SimpleRepo" 'PrefixI 'True) (S1 ('MetaSel ('Just "sRepoUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "sRepoCommit") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "sRepoType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RepoType)))) |
Constructors
Archive | |
Fields
|
Instances
Generic Archive | |||||
Defined in Pantry.Types Associated Types
| |||||
Show Archive | |||||
NFData Archive | |||||
Defined in Pantry.Types | |||||
Eq Archive | |||||
Ord Archive | |||||
type Rep Archive | |||||
Defined in Pantry.Types type Rep Archive = D1 ('MetaData "Archive" "Pantry.Types" "pantry-0.10.0-2c6hPrHSjDQ3SnTMTDZv1w-internal" 'False) (C1 ('MetaCons "Archive" 'PrefixI 'True) ((S1 ('MetaSel ('Just "archiveLocation") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ArchiveLocation) :*: S1 ('MetaSel ('Just "archiveHash") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SHA256)) :*: (S1 ('MetaSel ('Just "archiveSize") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 FileSize) :*: S1 ('MetaSel ('Just "archiveSubdir") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)))) |
data RawArchive #
Constructors
RawArchive | |
Fields
|
Instances
Generic RawArchive | |||||
Defined in Pantry.Types Associated Types
| |||||
Show RawArchive | |||||
Defined in Pantry.Types Methods showsPrec :: Int -> RawArchive -> ShowS # show :: RawArchive -> String # showList :: [RawArchive] -> ShowS # | |||||
NFData RawArchive | |||||
Defined in Pantry.Types Methods rnf :: RawArchive -> () # | |||||
Eq RawArchive | |||||
Defined in Pantry.Types | |||||
Ord RawArchive | |||||
Defined in Pantry.Types Methods compare :: RawArchive -> RawArchive -> Ordering # (<) :: RawArchive -> RawArchive -> Bool # (<=) :: RawArchive -> RawArchive -> Bool # (>) :: RawArchive -> RawArchive -> Bool # (>=) :: RawArchive -> RawArchive -> Bool # max :: RawArchive -> RawArchive -> RawArchive # min :: RawArchive -> RawArchive -> RawArchive # | |||||
type Rep RawArchive | |||||
Defined in Pantry.Types type Rep RawArchive = D1 ('MetaData "RawArchive" "Pantry.Types" "pantry-0.10.0-2c6hPrHSjDQ3SnTMTDZv1w-internal" 'False) (C1 ('MetaCons "RawArchive" 'PrefixI 'True) ((S1 ('MetaSel ('Just "raLocation") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ArchiveLocation) :*: S1 ('MetaSel ('Just "raHash") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe SHA256))) :*: (S1 ('MetaSel ('Just "raSize") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe FileSize)) :*: S1 ('MetaSel ('Just "raSubdir") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)))) |
data PackageLocationImmutable #
Constructors
PLIHackage !PackageIdentifier !BlobKey !TreeKey | |
PLIArchive !Archive !PackageMetadata | |
PLIRepo !Repo !PackageMetadata |
Instances
ToJSON PackageLocationImmutable | |||||
Defined in Pantry.Types Methods toJSON :: PackageLocationImmutable -> Value # toEncoding :: PackageLocationImmutable -> Encoding # toJSONList :: [PackageLocationImmutable] -> Value # | |||||
Generic PackageLocationImmutable | |||||
Defined in Pantry.Types Associated Types
Methods from :: PackageLocationImmutable -> Rep PackageLocationImmutable x # to :: Rep PackageLocationImmutable x -> PackageLocationImmutable # | |||||
Show PackageLocationImmutable | |||||
Defined in Pantry.Types Methods showsPrec :: Int -> PackageLocationImmutable -> ShowS # show :: PackageLocationImmutable -> String # showList :: [PackageLocationImmutable] -> ShowS # | |||||
NFData PackageLocationImmutable | |||||
Defined in Pantry.Types Methods rnf :: PackageLocationImmutable -> () # | |||||
Eq PackageLocationImmutable | |||||
Defined in Pantry.Types Methods (==) :: PackageLocationImmutable -> PackageLocationImmutable -> Bool # (/=) :: PackageLocationImmutable -> PackageLocationImmutable -> Bool # | |||||
Ord PackageLocationImmutable | |||||
Defined in Pantry.Types Methods compare :: PackageLocationImmutable -> PackageLocationImmutable -> Ordering # (<) :: PackageLocationImmutable -> PackageLocationImmutable -> Bool # (<=) :: PackageLocationImmutable -> PackageLocationImmutable -> Bool # (>) :: PackageLocationImmutable -> PackageLocationImmutable -> Bool # (>=) :: PackageLocationImmutable -> PackageLocationImmutable -> Bool # max :: PackageLocationImmutable -> PackageLocationImmutable -> PackageLocationImmutable # min :: PackageLocationImmutable -> PackageLocationImmutable -> PackageLocationImmutable # | |||||
Display PackageLocationImmutable | |||||
Defined in Pantry.Types Methods | |||||
FromJSON (WithJSONWarnings (Unresolved PackageLocationImmutable)) | |||||
Defined in Pantry.Types | |||||
type Rep PackageLocationImmutable | |||||
Defined in Pantry.Types type Rep PackageLocationImmutable = D1 ('MetaData "PackageLocationImmutable" "Pantry.Types" "pantry-0.10.0-2c6hPrHSjDQ3SnTMTDZv1w-internal" 'False) (C1 ('MetaCons "PLIHackage" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PackageIdentifier) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BlobKey) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TreeKey))) :+: (C1 ('MetaCons "PLIArchive" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Archive) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PackageMetadata)) :+: C1 ('MetaCons "PLIRepo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Repo) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PackageMetadata)))) |
data RawPackageLocationImmutable #
Constructors
RPLIHackage !PackageIdentifierRevision !(Maybe TreeKey) | |
RPLIArchive !RawArchive !RawPackageMetadata | |
RPLIRepo !Repo !RawPackageMetadata |
Instances
ToJSON RawPackageLocationImmutable | |||||
Defined in Pantry.Types Methods toJSON :: RawPackageLocationImmutable -> Value # toEncoding :: RawPackageLocationImmutable -> Encoding # toJSONList :: [RawPackageLocationImmutable] -> Value # toEncodingList :: [RawPackageLocationImmutable] -> Encoding # | |||||
Generic RawPackageLocationImmutable | |||||
Defined in Pantry.Types Associated Types
Methods from :: RawPackageLocationImmutable -> Rep RawPackageLocationImmutable x # to :: Rep RawPackageLocationImmutable x -> RawPackageLocationImmutable # | |||||
Show RawPackageLocationImmutable | |||||
Defined in Pantry.Types Methods showsPrec :: Int -> RawPackageLocationImmutable -> ShowS # show :: RawPackageLocationImmutable -> String # showList :: [RawPackageLocationImmutable] -> ShowS # | |||||
NFData RawPackageLocationImmutable | |||||
Defined in Pantry.Types Methods rnf :: RawPackageLocationImmutable -> () # | |||||
Eq RawPackageLocationImmutable | |||||
Defined in Pantry.Types Methods (==) :: RawPackageLocationImmutable -> RawPackageLocationImmutable -> Bool # (/=) :: RawPackageLocationImmutable -> RawPackageLocationImmutable -> Bool # | |||||
Ord RawPackageLocationImmutable | |||||
Defined in Pantry.Types Methods compare :: RawPackageLocationImmutable -> RawPackageLocationImmutable -> Ordering # (<) :: RawPackageLocationImmutable -> RawPackageLocationImmutable -> Bool # (<=) :: RawPackageLocationImmutable -> RawPackageLocationImmutable -> Bool # (>) :: RawPackageLocationImmutable -> RawPackageLocationImmutable -> Bool # (>=) :: RawPackageLocationImmutable -> RawPackageLocationImmutable -> Bool # max :: RawPackageLocationImmutable -> RawPackageLocationImmutable -> RawPackageLocationImmutable # min :: RawPackageLocationImmutable -> RawPackageLocationImmutable -> RawPackageLocationImmutable # | |||||
Display RawPackageLocationImmutable | |||||
Defined in Pantry.Types Methods | |||||
Pretty RawPackageLocationImmutable | |||||
Defined in Pantry.Types Methods | |||||
FromJSON (WithJSONWarnings (Unresolved (NonEmpty RawPackageLocationImmutable))) | |||||
Defined in Pantry.Types Methods parseJSON :: Value -> Parser (WithJSONWarnings (Unresolved (NonEmpty RawPackageLocationImmutable))) # parseJSONList :: Value -> Parser [WithJSONWarnings (Unresolved (NonEmpty RawPackageLocationImmutable))] # omittedField :: Maybe (WithJSONWarnings (Unresolved (NonEmpty RawPackageLocationImmutable))) # | |||||
type Rep RawPackageLocationImmutable | |||||
Defined in Pantry.Types type Rep RawPackageLocationImmutable = D1 ('MetaData "RawPackageLocationImmutable" "Pantry.Types" "pantry-0.10.0-2c6hPrHSjDQ3SnTMTDZv1w-internal" 'False) (C1 ('MetaCons "RPLIHackage" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PackageIdentifierRevision) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe TreeKey))) :+: (C1 ('MetaCons "RPLIArchive" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RawArchive) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RawPackageMetadata)) :+: C1 ('MetaCons "RPLIRepo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Repo) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RawPackageMetadata)))) |
data PackageLocation #
Constructors
PLImmutable !PackageLocationImmutable | |
PLMutable !(ResolvedPath Dir) |
Instances
Generic PackageLocation | |||||
Defined in Pantry.Types Associated Types
Methods from :: PackageLocation -> Rep PackageLocation x # to :: Rep PackageLocation x -> PackageLocation # | |||||
Show PackageLocation | |||||
Defined in Pantry.Types Methods showsPrec :: Int -> PackageLocation -> ShowS # show :: PackageLocation -> String # showList :: [PackageLocation] -> ShowS # | |||||
NFData PackageLocation | |||||
Defined in Pantry.Types Methods rnf :: PackageLocation -> () # | |||||
Eq PackageLocation | |||||
Defined in Pantry.Types Methods (==) :: PackageLocation -> PackageLocation -> Bool # (/=) :: PackageLocation -> PackageLocation -> Bool # | |||||
Display PackageLocation | |||||
Defined in Pantry.Types | |||||
type Rep PackageLocation | |||||
Defined in Pantry.Types type Rep PackageLocation = D1 ('MetaData "PackageLocation" "Pantry.Types" "pantry-0.10.0-2c6hPrHSjDQ3SnTMTDZv1w-internal" 'False) (C1 ('MetaCons "PLImmutable" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PackageLocationImmutable)) :+: C1 ('MetaCons "PLMutable" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ResolvedPath Dir)))) |
data RawPackageLocation #
Constructors
RPLImmutable !RawPackageLocationImmutable | |
RPLMutable !(ResolvedPath Dir) |
Instances
ToJSON RawPackageLocation | |||||
Defined in Pantry.Types Methods toJSON :: RawPackageLocation -> Value # toEncoding :: RawPackageLocation -> Encoding # toJSONList :: [RawPackageLocation] -> Value # toEncodingList :: [RawPackageLocation] -> Encoding # omitField :: RawPackageLocation -> Bool # | |||||
Generic RawPackageLocation | |||||
Defined in Pantry.Types Associated Types
Methods from :: RawPackageLocation -> Rep RawPackageLocation x # to :: Rep RawPackageLocation x -> RawPackageLocation # | |||||
Show RawPackageLocation | |||||
Defined in Pantry.Types Methods showsPrec :: Int -> RawPackageLocation -> ShowS # show :: RawPackageLocation -> String # showList :: [RawPackageLocation] -> ShowS # | |||||
NFData RawPackageLocation | |||||
Defined in Pantry.Types Methods rnf :: RawPackageLocation -> () # | |||||
Eq RawPackageLocation | |||||
Defined in Pantry.Types Methods (==) :: RawPackageLocation -> RawPackageLocation -> Bool # (/=) :: RawPackageLocation -> RawPackageLocation -> Bool # | |||||
FromJSON (WithJSONWarnings (Unresolved (NonEmpty RawPackageLocation))) | |||||
Defined in Pantry.Types Methods parseJSON :: Value -> Parser (WithJSONWarnings (Unresolved (NonEmpty RawPackageLocation))) # parseJSONList :: Value -> Parser [WithJSONWarnings (Unresolved (NonEmpty RawPackageLocation))] # omittedField :: Maybe (WithJSONWarnings (Unresolved (NonEmpty RawPackageLocation))) # | |||||
type Rep RawPackageLocation | |||||
Defined in Pantry.Types type Rep RawPackageLocation = D1 ('MetaData "RawPackageLocation" "Pantry.Types" "pantry-0.10.0-2c6hPrHSjDQ3SnTMTDZv1w-internal" 'False) (C1 ('MetaCons "RPLImmutable" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RawPackageLocationImmutable)) :+: C1 ('MetaCons "RPLMutable" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ResolvedPath Dir)))) |
data ResolvedPath t #
Constructors
ResolvedPath | |
Fields
|
Instances
Generic (ResolvedPath t) | |||||
Defined in Pantry.Types Associated Types
Methods from :: ResolvedPath t -> Rep (ResolvedPath t) x # to :: Rep (ResolvedPath t) x -> ResolvedPath t # | |||||
Show (ResolvedPath t) | |||||
Defined in Pantry.Types Methods showsPrec :: Int -> ResolvedPath t -> ShowS # show :: ResolvedPath t -> String # showList :: [ResolvedPath t] -> ShowS # | |||||
NFData (ResolvedPath t) | |||||
Defined in Pantry.Types Methods rnf :: ResolvedPath t -> () # | |||||
Eq (ResolvedPath t) | |||||
Defined in Pantry.Types Methods (==) :: ResolvedPath t -> ResolvedPath t -> Bool # (/=) :: ResolvedPath t -> ResolvedPath t -> Bool # | |||||
Ord (ResolvedPath t) | |||||
Defined in Pantry.Types Methods compare :: ResolvedPath t -> ResolvedPath t -> Ordering # (<) :: ResolvedPath t -> ResolvedPath t -> Bool # (<=) :: ResolvedPath t -> ResolvedPath t -> Bool # (>) :: ResolvedPath t -> ResolvedPath t -> Bool # (>=) :: ResolvedPath t -> ResolvedPath t -> Bool # max :: ResolvedPath t -> ResolvedPath t -> ResolvedPath t # min :: ResolvedPath t -> ResolvedPath t -> ResolvedPath t # | |||||
type Rep (ResolvedPath t) | |||||
Defined in Pantry.Types type Rep (ResolvedPath t) = D1 ('MetaData "ResolvedPath" "Pantry.Types" "pantry-0.10.0-2c6hPrHSjDQ3SnTMTDZv1w-internal" 'False) (C1 ('MetaCons "ResolvedPath" 'PrefixI 'True) (S1 ('MetaSel ('Just "resolvedRelative") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RelFilePath) :*: S1 ('MetaSel ('Just "resolvedAbsolute") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Path Abs t)))) |
data Unresolved a #
Instances
Applicative Unresolved | |
Defined in Pantry.Types Methods pure :: a -> Unresolved a # (<*>) :: Unresolved (a -> b) -> Unresolved a -> Unresolved b # liftA2 :: (a -> b -> c) -> Unresolved a -> Unresolved b -> Unresolved c # (*>) :: Unresolved a -> Unresolved b -> Unresolved b # (<*) :: Unresolved a -> Unresolved b -> Unresolved a # | |
Functor Unresolved | |
Defined in Pantry.Types Methods fmap :: (a -> b) -> Unresolved a -> Unresolved b # (<$) :: a -> Unresolved b -> Unresolved a # | |
FromJSON (WithJSONWarnings (Unresolved (NonEmpty RawPackageLocation))) | |
Defined in Pantry.Types Methods parseJSON :: Value -> Parser (WithJSONWarnings (Unresolved (NonEmpty RawPackageLocation))) # parseJSONList :: Value -> Parser [WithJSONWarnings (Unresolved (NonEmpty RawPackageLocation))] # omittedField :: Maybe (WithJSONWarnings (Unresolved (NonEmpty RawPackageLocation))) # | |
FromJSON (WithJSONWarnings (Unresolved (NonEmpty RawPackageLocationImmutable))) | |
Defined in Pantry.Types Methods parseJSON :: Value -> Parser (WithJSONWarnings (Unresolved (NonEmpty RawPackageLocationImmutable))) # parseJSONList :: Value -> Parser [WithJSONWarnings (Unresolved (NonEmpty RawPackageLocationImmutable))] # omittedField :: Maybe (WithJSONWarnings (Unresolved (NonEmpty RawPackageLocationImmutable))) # | |
FromJSON (WithJSONWarnings (Unresolved GlobalHintsLocation)) | |
Defined in Pantry.Types Methods parseJSON :: Value -> Parser (WithJSONWarnings (Unresolved GlobalHintsLocation)) # parseJSONList :: Value -> Parser [WithJSONWarnings (Unresolved GlobalHintsLocation)] # omittedField :: Maybe (WithJSONWarnings (Unresolved GlobalHintsLocation)) # | |
FromJSON (WithJSONWarnings (Unresolved PackageLocationImmutable)) | |
Defined in Pantry.Types | |
FromJSON (WithJSONWarnings (Unresolved RawSnapshotLayer)) | |
Defined in Pantry.Types Methods parseJSON :: Value -> Parser (WithJSONWarnings (Unresolved RawSnapshotLayer)) # parseJSONList :: Value -> Parser [WithJSONWarnings (Unresolved RawSnapshotLayer)] # omittedField :: Maybe (WithJSONWarnings (Unresolved RawSnapshotLayer)) # | |
FromJSON (WithJSONWarnings (Unresolved RawSnapshotLocation)) | |
Defined in Pantry.Types Methods parseJSON :: Value -> Parser (WithJSONWarnings (Unresolved RawSnapshotLocation)) # parseJSONList :: Value -> Parser [WithJSONWarnings (Unresolved RawSnapshotLocation)] # omittedField :: Maybe (WithJSONWarnings (Unresolved RawSnapshotLocation)) # | |
FromJSON (WithJSONWarnings (Unresolved SnapshotLocation)) | |
Defined in Pantry.Types Methods parseJSON :: Value -> Parser (WithJSONWarnings (Unresolved SnapshotLocation)) # parseJSONList :: Value -> Parser [WithJSONWarnings (Unresolved SnapshotLocation)] # omittedField :: Maybe (WithJSONWarnings (Unresolved SnapshotLocation)) # | |
FromJSON (WithJSONWarnings (Unresolved Locked)) Source # | |
Defined in Stack.Lock Methods parseJSON :: Value -> Parser (WithJSONWarnings (Unresolved Locked)) # parseJSONList :: Value -> Parser [WithJSONWarnings (Unresolved Locked)] # omittedField :: Maybe (WithJSONWarnings (Unresolved Locked)) # | |
(FromJSON (WithJSONWarnings (Unresolved a)), FromJSON (WithJSONWarnings (Unresolved b))) => FromJSON (WithJSONWarnings (Unresolved (LockedLocation a b))) Source # | |
Defined in Stack.Lock Methods parseJSON :: Value -> Parser (WithJSONWarnings (Unresolved (LockedLocation a b))) # parseJSONList :: Value -> Parser [WithJSONWarnings (Unresolved (LockedLocation a b))] # omittedField :: Maybe (WithJSONWarnings (Unresolved (LockedLocation a b))) # | |
FromJSON (Unresolved AbstractSnapshot) Source # | |
Defined in Stack.Types.Snapshot Methods parseJSON :: Value -> Parser (Unresolved AbstractSnapshot) # parseJSONList :: Value -> Parser [Unresolved AbstractSnapshot] # |
data PrintWarnings #
Constructors
YesPrintWarnings | |
NoPrintWarnings |
data PantryConfig #
Instances
Data Revision | |||||
Defined in Pantry.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Revision -> c Revision # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Revision # toConstr :: Revision -> Constr # dataTypeOf :: Revision -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Revision) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Revision) # gmapT :: (forall b. Data b => b -> b) -> Revision -> Revision # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Revision -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Revision -> r # gmapQ :: (forall d. Data d => d -> u) -> Revision -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Revision -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Revision -> m Revision # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Revision -> m Revision # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Revision -> m Revision # | |||||
Generic Revision | |||||
Defined in Pantry.Types Associated Types
| |||||
Show Revision | |||||
NFData Revision | |||||
Defined in Pantry.Types | |||||
Eq Revision | |||||
Ord Revision | |||||
Defined in Pantry.Types | |||||
Hashable Revision | |||||
Defined in Pantry.Types | |||||
PersistField Revision | |||||
Defined in Pantry.Types Methods toPersistValue :: Revision -> PersistValue # | |||||
PersistFieldSql Revision | |||||
Display Revision | |||||
Defined in Pantry.Types | |||||
SymbolToField "revision" HackageCabal Revision | |||||
Defined in Pantry.Storage Methods symbolToField :: EntityField HackageCabal Revision # | |||||
type Rep Revision | |||||
Defined in Pantry.Types |
snapshotLocation :: HasPantryConfig env => SnapName -> RIO env RawSnapshotLocation #
resolvePaths :: MonadIO m => Maybe (Path Abs Dir) -> Unresolved a -> m a #
mkSafeFilePath :: Text -> Maybe SafeFilePath #
parsePackageName :: String -> Maybe PackageName #
parsePackageNameThrowing :: MonadThrow m => String -> m PackageName #
parseVersionThrowing :: MonadThrow m => String -> m Version #
parseFlagName :: String -> Maybe FlagName #
packageNameString :: PackageName -> String #
versionString :: Version -> String #
flagNameString :: FlagName -> String #
moduleNameString :: ModuleName -> String #
toCabalStringMap :: Map a v -> Map (CabalString a) v #
unCabalStringMap :: Map (CabalString a) v -> Map a v #
parseSnapName :: MonadThrow m => Text -> m SnapName #
warnMissingCabalFile :: HasLogFunc env => RawPackageLocationImmutable -> RIO env () #
data RequireHackageIndex #
Require that the Hackage index is populated.
Since: pantry-0.1.0.0
Constructors
YesRequireHackageIndex | If there is nothing in the Hackage index, then perform an update |
NoRequireHackageIndex | Do not perform an update |
Instances
Show RequireHackageIndex | |
Defined in Pantry.Hackage Methods showsPrec :: Int -> RequireHackageIndex -> ShowS # show :: RequireHackageIndex -> String # showList :: [RequireHackageIndex] -> ShowS # |
data UsePreferredVersions #
Should we pay attention to Hackage's preferred versions?
Since: pantry-0.1.0.0
Constructors
UsePreferredVersions | |
IgnorePreferredVersions |
Instances
Show UsePreferredVersions | |
Defined in Pantry.Hackage Methods showsPrec :: Int -> UsePreferredVersions -> ShowS # show :: UsePreferredVersions -> String # showList :: [UsePreferredVersions] -> ShowS # |
data DidUpdateOccur #
Did an update occur when running updateHackageIndex
?
Since: pantry-0.1.0.0
Constructors
UpdateOccurred | |
NoUpdateOccurred |
hackageIndexTarballL :: HasPantryConfig env => SimpleGetter env (Path Abs File) #
Where does pantry download its 01-index.tar file from Hackage?
Since: pantry-0.1.0.0
Arguments
:: (HasPantryConfig env, HasLogFunc env) | |
=> Maybe Utf8Builder | reason for updating, if any |
-> RIO env DidUpdateOccur |
Download the most recent 01-index.tar file from Hackage and update the database tables.
This function will only perform an update once per PantryConfig
for user
sanity. See the return value to find out if it happened.
Since: pantry-0.1.0.0
getHackageTypoCorrections :: (HasPantryConfig env, HasLogFunc env) => PackageName -> RIO env [PackageName] #
Try to come up with typo corrections for given package identifier using Hackage package names. This can provide more user-friendly information in error messages.
Since: pantry-0.1.0.0
Arguments
:: (HasPantryConfig env, HasLogFunc env) | |
=> RequireHackageIndex | |
-> UsePreferredVersions | |
-> PackageName | package name |
-> RIO env (Map Version (Map Revision BlobKey)) |
Returns the versions of the package available on Hackage.
Since: pantry-0.1.0.0
fetchReposRaw :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => [(Repo, RawPackageMetadata)] -> RIO env () #
Like fetchRepos
, except with RawPackageMetadata
instead of
PackageMetadata
.
Since: pantry-0.5.3
fetchRepos :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => [(Repo, PackageMetadata)] -> RIO env () #
Fetch the given repositories at once and populate the pantry database.
Since: pantry-0.5.3
withRepo :: (HasLogFunc env, HasProcessContext env) => SimpleRepo -> RIO env a -> RIO env a #
Clone the repository (and, in the case of Git and if necessary, fetch the specific commit) and execute the action with the working directory set to the repository root.
Since: pantry-0.1.0.0
Convenient data type that allows you to work with pantry more easily than
using withPantryConfig
or withPantryConfig'
directly. Uses basically sane
settings, like sharing a pantry directory with Stack.
You can use runPantryApp
to use this. A simple example is:
{-# LANGUAGE OverloadedStrings #-} module Main (main) where -- From package Cabal-syntax import Distribution.Types.Version ( mkVersion ) -- From package pantry import Pantry ( CabalFileInfo (..), PackageIdentifierRevision (..), PantryApp , RawPackageLocationImmutable (..), loadPackageRaw, runPantryApp ) -- From package rio import RIO ( RIO, liftIO ) main :: IO () main = runPantryApp myPantryApp myPantryApp :: RIO PantryApp () myPantryApp = loadPackageRaw baseLocation >>= liftIO . print where baseVersion = mkVersion [4, 19, 0, 0] basePkgId = PackageIdentifierRevision "base" baseVersion CFILatest baseLocation = RPLIHackage basePkgId Nothing
Since: pantry-0.1.0.0
Instances
HasPantryConfig PantryApp | |
Defined in Pantry Methods | |
HasLogFunc PantryApp | |
HasProcessContext PantryApp | |
Defined in Pantry Methods | |
HasTerm PantryApp | |
HasStylesUpdate PantryApp | |
Defined in Pantry Methods |
data AddPackagesConfig #
Package settings to be passed to addPackagesToSnapshot
.
Since: pantry-0.1.0.0
Constructors
AddPackagesConfig | |
Fields
|
data CompletedSL #
A completed snapshot location, including the original raw and completed information.
Since: pantry-0.1.0.0
Constructors
CompletedSL !RawSnapshotLocation !SnapshotLocation |
data CompletedPLI #
A completed package location, including the original raw and completed information.
Since: pantry-0.1.0.0
Constructors
CompletedPLI !RawPackageLocationImmutable !PackageLocationImmutable |
data CompletePackageLocation #
Complete package location, plus whether the package has a cabal file. This is relevant to reproducibility, see https://tech.fpcomplete.com/blog/storing-generated-cabal-files
Since: pantry-0.4.0.0
Constructors
CompletePackageLocation | |
Fields |
Arguments
:: HasLogFunc env | |
=> Path Abs Dir | pantry root directory, where the SQLite database and Hackage downloads are kept. |
-> PackageIndexConfig | Package index configuration. You probably want
|
-> HpackExecutable | When converting an hpack |
-> Int | Maximum connection count |
-> CasaRepoPrefix | The casa pull URL e.g. https://casa.stackage.org/v1/pull. |
-> Int | Max casa keys to pull per request. |
-> (SnapName -> RawSnapshotLocation) | The location of snapshot synonyms |
-> (WantedCompiler -> GlobalHintsLocation) | The location of global hints |
-> (PantryConfig -> RIO env a) | What to do with the config |
-> RIO env a |
Create a new PantryConfig
with the given settings. For a version where
Hpack's approach to overwriting Cabal files is configurable and the use of
Casa (content-addressable storage archive) is optional, see
withPantryConfig'
.
For something easier to use in simple cases, see runPantryApp
.
Since: pantry-0.1.0.0
Arguments
:: HasLogFunc env | |
=> Path Abs Dir | pantry root directory, where the SQLite database and Hackage downloads are kept. |
-> PackageIndexConfig | Package index configuration. You probably want
|
-> HpackExecutable | When converting an hpack |
-> Force | Should Hpack force the overwriting of a Cabal file that has been modified manually? Since: pantry-0.10.0 |
-> Int | Maximum connection count |
-> Maybe (CasaRepoPrefix, Int) | Optionally, the Casa pull URL e.g. |
-> (SnapName -> RawSnapshotLocation) | The location of snapshot synonyms |
-> (WantedCompiler -> GlobalHintsLocation) | The location of global hints |
-> (PantryConfig -> RIO env a) | What to do with the config |
-> RIO env a |
Create a new PantryConfig
with the given settings.
For something easier to use in simple cases, see runPantryApp
.
Since: pantry-0.8.3
defaultCasaRepoPrefix :: CasaRepoPrefix #
Default pull URL for Casa.
Since: pantry-0.1.1.1
defaultCasaMaxPerRequest :: Int #
Default max keys to pull per request.
Since: pantry-0.1.1.1
defaultPackageIndexConfig :: PackageIndexConfig #
Default PackageIndexConfig
value using the official Hackage server.
Since: pantry-0.6.0
defaultDownloadPrefix :: Text #
The download prefix for the official Hackage server.
Since: pantry-0.6.0
Arguments
:: (HasPantryConfig env, HasLogFunc env) | |
=> RequireHackageIndex | |
-> PackageName | package name |
-> UsePreferredVersions | |
-> RIO env (Maybe PackageIdentifierRevision) |
Returns the latest version of the given package available from Hackage.
Since: pantry-0.1.0.0
Arguments
:: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) | |
=> RequireHackageIndex | |
-> PackageName | package name |
-> UsePreferredVersions | |
-> RIO env (Maybe PackageLocationImmutable) |
Returns location of the latest version of the given package available from Hackage.
Since: pantry-0.1.0.0
Arguments
:: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) | |
=> RequireHackageIndex | |
-> PackageName | package name |
-> Version | |
-> RIO env (Maybe (Revision, BlobKey, TreeKey)) |
Returns the latest revision of the given package version available from Hackage.
Since: pantry-0.1.0.0
fetchPackages :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env, Foldable f) => f PackageLocationImmutable -> RIO env () #
Download all of the packages provided into the local cache without performing any unpacking. Can be useful for build tools wanting to prefetch or provide an offline mode.
Since: pantry-0.1.0.0
Arguments
:: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) | |
=> Path Abs Dir | unpack directory |
-> RawPackageLocationImmutable | |
-> RIO env () |
Unpack a given RawPackageLocationImmutable
into the given directory. Does
not generate any extra subdirectories.
Since: pantry-0.1.0.0
Arguments
:: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) | |
=> Path Abs Dir | unpack directory |
-> PackageLocationImmutable | |
-> RIO env () |
Unpack a given PackageLocationImmutable
into the given directory. Does
not generate any extra subdirectories.
Since: pantry-0.1.0.0
loadCabalFileImmutable :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => PackageLocationImmutable -> RIO env GenericPackageDescription #
Load the cabal file for the given PackageLocationImmutable
.
This function ignores all warnings.
Since: pantry-0.1.0.0
loadCabalFileRawImmutable :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => RawPackageLocationImmutable -> RIO env GenericPackageDescription #
Load the cabal file for the given RawPackageLocationImmutable
.
This function ignores all warnings.
Note that, for now, this will not allow support for hpack files in these
package locations. Instead, all PackageLocationImmutable
s will require a
.cabal file. This may be relaxed in the future.
Since: pantry-0.1.0.0
Arguments
:: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) | |
=> Maybe Text | The program name used by Hpack (the library), defaults to "hpack". |
-> RawPackageLocation | |
-> RIO env GenericPackageDescription |
Same as loadCabalFileRawImmutable
, but takes a RawPackageLocation
.
Never prints warnings, see loadCabalFilePath
for that.
Since: pantry-0.8.0
Arguments
:: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) | |
=> Maybe Text | The program name used by Hpack (the library), defaults to "hpack". |
-> PackageLocation | |
-> RIO env GenericPackageDescription |
Same as loadCabalFileImmutable
, but takes a PackageLocation
. Never
prints warnings, see loadCabalFilePath
for that.
Since: pantry-0.8.0
Arguments
:: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) | |
=> Maybe Text | The program name used by Hpack (the library), defaults to "hpack". |
-> Path Abs Dir | project directory, with a cabal file or hpack file |
-> RIO env (PrintWarnings -> IO GenericPackageDescription, PackageName, Path Abs File) |
Parse the Cabal file for the package inside the given directory. Performs various sanity checks, such as the file name being correct and having only a single Cabal file.
Since: pantry-0.8.0
Arguments
:: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) | |
=> Maybe Text | The program name used by Hpack (the library), defaults to "hpack". |
-> Path Abs Dir | package directory |
-> RIO env (PackageName, Path Abs File) |
Get the file name for the Cabal file in the given directory.
If no Cabal file is present, or more than one is present, an exception is
thrown via throwM
.
If the directory contains a file named package.yaml, Hpack is used to generate a Cabal file from it.
Since: pantry-0.8.0
gpdPackageIdentifier :: GenericPackageDescription -> PackageIdentifier #
Get the PackageIdentifier
from a GenericPackageDescription
.
Since: pantry-0.1.0.0
gpdPackageName :: GenericPackageDescription -> PackageName #
Get the PackageName
from a GenericPackageDescription
.
Since: pantry-0.1.0.0
gpdVersion :: GenericPackageDescription -> Version #
Get the Version
from a GenericPackageDescription
.
Since: pantry-0.1.0.0
loadPackage :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => PackageLocationImmutable -> RIO env Package #
Load a Package
from a PackageLocationImmutable
.
Since: pantry-0.1.0.0
loadPackageRaw :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => RawPackageLocationImmutable -> RIO env Package #
Load a Package
from a RawPackageLocationImmutable
.
Load the package either from the local DB, Casa, or as a last resort, the third party (hackage, archive or repo).
Since: pantry-0.1.0.0
tryLoadPackageRawViaCasa :: (HasLogFunc env, HasPantryConfig env, HasProcessContext env) => RawPackageLocationImmutable -> TreeKey -> RIO env (Maybe Package) #
Maybe load the package from Casa.
completePackageLocation :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => RawPackageLocationImmutable -> RIO env CompletePackageLocation #
Fill in optional fields in a PackageLocationImmutable
for more reproducible builds.
Since: pantry-0.1.0.0
completeSnapshotLocation :: (HasPantryConfig env, HasLogFunc env) => RawSnapshotLocation -> RIO env SnapshotLocation #
Add in hashes to make a SnapshotLocation
reproducible.
Since: pantry-0.1.0.0
Arguments
:: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) | |
=> SnapshotLocation | |
-> Map RawSnapshotLocation SnapshotLocation | Cached snapshot locations from lock file |
-> Map RawPackageLocationImmutable PackageLocationImmutable | Cached locations from lock file |
-> RIO env (Snapshot, [CompletedSL], [CompletedPLI]) |
Parse a Snapshot
(all layers) from a SnapshotLocation
noting any
incomplete package locations. Debug output will include the raw snapshot
layer.
Since: pantry-0.1.0.0
Arguments
:: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) | |
=> Bool | Debug output includes the raw snapshot layer |
-> SnapshotLocation | |
-> Map RawSnapshotLocation SnapshotLocation | Cached snapshot locations from lock file |
-> Map RawPackageLocationImmutable PackageLocationImmutable | Cached locations from lock file |
-> RIO env (Snapshot, [CompletedSL], [CompletedPLI]) |
As for loadAndCompleteSnapshot
but allows toggling of the debug output of
the raw snapshot layer.
Since: pantry-0.5.7
Arguments
:: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) | |
=> RawSnapshotLocation | |
-> Map RawSnapshotLocation SnapshotLocation | Cached snapshot locations from lock file |
-> Map RawPackageLocationImmutable PackageLocationImmutable | Cached locations from lock file |
-> RIO env (Snapshot, [CompletedSL], [CompletedPLI]) |
Parse a Snapshot
(all layers) from a RawSnapshotLocation
completing
any incomplete package locations. Debug output will include the raw snapshot
layer.
Since: pantry-0.1.0.0
Arguments
:: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) | |
=> Bool | Debug output includes the raw snapshot layer |
-> RawSnapshotLocation | |
-> Map RawSnapshotLocation SnapshotLocation | Cached snapshot locations from lock file |
-> Map RawPackageLocationImmutable PackageLocationImmutable | Cached locations from lock file |
-> RIO env (Snapshot, [CompletedSL], [CompletedPLI]) |
As for loadAndCompleteSnapshotRaw
but allows toggling of the debug output
of the raw snapshot layer.
Since: pantry-0.5.7
Arguments
:: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) | |
=> Utf8Builder | Text description of where these new packages are coming from, for error messages only |
-> [RawPackageLocationImmutable] | new packages |
-> AddPackagesConfig | |
-> Map PackageName RawSnapshotPackage | packages from parent |
-> RIO env (Map PackageName RawSnapshotPackage, AddPackagesConfig) |
Add more packages to a snapshot
Note that any settings on a parent flag which is being replaced will be
ignored. For example, if package foo
is in the parent and has flag bar
set, and foo
also appears in new packages, then bar
will no longer be
set.
Returns any of the AddPackagesConfig
values not used.
Since: pantry-0.1.0.0
loadRawSnapshotLayer :: (HasPantryConfig env, HasLogFunc env) => RawSnapshotLocation -> RIO env (Either WantedCompiler (RawSnapshotLayer, CompletedSL)) #
Parse a SnapshotLayer
value from a SnapshotLocation
.
Returns a Left
value if provided an SLCompiler
constructor. Otherwise,
returns a Right
value providing both the Snapshot
and a hash of the input
configuration file.
Since: pantry-0.1.0.0
loadSnapshotLayer :: (HasPantryConfig env, HasLogFunc env) => SnapshotLocation -> RIO env (Either WantedCompiler RawSnapshotLayer) #
Parse a SnapshotLayer
value from a SnapshotLocation
.
Returns a Left
value if provided an SLCompiler
constructor. Otherwise,
returns a Right
value providing both the Snapshot
and a hash of the input
configuration file.
Since: pantry-0.1.0.0
getPackageLocationName :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => RawPackageLocationImmutable -> RIO env PackageName #
Get the PackageName
of the package at the given location.
Since: pantry-0.1.0.0
packageLocationIdent :: PackageLocationImmutable -> PackageIdentifier #
Get the PackageIdentifier
of the package at the given location.
Since: pantry-0.1.0.0
packageLocationVersion :: PackageLocationImmutable -> Version #
Get version of the package at the given location.
Since: pantry-0.1.0.0
getRawPackageLocationIdent :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => RawPackageLocationImmutable -> RIO env PackageIdentifier #
Get the PackageIdentifier
of the package at the given location.
Since: pantry-0.1.0.0
getRawPackageLocationTreeKey :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => RawPackageLocationImmutable -> RIO env TreeKey #
Get the TreeKey
of the package at the given location.
Since: pantry-0.1.0.0
getPackageLocationTreeKey :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => PackageLocationImmutable -> RIO env TreeKey #
Get the TreeKey
of the package at the given location.
Since: pantry-0.1.0.0
hpackExecutableL :: Lens' PantryConfig HpackExecutable #
Lens to view or modify the HpackExecutable
of a PantryConfig
.
Since: pantry-0.1.0.0
hpackForceL :: Lens' PantryConfig Force #
Lens to view or modify the Force
of a PantryConfig
.
Since: pantry-0.10.0
runPantryApp :: MonadIO m => RIO PantryApp a -> m a #
Run some code against pantry using basic sane settings.
For testing, see runPantryAppClean
.
Since: pantry-0.1.0.0
runPantryAppWith :: MonadIO m => Int -> CasaRepoPrefix -> Int -> RIO PantryApp a -> m a #
Run some code against pantry using basic sane settings.
For testing, see runPantryAppClean
.
Since: pantry-0.1.1.1
runPantryAppClean :: MonadIO m => RIO PantryApp a -> m a #
Like runPantryApp
, but uses an empty pantry directory instead of sharing
with Stack. Useful for testing.
Since: pantry-0.1.0.0
loadGlobalHints :: (HasTerm env, HasPantryConfig env) => WantedCompiler -> RIO env (Maybe (Map PackageName Version)) #
Load the global hints.
Since: pantry-9.4.0
partitionReplacedDependencies #
Arguments
:: Ord id | |
=> Map PackageName a | global packages |
-> (a -> PackageName) | package name getter |
-> (a -> id) | returns unique package id used for dependency pruning |
-> (a -> [id]) | returns unique package ids of direct package dependencies |
-> Set PackageName | overrides which global dependencies should get pruned |
-> (Map PackageName [PackageName], Map PackageName a) |
Partition a map of global packages with its versions into a Set of replaced packages and its dependencies and a map of remaining (untouched) packages.
Since: pantry-0.1.0.0
withSnapshotCache :: (HasPantryConfig env, HasLogFunc env) => SnapshotCacheHash -> RIO env (Map PackageName (Set ModuleName)) -> ((ModuleName -> RIO env [PackageName]) -> RIO env a) -> RIO env a #
Use a snapshot cache, which caches which modules are in which packages in a given snapshot. This is mostly intended for usage by Stack.
Since: pantry-0.1.0.0
An absolute path.
Instances
Data Abs | |
Defined in Path.Posix Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Abs -> c Abs # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Abs # dataTypeOf :: Abs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Abs) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Abs) # gmapT :: (forall b. Data b => b -> b) -> Abs -> Abs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Abs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Abs -> r # gmapQ :: (forall d. Data d => d -> u) -> Abs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Abs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Abs -> m Abs # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Abs -> m Abs # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Abs -> m Abs # | |
NFData (PrecompiledCache Abs) Source # | |
Defined in Stack.Types.Build Methods rnf :: PrecompiledCache Abs -> () # | |
FromJSON (Path Abs Dir) | |
FromJSON (Path Abs File) | |
FromJSONKey (Path Abs Dir) | |
Defined in Path.Posix Methods | |
FromJSONKey (Path Abs File) | |
Defined in Path.Posix Methods |
A relative path; one without a root. Note that a ..
path component to
represent the parent directory is not allowed by this library.
Instances
Data Rel | |
Defined in Path.Posix Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Rel -> c Rel # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Rel # dataTypeOf :: Rel -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Rel) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Rel) # gmapT :: (forall b. Data b => b -> b) -> Rel -> Rel # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Rel -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Rel -> r # gmapQ :: (forall d. Data d => d -> u) -> Rel -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Rel -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Rel -> m Rel # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Rel -> m Rel # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Rel -> m Rel # | |
NFData (PrecompiledCache Rel) Source # | |
Defined in Stack.Types.Build Methods rnf :: PrecompiledCache Rel -> () # | |
FromJSON (Path Rel Dir) | |
FromJSON (Path Rel File) | |
FromJSONKey (Path Rel Dir) | |
Defined in Path.Posix Methods | |
FromJSONKey (Path Rel File) | |
Defined in Path.Posix Methods |
A directory path.
Instances
Data Dir | |
Defined in Path.Posix Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Dir -> c Dir # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Dir # dataTypeOf :: Dir -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Dir) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Dir) # gmapT :: (forall b. Data b => b -> b) -> Dir -> Dir # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Dir -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Dir -> r # gmapQ :: (forall d. Data d => d -> u) -> Dir -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Dir -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Dir -> m Dir # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Dir -> m Dir # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Dir -> m Dir # | |
FromJSON (SomeBase Dir) | |
AnyPath (SomeBase Dir) | Since: path-io-1.8.0 |
Defined in Path.IO Methods canonicalizePath :: MonadIO m => SomeBase Dir -> m (AbsPath (SomeBase Dir)) # makeAbsolute :: MonadIO m => SomeBase Dir -> m (AbsPath (SomeBase Dir)) # makeRelative :: MonadThrow m => Path Abs Dir -> SomeBase Dir -> m (RelPath (SomeBase Dir)) # makeRelativeToCurrentDir :: MonadIO m => SomeBase Dir -> m (RelPath (SomeBase Dir)) # | |
Pretty (SomeBase Dir) | |
FromJSON (Path Abs Dir) | |
FromJSON (Path Rel Dir) | |
FromJSONKey (Path Abs Dir) | |
Defined in Path.Posix Methods | |
FromJSONKey (Path Rel Dir) | |
Defined in Path.Posix Methods | |
AnyPath (Path b Dir) | |
Defined in Path.IO Methods canonicalizePath :: MonadIO m => Path b Dir -> m (AbsPath (Path b Dir)) # makeAbsolute :: MonadIO m => Path b Dir -> m (AbsPath (Path b Dir)) # makeRelative :: MonadThrow m => Path Abs Dir -> Path b Dir -> m (RelPath (Path b Dir)) # makeRelativeToCurrentDir :: MonadIO m => Path b Dir -> m (RelPath (Path b Dir)) # | |
Pretty (Path b Dir) | |
type AbsPath (SomeBase Dir) | |
type RelPath (SomeBase Dir) | |
type AbsPath (Path b Dir) | |
type RelPath (Path b Dir) | |
ensureFileDurable :: MonadIO m => FilePath -> m () #
After a file is closed, this function opens it again and executes fsync()
internally on both the file and the directory that contains it. Note that this function
is intended to work around the non-durability of existing file APIs, as opposed to
being necessary for the API functions provided in this module.
The effectiveness of calling this function is debatable, as it relies on internal implementation details at the Kernel level that might change. We argue that, despite this fact, calling this function may bring benefits in terms of durability.
This function does not provide the same guarantee as if you would open and modify a
file using withBinaryFileDurable
or writeBinaryFileDurable
, since they ensure that
the fsync()
is called before the file is closed, so if possible use those instead.
Cross-Platform support
This function is a noop on Windows platforms.
Since: unliftio-0.2.12
writeBinaryFileDurable :: MonadIO m => FilePath -> ByteString -> m () #
Similar to writeBinaryFile
, but it also ensures that changes executed to the file
are guaranteed to be durable. It internally uses fsync()
and makes sure it
synchronizes the file on disk.
Cross-Platform support
This function behaves the same as writeBinaryFile
on Windows platforms.
Since: unliftio-0.2.12
writeBinaryFileDurableAtomic :: MonadIO m => FilePath -> ByteString -> m () #
Similar to writeBinaryFile
, but it also guarantes that changes executed to the file
are durable, also, in case of failure, the modified file is never going to get
corrupted. It internally uses fsync()
and makes sure it synchronizes the file on
disk.
Cross-Platform support
This function behaves the same as writeBinaryFile
on Windows platforms.
Since: unliftio-0.2.12
withBinaryFileDurable :: MonadUnliftIO m => FilePath -> IOMode -> (Handle -> m r) -> m r #
Opens a file with the following guarantees:
- It successfully closes the file in case of an asynchronous exception
- It reliably saves the file in the correct directory; including edge case situations like a different device being mounted to the current directory, or the current directory being renamed to some other name while the file is being used.
- It ensures durability by executing an
fsync()
call before closing the file handle
Cross-Platform support
This function behaves the same as withBinaryFile
on Windows platforms.
Since: unliftio-0.2.12
withBinaryFileDurableAtomic :: MonadUnliftIO m => FilePath -> IOMode -> (Handle -> m r) -> m r #
Opens a file with the following guarantees:
- It successfully closes the file in case of an asynchronous exception
- It reliably saves the file in the correct directory; including edge case situations like a different device being mounted to the current directory, or the current directory being renamed to some other name while the file is being used.
- It ensures durability by executing an
fsync()
call before closing the file handle - It keeps all changes in a temporary file, and after it is closed it atomically moves the temporary file to the original filepath, in case of catastrophic failure, the original file stays unaffected.
If you do not need durability but only atomicity, use withBinaryFileAtomic
instead,
which is faster as it does not perform fsync()
.
Important - Make sure not to close the Handle
, it will be closed for you,
otherwise it will result in invalid argument (Bad file descriptor)
exception.
Performance Considerations
When using a writable but non-truncating IOMode
(i.e. ReadWriteMode
and
AppendMode
), this function performs a copy operation of the specified input file to
guarantee the original file is intact in case of a catastrophic failure (no partial
writes). This approach may be prohibitive in scenarios where the input file is expected
to be large in size.
Cross-Platform support
This function behaves the same as withBinaryFile
on Windows platforms.
Since: unliftio-0.2.12
withBinaryFileAtomic :: MonadUnliftIO m => FilePath -> IOMode -> (Handle -> m r) -> m r #
Perform an action on a new or existing file at the destination file path. If previously the file existed at the supplied file path then:
- in case of
WriteMode
it will be overwritten - upon
ReadWriteMode
orAppendMode
files contents will be copied over into a temporary file, thus making sure no corruption can happen to an existing file upon any failures, even catastrophic one, yet its contents are availble for modification. - There is nothing atomic about
ReadMode
, so no special treatment there.
It is similar to withBinaryFileDurableAtomic
, but without the durability part. It
means that all modification can still disappear after it has been succesfully written
due to some extreme event like an abrupt power loss, but the contents will not be
corrupted in case when the file write did not end successfully.
The same performance caveats apply as for withBinaryFileDurableAtomic
due to making a
copy of the content of existing files during non-truncating writes.
Important - Do not close the handle, otherwise it will result in invalid argument
(Bad file descriptor)
exception
Note - on Linux operating system and only with supported file systems an anonymous
temporary file will be used while working on the file (see O_TMPFILE
in man
openat
). In case when such feature is not available or not supported a temporary file
".target-file-nameXXX.ext.tmp", where XXX is some random number, will be created
alongside the target file in the same directory
Since: unliftio-0.2.12
writeBinaryFile :: MonadIO m => FilePath -> ByteString -> m () #
Lifted version of writeFile
Since: unliftio-0.2.12
Re-exports from the rio-pretty print package
class HasStylesUpdate env where #
Environment values with a styles update.
Since: rio-prettyprint-0.1.0.0
Methods
stylesUpdateL :: Lens' env StylesUpdate #
Instances
HasStylesUpdate PantryApp | |
Defined in Pantry Methods | |
HasStylesUpdate SimplePrettyApp | |
Defined in RIO.PrettyPrint.Simple Methods | |
HasStylesUpdate StylesUpdate | |
Defined in RIO.PrettyPrint.StylesUpdate Methods | |
HasStylesUpdate EnvConfigPathInfo Source # | |
Defined in Stack.Path Methods | |
HasStylesUpdate Ctx Source # | |
Defined in Stack.Types.Build.ConstructPlan Methods | |
HasStylesUpdate BuildConfig Source # | |
Defined in Stack.Types.BuildConfig Methods | |
HasStylesUpdate Config Source # | |
Defined in Stack.Types.Config Methods | |
HasStylesUpdate DotConfig Source # | |
Defined in Stack.Types.DotConfig Methods | |
HasStylesUpdate EnvConfig Source # | |
Defined in Stack.Types.EnvConfig Methods | |
HasStylesUpdate GetPackageFileContext Source # | |
Defined in Stack.Types.PackageFile Methods | |
HasStylesUpdate Runner Source # | |
Defined in Stack.Types.Runner Methods |
class (HasLogFunc env, HasStylesUpdate env) => HasTerm env where #
Instances
HasTerm PantryApp | |
HasTerm SimplePrettyApp | |
Defined in RIO.PrettyPrint.Simple | |
HasTerm EnvConfigPathInfo Source # | |
Defined in Stack.Path | |
HasTerm Ctx Source # | |
HasTerm BuildConfig Source # | |
Defined in Stack.Types.BuildConfig | |
HasTerm Config Source # | |
HasTerm DotConfig Source # | |
HasTerm EnvConfig Source # | |
HasTerm GetPackageFileContext Source # | |
Defined in Stack.Types.PackageFile Methods | |
HasTerm Runner Source # | |
Minimal complete definition
Nothing
Instances
Pretty ModuleName | |
Defined in Text.PrettyPrint.Leijen.Extended Methods pretty :: ModuleName -> StyleDoc # | |
Pretty Arch | |
Defined in Text.PrettyPrint.Leijen.Extended | |
Pretty OS | |
Defined in Text.PrettyPrint.Leijen.Extended | |
Pretty ArchiveLocation | |
Defined in Pantry.Types Methods pretty :: ArchiveLocation -> StyleDoc # | |
Pretty GlobalHintsLocation | |
Defined in Pantry.Types Methods pretty :: GlobalHintsLocation -> StyleDoc # | |
Pretty PantryException | |
Defined in Pantry.Types Methods pretty :: PantryException -> StyleDoc # | |
Pretty RawPackageLocationImmutable | |
Defined in Pantry.Types Methods | |
Pretty RawSnapshotLocation | |
Defined in Pantry.Types Methods pretty :: RawSnapshotLocation -> StyleDoc # | |
Pretty PrettyException | |
Defined in RIO.PrettyPrint.PrettyException Methods pretty :: PrettyException -> StyleDoc # | |
Pretty StyleDoc | |
Defined in Text.PrettyPrint.Leijen.Extended | |
Pretty GhciPrettyException Source # | |
Defined in Stack.Ghci Methods pretty :: GhciPrettyException -> StyleDoc # | |
Pretty PrettyRawSnapshotLocation Source # | |
Defined in Stack.Prelude Methods | |
Pretty BuildPrettyException Source # | |
Defined in Stack.Types.Build.Exception Methods pretty :: BuildPrettyException -> StyleDoc # | |
Pretty ConfigPrettyException Source # | |
Defined in Stack.Types.Config.Exception Methods pretty :: ConfigPrettyException -> StyleDoc # | |
Pretty StoragePrettyException Source # | |
Defined in Stack.Types.Storage Methods | |
Pretty (SomeBase Dir) | |
Pretty (SomeBase File) | |
Pretty (Path b Dir) | |
Pretty (Path b File) | |
data PrettyException #
Type representing pretty exceptions.
Since: rio-prettyprint-0.1.4.0
Constructors
(Exception e, Pretty e) => PrettyException e |
Instances
Exception PrettyException | |
Defined in RIO.PrettyPrint.PrettyException Methods toException :: PrettyException -> SomeException # | |
Show PrettyException | |
Defined in RIO.PrettyPrint.PrettyException Methods showsPrec :: Int -> PrettyException -> ShowS # show :: PrettyException -> String # showList :: [PrettyException] -> ShowS # | |
Pretty PrettyException | |
Defined in RIO.PrettyPrint.PrettyException Methods pretty :: PrettyException -> StyleDoc # |
newtype PrettyRawSnapshotLocation Source #
Constructors
PrettyRawSnapshotLocation RawSnapshotLocation |
Instances
Pretty PrettyRawSnapshotLocation Source # | |
Defined in Stack.Prelude Methods |
A document annotated by a style.
Type representing styles of output.
Constructors
Error | Intended to be used sparingly, not to style entire long messages. For
example, to style the |
Warning | Intended to be used sparingly, not to style entire long messages. For
example, to style the |
Info | Intended to be used sparingly, not to style entire long messages. For
example, to style the |
Debug | Intended to be used sparingly, not to style entire long messages. For
example, to style the |
OtherLevel | Intended to be used sparingly, not to style entire long messages. For
example, to style the |
Good | Style in a way to emphasize that it is a particularly good thing. |
Shell | Style as a shell command, i.e. when suggesting something to the user that should be typed in directly as written. |
File | Style as a filename. See |
Url | Style as a URL. |
Dir | Style as a directory name. See |
Recommendation | Style used to highlight part of a recommended course of action. |
Current | Style in a way that emphasizes that it is related to a current thing. For example, to report the current package that is being processed when outputting the name of it. |
Target | Style used the highlight the target of a course of action. |
Module | Style as a module name. |
PkgComponent | Style used to highlight the named component of a package. |
Secondary | Style for secondary content. For example, to style timestamps. |
Highlight | Intended to be used sparingly, not to style entire long messages. For
example, to style the duration in a |
type StyleSpec = (Text, [SGR]) #
A style specification, pairing its 'key' with the corresponding list of
SGR
codes.
newtype StylesUpdate #
Updates to Styles
Constructors
StylesUpdate | |
Fields
|
Instances
FromJSON StylesUpdate | |
Defined in RIO.PrettyPrint.StylesUpdate | |
Monoid StylesUpdate | |
Defined in RIO.PrettyPrint.StylesUpdate Methods mempty :: StylesUpdate # mappend :: StylesUpdate -> StylesUpdate -> StylesUpdate # mconcat :: [StylesUpdate] -> StylesUpdate # | |
Semigroup StylesUpdate | The first styles update overrides the second one. |
Defined in RIO.PrettyPrint.StylesUpdate Methods (<>) :: StylesUpdate -> StylesUpdate -> StylesUpdate # sconcat :: NonEmpty StylesUpdate -> StylesUpdate # stimes :: Integral b => b -> StylesUpdate -> StylesUpdate # | |
Show StylesUpdate | |
Defined in RIO.PrettyPrint.StylesUpdate Methods showsPrec :: Int -> StylesUpdate -> ShowS # show :: StylesUpdate -> String # showList :: [StylesUpdate] -> ShowS # | |
Eq StylesUpdate | |
Defined in RIO.PrettyPrint.StylesUpdate | |
HasStylesUpdate StylesUpdate | |
Defined in RIO.PrettyPrint.StylesUpdate Methods | |
FromJSON (WithJSONWarnings StylesUpdate) | |
Defined in Data.Aeson.WarningParser Methods parseJSON :: Value -> Parser (WithJSONWarnings StylesUpdate) # parseJSONList :: Value -> Parser [WithJSONWarnings StylesUpdate] # |
(<+>) :: StyleDoc -> StyleDoc -> StyleDoc #
The document (x <+> y)
concatenates document x
and y
with a
(fromString " ")
in between. (infixr 6)
align :: StyleDoc -> StyleDoc #
The document (align x)
renders document x
with the nesting level set to
the current column. It is used for example to implement hang
.
As an example, we will put a document right above another one, regardless of the current nesting level:
x $$ y = align (x <> line <> y)
test = fromString "hi" <+> (fromString "nice" $$ fromString "world")
which will be layed out as:
hi nice world
bulletedList :: [StyleDoc] -> StyleDoc #
Display a bulleted list of StyleDoc
with *
as the bullet point.
debugBracket :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m, MonadUnliftIO m) => StyleDoc -> m a -> m a #
debug message action
brackets any output of the specified action
with
an initial and final message
at log level LevelDebug
. The initial message
is prefixed with the label Start:
. The final message is prefixed with
information about the duration of the action in milliseconds (ms) and, if
an exception is thrown by the action, the exception. For example:
Start: <message> <output of action> Finished in ...ms: <message>
or:
Start: <message> <output of action> Finished with exception in ...ms: <message> Exception thrown: <exception_message>
defaultStyles :: Styles #
Default styles for rio-prettyprint output.
displayWithColor :: (HasTerm env, Pretty a, MonadReader env m, HasCallStack) => a -> m Utf8Builder #
encloseSep :: StyleDoc -> StyleDoc -> StyleDoc -> [StyleDoc] -> StyleDoc #
The document (encloseSep l r sep xs)
concatenates the documents xs
separated by sep
and encloses the resulting document by l
and r
. The
documents are rendered horizontally if that fits the page. Otherwise they are
aligned vertically. All separators are put in front of the elements. For
example, the combinator list
can be defined with encloseSep
:
list xs = encloseSep lbracket rbracket comma xs test = fromString "list" <+> (list (map int [10, 200, 3000]))
Which is layed out with a page width of 20 as:
list [10,200,3000]
But when the page width is 15, it is layed out as:
list [10 ,200 ,3000]
fill :: Int -> StyleDoc -> StyleDoc #
The document (fill i x)
renders document x
. It than appends
(fromString " ")
s until the width is equal to i
. If the width of x
is already larger, nothing is appended. This combinator is quite useful in
practice to output a list of bindings. The following example demonstrates
this.
types = [ ("empty", "Doc a") , ("nest", "Int -> Doc a -> Doc a") , ("linebreak", "Doc a") ] ptype (name, tp) = fill 6 (fromString name) <+> fromString "::" <+> fromString tp test = fromString "let" <+> align (vcat (map ptype types))
Which is layed out as:
let empty :: Doc a nest :: Int -> Doc a -> Doc a linebreak :: Doc a
foldr' :: Foldable t => (a -> b -> b) -> b -> t a -> b #
foldr'
is a variant of foldr
that performs strict reduction from
right to left, i.e. starting with the right-most element. The input
structure must be finite, otherwise foldr'
runs out of space
(diverges).
If you want a strict right fold in constant space, you need a structure
that supports faster than O(n) access to the right-most element, such
as Seq
from the containers
package.
This method does not run in constant space for structures such as lists
that don't support efficient right-to-left iteration and so require
O(n) space to perform right-to-left reduction. Use of this method
with such a structure is a hint that the chosen structure may be a poor
fit for the task at hand. If the order in which the elements are
combined is not important, use foldl'
instead.
Since: base-4.6.0.0
fromPackageId :: IsString a => PackageIdentifier -> a Source #
Convert a package identifier to a value of a string-like type.
fromPackageName :: IsString a => PackageName -> a Source #
Convert a package name to a value of a string-like type.
hang :: Int -> StyleDoc -> StyleDoc #
The hang combinator implements hanging indentation. The document
(hang i x)
renders document x
with a nesting level set to the current
column plus i
. The following example uses hanging indentation for some
text:
test = hang 4 (fillSep (map fromString (words "the hang combinator indents these words !")))
Which lays out on a page with a width of 20 characters as:
the hang combinator indents these words !
The hang
combinator is implemented as:
hang i x = align (nest i x)
hcat :: [StyleDoc] -> StyleDoc #
The document (hcat xs)
concatenates all documents xs
horizontally with
(<>)
.
hsep :: [StyleDoc] -> StyleDoc #
The document (hsep xs)
concatenates all documents xs
horizontally with
(
.<+>
)
indent :: Int -> StyleDoc -> StyleDoc #
The document (indent i x)
indents document x
with i
spaces.
test = indent 4 (fillSep (map fromString (words "the indent combinator indents these words !")))
Which lays out with a page width of 20 as:
the indent combinator indents these words !
The line
document advances to the next line and indents to the current
nesting level. Document line
behaves like (fromString " ")
if the line
break is undone by group
.
logLevelToStyle :: LogLevel -> Style #
Arguments
:: Pretty a | |
=> Maybe Style | Style the items in the list? |
-> Bool | Use a serial comma? |
-> [a] | |
-> [StyleDoc] |
A helper function to yield a narrative list from a list of items, with a
final fullstop. For example, helps produce the output
"apple, ball and cat."
(no serial comma) or "apple, ball, and cat."
(serial comma) from ["apple", "ball", "cat"]
.
Since: rio-prettyprint-0.1.4.0
parens :: StyleDoc -> StyleDoc #
Document (parens x)
encloses document x
in parenthesis, "(" and
")".
parseStylesUpdateFromString :: String -> StylesUpdate #
Parse a string that is a colon-delimited sequence of key=value, where key
is a style name and value
is a semicolon-delimited list of ANSI
SGR
(Select Graphic Rendition) control codes (in decimal). Keys that are not
present in defaultStyles
are ignored. Items in the semicolon-delimited
list that are not recognised as valid control codes are ignored.
prettyDebug :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => StyleDoc -> m () #
prettyDebugL :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => [StyleDoc] -> m () #
prettyError :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => StyleDoc -> m () #
prettyErrorL :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => [StyleDoc] -> m () #
prettyGeneric :: (HasTerm env, HasCallStack, Pretty b, MonadReader env m, MonadIO m) => LogLevel -> b -> m () #
prettyInfo :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => StyleDoc -> m () #
prettyInfoL :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => [StyleDoc] -> m () #
prettyInfoS :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => String -> m () #
prettyNote :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => StyleDoc -> m () #
prettyNoteL :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => [StyleDoc] -> m () #
prettyNoteS :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => String -> m () #
prettyWarn :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => StyleDoc -> m () #
prettyWarnL :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => [StyleDoc] -> m () #
prettyWarnNoIndent :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => StyleDoc -> m () #
prettyWarnS :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => String -> m () #
punctuate :: StyleDoc -> [StyleDoc] -> [StyleDoc] #
(punctuate p xs)
concatenates all documents in xs
with document p
except for the last document.
someText = map fromString ["words", "in", "a", "tuple"] test = parens (align (cat (punctuate comma someText)))
This is layed out on a page width of 20 as:
(words,in,a,tuple)
But when the page width is 15, it is layed out as:
(words, in, a, tuple)
(If you want put the commas in front of their elements instead of at the end,
you should use encloseSep
.)
sep :: [StyleDoc] -> StyleDoc #
The document (sep xs)
concatenates all documents xs
either horizontally
with (<+>)
, if it fits the page, or vertically with (<> line <>)
.
sep xs = group (vsep xs)
The document softline
behaves like (fromString " ")
if the resulting
output fits the page, otherwise it behaves like line
.
softline = group line
spacedBulletedList :: [StyleDoc] -> StyleDoc #
Display a bulleted list of StyleDoc
with a blank line between
each and *
as the bullet point.
string :: String -> StyleDoc #
The document string s
concatenates all characters in s
using line
for
newline characters and fromString
for all other characters. It is used
whenever the text contains newline characters.
Since: rio-prettyprint-0.1.4.0
vsep :: [StyleDoc] -> StyleDoc #
The document (vsep xs)
concatenates all documents xs
vertically with
(<> line <>)
. If a group
undoes the line breaks inserted by vsep
,
all documents are separated with a space.
someText = map fromString (words ("text to lay out")) test = fromString "some" <+> vsep someText
This is layed out as:
some text to lay out
The align
combinator can be used to align the documents under their first
element
test = fromString "some" <+> align (vsep someText)
Which is printed as:
some text to lay out