-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Type-safe replacement for System.FilePath etc -- -- This module provides type-safe access to filepath manipulations. -- -- It is designed to be imported instead of System.FilePath and -- System.Directory and is intended to provide versions of -- functions from those modules which have equivalent functionality but -- are more typesafe. -- -- The heart of this module is the Path ar fd abstract type -- which represents file and directory paths. The idea is that there are -- two phantom type parameters - the first should be Abs or -- Rel, and the second File or Dir. A number of type -- synonyms are provided for common types: -- --
--   type AbsFile    = Path Abs File
--   type RelFile    = Path Rel File
--   type AbsDir     = Path Abs Dir
--   type RelDir     = Path Rel Dir
--   type RelPath fd = Path Rel fd
--   type DirPath ar = Path ar Dir
--   
-- -- The type of the combine (aka </>) function gives -- the idea: -- --
--   (</>) :: DirPath ar -> RelPath fd -> Path ar fd
--   
-- -- Together this enables us to give more meaningful types to a lot of the -- functions, and (hopefully) catch a bunch more errors at compile time. -- -- The basic API (and properties satisfied) are heavily influenced by -- Neil Mitchell's System.FilePath module. -- -- WARNING -- THE API IS NOT YET STABLE -- WARNING @package pathtype @version 0.0.1 -- | This module provides type-safe access to filepath manipulations. -- -- It is designed to be imported instead of System.FilePath and -- System.Directory. (It is intended to provide versions of -- functions from those modules which have equivalent functionality but -- are more typesafe). -- -- The heart of this module is the Path ar fd abstract type -- which represents file and directory paths. The idea is that there are -- two phantom type parameters - the first should be Abs or -- Rel, and the second File or Dir. A number of type -- synonyms are provided for common types: -- --
--   type AbsFile    = Path Abs File
--   type RelFile    = Path Rel File
--   type AbsDir     = Path Abs Dir
--   type RelDir     = Path Rel Dir
--   type RelPath fd = Path Rel fd
--   type DirPath ar = Path ar Dir
--   
-- -- The type of the combine (aka </>) function gives -- the idea: -- --
--   (</>) :: DirPath ar -> RelPath fd -> Path ar fd
--   
-- -- Together this enables us to give more meaningful types to a lot of the -- functions, and (hopefully) catch a bunch more errors at compile time. -- -- The basic API (and properties satisfied) are heavily influenced by -- Neil Mitchell's System.FilePath module. -- -- WARNING --- THE API IS NOT YET STABLE --- WARNING -- -- Ben Moseley - (c) Jan 2009 module System.Path -- | This is the main filepath abstract datatype data Path ar fd data Abs data Rel data File data Dir type AbsFile = Path Abs File type RelFile = Path Rel File type AbsDir = Path Abs Dir type RelDir = Path Rel Dir type AbsPath fd = Path Abs fd type RelPath fd = Path Rel fd type FilePath ar = Path ar File type DirPath ar = Path ar Dir -- | Convert the Path into a plain String. This is simply an -- alias for show. getPathString :: (AbsRelClass ar) => Path ar fd -> String rootDir :: AbsDir currentDir :: RelDir -- | Convert a String into a Path whose type is determined by -- its context. mkPath :: String -> Path ar fd mkRelFile :: String -> RelFile mkRelDir :: String -> RelDir mkAbsFile :: String -> AbsFile mkAbsDir :: String -> AbsDir mkRelPath :: String -> RelPath fd mkAbsPath :: String -> AbsPath fd mkFile :: String -> FilePath ar mkDir :: String -> DirPath ar -- | Examines the supplied string and constructs an absolute or relative -- path as appropriate. mkPathAbsOrRel :: String -> Either (AbsPath fd) (RelPath fd) -- | Searches for a file or directory with the supplied path string and -- returns a File or Dir path as appropriate. If neither -- exists at the supplied path, Nothing is returned. mkPathFileOrDir :: (AbsRelClass ar) => String -> IO (Maybe (Either (FilePath ar) (DirPath ar))) -- | Join an (absolute or relative) directory path with a relative (file or -- directory) path to form a new path. () :: DirPath ar -> RelPath fd -> Path ar fd -- | We only allow files (and not directories) to have extensions added by -- this function. This is because it's the vastly common case and an -- attempt to add one to a directory will - more often than not - -- represent an error. We don't however want to prevent the corresponding -- operation on directories, and so we provide a function that is more -- flexible: addFileOrDirExtension. (<.>) :: FilePath ar -> String -> FilePath ar -- | Add an extension, even if there is already one there. E.g. -- addExtension "foo.txt" "bat" -> "foo.txt.bat". -- --
--   > addExtension (mkFile "file.txt") "bib" == (mkFile "file.txt.bib")
--   > addExtension (mkFile "file.") ".bib" == (mkFile "file..bib")
--   > addExtension (mkFile "file") ".bib" == (mkFile "file.bib")
--   > takeFileName (addExtension (mkFile "") "ext") == mkFile ".ext"
--    Windows: addExtension "\\\\share" ".txt" == "\\\\share\\.txt"
--   
addExtension :: FilePath ar -> String -> FilePath ar -- | Join an (absolute or relative) directory path with a relative (file or -- directory) path to form a new path. combine :: DirPath ar -> RelPath fd -> Path ar fd -- | Remove last extension, and the "." preceding it. -- --
--   > dropExtension x == fst (splitExtension x)
--   
dropExtension :: FilePath ar -> FilePath ar -- | Drop all extensions -- --
--   > not $ hasExtension (dropExtensions x)
--   
dropExtensions :: FilePath ar -> FilePath ar dropFileName :: Path ar fd -> DirPath ar -- | Set the extension of a file, overwriting one if already present. -- --
--   > replaceExtension (mkFile "file.txt") ".bob" == (mkFile "file.bob")
--   > replaceExtension (mkFile "file.txt") "bob" == (mkFile "file.bob")
--   > replaceExtension (mkFile "file") ".bob" == (mkFile "file.bob")
--   > replaceExtension (mkFile "file.txt") "" == (mkFile "file")
--   > replaceExtension (mkFile "file.fred.bob") "txt" == (mkFile "file.fred.txt")
--   
replaceExtension :: FilePath ar -> String -> FilePath ar replaceBaseName :: Path ar fd -> String -> Path ar fd replaceDirectory :: Path ar1 fd -> DirPath ar2 -> Path ar2 fd replaceFileName :: Path ar fd -> String -> Path ar fd -- | Split on the extension. addExtension is the inverse. -- --
--   > uncurry (<.>) (splitExtension x) == x
--   > uncurry addExtension (splitExtension x) == x
--   > splitExtension (mkFile "file.txt") == (mkFile "file",".txt")
--   > splitExtension (mkFile "file") == (mkFile "file","")
--   > splitExtension (mkFile "file/file.txt") == (mkFile "file/file",".txt")
--   > splitExtension (mkFile "file.txt/boris") == (mkFile "file.txt/boris","")
--   > splitExtension (mkFile "file.txt/boris.ext") == (mkFile "file.txt/boris",".ext")
--   > splitExtension (mkFile "file/path.txt.bob.fred") == (mkFile "file/path.txt.bob",".fred")
--   
splitExtension :: FilePath ar -> (FilePath ar, String) -- | Split on all extensions -- --
--   > splitExtensions (mkFile "file.tar.gz") == (mkFile "file",".tar.gz")
--   
splitExtensions :: FilePath ar -> (FilePath ar, String) splitFileName :: Path ar fd -> (DirPath ar, RelPath fd) takeBaseName :: Path ar fd -> RelPath fd takeDirectory :: Path ar fd -> DirPath ar -- | Get the extension of a file, returns "" for no extension, -- .ext otherwise. -- --
--   > takeExtension x == snd (splitExtension x)
--   > takeExtension (addExtension x "ext") == ".ext"
--   > takeExtension (replaceExtension x "ext") == ".ext"
--   
takeExtension :: FilePath ar -> String -- | Get all extensions -- --
--   > takeExtensions (mkFile "file.tar.gz") == ".tar.gz"
--   
takeExtensions :: FilePath ar -> String takeFileName :: Path ar fd -> RelPath fd equalFilePath :: String -> String -> Bool -- | Constructs a Path from a list of components. joinPath :: [String] -> Path ar fd -- | Currently just transforms: -- --
--   > normalise (mkFile "/tmp/fred/./jim/./file") == mkFile "/tmp/fred/jim/file"
--   
normalise :: Path ar fd -> Path ar fd splitDirectories :: Path ar fd -> [String] splitPath :: Path ar fd -> [String] makeRelative :: AbsDir -> AbsPath fd -> RelPath fd isAbsolute :: (AbsRelClass ar) => Path ar fd -> Bool isAbsoluteString :: String -> Bool -- | Invariant - this should return True iff arg is of type Path Rel -- _ isRelative :: (AbsRelClass ar) => Path ar fd -> Bool isRelativeString :: String -> Bool -- | Does the given filename have an extension? -- --
--   > null (takeExtension x) == not (hasExtension x)
--   
hasExtension :: FilePath ar -> Bool -- | This is largely for System.FilePath compatability addTrailingPathSeparator :: String -> String -- | This is largely for System.FilePath compatability dropTrailingPathSeparator :: String -> String -- | File extension character -- --
--   > extSeparator == '.'
--   
extSeparator :: Char -- | This is largely for System.FilePath compatability hasTrailingPathSeparator :: String -> Bool -- | The character that separates directories. In the case where more than -- one character is possible, pathSeparator is the 'ideal' one. -- --
--    Windows: pathSeparator == '\\'
--    Posix:   pathSeparator ==  '/'
--   > isPathSeparator pathSeparator
--   
pathSeparator :: Char -- | The list of all possible separators. -- --
--    Windows: pathSeparators == ['\\', '/']
--    Posix:   pathSeparators == ['/']
--   > pathSeparator `elem` pathSeparators
--   
pathSeparators :: [Char] -- | The character that is used to separate the entries in the $PATH -- environment variable. -- --
--   Windows: searchPathSeparator == ';'
--   Posix:   searchPathSeparator == ':'
--   
searchPathSeparator :: Char -- | Is the character an extension character? -- --
--   > isExtSeparator a == (a == extSeparator)
--   
isExtSeparator :: Char -> Bool -- | Rather than using (== pathSeparator), use this. Test -- if something is a path separator. -- --
--   > isPathSeparator a == (a `elem` pathSeparators)
--   
isPathSeparator :: Char -> Bool -- | Is the character a file separator? -- --
--   > isSearchPathSeparator a == (a == searchPathSeparator)
--   
isSearchPathSeparator :: Char -> Bool -- | This is a more flexible variant of addExtension / -- . which can work with files or directories -- --
--   > addFileOrDirExtension (mkFile "/") "x" == (mkFile "/.x")
--   
addFileOrDirExtension :: Path ar fd -> String -> Path ar fd dropFileOrDirExtension :: Path ar fd -> Path ar fd dropFileOrDirExtensions :: Path ar fd -> Path ar fd splitFileOrDirExtension :: Path ar fd -> (Path ar fd, String) splitFileOrDirExtensions :: Path ar fd -> (Path ar fd, String) takeFileOrDirExtension :: Path ar fd -> String takeFileOrDirExtensions :: Path ar fd -> String getDirectoryContents :: (AbsRelClass ar) => DirPath ar -> IO ([AbsDir], [AbsFile]) -- | Retrieve the contents of a directory path (which may be relative) as -- absolute paths absDirectoryContents :: (AbsRelClass ar) => DirPath ar -> IO ([AbsDir], [AbsFile]) -- | Returns paths relative to the supplied (abs or relative) -- directory path. eg (for current working directory of -- /somewhere/cwd/): -- --
--   show (relDirectoryContents (mkRelDir "subDir1")) == (["subDir1A","subDir1B"],
--                                                        ["file1A","file1B"])
--   
relDirectoryContents :: (AbsRelClass ar) => DirPath ar -> IO ([RelDir], [RelFile]) instance Eq PathComponent instance Ord PathComponent instance Eq (Path ar fd) instance Ord (Path ar fd) instance Arbitrary (Path ar Dir) instance Arbitrary (Path ar File) instance Arbitrary PathComponent instance (AbsRelClass ar) => Read (Path ar fd) instance (AbsRelClass ar) => Show (Path ar fd) instance FileDirClass Dir instance FileDirClass File instance AbsRelClass Rel instance AbsRelClass Abs instance Show PathComponent