cpkg-0.2.5.8: Build tool for C
Safe HaskellSafe-Inferred
LanguageHaskell2010

Package.C

Synopsis

Types

data BuildVars Source #

Constructors

BuildVars 

Fields

newtype Version Source #

Constructors

Version [Natural] 

Instances

Instances details
Binary Version Source # 
Instance details

Defined in Package.C.Type.Version

Methods

put :: Version -> Put #

get :: Get Version #

putList :: [Version] -> Put #

FromDhall Version Source # 
Instance details

Defined in Package.C.Type.Version

Eq Version Source # 
Instance details

Defined in Package.C.Type.Version

Methods

(==) :: Version -> Version -> Bool #

(/=) :: Version -> Version -> Bool #

Ord Version Source # 
Instance details

Defined in Package.C.Type.Version

Hashable Version Source # 
Instance details

Defined in Package.C.Type.Version

Methods

hashWithSalt :: Int -> Version -> Int #

hash :: Version -> Int #

Pretty Version Source # 
Instance details

Defined in Package.C.Type.Version

Methods

pretty :: Version -> Doc ann #

prettyList :: [Version] -> Doc ann #

data Verbosity Source #

Constructors

Silent

Display nothing

Normal

Display progress information

Verbose

Display stderr from builds

Loud

Display stdout and stderr from builds

Diagnostic

Display stdout and stderr from builds, and display debug information

data TargetTriple Source #

Constructors

TargetTriple 

Instances

Instances details
Generic TargetTriple Source # 
Instance details

Defined in Package.C.Triple.Type

Associated Types

type Rep TargetTriple :: Type -> Type #

Show TargetTriple Source # 
Instance details

Defined in Package.C.Triple.Type

Binary TargetTriple Source # 
Instance details

Defined in Package.C.Triple.Type

ToDhall TargetTriple Source # 
Instance details

Defined in Package.C.Triple.Type

Eq TargetTriple Source # 
Instance details

Defined in Package.C.Triple.Type

Ord TargetTriple Source # 
Instance details

Defined in Package.C.Triple.Type

Hashable TargetTriple Source # 
Instance details

Defined in Package.C.Triple.Type

Pretty TargetTriple Source # 
Instance details

Defined in Package.C.Triple.Type

Methods

pretty :: TargetTriple -> Doc ann #

prettyList :: [TargetTriple] -> Doc ann #

type Rep TargetTriple Source # 
Instance details

Defined in Package.C.Triple.Type

data Command Source #

Instances

Instances details
Generic Command Source # 
Instance details

Defined in Package.C.Type

Associated Types

type Rep Command :: Type -> Type #

Methods

from :: Command -> Rep Command x #

to :: Rep Command x -> Command #

Binary Command Source # 
Instance details

Defined in Package.C.Type

Methods

put :: Command -> Put #

get :: Get Command #

putList :: [Command] -> Put #

Eq Command Source # 
Instance details

Defined in Package.C.Type

Methods

(==) :: Command -> Command -> Bool #

(/=) :: Command -> Command -> Bool #

Ord Command Source # 
Instance details

Defined in Package.C.Type

Hashable Command Source # 
Instance details

Defined in Package.C.Type

Methods

hashWithSalt :: Int -> Command -> Int #

hash :: Command -> Int #

type Rep Command Source # 
Instance details

Defined in Package.C.Type

