Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Abs
- data Rel
- data File
- data Dir
- toFilePath :: Path b t -> FilePath
- data Path b t
- callIO :: IO a -> ErrIO a
- type ErrIO = ExceptT Text IO
- class Eq (ExtensionType fp) => Extensions fp where
- type ExtensionType fp
- getExtension :: fp -> ExtensionType fp
- removeExtension :: fp -> fp
- addExtension :: ExtensionType fp -> fp -> fp
- (<.>) :: fp -> ExtensionType fp -> fp
- setExtension :: ExtensionType fp -> fp -> fp
- hasExtension :: ExtensionType fp -> fp -> Bool
- prop_add_has :: ExtensionType fp -> fp -> Bool
- prop_add_add_has :: ExtensionType fp -> ExtensionType fp -> fp -> Bool
- prop_set_get :: ExtensionType fp -> fp -> Bool
- class Filenames1 fp where
- getImmediateParentDir :: fp -> FilePath
- getParentDir :: fp -> FilePath
- getNakedFileName :: fp -> FilePath
- getNakedDir :: fp -> FilePath
- class Filenames4 fp file where
- type FileResultT4 fp file
- addDir :: fp -> file -> FileResultT4 fp file
- class Filenames5 dir fil res where
- stripPrefix :: dir -> fil -> Maybe res
- class Filenames3 fp file where
- type FileResultT fp file
- (</>), addFileName :: fp -> file -> FileResultT fp file
- class Filenames fp fr where
- getFileName :: fp -> fr
- newtype Extension = Extension FilePath
- takeBaseName' :: FilePath -> FilePath
- homeDir :: Path Abs Dir
- homeDir2 :: ErrIO (Path Abs Dir)
- currentDir :: ErrIO (Path Abs Dir)
- setCurrentDir :: Path Abs Dir -> ErrIO ()
- stripProperPrefix' :: Path b Dir -> Path b t -> ErrIO (Path Rel t)
- stripProperPrefixMaybe :: Path b Dir -> Path b t -> Maybe (Path Rel t)
- unPath :: a -> a
- makeRelFile :: FilePath -> Path Rel File
- makeRelDir :: FilePath -> Path Rel Dir
- makeAbsFile :: FilePath -> Path Abs File
- makeAbsDir :: FilePath -> Path Abs Dir
- makeRelFileT :: Text -> Path Rel File
- makeRelDirT :: Text -> Path Rel Dir
- makeAbsFileT :: Text -> Path Abs File
- makeAbsDirT :: Text -> Path Abs Dir
- toShortFilePath :: Path df ar -> FilePath
- unExtension :: Extension -> FilePath
- makeExtension :: FilePath -> Extension
- makeExtensionT :: Text -> Extension
- module Uniform.FileIOalgebra
- data IOMode
- closeFile2 :: Handle -> ErrIO ()
- listDir' :: (MonadIO m, MonadThrow m) => Path b Dir -> m ([Path Abs Dir], [Path Abs File])
- hGetLine :: Handle -> IO Text
- hPutStr :: Handle -> Text -> IO ()
Documentation
An absolute path.
Instances
Data Abs | |
Defined in Path.Posix gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Abs -> c Abs # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Abs # dataTypeOf :: Abs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Abs) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Abs) # gmapT :: (forall b. Data b => b -> b) -> Abs -> Abs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Abs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Abs -> r # gmapQ :: (forall d. Data d => d -> u) -> Abs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Abs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Abs -> m Abs # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Abs -> m Abs # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Abs -> m Abs # | |
FromJSON (Path Abs Dir) | |
FromJSON (Path Abs File) | |
FromJSONKey (Path Abs Dir) | |
Defined in Path.Posix | |
FromJSONKey (Path Abs File) | |
Defined in Path.Posix | |
Read (Path Abs Dir) Source # | |
Read (Path Abs File) Source # | |
Show (Path Abs Dir) Source # | |
Show (Path Abs File) Source # | |
Zeros (Path Abs Dir) Source # | |
Zeros (Path Abs File) Source # | |
DirOps (Path Abs Dir) Source # | |
Defined in Uniform.FileStrings doesDirExist' :: Path Abs Dir -> ErrIO Bool Source # createDir' :: Path Abs Dir -> ErrIO () Source # createDirIfMissing' :: Path Abs Dir -> ErrIO () Source # renameDir' :: Path Abs Dir -> Path Abs Dir -> ErrIO () Source # getDirectoryDirs' :: Path Abs Dir -> ErrIO [Path Abs Dir] Source # getDirectoryDirsNonHidden' :: Path Abs Dir -> ErrIO [Path Abs Dir] Source # copyDirRecursive :: Path Abs Dir -> Path Abs Dir -> ErrIO () Source # | |
FileOps2a (Path Abs Dir) (Path Abs File) Source # | |
A relative path; one without a root. Note that a ..
path component to
represent the parent directory is not allowed by this library.
Instances
A file path.
Instances
A directory path.
Instances
toFilePath :: Path b t -> FilePath #
Convert to a FilePath
type.
All directories have a trailing slash, so if you want no trailing
slash, you can use dropTrailingPathSeparator
from
the filepath package.
Path of some base and type.
The type variables are:
b
— base, the base location of the path; absolute or relative.t
— type, whether file or directory.
Internally is a string. The string can be of two formats only:
- File format:
file.txt
,foo/bar.txt
,/foo/bar.txt
- Directory format:
foo/
,/foo/bar/
All directories end in a trailing separator. There are no duplicate
path separators //
, no ..
, no ./
, no ~/
, etc.
Instances
class Eq (ExtensionType fp) => Extensions fp where Source #
type ExtensionType fp Source #
getExtension :: fp -> ExtensionType fp Source #
removeExtension :: fp -> fp Source #
addExtension :: ExtensionType fp -> fp -> fp Source #
(<.>) :: fp -> ExtensionType fp -> fp Source #
setExtension :: ExtensionType fp -> fp -> fp Source #
hasExtension :: ExtensionType fp -> fp -> Bool Source #
prop_add_has :: ExtensionType fp -> fp -> Bool Source #
prop_add_add_has :: ExtensionType fp -> ExtensionType fp -> fp -> Bool Source #
prop_set_get :: ExtensionType fp -> fp -> Bool Source #
Instances
class Filenames1 fp where Source #
getImmediateParentDir :: fp -> FilePath Source #
gets the name of the dir immediately above
getParentDir :: fp -> FilePath Source #
the parent dir of file
getNakedFileName :: fp -> FilePath Source #
filename without extension
getNakedDir :: fp -> FilePath Source #
get the last dir
Instances
Filenames1 FilePath Source # | |
Defined in Uniform.Filenames getImmediateParentDir :: FilePath -> FilePath Source # getParentDir :: FilePath -> FilePath Source # getNakedFileName :: FilePath -> FilePath Source # getNakedDir :: FilePath -> FilePath Source # | |
Filenames1 (Path ar Dir) Source # | |
Defined in Uniform.Filenames | |
Filenames1 (Path ar File) Source # | |
Defined in Uniform.Filenames |
class Filenames4 fp file where Source #
type FileResultT4 fp file Source #
addDir :: fp -> file -> FileResultT4 fp file Source #
Instances
Filenames4 FilePath FilePath Source # | |
Defined in Uniform.Filenames type FileResultT4 FilePath FilePath Source # | |
Filenames4 (Path b Dir) FilePath Source # | |
Filenames4 (Path b Dir) (Path Rel t) Source # | |
class Filenames5 dir fil res where Source #
stripPrefix :: dir -> fil -> Maybe res Source #
strip the
class Filenames3 fp file where Source #
type FileResultT fp file Source #
(</>) :: fp -> file -> FileResultT fp file Source #
addFileName :: fp -> file -> FileResultT fp file Source #
Instances
Filenames3 FilePath FilePath Source # | |
Defined in Uniform.Filenames type FileResultT FilePath FilePath Source # | |
Filenames3 (Path b Dir) FilePath Source # | |
Filenames3 (Path b Dir) (Path Rel t) Source # | |
takeBaseName' :: FilePath -> FilePath Source #
toShortFilePath :: Path df ar -> FilePath Source #
unExtension :: Extension -> FilePath Source #
makeExtension :: FilePath -> Extension Source #
makeExtensionT :: Text -> Extension Source #
module Uniform.FileIOalgebra
See openFile
closeFile2 :: Handle -> ErrIO () Source #