| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Darcs.Util.Path
Synopsis
- encodeWhite :: FilePath -> String
- decodeWhite :: String -> Either String FilePath
- encodeWhiteName :: Name -> ByteString
- decodeWhiteName :: ByteString -> Either String Name
- data AbsolutePath
- makeAbsolute :: AbsolutePath -> FilePath -> AbsolutePath
- ioAbsolute :: FilePath -> IO AbsolutePath
- data AbsolutePathOrStd
- makeAbsoluteOrStd :: AbsolutePath -> String -> AbsolutePathOrStd
- ioAbsoluteOrStd :: String -> IO AbsolutePathOrStd
- useAbsoluteOrStd :: (AbsolutePath -> a) -> a -> AbsolutePathOrStd -> a
- stdOut :: AbsolutePathOrStd
- data AbsoluteOrRemotePath
- ioAbsoluteOrRemote :: String -> IO AbsoluteOrRemotePath
- isRemote :: AbsoluteOrRemotePath -> Bool
- data SubPath
- makeSubPathOf :: AbsolutePath -> AbsolutePath -> Maybe SubPath
- simpleSubPath :: HasCallStack => FilePath -> Maybe SubPath
- floatSubPath :: SubPath -> Either String AnchoredPath
- makeRelativeTo :: HasCallStack => AbsolutePath -> AbsolutePath -> IO (Maybe SubPath)
- class FilePathOrURL a where
- class FilePathOrURL a => FilePathLike a where- toFilePath :: a -> FilePath
 
- getCurrentDirectory :: IO AbsolutePath
- setCurrentDirectory :: HasCallStack => FilePathLike p => p -> IO ()
- getUniquePathName :: Bool -> (FilePath -> String) -> (Int -> FilePath) -> IO FilePath
- filterPaths :: [AnchoredPath] -> AnchoredPath -> t -> Bool
- data Name
- name2fp :: Name -> FilePath
- makeName :: String -> Either String Name
- rawMakeName :: ByteString -> Either String Name
- eqAnycase :: Name -> Name -> Bool
- newtype AnchoredPath = AnchoredPath [Name]
- anchoredRoot :: AnchoredPath
- appendPath :: AnchoredPath -> Name -> AnchoredPath
- anchorPath :: FilePath -> AnchoredPath -> FilePath
- isPrefix :: AnchoredPath -> AnchoredPath -> Bool
- movedirfilename :: AnchoredPath -> AnchoredPath -> AnchoredPath -> AnchoredPath
- parent :: AnchoredPath -> Maybe AnchoredPath
- parents :: AnchoredPath -> [AnchoredPath]
- replaceParent :: AnchoredPath -> AnchoredPath -> Maybe AnchoredPath
- catPaths :: AnchoredPath -> AnchoredPath -> AnchoredPath
- flatten :: AnchoredPath -> ByteString
- inDarcsdir :: AnchoredPath -> Bool
- displayPath :: AnchoredPath -> FilePath
- realPath :: AnchoredPath -> FilePath
- isRoot :: AnchoredPath -> Bool
- darcsdirName :: Name
- floatPath :: FilePath -> Either String AnchoredPath
- unsafeFloatPath :: HasCallStack => FilePath -> AnchoredPath
Documentation
encodeWhite :: FilePath -> String Source #
encodeWhite translates whitespace in filenames to a darcs-specific
   format (numerical representation according to ord surrounded by
   backslashes).  Note that backslashes are also escaped since they are used
   in the encoding.
encodeWhite "hello there" == "hello\32\there" encodeWhite "hello\there" == "hello\92\there"
decodeWhite :: String -> Either String FilePath Source #
decodeWhite interprets the Darcs-specific "encoded" filenames
   produced by encodeWhite