type Rep Command = D1 ('MetaData "Command" "Package.C.Type" "cpkg-0.2.5.8-inplace" 'False) (((C1 ('MetaCons "CreateDirectory" 'PrefixI 'True) (S1 ('MetaSel ('Just "dir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "MakeExecutable" 'PrefixI 'True) (S1 ('MetaSel ('Just "file") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: (C1 ('MetaCons "Call" 'PrefixI 'True) ((S1 ('MetaSel ('Just "program") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "arguments") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String])) :*: (S1 ('MetaSel ('Just "environment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [EnvVar])) :*: S1 ('MetaSel ('Just "procDir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)))) :+: C1 ('MetaCons "SymlinkBinary" 'PrefixI 'True) (S1 ('MetaSel ('Just "file") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))) :+: ((C1 ('MetaCons "SymlinkManpage" 'PrefixI 'True) (S1 ('MetaSel ('Just "file") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "section") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: C1 ('MetaCons "Symlink" 'PrefixI 'True) (S1 ('MetaSel ('Just "tgt") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "linkName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: (C1 ('MetaCons "Write" 'PrefixI 'True) (S1 ('MetaSel ('Just "contents") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "file") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath)) :+: (C1 ('MetaCons "CopyFile" 'PrefixI 'True) (S1 ('MetaSel ('Just "src") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath) :*: S1 ('MetaSel ('Just "dest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath)) :+: C1 ('MetaCons "Patch" 'PrefixI 'True) (S1 ('MetaSel ('Just "patchContents") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))))))

data OS Source #

Instances

Instances details
Generic OS Source # 
Instance details

Defined in Package.C.Triple.Type

Associated Types

type Rep OS :: Type -> Type #

Methods

from :: OS -> Rep OS x #

to :: Rep OS x -> OS #

Binary OS Source # 
Instance details

Defined in Package.C.Triple.Type

Methods

put :: OS -> Put #

get :: Get OS #

putList :: [OS] -> Put #

ToDhall OS Source # 
Instance details

Defined in Package.C.Triple.Type

Eq OS Source # 
Instance details

Defined in Package.C.Triple.Type

Methods

(==) :: OS -> OS -> Bool #

(/=) :: OS -> OS -> Bool #

Ord OS Source # 
Instance details

Defined in Package.C.Triple.Type

Methods

compare :: OS -> OS -> Ordering #

(<) :: OS -> OS -> Bool #

(<=) :: OS -> OS -> Bool #

(>) :: OS -> OS -> Bool #

(>=) :: OS -> OS -> Bool #

max :: OS -> OS -> OS #

min :: OS -> OS -> OS #

Hashable OS Source # 
Instance details

Defined in Package.C.Triple.Type

Methods

hashWithSalt :: Int -> OS -> Int #

hash :: OS -> Int #

Pretty OS Source # 
Instance details

Defined in Package.C.Triple.Type

Methods

pretty :: OS -> Doc ann #

prettyList :: [OS] -> Doc ann #

type Rep OS Source # 
Instance details

Defined in Package.C.Triple.Type

