cabal-install-3.14.2.0: The command-line interface for Cabal and Hackage.
Copyright(c) Brent Yorgey Benedikt Huber 2009
LicenseBSD-like
Maintainer[email protected]
Stabilityprovisional
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Distribution.Client.Init.Types

Description

Some types used by the 'cabal init' command.

Synopsis

Data

data InitFlags Source #

InitFlags is a subset of flags available in the .cabal file that represent options that are relevant to the init command process.

Instances

Instances details
Monoid InitFlags Source # 
Instance details

Defined in Distribution.Client.Init.Types

Semigroup InitFlags Source # 
Instance details

Defined in Distribution.Client.Init.Types

Generic InitFlags Source # 
Instance details

Defined in Distribution.Client.Init.Types

Associated Types

type Rep InitFlags :: Type -> Type #

Show InitFlags Source # 
Instance details

Defined in Distribution.Client.Init.Types

Eq InitFlags Source # 
Instance details

Defined in Distribution.Client.Init.Types

type Rep InitFlags Source # 
Instance details

Defined in Distribution.Client.Init.Types

type Rep InitFlags = D1 ('MetaData "InitFlags" "Distribution.Client.Init.Types" "cabal-install-3.14.2.0-6uCrb2WuMbe9XikRFfughF" 'False) (C1 ('MetaCons "InitFlags" 'PrefixI 'True) (((((S1 ('MetaSel ('Just "interactive") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "quiet") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool))) :*: (S1 ('MetaSel ('Just "packageDir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath)) :*: S1 ('MetaSel ('Just "noComments") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)))) :*: ((S1 ('MetaSel ('Just "minimal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "simpleProject") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool))) :*: (S1 ('MetaSel ('Just "packageName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag PackageName)) :*: S1 ('MetaSel ('Just "version") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Version))))) :*: (((S1 ('MetaSel ('Just "cabalVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag CabalSpecVersion)) :*: S1 ('MetaSel ('Just "license") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag SpecLicense))) :*: (S1 ('MetaSel ('Just "author") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag String)) :*: S1 ('MetaSel ('Just "email") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag String)))) :*: ((S1 ('MetaSel ('Just "homepage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag String)) :*: S1 ('MetaSel ('Just "synopsis") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag String))) :*: (S1 ('MetaSel ('Just "category") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag String)) :*: S1 ('MetaSel ('Just "extraSrc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag [String])))))) :*: ((((S1 ('MetaSel ('Just "extraDoc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag [String])) :*: S1 ('MetaSel ('Just "packageType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag PackageType))) :*: (S1 ('MetaSel ('Just "mainIs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath)) :*: S1 ('MetaSel ('Just "language") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Language)))) :*: ((S1 ('MetaSel ('Just "exposedModules") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag [ModuleName])) :*: S1 ('MetaSel ('Just "otherModules") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag [ModuleName]))) :*: (S1 ('MetaSel ('Just "otherExts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag [Extension])) :*: S1 ('MetaSel ('Just "dependencies") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag [Dependency]))))) :*: (((S1 ('MetaSel ('Just "applicationDirs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag [String])) :*: S1 ('MetaSel ('Just "sourceDirs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag [String]))) :*: (S1 ('MetaSel ('Just "buildTools") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag [String])) :*: S1 ('MetaSel ('Just "initializeTestSuite") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)))) :*: ((S1 ('MetaSel ('Just "testDirs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag [String])) :*: S1 ('MetaSel ('Just "initHcPath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath))) :*: (S1 ('MetaSel ('Just "initVerbosity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Verbosity)) :*: S1 ('MetaSel ('Just "overwrite") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool))))))))

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.

data LibTarget Source #

LibTarget represents the relevant options set by the user when building a library package during the init command process.

Instances

Instances details
Show LibTarget Source # 
Instance details

Defined in Distribution.Client.Init.Types

Eq LibTarget Source # 
Instance details

Defined in Distribution.Client.Init.Types

data ExeTarget Source #

ExeTarget represents the relevant options set by the user when building an executable package.

Instances

Instances details
Show ExeTarget Source # 
Instance details

Defined in Distribution.Client.Init.Types

Eq ExeTarget Source # 
Instance details

Defined in Distribution.Client.Init.Types

data TestTarget Source #

TestTarget represents the relevant options set by the user when building a library package.

Instances

Instances details
Show TestTarget Source # 
Instance details

Defined in Distribution.Client.Init.Types

Eq TestTarget Source # 
Instance details

Defined in Distribution.Client.Init.Types

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

Instances details
Generic PackageType Source # 
Instance details

Defined in Distribution.Client.Init.Types

Associated Types

type Rep PackageType :: Type -> Type #

Show PackageType Source # 
Instance details

Defined in Distribution.Client.Init.Types

Eq PackageType Source # 
Instance details

Defined in Distribution.Client.Init.Types

type Rep PackageType Source # 
Instance details

Defined in Distribution.Client.Init.Types

type Rep PackageType = D1 ('MetaData "PackageType" "Distribution.Client.Init.Types" "cabal-install-3.14.2.0-6uCrb2WuMbe9XikRFfughF" 'False) ((C1 ('MetaCons "Library" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Executable" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LibraryAndExecutable" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TestSuite" 'PrefixI 'False) (U1 :: Type -> Type)))

Main file

data HsFilePath Source #

Instances

Instances details
Show HsFilePath Source # 
Instance details

Defined in Distribution.Client.Init.Types

Eq HsFilePath Source # 
Instance details

Defined in Distribution.Client.Init.Types

data HsFileType Source #

Instances

Instances details
Show HsFileType Source # 
Instance details

Defined in Distribution.Client.Init.Types

Eq HsFileType Source # 
Instance details

Defined in Distribution.Client.Init.Types

Typeclasses

class Monad m => Interactive m where Source #

Instances

Instances details
Interactive PromptIO Source # 
Instance details

Defined in Distribution.Client.Init.Types

Methods

getLine :: PromptIO String Source #

readFile :: FilePath -> PromptIO String Source #

getCurrentDirectory :: PromptIO FilePath Source #

getHomeDirectory :: PromptIO FilePath Source #

getDirectoryContents :: FilePath -> PromptIO [FilePath] Source #

listDirectory :: FilePath -> PromptIO [FilePath] Source #

doesDirectoryExist :: FilePath -> PromptIO Bool Source #

doesFileExist :: FilePath -> PromptIO Bool Source #

canonicalizePathNoThrow :: FilePath -> PromptIO FilePath Source #

readProcessWithExitCode :: FilePath -> [String] -> String -> PromptIO (ExitCode, String, String) Source #

maybeReadProcessWithExitCode :: FilePath -> [String] -> String -> PromptIO (Maybe (ExitCode, String, String)) Source #

getEnvironment :: PromptIO [(String, String)] Source #

getCurrentYear :: PromptIO Integer Source #

listFilesInside :: (FilePath -> PromptIO Bool) -> FilePath -> PromptIO [FilePath] Source #

listFilesRecursive :: FilePath -> PromptIO [FilePath] Source #

putStr :: String -> PromptIO () Source #

putStrLn :: String -> PromptIO () Source #

createDirectory :: FilePath -> PromptIO () Source #

removeDirectory :: FilePath -> PromptIO () Source #

writeFile :: FilePath -> String -> PromptIO () Source #

removeExistingFile :: FilePath -> PromptIO () Source #

copyFile :: FilePath -> FilePath -> PromptIO () Source #

renameDirectory :: FilePath -> FilePath -> PromptIO () Source #

hFlush :: Handle -> PromptIO () Source #

message :: Verbosity -> Severity -> String -> PromptIO () Source #

break :: PromptIO Bool Source #

throwPrompt :: BreakException -> PromptIO a Source #

getLastChosenLanguage :: PromptIO (Maybe String) Source #

setLastChosenLanguage :: Maybe String -> PromptIO () Source #

Interactive PurePrompt Source # 
Instance details

Defined in Distribution.Client.Init.Types

Methods

getLine :: PurePrompt String Source #

readFile :: FilePath -> PurePrompt String Source #

getCurrentDirectory :: PurePrompt FilePath Source #

getHomeDirectory :: PurePrompt FilePath Source #

getDirectoryContents :: FilePath -> PurePrompt [FilePath] Source #

listDirectory :: FilePath -> PurePrompt [FilePath] Source #

doesDirectoryExist :: FilePath -> PurePrompt Bool Source #

doesFileExist :: FilePath -> PurePrompt Bool Source #

canonicalizePathNoThrow :: FilePath -> PurePrompt FilePath Source #

readProcessWithExitCode :: FilePath -> [String] -> String -> PurePrompt (ExitCode, String, String) Source #

maybeReadProcessWithExitCode :: FilePath -> [String] -> String -> PurePrompt (Maybe (ExitCode, String, String)) Source #

getEnvironment :: PurePrompt [(String, String)] Source #

getCurrentYear :: PurePrompt Integer Source #

listFilesInside :: (FilePath -> PurePrompt Bool) -> FilePath -> PurePrompt [FilePath] Source #

listFilesRecursive :: FilePath -> PurePrompt [FilePath] Source #

putStr :: String -> PurePrompt () Source #

putStrLn :: String -> PurePrompt () Source #

createDirectory :: FilePath -> PurePrompt () Source #

removeDirectory :: FilePath -> PurePrompt () Source #

writeFile :: FilePath -> String -> PurePrompt () Source #

removeExistingFile :: FilePath -> PurePrompt () Source #

copyFile :: FilePath -> FilePath -> PurePrompt () Source #

renameDirectory :: FilePath -> FilePath -> PurePrompt () Source #

hFlush :: Handle -> PurePrompt () Source #

message :: Verbosity -> Severity -> String -> PurePrompt () Source #

break :: PurePrompt Bool Source #

throwPrompt :: BreakException -> PurePrompt a Source #

getLastChosenLanguage :: PurePrompt (Maybe String) Source #

setLastChosenLanguage :: Maybe String -> PurePrompt () Source #

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.

Constructors

BreakException String 

data PromptIO a Source #

Instances

Instances details
MonadIO PromptIO Source # 
Instance details

Defined in Distribution.Client.Init.Types

Methods

liftIO :: IO a -> PromptIO a #

Applicative PromptIO Source # 
Instance details

Defined in Distribution.Client.Init.Types

Methods

pure :: a -> PromptIO a #

(<*>) :: PromptIO (a -> b) -> PromptIO a -> PromptIO b #

liftA2 :: (a -> b -> c) -> PromptIO a -> PromptIO b -> PromptIO c #

(*>) :: PromptIO a -> PromptIO b -> PromptIO b #

(<*) :: PromptIO a -> PromptIO b -> PromptIO a #

Functor PromptIO Source # 
Instance details

Defined in Distribution.Client.Init.Types

Methods

fmap :: (a -> b) -> PromptIO a -> PromptIO b #

(<$) :: a -> PromptIO b -> PromptIO a #

Monad PromptIO Source # 
Instance details

Defined in Distribution.Client.Init.Types

Methods

(>>=) :: PromptIO a -> (a -> PromptIO b) -> PromptIO b #

(>>) :: PromptIO a -> PromptIO b -> PromptIO b #

return :: a -> PromptIO a #

Interactive PromptIO Source # 
Instance details

Defined in Distribution.Client.Init.Types

Methods

getLine :: PromptIO String Source #

readFile :: FilePath -> PromptIO String Source #

getCurrentDirectory :: PromptIO FilePath Source #

getHomeDirectory :: PromptIO FilePath Source #

getDirectoryContents :: FilePath -> PromptIO [FilePath] Source #

listDirectory :: FilePath -> PromptIO [FilePath] Source #

doesDirectoryExist :: FilePath -> PromptIO Bool Source #

doesFileExist :: FilePath -> PromptIO Bool Source #

canonicalizePathNoThrow :: FilePath -> PromptIO FilePath Source #

readProcessWithExitCode :: FilePath -> [String] -> String -> PromptIO (ExitCode, String, String) Source #

maybeReadProcessWithExitCode :: FilePath -> [String] -> String -> PromptIO (Maybe (ExitCode, String, String)) Source #

getEnvironment :: PromptIO [(String, String)] Source #

getCurrentYear :: PromptIO Integer Source #

listFilesInside :: (FilePath -> PromptIO Bool) -> FilePath -> PromptIO [FilePath] Source #

listFilesRecursive :: FilePath -> PromptIO [FilePath] Source #

putStr :: String -> PromptIO () Source #

putStrLn :: String -> PromptIO () Source #

createDirectory :: FilePath -> PromptIO () Source #

removeDirectory :: FilePath -> PromptIO () Source #

writeFile :: FilePath -> String -> PromptIO () Source #

removeExistingFile :: FilePath -> PromptIO () Source #

copyFile :: FilePath -> FilePath -> PromptIO () Source #

renameDirectory :: FilePath -> FilePath -> PromptIO () Source #

hFlush :: Handle -> PromptIO () Source #

message :: Verbosity -> Severity -> String -> PromptIO () Source #

break :: PromptIO Bool Source #

throwPrompt :: BreakException -> PromptIO a Source #

getLastChosenLanguage :: PromptIO (Maybe String) Source #

setLastChosenLanguage :: Maybe String -> PromptIO () Source #

data PurePrompt a Source #

Instances

Instances details
Applicative PurePrompt Source # 
Instance details

Defined in Distribution.Client.Init.Types

Methods

pure :: a -> PurePrompt a #

(<*>) :: PurePrompt (a -> b) -> PurePrompt a -> PurePrompt b #

liftA2 :: (a -> b -> c) -> PurePrompt a -> PurePrompt b -> PurePrompt c #

(*>) :: PurePrompt a -> PurePrompt b -> PurePrompt b #

(<*) :: PurePrompt a -> PurePrompt b -> PurePrompt a #

Functor PurePrompt Source # 
Instance details

Defined in Distribution.Client.Init.Types

Methods

fmap :: (a -> b) -> PurePrompt a -> PurePrompt b #

(<$) :: a -> PurePrompt b -> PurePrompt a #

Monad PurePrompt Source # 
Instance details

Defined in Distribution.Client.Init.Types

Methods

(>>=) :: PurePrompt a -> (a -> PurePrompt b) -> PurePrompt b #

(>>) :: PurePrompt a -> PurePrompt b -> PurePrompt b #

return :: a -> PurePrompt a #

Interactive PurePrompt Source # 
Instance details

Defined in Distribution.Client.Init.Types

Methods

getLine :: PurePrompt String Source #

readFile :: FilePath -> PurePrompt String Source #

getCurrentDirectory :: PurePrompt FilePath Source #

getHomeDirectory :: PurePrompt FilePath Source #

getDirectoryContents :: FilePath -> PurePrompt [FilePath] Source #

listDirectory :: FilePath -> PurePrompt [FilePath] Source #

doesDirectoryExist :: FilePath -> PurePrompt Bool Source #

doesFileExist :: FilePath -> PurePrompt Bool Source #

canonicalizePathNoThrow :: FilePath -> PurePrompt FilePath Source #

readProcessWithExitCode :: FilePath -> [String] -> String -> PurePrompt (ExitCode, String, String) Source #

maybeReadProcessWithExitCode :: FilePath -> [String] -> String -> PurePrompt (Maybe (ExitCode, String, String)) Source #

getEnvironment :: PurePrompt [(String, String)] Source #

getCurrentYear :: PurePrompt Integer Source #

listFilesInside :: (FilePath -> PurePrompt Bool) -> FilePath -> PurePrompt [FilePath] Source #

listFilesRecursive :: FilePath -> PurePrompt [FilePath] Source #

putStr :: String -> PurePrompt () Source #

putStrLn :: String -> PurePrompt () Source #

createDirectory :: FilePath -> PurePrompt () Source #

removeDirectory :: FilePath -> PurePrompt () Source #

writeFile :: FilePath -> String -> PurePrompt () Source #

removeExistingFile :: FilePath -> PurePrompt () Source #

copyFile :: FilePath -> FilePath -> PurePrompt () Source #

renameDirectory :: FilePath -> FilePath -> PurePrompt () Source #

hFlush :: Handle -> PurePrompt () Source #

message :: Verbosity -> Severity -> String -> PurePrompt () Source #

break :: PurePrompt Bool Source #

throwPrompt :: BreakException -> PurePrompt a Source #

getLastChosenLanguage :: PurePrompt (Maybe String) Source #

setLastChosenLanguage :: Maybe String -> PurePrompt () Source #

data Severity Source #

Used to inform the intent of prompted messages.

Constructors

Info 
Warning 
Error 

Instances

Instances details
Eq Severity Source # 
Instance details

Defined in Distribution.Client.Init.Types

Aliases

type IsLiterate = Bool Source #

Convenience alias for the literate haskell flag

type IsSimple = Bool Source #

Convenience alias for generating simple projects

File creator opts

Formatters

data FieldAnnotation Source #

Annotations for cabal file PrettyField.

Constructors

FieldAnnotation 

Fields

Other conveniences

data DefaultPrompt t Source #

Defines whether or not a prompt will have a default value, is optional, or is mandatory.

Instances

Instances details
Functor DefaultPrompt Source # 
Instance details

Defined in Distribution.Client.Init.Types

Methods

fmap :: (a -> b) -> DefaultPrompt a -> DefaultPrompt b #

(<$) :: a -> DefaultPrompt b -> DefaultPrompt a #

Eq t => Eq (DefaultPrompt t) Source # 
Instance details

Defined in Distribution.Client.Init.Types