Copyright | (c) Brent Yorgey Benedikt Huber 2009 |
---|---|
License | BSD-like |
Maintainer | cabal-devel@haskell.org |
Stability | provisional |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Some types used by the 'cabal init' command.
Synopsis
- data InitFlags = InitFlags {
- interactive :: Flag Bool
- quiet :: Flag Bool
- packageDir :: Flag FilePath
- noComments :: Flag Bool
- minimal :: Flag Bool
- simpleProject :: Flag Bool
- packageName :: Flag PackageName
- version :: Flag Version
- cabalVersion :: Flag CabalSpecVersion
- license :: Flag SpecLicense
- author :: Flag String
- email :: Flag String
- homepage :: Flag String
- synopsis :: Flag String
- category :: Flag String
- extraSrc :: Flag [String]
- extraDoc :: Flag [String]
- packageType :: Flag PackageType
- mainIs :: Flag FilePath
- language :: Flag Language
- exposedModules :: Flag [ModuleName]
- otherModules :: Flag [ModuleName]
- otherExts :: Flag [Extension]
- dependencies :: Flag [Dependency]
- applicationDirs :: Flag [String]
- sourceDirs :: Flag [String]
- buildTools :: Flag [String]
- initializeTestSuite :: Flag Bool
- testDirs :: Flag [String]
- initHcPath :: Flag FilePath
- initVerbosity :: Flag Verbosity
- overwrite :: Flag Bool
- data PkgDescription = PkgDescription {}
- data LibTarget = LibTarget {}
- data ExeTarget = ExeTarget {}
- data TestTarget = TestTarget {}
- data PackageType
- data HsFilePath = HsFilePath {}
- data HsFileType
- fromHsFilePath :: HsFilePath -> Maybe FilePath
- toHsFilePath :: FilePath -> HsFilePath
- toLiterateHs :: HsFilePath -> HsFilePath
- toStandardHs :: HsFilePath -> HsFilePath
- mkLiterate :: HsFilePath -> [String] -> [String]
- isHsFilePath :: FilePath -> Bool
- class Monad m => Interactive m where
- getLine :: m String
- readFile :: FilePath -> m String
- getCurrentDirectory :: m FilePath
- getHomeDirectory :: m FilePath
- getDirectoryContents :: FilePath -> m [FilePath]
- listDirectory :: FilePath -> m [FilePath]
- doesDirectoryExist :: FilePath -> m Bool
- doesFileExist :: FilePath -> m Bool
- canonicalizePathNoThrow :: FilePath -> m FilePath
- readProcessWithExitCode :: FilePath -> [String] -> String -> m (ExitCode, String, String)
- getEnvironment :: m [(String, String)]
- getCurrentYear :: m Integer
- listFilesInside :: (FilePath -> m Bool) -> FilePath -> m [FilePath]
- listFilesRecursive :: FilePath -> m [FilePath]
- putStr :: String -> m ()
- putStrLn :: String -> m ()
- createDirectory :: FilePath -> m ()
- removeDirectory :: FilePath -> m ()
- writeFile :: FilePath -> String -> m ()
- removeExistingFile :: FilePath -> m ()
- copyFile :: FilePath -> FilePath -> m ()
- renameDirectory :: FilePath -> FilePath -> m ()
- hFlush :: Handle -> m ()
- message :: Verbosity -> Severity -> String -> m ()
- break :: m Bool
- throwPrompt :: BreakException -> m a
- newtype BreakException = BreakException String
- newtype PurePrompt a = PurePrompt {
- _runPrompt :: NonEmpty String -> Either BreakException (a, NonEmpty String)
- evalPrompt :: PurePrompt a -> NonEmpty String -> a
- data Severity
- type IsLiterate = Bool
- type IsSimple = Bool
- data WriteOpts = WriteOpts {}
- data ProjectSettings = ProjectSettings {}
- data FieldAnnotation = FieldAnnotation {}
- data DefaultPrompt t
Data
InitFlags is a subset of flags available in the
.cabal
file that represent options that are relevant to the
init command process.
InitFlags | |
|
Instances
Targets and descriptions
data PkgDescription Source #
PkgDescription
represents the relevant options set by the
user when building a package description during the init command
process.
Instances
Show PkgDescription Source # | |
Defined in Distribution.Client.Init.Types showsPrec :: Int -> PkgDescription -> ShowS # show :: PkgDescription -> String # showList :: [PkgDescription] -> ShowS # | |
Eq PkgDescription Source # | |
Defined in Distribution.Client.Init.Types (==) :: PkgDescription -> PkgDescription -> Bool # (/=) :: PkgDescription -> PkgDescription -> Bool # |
LibTarget
represents the relevant options set by the
user when building a library package during the init command
process.
LibTarget | |
|
ExeTarget
represents the relevant options set by the
user when building an executable package.
ExeTarget | |
|
data TestTarget Source #
TestTarget
represents the relevant options set by the
user when building a library package.
TestTarget | |
|
Instances
Show TestTarget Source # | |
Defined in Distribution.Client.Init.Types showsPrec :: Int -> TestTarget -> ShowS # show :: TestTarget -> String # showList :: [TestTarget] -> ShowS # | |
Eq TestTarget Source # | |
Defined in Distribution.Client.Init.Types (==) :: TestTarget -> TestTarget -> Bool # (/=) :: TestTarget -> TestTarget -> Bool # |
package types
data PackageType Source #
Enum to denote whether the user wants to build a library target, executable target, library and executable targets, or a standalone test suite.
Instances
Main file
data HsFilePath Source #
Instances
Show HsFilePath Source # | |
Defined in Distribution.Client.Init.Types showsPrec :: Int -> HsFilePath -> ShowS # show :: HsFilePath -> String # showList :: [HsFilePath] -> ShowS # | |
Eq HsFilePath Source # | |
Defined in Distribution.Client.Init.Types (==) :: HsFilePath -> HsFilePath -> Bool # (/=) :: HsFilePath -> HsFilePath -> Bool # |
data HsFileType Source #
Instances
Show HsFileType Source # | |
Defined in Distribution.Client.Init.Types showsPrec :: Int -> HsFileType -> ShowS # show :: HsFileType -> String # showList :: [HsFileType] -> ShowS # | |
Eq HsFileType Source # | |
Defined in Distribution.Client.Init.Types (==) :: HsFileType -> HsFileType -> Bool # (/=) :: HsFileType -> HsFileType -> Bool # |
fromHsFilePath :: HsFilePath -> Maybe FilePath Source #
toHsFilePath :: FilePath -> HsFilePath Source #
toLiterateHs :: HsFilePath -> HsFilePath Source #
toStandardHs :: HsFilePath -> HsFilePath Source #
mkLiterate :: HsFilePath -> [String] -> [String] Source #
isHsFilePath :: FilePath -> Bool Source #
Typeclasses
class Monad m => Interactive m where Source #
readFile :: FilePath -> m String Source #
getCurrentDirectory :: m FilePath Source #
getHomeDirectory :: m FilePath Source #
getDirectoryContents :: FilePath -> m [FilePath] Source #
listDirectory :: FilePath -> m [FilePath] Source #
doesDirectoryExist :: FilePath -> m Bool Source #
doesFileExist :: FilePath -> m Bool Source #
canonicalizePathNoThrow :: FilePath -> m FilePath Source #
readProcessWithExitCode :: FilePath -> [String] -> String -> m (ExitCode, String, String) Source #
getEnvironment :: m [(String, String)] Source #
getCurrentYear :: m Integer Source #
listFilesInside :: (FilePath -> m Bool) -> FilePath -> m [FilePath] Source #
listFilesRecursive :: FilePath -> m [FilePath] Source #
putStr :: String -> m () Source #
putStrLn :: String -> m () Source #
createDirectory :: FilePath -> m () Source #
removeDirectory :: FilePath -> m () Source #
writeFile :: FilePath -> String -> m () Source #
removeExistingFile :: FilePath -> m () Source #
copyFile :: FilePath -> FilePath -> m () Source #
renameDirectory :: FilePath -> FilePath -> m () Source #
hFlush :: Handle -> m () Source #
message :: Verbosity -> Severity -> String -> m () Source #
throwPrompt :: BreakException -> m a Source #
Instances
newtype BreakException Source #
A pure exception thrown exclusively by the pure prompter to cancel infinite loops in the prompting process.
For example, in order to break on parse errors, or user-driven continuations that do not make sense to test.
Instances
Exception BreakException Source # | |
Defined in Distribution.Client.Init.Types | |
Show BreakException Source # | |
Defined in Distribution.Client.Init.Types showsPrec :: Int -> BreakException -> ShowS # show :: BreakException -> String # showList :: [BreakException] -> ShowS # | |
Eq BreakException Source # | |
Defined in Distribution.Client.Init.Types (==) :: BreakException -> BreakException -> Bool # (/=) :: BreakException -> BreakException -> Bool # |
newtype PurePrompt a Source #
PurePrompt | |
|
Instances
evalPrompt :: PurePrompt a -> NonEmpty String -> a Source #
Used to inform the intent of prompted messages.
Aliases
type IsLiterate = Bool Source #
Convenience alias for the literate haskell flag
File creator opts
data ProjectSettings Source #
Instances
Show ProjectSettings Source # | |
Defined in Distribution.Client.Init.Types showsPrec :: Int -> ProjectSettings -> ShowS # show :: ProjectSettings -> String # showList :: [ProjectSettings] -> ShowS # | |
Eq ProjectSettings Source # | |
Defined in Distribution.Client.Init.Types (==) :: ProjectSettings -> ProjectSettings -> Bool # (/=) :: ProjectSettings -> ProjectSettings -> Bool # |
Formatters
data FieldAnnotation Source #
Annotations for cabal file PrettyField.
FieldAnnotation | |
|
Other conveniences
data DefaultPrompt t Source #
Defines whether or not a prompt will have a default value, is optional, or is mandatory.
Instances
Functor DefaultPrompt Source # | |
Defined in Distribution.Client.Init.Types fmap :: (a -> b) -> DefaultPrompt a -> DefaultPrompt b # (<$) :: a -> DefaultPrompt b -> DefaultPrompt a # | |
Eq t => Eq (DefaultPrompt t) Source # | |
Defined in Distribution.Client.Init.Types (==) :: DefaultPrompt t -> DefaultPrompt t -> Bool # (/=) :: DefaultPrompt t -> DefaultPrompt t -> Bool # |