Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data DecodeOptions = DecodeOptions {}
- newtype ProgramName = ProgramName {}
- defaultDecodeOptions :: DecodeOptions
- packageConfig :: FilePath
- data DecodeResult = DecodeResult {}
- readPackageConfig :: DecodeOptions -> IO (Either String DecodeResult)
- readPackageConfigWithError :: DecodeOptions -> IO (Either HpackError DecodeResult)
- renamePackage :: String -> Package -> Package
- packageDependencies :: Package -> [(String, DependencyInfo)]
- package :: String -> String -> Package
- section :: a -> Section a
- data Package = Package {
- packageName :: String
- packageVersion :: String
- packageSynopsis :: Maybe String
- packageDescription :: Maybe String
- packageHomepage :: Maybe String
- packageBugReports :: Maybe String
- packageCategory :: Maybe String
- packageStability :: Maybe String
- packageAuthor :: [String]
- packageMaintainer :: [String]
- packageCopyright :: [String]
- packageBuildType :: BuildType
- packageLicense :: Maybe String
- packageLicenseFile :: [FilePath]
- packageTestedWith :: [String]
- packageFlags :: [Flag]
- packageExtraSourceFiles :: [Path]
- packageExtraDocFiles :: [Path]
- packageDataFiles :: [Path]
- packageDataDir :: Maybe FilePath
- packageSourceRepository :: Maybe SourceRepository
- packageCustomSetup :: Maybe CustomSetup
- packageLibrary :: Maybe (Section Library)
- packageInternalLibraries :: Map String (Section Library)
- packageExecutables :: Map String (Section Executable)
- packageTests :: Map String (Section Executable)
- packageBenchmarks :: Map String (Section Executable)
- packageVerbatim :: [Verbatim]
- newtype Dependencies = Dependencies {}
- data DependencyInfo = DependencyInfo {}
- data VersionConstraint
- data DependencyVersion = DependencyVersion (Maybe SourceDependency) VersionConstraint
- data SourceDependency
- type GitRef = String
- type GitUrl = String
- data BuildTool
- newtype SystemBuildTools = SystemBuildTools {}
- type GhcOption = String
- data Verbatim
- data VerbatimValue
- verbatimValueToString :: VerbatimValue -> String
- data CustomSetup = CustomSetup {}
- data Section a = Section {
- sectionData :: a
- sectionSourceDirs :: [FilePath]
- sectionDependencies :: Dependencies
- sectionPkgConfigDependencies :: [String]
- sectionDefaultExtensions :: [String]
- sectionOtherExtensions :: [String]
- sectionLanguage :: Maybe Language
- sectionGhcOptions :: [GhcOption]
- sectionGhcProfOptions :: [GhcProfOption]
- sectionGhcSharedOptions :: [GhcOption]
- sectionGhcjsOptions :: [GhcjsOption]
- sectionCppOptions :: [CppOption]
- sectionCcOptions :: [CcOption]
- sectionCSources :: [Path]
- sectionCxxOptions :: [CxxOption]
- sectionCxxSources :: [Path]
- sectionJsSources :: [Path]
- sectionExtraLibDirs :: [FilePath]
- sectionExtraLibraries :: [FilePath]
- sectionExtraFrameworksDirs :: [FilePath]
- sectionFrameworks :: [FilePath]
- sectionIncludeDirs :: [FilePath]
- sectionInstallIncludes :: [FilePath]
- sectionLdOptions :: [LdOption]
- sectionBuildable :: Maybe Bool
- sectionConditionals :: [Conditional (Section a)]
- sectionBuildTools :: Map BuildTool DependencyVersion
- sectionSystemBuildTools :: SystemBuildTools
- sectionVerbatim :: [Verbatim]
- data Library = Library {}
- data Executable = Executable {}
- data Conditional a = Conditional {
- conditionalCondition :: Cond
- conditionalThen :: a
- conditionalElse :: Maybe a
- data Cond
- data Flag = Flag {}
- data SourceRepository = SourceRepository {}
- newtype Language = Language String
- data BuildType
- type GhcProfOption = String
- type GhcjsOption = String
- type CppOption = String
- type CcOption = String
- type LdOption = String
- newtype Path = Path {}
- newtype Module = Module {}
Documentation
NOTE: This module is exposed to allow integration of Hpack into other tools. It is not meant for general use by end users. The following caveats apply:
- The API is undocumented, consult the source instead.
- The exposed types and functions primarily serve Hpack's own needs, not that of a public API. Breaking changes can happen as Hpack evolves.
As an Hpack user you either want to use the hpack
executable or a build
tool that supports Hpack (e.g. stack
or cabal2nix
).
data DecodeOptions Source #
newtype ProgramName Source #
Instances
IsString ProgramName Source # | |
Defined in Hpack.Error fromString :: String -> ProgramName # | |
Show ProgramName Source # | |
Defined in Hpack.Error showsPrec :: Int -> ProgramName -> ShowS # show :: ProgramName -> String # showList :: [ProgramName] -> ShowS # | |
Eq ProgramName Source # | |
Defined in Hpack.Error (==) :: ProgramName -> ProgramName -> Bool # (/=) :: ProgramName -> ProgramName -> Bool # |
data DecodeResult Source #
Instances
Show DecodeResult Source # | |
Defined in Hpack.Config showsPrec :: Int -> DecodeResult -> ShowS # show :: DecodeResult -> String # showList :: [DecodeResult] -> ShowS # | |
Eq DecodeResult Source # | |
Defined in Hpack.Config (==) :: DecodeResult -> DecodeResult -> Bool # (/=) :: DecodeResult -> DecodeResult -> Bool # |
packageDependencies :: Package -> [(String, DependencyInfo)] Source #
newtype Dependencies Source #
Instances
data DependencyInfo Source #
Instances
Show DependencyInfo Source # | |
Defined in Hpack.Syntax.Dependencies showsPrec :: Int -> DependencyInfo -> ShowS # show :: DependencyInfo -> String # showList :: [DependencyInfo] -> ShowS # | |
Eq DependencyInfo Source # | |
Defined in Hpack.Syntax.Dependencies (==) :: DependencyInfo -> DependencyInfo -> Bool # (/=) :: DependencyInfo -> DependencyInfo -> Bool # | |
Ord DependencyInfo Source # | |
Defined in Hpack.Syntax.Dependencies compare :: DependencyInfo -> DependencyInfo -> Ordering # (<) :: DependencyInfo -> DependencyInfo -> Bool # (<=) :: DependencyInfo -> DependencyInfo -> Bool # (>) :: DependencyInfo -> DependencyInfo -> Bool # (>=) :: DependencyInfo -> DependencyInfo -> Bool # max :: DependencyInfo -> DependencyInfo -> DependencyInfo # min :: DependencyInfo -> DependencyInfo -> DependencyInfo # |
data VersionConstraint Source #
Instances
Show VersionConstraint Source # | |
Defined in Hpack.Syntax.DependencyVersion showsPrec :: Int -> VersionConstraint -> ShowS # show :: VersionConstraint -> String # showList :: [VersionConstraint] -> ShowS # | |
Eq VersionConstraint Source # | |
Defined in Hpack.Syntax.DependencyVersion (==) :: VersionConstraint -> VersionConstraint -> Bool # (/=) :: VersionConstraint -> VersionConstraint -> Bool # | |
Ord VersionConstraint Source # | |
Defined in Hpack.Syntax.DependencyVersion compare :: VersionConstraint -> VersionConstraint -> Ordering # (<) :: VersionConstraint -> VersionConstraint -> Bool # (<=) :: VersionConstraint -> VersionConstraint -> Bool # (>) :: VersionConstraint -> VersionConstraint -> Bool # (>=) :: VersionConstraint -> VersionConstraint -> Bool # max :: VersionConstraint -> VersionConstraint -> VersionConstraint # min :: VersionConstraint -> VersionConstraint -> VersionConstraint # | |
FromValue VersionConstraint Source # | |
Defined in Hpack.Syntax.DependencyVersion |
data DependencyVersion Source #
Instances
Show DependencyVersion Source # | |
Defined in Hpack.Syntax.DependencyVersion showsPrec :: Int -> DependencyVersion -> ShowS # show :: DependencyVersion -> String # showList :: [DependencyVersion] -> ShowS # | |
Eq DependencyVersion Source # | |
Defined in Hpack.Syntax.DependencyVersion (==) :: DependencyVersion -> DependencyVersion -> Bool # (/=) :: DependencyVersion -> DependencyVersion -> Bool # | |
Ord DependencyVersion Source # | |
Defined in Hpack.Syntax.DependencyVersion compare :: DependencyVersion -> DependencyVersion -> Ordering # (<) :: DependencyVersion -> DependencyVersion -> Bool # (<=) :: DependencyVersion -> DependencyVersion -> Bool # (>) :: DependencyVersion -> DependencyVersion -> Bool # (>=) :: DependencyVersion -> DependencyVersion -> Bool # max :: DependencyVersion -> DependencyVersion -> DependencyVersion # min :: DependencyVersion -> DependencyVersion -> DependencyVersion # |
data SourceDependency Source #
Instances
Show SourceDependency Source # | |
Defined in Hpack.Syntax.DependencyVersion showsPrec :: Int -> SourceDependency -> ShowS # show :: SourceDependency -> String # showList :: [SourceDependency] -> ShowS # | |
Eq SourceDependency Source # | |
Defined in Hpack.Syntax.DependencyVersion (==) :: SourceDependency -> SourceDependency -> Bool # (/=) :: SourceDependency -> SourceDependency -> Bool # | |
Ord SourceDependency Source # | |
Defined in Hpack.Syntax.DependencyVersion compare :: SourceDependency -> SourceDependency -> Ordering # (<) :: SourceDependency -> SourceDependency -> Bool # (<=) :: SourceDependency -> SourceDependency -> Bool # (>) :: SourceDependency -> SourceDependency -> Bool # (>=) :: SourceDependency -> SourceDependency -> Bool # max :: SourceDependency -> SourceDependency -> SourceDependency # min :: SourceDependency -> SourceDependency -> SourceDependency # |
newtype SystemBuildTools Source #
Instances
Monoid SystemBuildTools Source # | |
Defined in Hpack.Syntax.BuildTools | |
Semigroup SystemBuildTools Source # | |
Defined in Hpack.Syntax.BuildTools (<>) :: SystemBuildTools -> SystemBuildTools -> SystemBuildTools # sconcat :: NonEmpty SystemBuildTools -> SystemBuildTools # stimes :: Integral b => b -> SystemBuildTools -> SystemBuildTools # | |
Show SystemBuildTools Source # | |
Defined in Hpack.Syntax.BuildTools showsPrec :: Int -> SystemBuildTools -> ShowS # show :: SystemBuildTools -> String # showList :: [SystemBuildTools] -> ShowS # | |
Eq SystemBuildTools Source # | |
Defined in Hpack.Syntax.BuildTools (==) :: SystemBuildTools -> SystemBuildTools -> Bool # (/=) :: SystemBuildTools -> SystemBuildTools -> Bool # | |
FromValue SystemBuildTools Source # | |
Defined in Hpack.Syntax.BuildTools |
data VerbatimValue Source #
Instances
Show VerbatimValue Source # | |
Defined in Hpack.Config showsPrec :: Int -> VerbatimValue -> ShowS # show :: VerbatimValue -> String # showList :: [VerbatimValue] -> ShowS # | |
Eq VerbatimValue Source # | |
Defined in Hpack.Config (==) :: VerbatimValue -> VerbatimValue -> Bool # (/=) :: VerbatimValue -> VerbatimValue -> Bool # | |
FromValue VerbatimValue Source # | |
Defined in Hpack.Config |
data CustomSetup Source #
Instances
Show CustomSetup Source # | |
Defined in Hpack.Config showsPrec :: Int -> CustomSetup -> ShowS # show :: CustomSetup -> String # showList :: [CustomSetup] -> ShowS # | |
Eq CustomSetup Source # | |
Defined in Hpack.Config (==) :: CustomSetup -> CustomSetup -> Bool # (/=) :: CustomSetup -> CustomSetup -> Bool # |
Instances
Foldable Section Source # | |
Defined in Hpack.Config fold :: Monoid m => Section m -> m # foldMap :: Monoid m => (a -> m) -> Section a -> m # foldMap' :: Monoid m => (a -> m) -> Section a -> m # foldr :: (a -> b -> b) -> b -> Section a -> b # foldr' :: (a -> b -> b) -> b -> Section a -> b # foldl :: (b -> a -> b) -> b -> Section a -> b # foldl' :: (b -> a -> b) -> b -> Section a -> b # foldr1 :: (a -> a -> a) -> Section a -> a # foldl1 :: (a -> a -> a) -> Section a -> a # elem :: Eq a => a -> Section a -> Bool # maximum :: Ord a => Section a -> a # minimum :: Ord a => Section a -> a # | |
Traversable Section Source # | |
Functor Section Source # | |
Show a => Show (Section a) Source # | |
Eq a => Eq (Section a) Source # | |
data Executable Source #
Instances
Show Executable Source # | |
Defined in Hpack.Config showsPrec :: Int -> Executable -> ShowS # show :: Executable -> String # showList :: [Executable] -> ShowS # | |
Eq Executable Source # | |
Defined in Hpack.Config (==) :: Executable -> Executable -> Bool # (/=) :: Executable -> Executable -> Bool # |
data Conditional a Source #
Conditional | |
|
Instances
Flag | |
|
data SourceRepository Source #
Instances
Show SourceRepository Source # | |
Defined in Hpack.Config showsPrec :: Int -> SourceRepository -> ShowS # show :: SourceRepository -> String # showList :: [SourceRepository] -> ShowS # | |
Eq SourceRepository Source # | |
Defined in Hpack.Config (==) :: SourceRepository -> SourceRepository -> Bool # (/=) :: SourceRepository -> SourceRepository -> Bool # |
Instances
Bounded BuildType Source # | |
Enum BuildType Source # | |
Defined in Hpack.Config succ :: BuildType -> BuildType # pred :: BuildType -> BuildType # fromEnum :: BuildType -> Int # enumFrom :: BuildType -> [BuildType] # enumFromThen :: BuildType -> BuildType -> [BuildType] # enumFromTo :: BuildType -> BuildType -> [BuildType] # enumFromThenTo :: BuildType -> BuildType -> BuildType -> [BuildType] # | |
Show BuildType Source # | |
Eq BuildType Source # | |
FromValue BuildType Source # | |
type GhcProfOption = String Source #
type GhcjsOption = String Source #