Safe Haskell | None |
---|---|
Language | Haskell2010 |
Functions and instances used by but not related to cabal-debian. These could conceivably be moved into more general libraries.
- curry3 :: ((a, b, c) -> d) -> a -> b -> c -> d
- type DebMap = Map BinPkgName (Maybe DebianVersion)
- buildDebVersionMap :: IO DebMap
- (!) :: DebMap -> BinPkgName -> DebianVersion
- strip :: String -> String
- stripWith :: (a -> Bool) -> [a] -> [a]
- strictReadF :: (Text -> r) -> FilePath -> IO r
- replaceFile :: FilePath -> String -> IO ()
- modifyFile :: FilePath -> (String -> IO (Maybe String)) -> IO ()
- diffFile :: FilePath -> Text -> IO (Maybe String)
- removeIfExists :: FilePath -> IO ()
- dpkgFileMap :: IO (Map FilePath (Set BinPkgName))
- debOfFile :: FilePath -> ReaderT (Map FilePath (Set BinPkgName)) IO (Maybe BinPkgName)
- cond :: t -> t -> Bool -> t
- readFile' :: FilePath -> IO Text
- readFileMaybe :: FilePath -> IO (Maybe Text)
- showDeps :: Relations -> String
- showDeps' :: Relations -> String
- withCurrentDirectory :: FilePath -> IO a -> IO a
- getDirectoryContents' :: FilePath -> IO [FilePath]
- setMapMaybe :: (Ord a, Ord b) => (a -> Maybe b) -> Set a -> Set b
- zipMaps :: Ord k => (k -> Maybe a -> Maybe b -> Maybe c) -> Map k a -> Map k b -> Map k c
- foldEmpty :: r -> ([a] -> r) -> [a] -> r
- maybeL :: Lens' a (Maybe b) -> Maybe b -> a -> a
- indent :: [Char] -> String -> String
- maybeRead :: Read a => String -> Maybe a
- read' :: Read a => (String -> a) -> String -> a
- modifyM :: MonadState a m => (a -> m a) -> m ()
- intToVerbosity' :: Int -> Verbosity
- listElemLens :: (a -> Bool) -> Lens' [a] (Maybe a)
- maybeLens :: a -> Lens' a b -> Lens' (Maybe a) b
- fromEmpty :: Set a -> Set a -> Set a
- fromSingleton :: a -> ([a] -> a) -> Set a -> a
- (.?=) :: Monad m => Lens' a (Maybe b) -> Maybe b -> StateT a m ()
- escapeDebianWildcards :: String -> String
- module Data.Version
- mkFlagName :: String -> FlagName
- mkPackageName :: String -> PackageName
- mkVersion :: [Int] -> Version
- mkVersion' :: Version -> Version
- versionNumbers :: Version -> [Int]
- unPackageName :: PackageName -> String
Documentation
type DebMap = Map BinPkgName (Maybe DebianVersion) Source #
buildDebVersionMap :: IO DebMap Source #
Read and parse the status file for installed debian packages: varlibdpkgstatus
(!) :: DebMap -> BinPkgName -> DebianVersion 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.
removeIfExists :: FilePath -> IO () Source #
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.
withCurrentDirectory :: FilePath -> IO a -> IO a Source #
From Darcs.Utils - set the working directory and run an IO operation.
maybeL :: Lens' a (Maybe b) -> Maybe b -> a -> a Source #
If the current value of view x is Nothing, replace it with f.
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).
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.
module Data.Version
mkFlagName :: String -> FlagName Source #
mkPackageName :: String -> PackageName Source #
mkVersion' :: Version -> Version Source #
versionNumbers :: Version -> [Int] Source #
unPackageName :: PackageName -> String #