decodeWhite "hello\32\there" == Right "hello there" decodeWhite "hello\92\there" == Right "hello\there" decodeWhite "hello\there" == Left "malformed filename"
encodeWhiteName :: Name -> ByteString Source #
decodeWhiteName :: ByteString -> Either String Name Source #
AbsolutePath
data AbsolutePath Source #
Instances
| Show AbsolutePath Source # | |
| Defined in Darcs.Util.Path Methods showsPrec :: Int -> AbsolutePath -> ShowS # show :: AbsolutePath -> String # showList :: [AbsolutePath] -> ShowS # | |
| FilePathLike AbsolutePath Source # | |
| Defined in Darcs.Util.Path Methods toFilePath :: AbsolutePath -> FilePath Source # | |
| FilePathOrURL AbsolutePath Source # | |
| Defined in Darcs.Util.Path Methods toPath :: AbsolutePath -> String Source # | |
| Eq AbsolutePath Source # | |
| Defined in Darcs.Util.Path | |
| Ord AbsolutePath Source # | |
| Defined in Darcs.Util.Path Methods compare :: AbsolutePath -> AbsolutePath -> Ordering # (<) :: AbsolutePath -> AbsolutePath -> Bool # (<=) :: AbsolutePath -> AbsolutePath -> Bool # (>) :: AbsolutePath -> AbsolutePath -> Bool # (>=) :: AbsolutePath -> AbsolutePath -> Bool # max :: AbsolutePath -> AbsolutePath -> AbsolutePath # min :: AbsolutePath -> AbsolutePath -> AbsolutePath # | |
makeAbsolute :: AbsolutePath -> FilePath -> AbsolutePath Source #
Take an absolute path and a string representing a (possibly relative) path and combine them into an absolute path. If the second argument is already absolute, then the first argument gets ignored. This function also takes care that the result is converted to Posix convention and normalized. Also, parent directories ("..") at the front of the string argument get canceled out against trailing directory parts of the absolute path argument.
Regarding the last point, someone more familiar with how these functions are used should verify that this is indeed necessary or at least useful.
ioAbsolute :: FilePath -> IO AbsolutePath Source #
Interpret a possibly relative path wrt the current working directory. This also canonicalizes the path, resolving symbolic links etc.
AbsolutePathOrStd
data AbsolutePathOrStd Source #
This is for situations where a string (e.g. a command line argument) may take the value "-" to mean stdin or stdout (which one depends on context) instead of a normal file path.
Instances
| Show AbsolutePathOrStd Source # | |
| Defined in Darcs.Util.Path Methods showsPrec :: Int -> AbsolutePathOrStd -> ShowS # show :: AbsolutePathOrStd -> String # showList :: [AbsolutePathOrStd] -> ShowS # | |
| Eq AbsolutePathOrStd Source # | |
| Defined in Darcs.Util.Path Methods (==) :: AbsolutePathOrStd -> AbsolutePathOrStd -> Bool # (/=) :: AbsolutePathOrStd -> AbsolutePathOrStd -> Bool # | |
| Ord AbsolutePathOrStd Source # | |
| Defined in Darcs.Util.Path Methods compare :: AbsolutePathOrStd -> AbsolutePathOrStd -> Ordering # (<) :: AbsolutePathOrStd -> AbsolutePathOrStd -> Bool # (<=) :: AbsolutePathOrStd -> AbsolutePathOrStd -> Bool # (>) :: AbsolutePathOrStd -> AbsolutePathOrStd -> Bool # (>=) :: AbsolutePathOrStd -> AbsolutePathOrStd -> Bool # max :: AbsolutePathOrStd -> AbsolutePathOrStd -> AbsolutePathOrStd # min :: AbsolutePathOrStd -> AbsolutePathOrStd -> AbsolutePathOrStd # | |
useAbsoluteOrStd :: (AbsolutePath -> a) -> a -> AbsolutePathOrStd -> a Source #
Execute either the first or the second argument action, depending on
 whether the given path is an AbsolutePath or stdin/stdout.
AbsoluteOrRemotePath
data AbsoluteOrRemotePath Source #
Instances
isRemote :: AbsoluteOrRemotePath -> Bool Source #
SubPath
Paths which are relative to the local darcs repository and normalized. Note: These are understood not to have the dot in front.
makeSubPathOf :: AbsolutePath -> AbsolutePath -> Maybe SubPath Source #
Make the second path relative to the first, if possible.
 Note that this returns an empty SubPath if the inputs are equal.