type Rep OS = D1 ('MetaData "OS" "Package.C.Triple.Type" "cpkg-0.2.5.8-inplace" 'False) (((C1 ('MetaCons "Darwin" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Dragonfly" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FreeBSD" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Linux" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OpenBSD" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NetBSD" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Solaris" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "Windows" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Redox" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Haiku" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IOS" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "AIX" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Hurd" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Android" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NoOs" 'PrefixI 'False) (U1 :: Type -> Type)))))

data Arch Source #

Instances

Instances details
Generic Arch Source # 
Instance details

Defined in Package.C.Triple.Type

Associated Types

type Rep Arch :: Type -> Type #

Methods

from :: Arch -> Rep Arch x #

to :: Rep Arch x -> Arch #

Binary Arch Source # 
Instance details

Defined in Package.C.Triple.Type

Methods

put :: Arch -> Put #

get :: Get Arch #

putList :: [Arch] -> Put #

ToDhall Arch Source # 
Instance details

Defined in Package.C.Triple.Type

Eq Arch Source # 
Instance details

Defined in Package.C.Triple.Type

Methods

(==) :: Arch -> Arch -> Bool #

(/=) :: Arch -> Arch -> Bool #

Ord Arch Source # 
Instance details

Defined in Package.C.Triple.Type

Methods

compare :: Arch -> Arch -> Ordering #

(<) :: Arch -> Arch -> Bool #

(<=) :: Arch -> Arch -> Bool #

(>) :: Arch -> Arch -> Bool #

(>=) :: Arch -> Arch -> Bool #

max :: Arch -> Arch -> Arch #

min :: Arch -> Arch -> Arch #

Hashable Arch Source # 
Instance details

Defined in Package.C.Triple.Type

Methods

hashWithSalt :: Int -> Arch -> Int #

hash :: Arch -> Int #

Pretty Arch Source # 
Instance details

Defined in Package.C.Triple.Type

Methods

pretty :: Arch -> Doc ann #

prettyList :: [Arch] -> Doc ann #

type Rep Arch Source # 
Instance details

Defined in Package.C.Triple.Type

type Rep Arch = D1 ('MetaData "Arch" "Package.C.Triple.Type" "cpkg-0.2.5.8-inplace" 'False) ((((C1 ('MetaCons "X64" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AArch" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Arm" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "RISCV64" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PowerPC" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "PowerPC64" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PowerPC64le" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Sparc64" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "S390x" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Alpha" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "M68k" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Mips" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MipsEl" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mips64" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Mips64El" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "X86" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SH4" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "HPPA" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "HPPA64" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MipsIsa32r6El" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "MipsIsa32r6" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MipsIsa64r6El" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MipsIsa64r6" 'PrefixI 'False) (U1 :: Type -> Type))))))

data Manufacturer Source #

Constructors

Unknown 
Apple 
IBM 
PC 

Instances

Instances details
Generic Manufacturer Source # 
Instance details

Defined in Package.C.Triple.Type

Associated Types

type Rep Manufacturer :: Type -> Type #

Binary Manufacturer Source # 
Instance details

Defined in Package.C.Triple.Type

ToDhall Manufacturer Source # 
Instance details

Defined in Package.C.Triple.Type

Eq Manufacturer Source # 
Instance details

Defined in Package.C.Triple.Type

Ord Manufacturer Source # 
Instance details

Defined in Package.C.Triple.Type

Hashable Manufacturer Source # 
Instance details

Defined in Package.C.Triple.Type

Pretty Manufacturer Source # 
Instance details

Defined in Package.C.Triple.Type

Methods

pretty :: Manufacturer -> Doc ann #

prettyList :: [Manufacturer] -> Doc ann #

type Rep Manufacturer Source # 
Instance details

Defined in Package.C.Triple.Type

type Rep Manufacturer = D1 ('MetaData "Manufacturer" "Package.C.Triple.Type" "cpkg-0.2.5.8-inplace" 'False) ((C1 ('MetaCons "Unknown" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Apple" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "IBM" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PC" 'PrefixI 'False) (U1 :: Type -> Type)))

data ABI Source #

Instances

Instances details
Generic ABI Source # 
Instance details

Defined in Package.C.Triple.Type

Associated Types

type Rep ABI :: Type -> Type #

Methods

from :: ABI -> Rep ABI x #

to :: Rep ABI x -> ABI #

Binary ABI Source # 
Instance details

Defined in Package.C.Triple.Type

Methods

put :: ABI -> Put #

get :: Get ABI #

putList :: [ABI] -> Put #

ToDhall ABI Source # 
Instance details

Defined in Package.C.Triple.Type

Eq ABI Source # 
Instance details

Defined in Package.C.Triple.Type

Methods

(==) :: ABI -> ABI -> Bool #

(/=) :: ABI -> ABI -> Bool #

Ord ABI Source # 
Instance details

Defined in Package.C.Triple.Type

Methods

compare :: ABI -> ABI -> Ordering #

(<) :: ABI -> ABI -> Bool #

(<=) :: ABI -> ABI -> Bool #

(>) :: ABI -> ABI -> Bool #

(>=) :: ABI -> ABI -> Bool #

max :: ABI -> ABI -> ABI #

min :: ABI -> ABI -> ABI #

Hashable ABI Source # 
Instance details

Defined in Package.C.Triple.Type

Methods

hashWithSalt :: Int -> ABI -> Int #

hash :: ABI -> Int #

Pretty ABI Source # 
Instance details

Defined in Package.C.Triple.Type

Methods

pretty :: ABI -> Doc ann #

prettyList :: [ABI] -> Doc ann #

type Rep ABI Source # 
Instance details

Defined in Package.C.Triple.Type

type Rep ABI = D1 ('MetaData "ABI" "Package.C.Triple.Type" "cpkg-0.2.5.8-inplace" 'False) ((C1 ('MetaCons "GNU" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "GNUabi64" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GNUeabi" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "GNUeabihf" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "GNUspe" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MinGw" 'PrefixI 'False) (U1 :: Type -> Type))))

newtype InstallDb Source #

Constructors

InstallDb 

Instances

Instances details
Monoid InstallDb Source # 
Instance details

Defined in Package.C.Db.Type

Semigroup InstallDb Source # 
Instance details

Defined in Package.C.Db.Type

Binary InstallDb Source # 
Instance details

Defined in Package.C.Db.Type

data BuildCfg Source #

Constructors

BuildCfg 

Instances

Instances details
Generic BuildCfg Source # 
Instance details

Defined in Package.C.Db.Type

Associated Types

type Rep BuildCfg :: Type -> Type #

Methods

from :: BuildCfg -> Rep BuildCfg x #

to :: Rep BuildCfg x -> BuildCfg #

Binary BuildCfg Source # 
Instance details

Defined in Package.C.Db.Type

Methods

put :: BuildCfg -> Put #

get :: Get BuildCfg #

putList :: [BuildCfg] -> Put #

Eq BuildCfg Source # 
Instance details

Defined in Package.C.Db.Type

Ord BuildCfg Source # 
Instance details

Defined in Package.C.Db.Type

Hashable BuildCfg Source # 
Instance details

Defined in Package.C.Db.Type

Methods

hashWithSalt :: Int -> BuildCfg -> Int #

hash :: BuildCfg -> Int #

type Rep BuildCfg Source # 
Instance details

Defined in Package.C.Db.Type

data EnvVar Source #

Constructors

EnvVar 

Fields

Instances

Instances details
Generic EnvVar Source # 
Instance details

Defined in Package.C.Type

Associated Types

type Rep EnvVar :: Type -> Type #

Methods

from :: EnvVar -> Rep EnvVar x #

to :: Rep EnvVar x -> EnvVar #

Binary EnvVar Source # 
Instance details

Defined in Package.C.Type

Methods

put :: EnvVar -> Put #

get :: Get EnvVar #

putList :: [EnvVar] -> Put #

Eq EnvVar Source # 
Instance details

Defined in Package.C.Type

Methods

(==) :: EnvVar -> EnvVar -> Bool #

(/=) :: EnvVar -> EnvVar -> Bool #

Ord EnvVar Source # 
Instance details

Defined in Package.C.Type

Hashable EnvVar Source # 
Instance details

Defined in Package.C.Type

Methods

hashWithSalt :: Int -> EnvVar -> Int #

hash :: EnvVar -> Int #

type Rep EnvVar Source # 
Instance details

Defined in Package.C.Type

type Rep EnvVar = D1 ('MetaData "EnvVar" "Package.C.Type" "cpkg-0.2.5.8-inplace" 'False) (C1 ('MetaCons "EnvVar" 'PrefixI 'True) (S1 ('MetaSel ('Just "var") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "value") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

data Dep Source #

Constructors

Dep 

Fields

Instances

Instances details
Generic Dep Source # 
Instance details

Defined in Package.C.Type.Shared

Associated Types

type Rep Dep :: Type -> Type #

Methods

from :: Dep -> Rep Dep x #

to :: Rep Dep x -> Dep #

FromDhall Dep Source # 
Instance details

Defined in Package.C.Type.Shared

type Rep Dep Source # 
Instance details

Defined in Package.C.Type.Shared

type Rep Dep

Functions

buildCPkg Source #

Arguments

:: CPkg 
-> Maybe TargetTriple 
-> Bool

Should we build static libraries?

-> Bool

Should we install globally?

-> Bool

Was this package installed manually?

-> [FilePath]

Shared data directories

-> [FilePath]

Library directories

-> [FilePath]

Include directories

-> [FilePath]

Directories to add to PATH

-> PkgM () 

buildByName :: PackId -> Maybe TargetTriple -> Maybe String -> Bool -> Bool -> PkgM () Source #

Manually install a package

cleanCache :: MonadIO m => m () Source #

Since: 0.2.3.0

Dhall functionality

Packaging

Parsers

Version