Copyright | Isaac Jones 2003-2005 |
---|---|
License | BSD3 |
Maintainer | cabal-devel@haskell.org |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Distribution.Simple
Description
This is the command line front end to the Simple build system. When given the parsed command-line args and package information, is able to perform basic commands like configure, build, install, register, etc.
This module exports the main functions that Setup.hs scripts use. It
re-exports the UserHooks
type, the standard entry points like
defaultMain
and defaultMainWithHooks
and the predefined sets of
UserHooks
that custom Setup.hs
scripts can extend to add their own
behaviour.
This module isn't called "Simple" because it's simple. Far from it. It's called "Simple" because it does complicated things to simple software.
The original idea was that there could be different build systems that all presented the same compatible command line interfaces. There is still a Distribution.Make system but in practice no packages use it.
Synopsis
- data Module = Module DefUnitId ModuleName
- packageName :: Package pkg => pkg -> PackageName
- class Package pkg where
- packageId :: pkg -> PackageIdentifier
- type PackageId = PackageIdentifier
- data ComponentId
- data Dependency = Dependency PackageName VersionRange (NonEmptySet LibraryName)
- data UnitId
- class Package pkg => HasUnitId pkg where
- installedUnitId :: pkg -> UnitId
- data PackageName
- data PackageIdentifier = PackageIdentifier {}
- mkUnitId :: String -> UnitId
- data DefUnitId
- unComponentId :: ComponentId -> String
- newSimpleUnitId :: ComponentId -> UnitId
- unsafeMkDefUnitId :: UnitId -> DefUnitId
- mkComponentId :: String -> ComponentId
- getHSLibraryName :: UnitId -> String
- mkLegacyUnitId :: PackageId -> UnitId
- unUnitId :: UnitId -> String
- mkPackageName :: String -> PackageName
- mkPackageNameST :: ShortText -> PackageName
- unPackageName :: PackageName -> String
- unPackageNameST :: PackageName -> ShortText
- class HasMungedPackageId pkg where
- mungedId :: pkg -> MungedPackageId
- class HasUnitId pkg => PackageInstalled pkg where
- installedDepends :: pkg -> [UnitId]
- packageVersion :: Package pkg => pkg -> Version
- data AbiHash
- mkAbiHash :: String -> AbiHash
- unAbiHash :: AbiHash -> String
- depLibraries :: Dependency -> NonEmptySet LibraryName
- depPkgName :: Dependency -> PackageName
- depVerRange :: Dependency -> VersionRange
- mainLibSet :: NonEmptySet LibraryName
- mkDependency :: PackageName -> VersionRange -> NonEmptySet LibraryName -> Dependency
- simplifyDependency :: Dependency -> Dependency
- data PkgconfigName
- mkPkgconfigName :: String -> PkgconfigName
- unPkgconfigName :: PkgconfigName -> String
- mungedName' :: HasMungedPackageId pkg => pkg -> MungedPackageName
- mungedVersion' :: HasMungedPackageId munged => munged -> Version
- data Version
- thisVersion :: Version -> VersionRange
- anyVersion :: VersionRange
- nullVersion :: Version
- alterVersion :: ([Int] -> [Int]) -> Version -> Version
- mkVersion :: [Int] -> Version
- mkVersion' :: Version -> Version
- version0 :: Version
- versionNumbers :: Version -> [Int]
- data VersionRangeF a where
- ThisVersionF Version
- LaterVersionF Version
- OrLaterVersionF Version
- EarlierVersionF Version
- OrEarlierVersionF Version
- MajorBoundVersionF Version
- UnionVersionRangesF a a
- IntersectVersionRangesF a a
- pattern GTLowerBound :: VersionRangeF a
- pattern LEUpperBound :: VersionRangeF a
- pattern TZUpperBound :: VersionRangeF a
- data VersionRange
- anaVersionRange :: (a -> VersionRangeF a) -> a -> VersionRange
- cataVersionRange :: (VersionRangeF a -> a) -> VersionRange -> a
- earlierVersion :: Version -> VersionRange
- embedVersionRange :: VersionRangeF VersionRange -> VersionRange
- hyloVersionRange :: (VersionRangeF VersionRange -> VersionRange) -> (VersionRange -> VersionRangeF VersionRange) -> VersionRange -> VersionRange
- intersectVersionRanges :: VersionRange -> VersionRange -> VersionRange
- laterVersion :: Version -> VersionRange
- majorBoundVersion :: Version -> VersionRange
- majorUpperBound :: Version -> Version
- noVersion :: VersionRange
- notThisVersion :: Version -> VersionRange
- orEarlierVersion :: Version -> VersionRange
- orLaterVersion :: Version -> VersionRange
- projectVersionRange :: VersionRange -> VersionRangeF VersionRange
- unionVersionRanges :: VersionRange -> VersionRange -> VersionRange
- wildcardUpperBound :: Version -> Version
- withinVersion :: Version -> VersionRange
- simplifyVersionRange :: VersionRange -> VersionRange
- isAnyVersion :: VersionRange -> Bool
- data Bound
- data LowerBound = LowerBound !Version !Bound
- data UpperBound
- data VersionInterval = VersionInterval !LowerBound !UpperBound
- asVersionIntervals :: VersionRange -> [VersionInterval]
- data VersionIntervals
- fromVersionIntervals :: VersionIntervals -> VersionRange
- toVersionIntervals :: VersionRange -> VersionIntervals
- unVersionIntervals :: VersionIntervals -> [VersionInterval]
- foldVersionRange :: a -> (Version -> a) -> (Version -> a) -> (Version -> a) -> (a -> a -> a) -> (a -> a -> a) -> VersionRange -> a
- hasGTLowerBound :: VersionRange -> Bool
- hasLEUpperBound :: VersionRange -> Bool
- hasLowerBound :: VersionRange -> Bool
- hasTrailingZeroUpperBound :: VersionRange -> Bool
- hasUpperBound :: VersionRange -> Bool
- normaliseVersionRange :: VersionRange -> VersionRange
- stripParensVersionRange :: VersionRange -> VersionRange
- withinRange :: Version -> VersionRange -> Bool
- isNoVersion :: VersionRange -> Bool
- isSpecificVersion :: VersionRange -> Maybe Version
- removeLowerBound :: VersionRange -> VersionRange
- removeUpperBound :: VersionRange -> VersionRange
- transformCaret :: VersionRange -> VersionRange
- transformCaretLower :: VersionRange -> VersionRange
- transformCaretUpper :: VersionRange -> VersionRange
- data License
- = GPL (Maybe Version)
- | AGPL (Maybe Version)
- | LGPL (Maybe Version)
- | BSD2
- | BSD3
- | BSD4
- | MIT
- | ISC
- | MPL Version
- | Apache (Maybe Version)
- | PublicDomain
- | AllRightsReserved
- | UnspecifiedLicense
- | OtherLicense
- | UnknownLicense String
- licenseFromSPDX :: License -> License
- licenseToSPDX :: License -> License
- knownLicenses :: [License]
- module Distribution.Simple.Compiler
- data KnownExtension
- = OverlappingInstances
- | UndecidableInstances
- | IncoherentInstances
- | DoRec
- | RecursiveDo
- | ParallelListComp
- | MultiParamTypeClasses
- | MonomorphismRestriction
- | DeepSubsumption
- | FunctionalDependencies
- | Rank2Types
- | RankNTypes
- | PolymorphicComponents
- | ExistentialQuantification
- | ScopedTypeVariables
- | PatternSignatures
- | ImplicitParams
- | FlexibleContexts
- | FlexibleInstances
- | EmptyDataDecls
- | CPP
- | KindSignatures
- | BangPatterns
- | TypeSynonymInstances
- | TemplateHaskell
- | ForeignFunctionInterface
- | Arrows
- | Generics
- | ImplicitPrelude
- | NamedFieldPuns
- | PatternGuards
- | GeneralizedNewtypeDeriving
- | GeneralisedNewtypeDeriving
- | ExtensibleRecords
- | RestrictedTypeSynonyms
- | HereDocuments
- | MagicHash
- | TypeFamilies
- | StandaloneDeriving
- | UnicodeSyntax
- | UnliftedFFITypes
- | InterruptibleFFI
- | CApiFFI
- | LiberalTypeSynonyms
- | TypeOperators
- | RecordWildCards
- | RecordPuns
- | DisambiguateRecordFields
- | TraditionalRecordSyntax
- | OverloadedStrings
- | GADTs
- | GADTSyntax
- | MonoPatBinds
- | RelaxedPolyRec
- | ExtendedDefaultRules
- | NamedDefaults
- | UnboxedTuples
- | DeriveDataTypeable
- | DeriveGeneric
- | DefaultSignatures
- | InstanceSigs
- | ConstrainedClassMethods
- | PackageImports
- | ImpredicativeTypes
- | NewQualifiedOperators
- | PostfixOperators
- | QuasiQuotes
- | TransformListComp
- | MonadComprehensions
- | ViewPatterns
- | XmlSyntax
- | RegularPatterns
- | TupleSections
- | GHCForeignImportPrim
- | NPlusKPatterns
- | DoAndIfThenElse
- | MultiWayIf
- | LambdaCase
- | RebindableSyntax
- | ExplicitForAll
- | DatatypeContexts
- | MonoLocalBinds
- | DeriveFunctor
- | DeriveTraversable
- | DeriveFoldable
- | NondecreasingIndentation
- | SafeImports
- | Safe
- | Trustworthy
- | Unsafe
- | ConstraintKinds
- | PolyKinds
- | DataKinds
- | TypeData
- | ParallelArrays
- | RoleAnnotations
- | OverloadedLists
- | EmptyCase
- | AutoDeriveTypeable
- | NegativeLiterals
- | BinaryLiterals
- | NumDecimals
- | NullaryTypeClasses
- | ExplicitNamespaces
- | AllowAmbiguousTypes
- | JavaScriptFFI
- | PatternSynonyms
- | PartialTypeSignatures
- | NamedWildCards
- | DeriveAnyClass
- | DeriveLift
- | StaticPointers
- | StrictData
- | Strict
- | ApplicativeDo
- | DuplicateRecordFields
- | TypeApplications
- | TypeInType
- | UndecidableSuperClasses
- | MonadFailDesugaring
- | TemplateHaskellQuotes
- | OverloadedLabels
- | TypeFamilyDependencies
- | DerivingStrategies
- | DerivingVia
- | UnboxedSums
- | HexFloatLiterals
- | BlockArguments
- | NumericUnderscores
- | QuantifiedConstraints
- | StarIsType
- | EmptyDataDeriving
- | CUSKs
- | ImportQualifiedPost
- | StandaloneKindSignatures
- | UnliftedNewtypes
- | LexicalNegation
- | QualifiedDo
- | LinearTypes
- | RequiredTypeArguments
- | FieldSelectors
- | OverloadedRecordDot
- | OverloadedRecordUpdate
- | UnliftedDatatypes
- | ExtendedLiterals
- | AlternativeLayoutRule
- | AlternativeLayoutRuleTransitional
- | RelaxedLayout
- | TypeAbstractions
- | ListTuplePuns
- | MultilineStrings
- | OrPatterns
- data Extension
- data Language
- classifyExtension :: String -> Extension
- classifyLanguage :: String -> Language
- deprecatedExtensions :: [(Extension, Maybe Extension)]
- knownExtensions :: [KnownExtension]
- knownLanguages :: [Language]
- defaultMain :: IO ()
- defaultMainNoRead :: GenericPackageDescription -> IO ()
- defaultMainArgs :: [String] -> IO ()
- data UserHooks = UserHooks {
- readDesc :: IO (Maybe GenericPackageDescription)
- hookedPreProcessors :: [PPSuffixHandler]
- hookedPrograms :: [Program]
- preConf :: Args -> ConfigFlags -> IO HookedBuildInfo
- confHook :: (GenericPackageDescription, HookedBuildInfo) -> ConfigFlags -> IO LocalBuildInfo
- postConf :: Args -> ConfigFlags -> PackageDescription -> LocalBuildInfo -> IO ()
- preBuild :: Args -> BuildFlags -> IO HookedBuildInfo
- buildHook :: PackageDescription -> LocalBuildInfo -> UserHooks -> BuildFlags -> IO ()
- postBuild :: Args -> BuildFlags -> PackageDescription -> LocalBuildInfo -> IO ()
- preRepl :: Args -> ReplFlags -> IO HookedBuildInfo
- replHook :: PackageDescription -> LocalBuildInfo -> UserHooks -> ReplFlags -> [String] -> IO ()
- postRepl :: Args -> ReplFlags -> PackageDescription -> LocalBuildInfo -> IO ()
- preClean :: Args -> CleanFlags -> IO HookedBuildInfo
- cleanHook :: PackageDescription -> () -> UserHooks -> CleanFlags -> IO ()
- postClean :: Args -> CleanFlags -> PackageDescription -> () -> IO ()
- preCopy :: Args -> CopyFlags -> IO HookedBuildInfo
- copyHook :: PackageDescription -> LocalBuildInfo -> UserHooks -> CopyFlags -> IO ()
- postCopy :: Args -> CopyFlags -> PackageDescription -> LocalBuildInfo -> IO ()
- preInst :: Args -> InstallFlags -> IO HookedBuildInfo
- instHook :: PackageDescription -> LocalBuildInfo -> UserHooks -> InstallFlags -> IO ()
- postInst :: Args -> InstallFlags -> PackageDescription -> LocalBuildInfo -> IO ()
- preReg :: Args -> RegisterFlags -> IO HookedBuildInfo
- regHook :: PackageDescription -> LocalBuildInfo -> UserHooks -> RegisterFlags -> IO ()
- postReg :: Args -> RegisterFlags -> PackageDescription -> LocalBuildInfo -> IO ()
- preUnreg :: Args -> RegisterFlags -> IO HookedBuildInfo
- unregHook :: PackageDescription -> LocalBuildInfo -> UserHooks -> RegisterFlags -> IO ()
- postUnreg :: Args -> RegisterFlags -> PackageDescription -> LocalBuildInfo -> IO ()
- preHscolour :: Args -> HscolourFlags -> IO HookedBuildInfo
- hscolourHook :: PackageDescription -> LocalBuildInfo -> UserHooks -> HscolourFlags -> IO ()
- postHscolour :: Args -> HscolourFlags -> PackageDescription -> LocalBuildInfo -> IO ()
- preHaddock :: Args -> HaddockFlags -> IO HookedBuildInfo
- haddockHook :: PackageDescription -> LocalBuildInfo -> UserHooks -> HaddockFlags -> IO ()
- postHaddock :: Args -> HaddockFlags -> PackageDescription -> LocalBuildInfo -> IO ()
- preTest :: Args -> TestFlags -> IO HookedBuildInfo
- testHook :: Args -> PackageDescription -> LocalBuildInfo -> UserHooks -> TestFlags -> IO ()
- postTest :: Args -> TestFlags -> PackageDescription -> LocalBuildInfo -> IO ()
- preBench :: Args -> BenchmarkFlags -> IO HookedBuildInfo
- benchHook :: Args -> PackageDescription -> LocalBuildInfo -> UserHooks -> BenchmarkFlags -> IO ()
- postBench :: Args -> BenchmarkFlags -> PackageDescription -> LocalBuildInfo -> IO ()
- type Args = [String]
- defaultMainWithHooks :: UserHooks -> IO ()
- defaultMainWithSetupHooks :: SetupHooks -> IO ()
- defaultMainWithSetupHooksArgs :: SetupHooks -> [String] -> IO ()
- defaultMainWithHooksArgs :: UserHooks -> [String] -> IO ()
- defaultMainWithHooksNoRead :: UserHooks -> GenericPackageDescription -> IO ()
- defaultMainWithHooksNoReadArgs :: UserHooks -> GenericPackageDescription -> [String] -> IO ()
- simpleUserHooks :: UserHooks
- autoconfUserHooks :: UserHooks
- autoconfSetupHooks :: SetupHooks
- emptyUserHooks :: UserHooks
Documentation
Instances
Parsec Module | |||||
Defined in Distribution.Types.Module | |||||
Pretty Module | |||||
Defined in Distribution.Types.Module | |||||
Structured Module | |||||
Defined in Distribution.Types.Module | |||||
Binary Module | |||||
NFData Module | |||||
Defined in Distribution.Types.Module | |||||
Data Module | |||||
Defined in Distribution.Types.Module Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Module -> c Module # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Module # toConstr :: Module -> Constr # dataTypeOf :: Module -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Module) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Module) # gmapT :: (forall b. Data b => b -> b) -> Module -> Module # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Module -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Module -> r # gmapQ :: (forall d. Data d => d -> u) -> Module -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Module -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Module -> m Module # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Module -> m Module # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Module -> m Module # | |||||
Generic Module | |||||
Defined in Distribution.Types.Module Associated Types
| |||||
Read Module | |||||
Show Module | |||||
Eq Module | |||||
Ord Module | |||||
type Rep Module | |||||
Defined in Distribution.Types.Module type Rep Module = D1 ('MetaData "Module" "Distribution.Types.Module" "Cabal-syntax-3.16.0.0-inplace" 'False) (C1 ('MetaCons "Module" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DefUnitId) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ModuleName))) |
packageName :: Package pkg => pkg -> PackageName #
Methods
packageId :: pkg -> PackageIdentifier #
Instances
Package LinkedComponent Source # | |
Defined in Distribution.Backpack.LinkedComponent Methods | |
Package GenericPackageDescription | |
Defined in Distribution.Types.GenericPackageDescription Methods packageId :: GenericPackageDescription -> PackageIdentifier # | |
Package InstalledPackageInfo | |
Defined in Distribution.Types.InstalledPackageInfo Methods packageId :: InstalledPackageInfo -> PackageIdentifier # | |
Package PackageDescription | |
Defined in Distribution.Types.PackageDescription Methods packageId :: PackageDescription -> PackageIdentifier # | |
Package PackageIdentifier | |
Defined in Distribution.Package Methods | |
Package (AnnotatedId id) Source # | |
Defined in Distribution.Types.AnnotatedId Methods packageId :: AnnotatedId id -> PackageIdentifier # |
type PackageId = PackageIdentifier #
data ComponentId #
Instances
data Dependency #
Constructors
Dependency PackageName VersionRange (NonEmptySet LibraryName) |
Instances
Parsec Dependency | |||||
Defined in Distribution.Types.Dependency Methods parsec :: CabalParsing m => m Dependency | |||||
Pretty Dependency | |||||
Defined in Distribution.Types.Dependency | |||||
Structured Dependency | |||||
Defined in Distribution.Types.Dependency | |||||
Binary Dependency | |||||
Defined in Distribution.Types.Dependency | |||||
NFData Dependency | |||||
Defined in Distribution.Types.Dependency Methods rnf :: Dependency -> () # | |||||
Data Dependency | |||||
Defined in Distribution.Types.Dependency Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Dependency -> c Dependency # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Dependency # toConstr :: Dependency -> Constr # dataTypeOf :: Dependency -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Dependency) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Dependency) # gmapT :: (forall b. Data b => b -> b) -> Dependency -> Dependency # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Dependency -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Dependency -> r # gmapQ :: (forall d. Data d => d -> u) -> Dependency -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Dependency -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Dependency -> m Dependency # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Dependency -> m Dependency # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Dependency -> m Dependency # | |||||
Generic Dependency | |||||
Defined in Distribution.Types.Dependency Associated Types
| |||||
Read Dependency | |||||
Defined in Distribution.Types.Dependency Methods readsPrec :: Int -> ReadS Dependency # readList :: ReadS [Dependency] # readPrec :: ReadPrec Dependency # readListPrec :: ReadPrec [Dependency] # | |||||
Show Dependency | |||||
Defined in Distribution.Types.Dependency Methods showsPrec :: Int -> Dependency -> ShowS # show :: Dependency -> String # showList :: [Dependency] -> ShowS # | |||||
Eq Dependency | |||||
Defined in Distribution.Types.Dependency | |||||
Ord Dependency | |||||
Defined in Distribution.Types.Dependency Methods compare :: Dependency -> Dependency -> Ordering # (<) :: Dependency -> Dependency -> Bool # (<=) :: Dependency -> Dependency -> Bool # (>) :: Dependency -> Dependency -> Bool # (>=) :: Dependency -> Dependency -> Bool # max :: Dependency -> Dependency -> Dependency # min :: Dependency -> Dependency -> Dependency # | |||||
type Rep Dependency | |||||
Defined in Distribution.Types.Dependency type Rep Dependency = D1 ('MetaData "Dependency" "Distribution.Types.Dependency" "Cabal-syntax-3.16.0.0-inplace" 'False) (C1 ('MetaCons "Dependency" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PackageName) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VersionRange) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmptySet LibraryName))))) |
Instances
Parsec UnitId | |||||
Defined in Distribution.Types.UnitId | |||||
Pretty UnitId | |||||
Defined in Distribution.Types.UnitId | |||||
Structured UnitId | |||||
Defined in Distribution.Types.UnitId | |||||
Binary UnitId | |||||
NFData UnitId | |||||
Defined in Distribution.Types.UnitId | |||||
Data UnitId | |||||
Defined in Distribution.Types.UnitId Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UnitId -> c UnitId # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UnitId # toConstr :: UnitId -> Constr # dataTypeOf :: UnitId -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UnitId) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UnitId) # gmapT :: (forall b. Data b => b -> b) -> UnitId -> UnitId # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UnitId -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UnitId -> r # gmapQ :: (forall d. Data d => d -> u) -> UnitId -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> UnitId -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> UnitId -> m UnitId # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UnitId -> m UnitId # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UnitId -> m UnitId # | |||||
IsString UnitId | |||||
Defined in Distribution.Types.UnitId Methods fromString :: String -> UnitId # | |||||
Generic UnitId | |||||
Defined in Distribution.Types.UnitId Associated Types
| |||||
Read UnitId | |||||
Show UnitId | |||||
Eq UnitId | |||||
Ord UnitId | |||||
type Rep UnitId | |||||
Defined in Distribution.Types.UnitId |
class Package pkg => HasUnitId pkg where #
Methods
installedUnitId :: pkg -> UnitId #
Instances
HasUnitId InstalledPackageInfo | |
Defined in Distribution.Types.InstalledPackageInfo Methods installedUnitId :: InstalledPackageInfo -> UnitId # |
data PackageName #
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 | |||||
Binary PackageName | |||||
Defined in Distribution.Types.PackageName | |||||
NFData PackageName | |||||
Defined in Distribution.Types.PackageName Methods rnf :: 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 | |||||
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 # | |||||
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 # | |||||
type Rep PackageName | |||||
Defined in Distribution.Types.PackageName type Rep PackageName = D1 ('MetaData "PackageName" "Distribution.Types.PackageName" "Cabal-syntax-3.16.0.0-inplace" 'True) (C1 ('MetaCons "PackageName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ShortText))) |
data PackageIdentifier #
Constructors
PackageIdentifier | |
Fields
|
Instances
Package PackageIdentifier | |||||
Defined in Distribution.Package Methods | |||||
Parsec PackageIdentifier | |||||
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 | |||||
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 -> () # | |||||
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 # | |||||
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 # | |||||
type Rep PackageIdentifier | |||||
Defined in Distribution.Types.PackageId type Rep PackageIdentifier = D1 ('MetaData "PackageIdentifier" "Distribution.Types.PackageId" "Cabal-syntax-3.16.0.0-inplace" 'False) (C1 ('MetaCons "PackageIdentifier" 'PrefixI 'True) (S1 ('MetaSel ('Just "pkgName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PackageName) :*: S1 ('MetaSel ('Just "pkgVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version))) |
Instances
Parsec DefUnitId | |||||
Defined in Distribution.Types.UnitId | |||||
Pretty DefUnitId | |||||
Defined in Distribution.Types.UnitId | |||||
Structured DefUnitId | |||||
Defined in Distribution.Types.UnitId | |||||
Binary DefUnitId | |||||
NFData DefUnitId | |||||
Defined in Distribution.Types.UnitId | |||||
Data DefUnitId | |||||
Defined in Distribution.Types.UnitId Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DefUnitId -> c DefUnitId # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DefUnitId # toConstr :: DefUnitId -> Constr # dataTypeOf :: DefUnitId -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DefUnitId) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DefUnitId) # gmapT :: (forall b. Data b => b -> b) -> DefUnitId -> DefUnitId # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DefUnitId -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DefUnitId -> r # gmapQ :: (forall d. Data d => d -> u) -> DefUnitId -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DefUnitId -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DefUnitId -> m DefUnitId # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DefUnitId -> m DefUnitId # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DefUnitId -> m DefUnitId # | |||||
Generic DefUnitId | |||||
Defined in Distribution.Types.UnitId Associated Types
| |||||
Read DefUnitId | |||||
Show DefUnitId | |||||
Eq DefUnitId | |||||
Ord DefUnitId | |||||
type Rep DefUnitId | |||||
Defined in Distribution.Types.UnitId |
unComponentId :: ComponentId -> String #
newSimpleUnitId :: ComponentId -> UnitId #
unsafeMkDefUnitId :: UnitId -> DefUnitId #
mkComponentId :: String -> ComponentId #
getHSLibraryName :: UnitId -> String #
mkLegacyUnitId :: PackageId -> UnitId #
mkPackageName :: String -> PackageName #
mkPackageNameST :: ShortText -> PackageName #
unPackageName :: PackageName -> String #
unPackageNameST :: PackageName -> ShortText #
class HasMungedPackageId pkg where #
Instances
HasMungedPackageId InstalledPackageInfo | |
Defined in Distribution.Types.InstalledPackageInfo | |
HasMungedPackageId MungedPackageId | |
Defined in Distribution.Package |
class HasUnitId pkg => PackageInstalled pkg where #
Methods
installedDepends :: pkg -> [UnitId] #
Instances
PackageInstalled InstalledPackageInfo | |
Defined in Distribution.Types.InstalledPackageInfo Methods installedDepends :: InstalledPackageInfo -> [UnitId] # |
packageVersion :: Package pkg => pkg -> Version #
Instances
Parsec AbiHash | |||||
Defined in Distribution.Types.AbiHash | |||||
Pretty AbiHash | |||||
Defined in Distribution.Types.AbiHash | |||||
Structured AbiHash | |||||
Defined in Distribution.Types.AbiHash | |||||
Binary AbiHash | |||||
NFData AbiHash | |||||
Defined in Distribution.Types.AbiHash | |||||
IsString AbiHash | |||||
Defined in Distribution.Types.AbiHash Methods fromString :: String -> AbiHash # | |||||
Generic AbiHash | |||||
Defined in Distribution.Types.AbiHash Associated Types
| |||||
Read AbiHash | |||||
Show AbiHash | |||||
Eq AbiHash | |||||
type Rep AbiHash | |||||
Defined in Distribution.Types.AbiHash |
depPkgName :: Dependency -> PackageName #
depVerRange :: Dependency -> VersionRange #
mkDependency :: PackageName -> VersionRange -> NonEmptySet LibraryName -> Dependency #
data PkgconfigName #
Instances
Parsec PkgconfigName | |||||
Defined in Distribution.Types.PkgconfigName Methods parsec :: CabalParsing m => m PkgconfigName | |||||
Pretty PkgconfigName | |||||
Defined in Distribution.Types.PkgconfigName | |||||
Structured PkgconfigName | |||||
Defined in Distribution.Types.PkgconfigName | |||||
Binary PkgconfigName | |||||
Defined in Distribution.Types.PkgconfigName | |||||
NFData PkgconfigName | |||||
Defined in Distribution.Types.PkgconfigName Methods rnf :: PkgconfigName -> () # | |||||
Data PkgconfigName | |||||
Defined in Distribution.Types.PkgconfigName Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PkgconfigName -> c PkgconfigName # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PkgconfigName # toConstr :: PkgconfigName -> Constr # dataTypeOf :: PkgconfigName -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PkgconfigName) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PkgconfigName) # gmapT :: (forall b. Data b => b -> b) -> PkgconfigName -> PkgconfigName # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PkgconfigName -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PkgconfigName -> r # gmapQ :: (forall d. Data d => d -> u) -> PkgconfigName -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PkgconfigName -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PkgconfigName -> m PkgconfigName # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PkgconfigName -> m PkgconfigName # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PkgconfigName -> m PkgconfigName # | |||||
IsString PkgconfigName | |||||
Defined in Distribution.Types.PkgconfigName Methods fromString :: String -> PkgconfigName # | |||||
Generic PkgconfigName | |||||
Defined in Distribution.Types.PkgconfigName Associated Types
| |||||
Read PkgconfigName | |||||
Defined in Distribution.Types.PkgconfigName Methods readsPrec :: Int -> ReadS PkgconfigName # readList :: ReadS [PkgconfigName] # | |||||
Show PkgconfigName | |||||
Defined in Distribution.Types.PkgconfigName Methods showsPrec :: Int -> PkgconfigName -> ShowS # show :: PkgconfigName -> String # showList :: [PkgconfigName] -> ShowS # | |||||
Eq PkgconfigName | |||||
Defined in Distribution.Types.PkgconfigName Methods (==) :: PkgconfigName -> PkgconfigName -> Bool # (/=) :: PkgconfigName -> PkgconfigName -> Bool # | |||||
Ord PkgconfigName | |||||
Defined in Distribution.Types.PkgconfigName Methods compare :: PkgconfigName -> PkgconfigName -> Ordering # (<) :: PkgconfigName -> PkgconfigName -> Bool # (<=) :: PkgconfigName -> PkgconfigName -> Bool # (>) :: PkgconfigName -> PkgconfigName -> Bool # (>=) :: PkgconfigName -> PkgconfigName -> Bool # max :: PkgconfigName -> PkgconfigName -> PkgconfigName # min :: PkgconfigName -> PkgconfigName -> PkgconfigName # | |||||
type Rep PkgconfigName | |||||
Defined in Distribution.Types.PkgconfigName type Rep PkgconfigName = D1 ('MetaData "PkgconfigName" "Distribution.Types.PkgconfigName" "Cabal-syntax-3.16.0.0-inplace" 'True) (C1 ('MetaCons "PkgconfigName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ShortText))) |
mkPkgconfigName :: String -> PkgconfigName #
unPkgconfigName :: PkgconfigName -> String #
mungedName' :: HasMungedPackageId pkg => pkg -> MungedPackageName #
mungedVersion' :: HasMungedPackageId munged => munged -> Version #
Instances
Parsec Version | |||||
Defined in Distribution.Types.Version | |||||
Pretty Version | |||||
Defined in Distribution.Types.Version | |||||
Structured Version | |||||
Defined in Distribution.Types.Version | |||||
Binary Version | |||||
NFData 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 | |||||
Eq Version | |||||
Ord Version | |||||
Defined in Distribution.Types.Version | |||||
type Rep Version | |||||
Defined in Distribution.Types.Version type Rep Version = D1 ('MetaData "Version" "Distribution.Types.Version" "Cabal-syntax-3.16.0.0-inplace" '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]))) |
thisVersion :: Version -> VersionRange #
nullVersion :: Version #
mkVersion' :: Version -> Version #
versionNumbers :: Version -> [Int] #
data VersionRangeF a #
Constructors
ThisVersionF Version | |
LaterVersionF Version | |
OrLaterVersionF Version | |
EarlierVersionF Version | |
OrEarlierVersionF Version | |
MajorBoundVersionF Version | |
UnionVersionRangesF a a | |
IntersectVersionRangesF a a |
Bundled Patterns
pattern GTLowerBound :: VersionRangeF a | |
pattern LEUpperBound :: VersionRangeF a | |
pattern TZUpperBound :: VersionRangeF a |
Instances
Functor VersionRangeF | |||||
Defined in Distribution.Types.VersionRange.Internal Methods fmap :: (a -> b) -> VersionRangeF a -> VersionRangeF b # (<$) :: a -> VersionRangeF b -> VersionRangeF a # | |||||
Foldable VersionRangeF | |||||
Defined in Distribution.Types.VersionRange.Internal Methods fold :: Monoid m => VersionRangeF m -> m # foldMap :: Monoid m => (a -> m) -> VersionRangeF a -> m # foldMap' :: Monoid m => (a -> m) -> VersionRangeF a -> m # foldr :: (a -> b -> b) -> b -> VersionRangeF a -> b # foldr' :: (a -> b -> b) -> b -> VersionRangeF a -> b # foldl :: (b -> a -> b) -> b -> VersionRangeF a -> b # foldl' :: (b -> a -> b) -> b -> VersionRangeF a -> b # foldr1 :: (a -> a -> a) -> VersionRangeF a -> a # foldl1 :: (a -> a -> a) -> VersionRangeF a -> a # toList :: VersionRangeF a -> [a] # null :: VersionRangeF a -> Bool # length :: VersionRangeF a -> Int # elem :: Eq a => a -> VersionRangeF a -> Bool # maximum :: Ord a => VersionRangeF a -> a # minimum :: Ord a => VersionRangeF a -> a # sum :: Num a => VersionRangeF a -> a # product :: Num a => VersionRangeF a -> a # | |||||
Traversable VersionRangeF | |||||
Defined in Distribution.Types.VersionRange.Internal Methods traverse :: Applicative f => (a -> f b) -> VersionRangeF a -> f (VersionRangeF b) # sequenceA :: Applicative f => VersionRangeF (f a) -> f (VersionRangeF a) # mapM :: Monad m => (a -> m b) -> VersionRangeF a -> m (VersionRangeF b) # sequence :: Monad m => VersionRangeF (m a) -> m (VersionRangeF a) # | |||||
Data a => Data (VersionRangeF a) | |||||
Defined in Distribution.Types.VersionRange.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VersionRangeF a -> c (VersionRangeF a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VersionRangeF a) # toConstr :: VersionRangeF a -> Constr # dataTypeOf :: VersionRangeF a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (VersionRangeF a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VersionRangeF a)) # gmapT :: (forall b. Data b => b -> b) -> VersionRangeF a -> VersionRangeF a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VersionRangeF a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VersionRangeF a -> r # gmapQ :: (forall d. Data d => d -> u) -> VersionRangeF a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> VersionRangeF a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> VersionRangeF a -> m (VersionRangeF a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VersionRangeF a -> m (VersionRangeF a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VersionRangeF a -> m (VersionRangeF a) # | |||||
Generic (VersionRangeF a) | |||||
Defined in Distribution.Types.VersionRange.Internal Associated Types
Methods from :: VersionRangeF a -> Rep (VersionRangeF a) x # to :: Rep (VersionRangeF a) x -> VersionRangeF a # | |||||
Read a => Read (VersionRangeF a) | |||||
Defined in Distribution.Types.VersionRange.Internal Methods readsPrec :: Int -> ReadS (VersionRangeF a) # readList :: ReadS [VersionRangeF a] # readPrec :: ReadPrec (VersionRangeF a) # readListPrec :: ReadPrec [VersionRangeF a] # | |||||
Show a => Show (VersionRangeF a) | |||||
Defined in Distribution.Types.VersionRange.Internal Methods showsPrec :: Int -> VersionRangeF a -> ShowS # show :: VersionRangeF a -> String # showList :: [VersionRangeF a] -> ShowS # | |||||
Eq a => Eq (VersionRangeF a) | |||||
Defined in Distribution.Types.VersionRange.Internal Methods (==) :: VersionRangeF a -> VersionRangeF a -> Bool # (/=) :: VersionRangeF a -> VersionRangeF a -> Bool # | |||||
type Rep (VersionRangeF a) | |||||
Defined in Distribution.Types.VersionRange.Internal type Rep (VersionRangeF a) = D1 ('MetaData "VersionRangeF" "Distribution.Types.VersionRange.Internal" "Cabal-syntax-3.16.0.0-inplace" 'False) (((C1 ('MetaCons "ThisVersionF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version)) :+: C1 ('MetaCons "LaterVersionF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version))) :+: (C1 ('MetaCons "OrLaterVersionF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version)) :+: C1 ('MetaCons "EarlierVersionF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version)))) :+: ((C1 ('MetaCons "OrEarlierVersionF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version)) :+: C1 ('MetaCons "MajorBoundVersionF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version))) :+: (C1 ('MetaCons "UnionVersionRangesF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "IntersectVersionRangesF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))))) |
data VersionRange #
Instances
Parsec VersionRange | |||||
Defined in Distribution.Types.VersionRange.Internal Methods parsec :: CabalParsing m => m VersionRange | |||||
Pretty VersionRange | |||||
Defined in Distribution.Types.VersionRange.Internal | |||||
Structured VersionRange | |||||
Defined in Distribution.Types.VersionRange.Internal | |||||
Binary VersionRange | |||||
Defined in Distribution.Types.VersionRange.Internal | |||||
NFData VersionRange | |||||
Defined in Distribution.Types.VersionRange.Internal Methods rnf :: VersionRange -> () # | |||||
Data VersionRange | |||||
Defined in Distribution.Types.VersionRange.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VersionRange -> c VersionRange # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VersionRange # toConstr :: VersionRange -> Constr # dataTypeOf :: VersionRange -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c VersionRange) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VersionRange) # gmapT :: (forall b. Data b => b -> b) -> VersionRange -> VersionRange # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VersionRange -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VersionRange -> r # gmapQ :: (forall d. Data d => d -> u) -> VersionRange -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> VersionRange -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> VersionRange -> m VersionRange # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VersionRange -> m VersionRange # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VersionRange -> m VersionRange # | |||||
Generic VersionRange | |||||
Defined in Distribution.Types.VersionRange.Internal Associated Types
| |||||
Read VersionRange | |||||
Defined in Distribution.Types.VersionRange.Internal Methods readsPrec :: Int -> ReadS VersionRange # readList :: ReadS [VersionRange] # | |||||
Show VersionRange | |||||
Defined in Distribution.Types.VersionRange.Internal Methods showsPrec :: Int -> VersionRange -> ShowS # show :: VersionRange -> String # showList :: [VersionRange] -> ShowS # | |||||
Eq VersionRange | |||||
Defined in Distribution.Types.VersionRange.Internal | |||||
Ord VersionRange | |||||
Defined in Distribution.Types.VersionRange.Internal Methods compare :: VersionRange -> VersionRange -> Ordering # (<) :: VersionRange -> VersionRange -> Bool # (<=) :: VersionRange -> VersionRange -> Bool # (>) :: VersionRange -> VersionRange -> Bool # (>=) :: VersionRange -> VersionRange -> Bool # max :: VersionRange -> VersionRange -> VersionRange # min :: VersionRange -> VersionRange -> VersionRange # | |||||
Newtype (CompilerFlavor, VersionRange) TestedWith | |||||
Defined in Distribution.FieldGrammar.Newtypes Methods pack :: (CompilerFlavor, VersionRange) -> TestedWith unpack :: TestedWith -> (CompilerFlavor, VersionRange) | |||||
type Rep VersionRange | |||||
Defined in Distribution.Types.VersionRange.Internal type Rep VersionRange = D1 ('MetaData "VersionRange" "Distribution.Types.VersionRange.Internal" "Cabal-syntax-3.16.0.0-inplace" 'False) (((C1 ('MetaCons "ThisVersion" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version)) :+: C1 ('MetaCons "LaterVersion" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version))) :+: (C1 ('MetaCons "OrLaterVersion" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version)) :+: C1 ('MetaCons "EarlierVersion" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version)))) :+: ((C1 ('MetaCons "OrEarlierVersion" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version)) :+: C1 ('MetaCons "MajorBoundVersion" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version))) :+: (C1 ('MetaCons "UnionVersionRanges" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VersionRange) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VersionRange)) :+: C1 ('MetaCons "IntersectVersionRanges" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VersionRange) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VersionRange))))) |
anaVersionRange :: (a -> VersionRangeF a) -> a -> VersionRange #
cataVersionRange :: (VersionRangeF a -> a) -> VersionRange -> a #
earlierVersion :: Version -> VersionRange #
hyloVersionRange :: (VersionRangeF VersionRange -> VersionRange) -> (VersionRange -> VersionRangeF VersionRange) -> VersionRange -> VersionRange #
laterVersion :: Version -> VersionRange #
majorUpperBound :: Version -> Version #
notThisVersion :: Version -> VersionRange #
orEarlierVersion :: Version -> VersionRange #
orLaterVersion :: Version -> VersionRange #
wildcardUpperBound :: Version -> Version #
withinVersion :: Version -> VersionRange #
isAnyVersion :: VersionRange -> Bool #
Constructors
ExclusiveBound | |
InclusiveBound |
data LowerBound #
Constructors
LowerBound !Version !Bound |
Instances
Show LowerBound | |
Defined in Distribution.Types.VersionInterval Methods showsPrec :: Int -> LowerBound -> ShowS # show :: LowerBound -> String # showList :: [LowerBound] -> ShowS # | |
Eq LowerBound | |
Defined in Distribution.Types.VersionInterval |
data UpperBound #
Constructors
NoUpperBound | |
UpperBound !Version !Bound |
Instances
Show UpperBound | |
Defined in Distribution.Types.VersionInterval Methods showsPrec :: Int -> UpperBound -> ShowS # show :: UpperBound -> String # showList :: [UpperBound] -> ShowS # | |
Eq UpperBound | |
Defined in Distribution.Types.VersionInterval |
data VersionInterval #
Constructors
VersionInterval !LowerBound !UpperBound |
Instances
Show VersionInterval | |
Defined in Distribution.Types.VersionInterval Methods showsPrec :: Int -> VersionInterval -> ShowS # show :: VersionInterval -> String # showList :: [VersionInterval] -> ShowS # | |
Eq VersionInterval | |
Defined in Distribution.Types.VersionInterval Methods (==) :: VersionInterval -> VersionInterval -> Bool # (/=) :: VersionInterval -> VersionInterval -> Bool # |
data VersionIntervals #
Instances
Show VersionIntervals | |
Defined in Distribution.Types.VersionInterval Methods showsPrec :: Int -> VersionIntervals -> ShowS # show :: VersionIntervals -> String # showList :: [VersionIntervals] -> ShowS # | |
Eq VersionIntervals | |
Defined in Distribution.Types.VersionInterval Methods (==) :: VersionIntervals -> VersionIntervals -> Bool # (/=) :: VersionIntervals -> VersionIntervals -> Bool # |
foldVersionRange :: a -> (Version -> a) -> (Version -> a) -> (Version -> a) -> (a -> a -> a) -> (a -> a -> a) -> VersionRange -> a #
hasGTLowerBound :: VersionRange -> Bool #
hasLEUpperBound :: VersionRange -> Bool #
hasLowerBound :: VersionRange -> Bool #
hasUpperBound :: VersionRange -> Bool #
withinRange :: Version -> VersionRange -> Bool #
isNoVersion :: VersionRange -> Bool #
Constructors
GPL (Maybe Version) | |
AGPL (Maybe Version) | |
LGPL (Maybe Version) | |
BSD2 | |
BSD3 | |
BSD4 | |
MIT | |
ISC | |
MPL Version | |
Apache (Maybe Version) | |
PublicDomain | |
AllRightsReserved | |
UnspecifiedLicense | |
OtherLicense | |
UnknownLicense String |
Instances
Parsec License | |||||
Defined in Distribution.License | |||||
Pretty License | |||||
Defined in Distribution.License | |||||
Structured License | |||||
Defined in Distribution.License | |||||
Binary License | |||||
NFData License | |||||
Defined in Distribution.License | |||||
Data License | |||||
Defined in Distribution.License Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> License -> c License # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c License # toConstr :: License -> Constr # dataTypeOf :: License -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c License) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c License) # gmapT :: (forall b. Data b => b -> b) -> License -> License # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> License -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> License -> r # gmapQ :: (forall d. Data d => d -> u) -> License -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> License -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> License -> m License # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> License -> m License # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> License -> m License # | |||||
Generic License | |||||
Defined in Distribution.License Associated Types
| |||||
Read License | |||||
Show License | |||||
Eq License | |||||
Ord License | |||||
Defined in Distribution.License | |||||
Newtype (Either License License) SpecLicense | |||||
Newtype (Either License License) SpecLicenseLenient | |||||
type Rep License | |||||
Defined in Distribution.License type Rep License = D1 ('MetaData "License" "Distribution.License" "Cabal-syntax-3.16.0.0-inplace" 'False) (((C1 ('MetaCons "GPL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Version))) :+: (C1 ('MetaCons "AGPL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Version))) :+: C1 ('MetaCons "LGPL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Version))))) :+: ((C1 ('MetaCons "BSD2" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BSD3" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BSD4" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MIT" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "ISC" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MPL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version))) :+: (C1 ('MetaCons "Apache" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Version))) :+: C1 ('MetaCons "PublicDomain" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "AllRightsReserved" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnspecifiedLicense" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "OtherLicense" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnknownLicense" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))))) |
licenseFromSPDX :: License -> License #
licenseToSPDX :: License -> License #
knownLicenses :: [License] #
module Distribution.Simple.Compiler
data KnownExtension #
Constructors
OverlappingInstances | |
UndecidableInstances | |
IncoherentInstances | |
DoRec | |
RecursiveDo | |
ParallelListComp | |
MultiParamTypeClasses | |
MonomorphismRestriction | |
DeepSubsumption | |
FunctionalDependencies | |
Rank2Types | |
RankNTypes | |
PolymorphicComponents | |
ExistentialQuantification | |
ScopedTypeVariables | |
PatternSignatures | |
ImplicitParams | |
FlexibleContexts | |
FlexibleInstances | |
EmptyDataDecls | |
CPP | |
KindSignatures | |
BangPatterns | |
TypeSynonymInstances | |
TemplateHaskell | |
ForeignFunctionInterface | |
Arrows | |
Generics | |
ImplicitPrelude | |
NamedFieldPuns | |
PatternGuards | |
GeneralizedNewtypeDeriving | |
GeneralisedNewtypeDeriving | |
ExtensibleRecords | |
RestrictedTypeSynonyms | |
HereDocuments | |
MagicHash | |
TypeFamilies | |
StandaloneDeriving | |
UnicodeSyntax | |
UnliftedFFITypes | |
InterruptibleFFI | |
CApiFFI | |
LiberalTypeSynonyms | |
TypeOperators | |
RecordWildCards | |
RecordPuns | |
DisambiguateRecordFields | |
TraditionalRecordSyntax | |
OverloadedStrings | |
GADTs | |
GADTSyntax | |
MonoPatBinds | |
RelaxedPolyRec | |
ExtendedDefaultRules | |
NamedDefaults | |
UnboxedTuples | |
DeriveDataTypeable | |
DeriveGeneric | |
DefaultSignatures | |
InstanceSigs | |
ConstrainedClassMethods | |
PackageImports | |
ImpredicativeTypes | |
NewQualifiedOperators | |
PostfixOperators | |
QuasiQuotes | |
TransformListComp | |
MonadComprehensions | |
ViewPatterns | |
XmlSyntax | |
RegularPatterns | |
TupleSections | |
GHCForeignImportPrim | |
NPlusKPatterns | |
DoAndIfThenElse | |
MultiWayIf | |
LambdaCase | |
RebindableSyntax | |
ExplicitForAll | |
DatatypeContexts | |
MonoLocalBinds | |
DeriveFunctor | |
DeriveTraversable | |
DeriveFoldable | |
NondecreasingIndentation | |
SafeImports | |
Safe | |
Trustworthy | |
Unsafe | |
ConstraintKinds | |
PolyKinds | |
DataKinds | |
TypeData | |
ParallelArrays | |
RoleAnnotations | |
OverloadedLists | |
EmptyCase | |
AutoDeriveTypeable | |
NegativeLiterals | |
BinaryLiterals | |
NumDecimals | |
NullaryTypeClasses | |
ExplicitNamespaces | |
AllowAmbiguousTypes | |
JavaScriptFFI | |
PatternSynonyms | |
PartialTypeSignatures | |
NamedWildCards | |
DeriveAnyClass | |
DeriveLift | |
StaticPointers | |
StrictData | |
Strict | |
ApplicativeDo | |
DuplicateRecordFields | |
TypeApplications | |
TypeInType | |
UndecidableSuperClasses | |
MonadFailDesugaring | |
TemplateHaskellQuotes | |
OverloadedLabels | |
TypeFamilyDependencies | |
DerivingStrategies | |
DerivingVia | |
UnboxedSums | |
HexFloatLiterals | |
BlockArguments | |
NumericUnderscores | |
QuantifiedConstraints | |
StarIsType | |
EmptyDataDeriving | |
CUSKs | |
ImportQualifiedPost | |
StandaloneKindSignatures | |
UnliftedNewtypes | |
LexicalNegation | |
QualifiedDo | |
LinearTypes | |
RequiredTypeArguments | |
FieldSelectors | |
OverloadedRecordDot | |
OverloadedRecordUpdate | |
UnliftedDatatypes | |
ExtendedLiterals | |
AlternativeLayoutRule | |
AlternativeLayoutRuleTransitional | |
RelaxedLayout | |
TypeAbstractions | |
ListTuplePuns | |
MultilineStrings | |
OrPatterns |
Instances
Pretty KnownExtension | |||||
Defined in Language.Haskell.Extension | |||||
Structured KnownExtension | |||||
Defined in Language.Haskell.Extension | |||||
Binary KnownExtension | |||||
Defined in Language.Haskell.Extension Methods put :: KnownExtension -> Put # get :: Get KnownExtension # putList :: [KnownExtension] -> Put # | |||||
NFData KnownExtension | |||||
Defined in Language.Haskell.Extension Methods rnf :: KnownExtension -> () # | |||||
Data KnownExtension | |||||
Defined in Language.Haskell.Extension Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> KnownExtension -> c KnownExtension # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c KnownExtension # toConstr :: KnownExtension -> Constr # dataTypeOf :: KnownExtension -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c KnownExtension) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c KnownExtension) # gmapT :: (forall b. Data b => b -> b) -> KnownExtension -> KnownExtension # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> KnownExtension -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> KnownExtension -> r # gmapQ :: (forall d. Data d => d -> u) -> KnownExtension -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> KnownExtension -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> KnownExtension -> m KnownExtension # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> KnownExtension -> m KnownExtension # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> KnownExtension -> m KnownExtension # | |||||
Bounded KnownExtension | |||||
Defined in Language.Haskell.Extension | |||||
Enum KnownExtension | |||||
Defined in Language.Haskell.Extension Methods succ :: KnownExtension -> KnownExtension # pred :: KnownExtension -> KnownExtension # toEnum :: Int -> KnownExtension # fromEnum :: KnownExtension -> Int # enumFrom :: KnownExtension -> [KnownExtension] # enumFromThen :: KnownExtension -> KnownExtension -> [KnownExtension] # enumFromTo :: KnownExtension -> KnownExtension -> [KnownExtension] # enumFromThenTo :: KnownExtension -> KnownExtension -> KnownExtension -> [KnownExtension] # | |||||
Generic KnownExtension | |||||
Defined in Language.Haskell.Extension Associated Types
Methods from :: KnownExtension -> Rep KnownExtension x # to :: Rep KnownExtension x -> KnownExtension # | |||||
Read KnownExtension | |||||
Defined in Language.Haskell.Extension Methods readsPrec :: Int -> ReadS KnownExtension # readList :: ReadS [KnownExtension] # | |||||
Show KnownExtension | |||||
Defined in Language.Haskell.Extension Methods showsPrec :: Int -> KnownExtension -> ShowS # show :: KnownExtension -> String # showList :: [KnownExtension] -> ShowS # | |||||
Eq KnownExtension | |||||
Defined in Language.Haskell.Extension Methods (==) :: KnownExtension -> KnownExtension -> Bool # (/=) :: KnownExtension -> KnownExtension -> Bool # | |||||
Ord KnownExtension | |||||
Defined in Language.Haskell.Extension Methods compare :: KnownExtension -> KnownExtension -> Ordering # (<) :: KnownExtension -> KnownExtension -> Bool # (<=) :: KnownExtension -> KnownExtension -> Bool # (>) :: KnownExtension -> KnownExtension -> Bool # (>=) :: KnownExtension -> KnownExtension -> Bool # max :: KnownExtension -> KnownExtension -> KnownExtension # min :: KnownExtension -> KnownExtension -> KnownExtension # | |||||
type Rep KnownExtension | |||||
Defined in Language.Haskell.Extension type Rep KnownExtension = D1 ('MetaData "KnownExtension" "Language.Haskell.Extension" "Cabal-syntax-3.16.0.0-inplace" 'False) (((((((C1 ('MetaCons "OverlappingInstances" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UndecidableInstances" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "IncoherentInstances" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DoRec" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "RecursiveDo" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ParallelListComp" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MultiParamTypeClasses" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MonomorphismRestriction" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DeepSubsumption" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "FunctionalDependencies" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Rank2Types" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RankNTypes" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PolymorphicComponents" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExistentialQuantification" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "ScopedTypeVariables" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PatternSignatures" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ImplicitParams" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "FlexibleContexts" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FlexibleInstances" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "EmptyDataDecls" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CPP" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "KindSignatures" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BangPatterns" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "TypeSynonymInstances" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TemplateHaskell" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ForeignFunctionInterface" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Arrows" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Generics" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "ImplicitPrelude" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NamedFieldPuns" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PatternGuards" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "GeneralizedNewtypeDeriving" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GeneralisedNewtypeDeriving" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "ExtensibleRecords" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RestrictedTypeSynonyms" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HereDocuments" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MagicHash" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TypeFamilies" 'PrefixI 'False) (U1 :: Type -> Type))))))) :+: (((((C1 ('MetaCons "StandaloneDeriving" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnicodeSyntax" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "UnliftedFFITypes" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InterruptibleFFI" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "CApiFFI" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LiberalTypeSynonyms" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TypeOperators" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "RecordWildCards" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RecordPuns" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "DisambiguateRecordFields" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TraditionalRecordSyntax" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "OverloadedStrings" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "GADTs" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GADTSyntax" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "MonoPatBinds" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RelaxedPolyRec" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ExtendedDefaultRules" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NamedDefaults" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnboxedTuples" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "DeriveDataTypeable" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DeriveGeneric" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DefaultSignatures" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InstanceSigs" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ConstrainedClassMethods" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PackageImports" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ImpredicativeTypes" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NewQualifiedOperators" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PostfixOperators" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "QuasiQuotes" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TransformListComp" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MonadComprehensions" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ViewPatterns" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "XmlSyntax" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "RegularPatterns" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TupleSections" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "GHCForeignImportPrim" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NPlusKPatterns" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DoAndIfThenElse" 'PrefixI 'False) (U1 :: Type -> Type)))))))) :+: ((((((C1 ('MetaCons "MultiWayIf" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LambdaCase" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RebindableSyntax" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExplicitForAll" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "DatatypeContexts" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MonoLocalBinds" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DeriveFunctor" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DeriveTraversable" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DeriveFoldable" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "NondecreasingIndentation" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SafeImports" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Safe" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Trustworthy" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Unsafe" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "ConstraintKinds" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PolyKinds" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DataKinds" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TypeData" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ParallelArrays" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "RoleAnnotations" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OverloadedLists" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "EmptyCase" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AutoDeriveTypeable" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "NegativeLiterals" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BinaryLiterals" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NumDecimals" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NullaryTypeClasses" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExplicitNamespaces" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "AllowAmbiguousTypes" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "JavaScriptFFI" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PatternSynonyms" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PartialTypeSignatures" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NamedWildCards" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "DeriveAnyClass" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DeriveLift" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "StaticPointers" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "StrictData" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Strict" 'PrefixI 'False) (U1 :: Type -> Type))))))) :+: (((((C1 ('MetaCons "ApplicativeDo" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DuplicateRecordFields" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TypeApplications" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TypeInType" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "UndecidableSuperClasses" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MonadFailDesugaring" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TemplateHaskellQuotes" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "OverloadedLabels" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TypeFamilyDependencies" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "DerivingStrategies" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DerivingVia" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "UnboxedSums" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "HexFloatLiterals" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BlockArguments" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "NumericUnderscores" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "QuantifiedConstraints" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "StarIsType" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EmptyDataDeriving" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CUSKs" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "ImportQualifiedPost" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StandaloneKindSignatures" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "UnliftedNewtypes" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LexicalNegation" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "QualifiedDo" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LinearTypes" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RequiredTypeArguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "FieldSelectors" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OverloadedRecordDot" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "OverloadedRecordUpdate" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnliftedDatatypes" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ExtendedLiterals" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AlternativeLayoutRule" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AlternativeLayoutRuleTransitional" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "RelaxedLayout" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TypeAbstractions" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ListTuplePuns" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MultilineStrings" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OrPatterns" 'PrefixI 'False) (U1 :: Type -> Type))))))))) |
Instances
Parsec Extension | |||||
Defined in Language.Haskell.Extension | |||||
Pretty Extension | |||||
Defined in Language.Haskell.Extension | |||||
Structured Extension | |||||
Defined in Language.Haskell.Extension | |||||
Binary Extension | |||||
NFData Extension | |||||
Defined in Language.Haskell.Extension | |||||
Data Extension | |||||
Defined in Language.Haskell.Extension Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Extension -> c Extension # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Extension # toConstr :: Extension -> Constr # dataTypeOf :: Extension -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Extension) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Extension) # gmapT :: (forall b. Data b => b -> b) -> Extension -> Extension # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Extension -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Extension -> r # gmapQ :: (forall d. Data d => d -> u) -> Extension -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Extension -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Extension -> m Extension # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Extension -> m Extension # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Extension -> m Extension # | |||||
Generic Extension | |||||
Defined in Language.Haskell.Extension Associated Types
| |||||
Read Extension | |||||
Show Extension | |||||
Eq Extension | |||||
Ord Extension | |||||
type Rep Extension | |||||
Defined in Language.Haskell.Extension type Rep Extension = D1 ('MetaData "Extension" "Language.Haskell.Extension" "Cabal-syntax-3.16.0.0-inplace" 'False) (C1 ('MetaCons "EnableExtension" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 KnownExtension)) :+: (C1 ('MetaCons "DisableExtension" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 KnownExtension)) :+: C1 ('MetaCons "UnknownExtension" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))) |
Constructors
Haskell98 | |
Haskell2010 | |
GHC2021 | |
GHC2024 | |
UnknownLanguage String |
Instances
Parsec Language | |||||
Defined in Language.Haskell.Extension | |||||
Pretty Language | |||||
Defined in Language.Haskell.Extension | |||||
Structured Language | |||||
Defined in Language.Haskell.Extension | |||||
Binary Language | |||||
NFData Language | |||||
Defined in Language.Haskell.Extension | |||||
Data Language | |||||
Defined in Language.Haskell.Extension Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Language -> c Language # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Language # toConstr :: Language -> Constr # dataTypeOf :: Language -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Language) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Language) # gmapT :: (forall b. Data b => b -> b) -> Language -> Language # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Language -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Language -> r # gmapQ :: (forall d. Data d => d -> u) -> Language -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Language -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Language -> m Language # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Language -> m Language # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Language -> m Language # | |||||
Generic Language | |||||
Defined in Language.Haskell.Extension Associated Types
| |||||
Read Language | |||||
Show Language | |||||
Eq Language | |||||
Ord Language | |||||
Defined in Language.Haskell.Extension | |||||
type Rep Language | |||||
Defined in Language.Haskell.Extension type Rep Language = D1 ('MetaData "Language" "Language.Haskell.Extension" "Cabal-syntax-3.16.0.0-inplace" 'False) ((C1 ('MetaCons "Haskell98" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Haskell2010" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "GHC2021" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "GHC2024" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnknownLanguage" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))))) |
classifyExtension :: String -> Extension #
classifyLanguage :: String -> Language #
deprecatedExtensions :: [(Extension, Maybe Extension)] #
knownLanguages :: [Language] #
Simple interface
defaultMain :: IO () Source #
A simple implementation of main
for a Cabal setup script.
It reads the package description file using IO, and performs the
action specified on the command line.
defaultMainNoRead :: GenericPackageDescription -> IO () Source #
Like defaultMain
, but accepts the package description as input
rather than using IO to read it.
defaultMainArgs :: [String] -> IO () Source #
A version of defaultMain
that is passed the command line
arguments, rather than getting them from the environment.
Customization
Hooks allow authors to add specific functionality before and after a command is run, and also to specify additional preprocessors.
- WARNING: The hooks interface is under rather constant flux as we try to understand users needs. Setup files that depend on this interface may break in future releases.
Constructors
UserHooks | |
Fields
|
defaultMainWithHooks :: UserHooks -> IO () Source #
A customizable version of defaultMain
.
defaultMainWithSetupHooks :: SetupHooks -> IO () Source #
defaultMainWithSetupHooksArgs :: SetupHooks -> [String] -> IO () Source #
defaultMainWithHooksArgs :: UserHooks -> [String] -> IO () Source #
A customizable version of defaultMain
that also takes the command
line arguments.
defaultMainWithHooksNoRead :: UserHooks -> GenericPackageDescription -> IO () Source #
A customizable version of defaultMainNoRead
.
defaultMainWithHooksNoReadArgs :: UserHooks -> GenericPackageDescription -> [String] -> IO () Source #
A customizable version of defaultMainNoRead
that also takes the
command line arguments.
Since: 2.2.0.0
Standard sets of hooks
simpleUserHooks :: UserHooks Source #
Hooks that correspond to a plain instantiation of the "simple" build system
emptyUserHooks :: UserHooks Source #
Empty UserHooks
which do nothing.