simpleSubPath :: HasCallStack => FilePath -> Maybe SubPath Source #
floatSubPath :: SubPath -> Either String AnchoredPath Source #
Transform a SubPath into an AnchoredPath.
makeRelativeTo :: HasCallStack => AbsolutePath -> AbsolutePath -> IO (Maybe SubPath) Source #
Miscellaneous
class FilePathOrURL a where Source #
Instances
| FilePathOrURL FilePath Source # | |
| FilePathOrURL AbsoluteOrRemotePath Source # | |
| Defined in Darcs.Util.Path Methods toPath :: AbsoluteOrRemotePath -> String Source # | |
| FilePathOrURL AbsolutePath Source # | |
| Defined in Darcs.Util.Path Methods toPath :: AbsolutePath -> String Source # | |
| FilePathOrURL SubPath Source # | |
class FilePathOrURL a => FilePathLike a where Source #
Methods
toFilePath :: a -> FilePath Source #
Instances
| FilePathLike FilePath Source # | |
| Defined in Darcs.Util.Path Methods toFilePath :: FilePath -> FilePath Source # | |
| FilePathLike AbsolutePath Source # | |
| Defined in Darcs.Util.Path Methods toFilePath :: AbsolutePath -> FilePath Source # | |
| FilePathLike SubPath Source # | |
| Defined in Darcs.Util.Path Methods toFilePath :: SubPath -> FilePath Source # | |
setCurrentDirectory :: HasCallStack => FilePathLike p => p -> IO () Source #
getUniquePathName :: Bool -> (FilePath -> String) -> (Int -> FilePath) -> IO FilePath Source #
Iteratively tries find first non-existing path generated by buildName, it feeds to buildName the number starting with -1. When it generates non-existing path and it isn't first, it displays the message created with buildMsg. Usually used for generation of the name like path_number when path already exist (e.g. darcs.net_0).
Tree filtering.
filterPaths :: [AnchoredPath] -> AnchoredPath -> t -> Bool Source #
Construct a filter from a list of AnchoredPaths, that will accept any path that is either a parent or a child of any of the listed paths, and discard everything else.
AnchoredPaths: relative paths within a Tree. All paths are
rawMakeName :: ByteString -> Either String Name Source #
Make a Name from a ByteString.
newtype AnchoredPath Source #
This is a type of "sane" file paths. These are always canonic in the sense that there are no stray slashes, no ".." components and similar. They are usually used to refer to a location within a Tree, but a relative filesystem path works just as well. These are either constructed from individual name components (using "appendPath", "catPaths" and "makeName"), or converted from a FilePath ("unsafeFloatPath" -- but take care when doing that).
Constructors
| AnchoredPath [Name] | 
Instances
appendPath :: AnchoredPath -> Name -> AnchoredPath Source #
Append an element to the end of a path.
anchorPath :: FilePath -> AnchoredPath -> FilePath Source #
isPrefix :: AnchoredPath -> AnchoredPath -> Bool Source #
Check whether a path is a prefix of another path.
movedirfilename :: AnchoredPath -> AnchoredPath -> AnchoredPath -> AnchoredPath Source #
The effect of renaming on paths. The first argument is the old path, the second is the new path, and the third is the possibly affected path we are interested in.
parent :: AnchoredPath -> Maybe AnchoredPath Source #
Get parent (path) of a given path. foobarbaz -> foo/bar
parents :: AnchoredPath -> [AnchoredPath] Source #
List all (proper) parents of a given path. foobarbaz -> [.,foo, foo/bar]
replaceParent :: AnchoredPath -> AnchoredPath -> Maybe AnchoredPath Source #
Replace the second arg's parent with the first arg.
catPaths :: AnchoredPath -> AnchoredPath -> AnchoredPath Source #
Catenate two paths together. Not very safe, but sometimes useful (e.g. when you are representing paths relative to a different point than a Tree root).
flatten :: AnchoredPath -> ByteString Source #
inDarcsdir :: AnchoredPath -> Bool Source #
Is the given path in (or equal to) the _darcs metadata directory?
displayPath :: AnchoredPath -> FilePath Source #
For displaying paths to the user. It should never be used
 for on-disk patch storage. This adds the "./" for consistency
 with how repo paths are displayed by showPatch and friends,
 except for the root path which is displayed as plain ".".
realPath :: AnchoredPath -> FilePath Source #
Interpret an AnchoredPath as relative the current working
 directory. Intended for IO operations in the file system.
 Use with care!
isRoot :: AnchoredPath -> Bool Source #
darcsdirName :: Name Source #
Unsafe AnchoredPath functions.
unsafeFloatPath :: HasCallStack => FilePath -> AnchoredPath Source #
Take a relative FilePath and turn it into an AnchoredPath. This is a partial function. Basically, by using unsafeFloatPath, you are testifying that the argument is a path relative to some common root -- i.e. the root of the associated Tree object. In particular, the input path may not contain any ocurrences of "." or ".." after normalising. You should sanitize any FilePaths before you declare them "good" by converting into AnchoredPath (using this function), especially if the FilePath come from any external source (command line, file, environment, network, etc)