cabal-debian-5.2.1: Create a Debianization for a Cabal package
Safe HaskellSafe-Inferred
LanguageHaskell2010

Debian.Debianize.Prelude

Description

Functions and instances used by but not related to cabal-debian. These could conceivably be moved into more general libraries.

Synopsis

Documentation

curry3 :: ((a, b, c) -> d) -> a -> b -> c -> d Source #

buildDebVersionMap :: IO DebMap Source #

Query versions of installed packages

stripWith :: (a -> Bool) -> [a] -> [a] Source #

strictReadF :: (Text -> r) -> FilePath -> IO r Source #

replaceFile :: FilePath -> String -> IO () Source #

Write a file which we might still be reading from in order to compute the text argument.

modifyFile :: FilePath -> (String -> IO (Maybe String)) -> IO () Source #

Compute the new file contents from the old. If f returns Nothing do not write.

dpkgFileMap :: IO (Map FilePath (Set BinPkgName)) Source #

Create a map from pathname to the names of the packages that contains that pathname using the contents of the debian package info directory varlibdpkginfo.

debOfFile :: FilePath -> ReaderT (Map FilePath (Set BinPkgName)) IO (Maybe BinPkgName) Source #

Given a path, return the name of the package that owns it.

cond :: t -> t -> Bool -> t Source #

withCurrentDirectory :: FilePath -> IO a -> IO a Source #

From Darcs.Utils - set the working directory and run an IO operation.

getDirectoryContents' :: FilePath -> IO [FilePath] Source #

Get directory contents minus dot files.

setMapMaybe :: Ord b => (a -> Maybe b) -> Set a -> Set b Source #

zipMaps :: Ord k => (k -> Maybe a -> Maybe b -> Maybe c) -> Map k a -> Map k b -> Map k c Source #

foldEmpty :: r -> ([a] -> r) -> [a] -> r Source #

maybeL :: Lens' a (Maybe b) -> Maybe b -> a -> a Source #

If the current value of view x is Nothing, replace it with f.

read' :: Read a => (String -> a) -> String -> a Source #

modifyM :: MonadState a m => (a -> m a) -> m () Source #

intToVerbosity' :: Int -> Verbosity Source #

Version of intToVerbosity that first clamps its argument to the acceptable range (0-3).

listElemLens :: (a -> Bool) -> Lens' [a] (Maybe a) Source #

maybeLens :: a -> Lens' a b -> Lens' (Maybe a) b Source #

fromEmpty :: Set a -> Set a -> Set a Source #

fromSingleton :: a -> ([a] -> a) -> Set a -> a Source #

(.?=) :: Monad m => Lens' a (Maybe b) -> Maybe b -> StateT a m () Source #

Set b if it currently isNothing and the argument isJust, that is 1. Nothing happens if the argument isNothing 2. Nothing happens if the current value isJust

escapeDebianWildcards :: String -> String Source #

This should probably be used in a lot of places.

data PackageIdentifier #

The name and version of a package.

Constructors

PackageIdentifier 

Fields

Instances

Instances details
Package PackageIdentifier 
Instance details

Defined in Distribution.Package

Parsec PackageIdentifier
>>> simpleParsec "foo-bar-0" :: Maybe PackageIdentifier
Just (PackageIdentifier {pkgName = PackageName "foo-bar", pkgVersion = mkVersion [0]})
>>> simpleParsec "foo-bar" :: Maybe PackageIdentifier
Just (PackageIdentifier {pkgName = PackageName "foo-bar", pkgVersion = mkVersion []})

Note: Stricter than Text instance

>>> simpleParsec "foo-bar-0-0" :: Maybe PackageIdentifier
Nothing
>>> simpleParsec "foo-bar.0" :: Maybe PackageIdentifier
Nothing
>>> simpleParsec "foo-bar.4-2" :: Maybe PackageIdentifier
Nothing
>>> simpleParsec "1.2.3" :: Maybe PackageIdentifier
Nothing
Instance details

Defined in Distribution.Types.PackageId

Pretty PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Structured PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Data PackageIdentifier 
Instance details

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 
Instance details

Defined in Distribution.Types.PackageId

Associated Types

type Rep PackageIdentifier :: Type -> Type #

Read PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Show PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Binary PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

NFData PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Methods

rnf :: PackageIdentifier -> () #

Eq PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Ord PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Pretty (PP PackageIdentifier) Source # 
Instance details

Defined in Debian.Debianize.Prelude

type Rep PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

type Rep PackageIdentifier = D1 ('MetaData "PackageIdentifier" "Distribution.Types.PackageId" "Cabal-3.6.3.0" 'False) (C1 ('MetaCons "PackageIdentifier" 'PrefixI 'True) (S1 ('MetaSel ('Just "pkgName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PackageName) :*: S1 ('MetaSel ('Just "pkgVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version)))

data PackageName #

A package name.

Use mkPackageName and unPackageName to convert from/to a String.

This type is opaque since Cabal-2.0

Since: Cabal-2.0.0.2

Instances

Instances details
Parsec PackageName 
Instance details

Defined in Distribution.Types.PackageName

Methods

parsec :: CabalParsing m => m PackageName #

Pretty PackageName 
Instance details

Defined in Distribution.Types.PackageName

Structured PackageName 
Instance details

Defined in Distribution.Types.PackageName

Data PackageName 
Instance details

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

mkPackageName

Since: Cabal-2.0.0.2

Instance details

Defined in Distribution.Types.PackageName

Generic PackageName 
Instance details

Defined in Distribution.Types.PackageName

Associated Types

type Rep PackageName :: Type -> Type #

Read PackageName 
Instance details

Defined in Distribution.Types.PackageName

Show PackageName 
Instance details

Defined in Distribution.Types.PackageName

Binary PackageName 
Instance details

Defined in Distribution.Types.PackageName

NFData PackageName 
Instance details

Defined in Distribution.Types.PackageName

Methods

rnf :: PackageName -> () #

Eq PackageName 
Instance details

Defined in Distribution.Types.PackageName

Ord PackageName 
Instance details

Defined in Distribution.Types.PackageName

Pretty (PP PackageName) Source # 
Instance details

Defined in Debian.Debianize.Prelude

type Rep PackageName 
Instance details

Defined in Distribution.Types.PackageName

type Rep PackageName = D1 ('MetaData "PackageName" "Distribution.Types.PackageName" "Cabal-3.6.3.0" 'True) (C1 ('MetaCons "PackageName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ShortText)))

mkPackageName :: String -> PackageName #

Construct a PackageName from a String

mkPackageName is the inverse to unPackageName

Note: No validations are performed to ensure that the resulting PackageName is valid

Since: Cabal-2.0.0.2

Orphan instances