uniform-fileio-0.1.2: Uniform file handling operations
Safe HaskellNone
LanguageHaskell2010

Uniform.Filenames

Description

the operations on filenames and extensions uses the Path library, but wraps it in Path (to construct a read) is a class except for the make

Synopsis

Documentation

class Eq (ExtensionType fp) => Extensions fp where Source #

Associated Types

type ExtensionType fp Source #

Instances

Instances details
Extensions FilePath Source # 
Instance details

Defined in Uniform.Filenames

Associated Types

type ExtensionType FilePath Source #

Extensions (Path ar File) Source # 
Instance details

Defined in Uniform.Filenames

Associated Types

type ExtensionType (Path ar File) Source #

class Filenames1 fp where Source #

Methods

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

class Filenames4 fp file where Source #

Associated Types

type FileResultT4 fp file Source #

Methods

addDir :: fp -> file -> FileResultT4 fp file Source #

Instances

Instances details
Filenames4 FilePath FilePath Source # 
Instance details

Defined in Uniform.Filenames

Associated Types

type FileResultT4 FilePath FilePath Source #

Filenames4 (Path b Dir) FilePath Source # 
Instance details

Defined in Uniform.Filenames

Associated Types

type FileResultT4 (Path b Dir) FilePath Source #

Filenames4 (Path b Dir) (Path Rel t) Source # 
Instance details

Defined in Uniform.Filenames

Associated Types

type FileResultT4 (Path b Dir) (Path Rel t) Source #

Methods

addDir :: Path b Dir -> Path Rel t -> FileResultT4 (Path b Dir) (Path Rel t) Source #

class Filenames5 dir fil res where Source #

Methods

stripPrefix :: dir -> fil -> Maybe res Source #

strip the

Instances

Instances details
Filenames5 (Path b Dir) (Path b t) (Path Rel t) Source # 
Instance details

Defined in Uniform.Filenames

Methods

stripPrefix :: Path b Dir -> Path b t -> Maybe (Path Rel t) Source #

class Filenames3 fp file where Source #

Minimal complete definition

addFileName

Associated Types

type FileResultT fp file Source #

Methods

(</>) :: fp -> file -> FileResultT fp file Source #

addFileName :: fp -> file -> FileResultT fp file Source #

Instances

Instances details
Filenames3 FilePath FilePath Source # 
Instance details

Defined in Uniform.Filenames

Associated Types

type FileResultT FilePath FilePath Source #

Filenames3 (Path b Dir) FilePath Source # 
Instance details

Defined in Uniform.Filenames

Associated Types

type FileResultT (Path b Dir) FilePath Source #

Filenames3 (Path b Dir) (Path Rel t) Source # 
Instance details

Defined in Uniform.Filenames

Associated Types

type FileResultT (Path b Dir) (Path Rel t) Source #

class Filenames fp fr where Source #

Methods

getFileName :: fp -> fr Source #

Instances

Instances details
Filenames FilePath FilePath Source # 
Instance details

Defined in Uniform.Filenames

Filenames (Path ar File) (Path Rel File) Source # 
Instance details

Defined in Uniform.Filenames

unPath :: a -> a Source #

callIO :: (MonadError m, MonadIO m, ErrorType m ~ Text) => IO a -> m a #

this is using catch to grab all errors

data Abs #

An absolute path.

Instances

Instances details
Data Abs 
Instance details

Defined in Path.Posix

Methods

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 #

toConstr :: Abs -> Constr #

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 #

Read (Path Abs File) Source # 
Instance details

Defined in Uniform.PathShowCase

Read (Path Abs Dir) Source # 
Instance details

Defined in Uniform.PathShowCase

Show (Path Abs File) Source # 
Instance details

Defined in Uniform.PathShowCase

Show (Path Abs Dir) Source # 
Instance details

Defined in Uniform.PathShowCase

FromJSON (Path Abs File) 
Instance details

Defined in Path.Posix

FromJSON (Path Abs Dir) 
Instance details

Defined in Path.Posix

FromJSONKey (Path Abs File) 
Instance details

Defined in Path.Posix

FromJSONKey (Path Abs Dir) 
Instance details

Defined in Path.Posix

Zeros (Path Abs File) Source # 
Instance details

Defined in Uniform.Filenames

Zeros (Path Abs Dir) Source # 
Instance details

Defined in Uniform.Filenames

DirOps (Path Abs Dir) Source # 
Instance details

Defined in Uniform.FileStrings

FileOps2a (Path Abs Dir) (Path Abs File) Source # 
Instance details

Defined in Uniform.FileStrings

data Rel #

A relative path; one without a root. Note that a .. path component to represent the parent directory is not allowed by this library.

Instances

Instances details
Data Rel 
Instance details

Defined in Path.Posix

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Rel -> c Rel #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Rel #

toConstr :: Rel -> Constr #

dataTypeOf :: Rel -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Rel) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Rel) #

gmapT :: (forall b. Data b => b -> b) -> Rel -> Rel #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Rel -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Rel -> r #

gmapQ :: (forall d. Data d => d -> u) -> Rel -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Rel -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Rel -> m Rel #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Rel -> m Rel #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Rel -> m Rel #

Read (Path Rel File) Source # 
Instance details

Defined in Uniform.PathShowCase

Read (Path Rel Dir) Source # 
Instance details

Defined in Uniform.PathShowCase

Show (Path Rel File) Source # 
Instance details

Defined in Uniform.PathShowCase

Show (Path Rel Dir) Source # 
Instance details

Defined in Uniform.PathShowCase

FromJSON (Path Rel File) 
Instance details

Defined in Path.Posix

FromJSON (Path Rel Dir) 
Instance details

Defined in Path.Posix

FromJSONKey (Path Rel File) 
Instance details

Defined in Path.Posix

FromJSONKey (Path Rel Dir) 
Instance details

Defined in Path.Posix

Zeros (Path Rel File) Source # 
Instance details

Defined in Uniform.Filenames

Zeros (Path Rel Dir) Source # 
Instance details

Defined in Uniform.Filenames

DirOps (Path Rel Dir) Source # 
Instance details

Defined in Uniform.FileStrings

Filenames4 (Path b Dir) (Path Rel t) Source # 
Instance details

Defined in Uniform.Filenames

Associated Types

type FileResultT4 (Path b Dir) (Path Rel t) Source #

Methods

addDir :: Path b Dir -> Path Rel t -> FileResultT4 (Path b Dir) (Path Rel t) Source #

Filenames3 (Path b Dir) (Path Rel t) Source # 
Instance details

Defined in Uniform.Filenames

Associated Types

type FileResultT (Path b Dir) (Path Rel t) Source #

Filenames (Path ar File) (Path Rel File) Source # 
Instance details

Defined in Uniform.Filenames

FileOps2a (Path Rel Dir) (Path Rel File) Source # 
Instance details

Defined in Uniform.FileStrings

Filenames5 (Path b Dir) (Path b t) (Path Rel t) Source # 
Instance details

Defined in Uniform.Filenames

Methods

stripPrefix :: Path b Dir -> Path b t -> Maybe (Path Rel t) Source #

type FileResultT4 (Path b Dir) (Path Rel t) Source # 
Instance details

Defined in Uniform.Filenames

type FileResultT4 (Path b Dir) (Path Rel t) = Path b t
type FileResultT (Path b Dir) (Path Rel t) Source # 
Instance details

Defined in Uniform.Filenames

type FileResultT (Path b Dir) (Path Rel t) = Path b t

data File #

A file path.

Instances

Instances details
Data File 
Instance details

Defined in Path.Posix

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> File -> c File #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c File #

toConstr :: File -> Constr #

dataTypeOf :: File -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c File) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c File) #

gmapT :: (forall b. Data b => b -> b) -> File -> File #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> File -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> File -> r #

gmapQ :: (forall d. Data d => d -> u) -> File -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> File -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> File -> m File #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> File -> m File #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> File -> m File #

FromJSON (SomeBase File) 
Instance details

Defined in Path.Posix

Read (Path Abs File) Source # 
Instance details

Defined in Uniform.PathShowCase

Read (Path Rel File) Source # 
Instance details

Defined in Uniform.PathShowCase

Show (Path Abs File) Source # 
Instance details

Defined in Uniform.PathShowCase

Show (Path Rel File) Source # 
Instance details

Defined in Uniform.PathShowCase

FromJSON (Path Abs File) 
Instance details

Defined in Path.Posix

FromJSON (Path Rel File) 
Instance details

Defined in Path.Posix

FromJSONKey (Path Abs File) 
Instance details

Defined in Path.Posix

FromJSONKey (Path Rel File) 
Instance details

Defined in Path.Posix

AnyPath (Path b File) 
Instance details

Defined in Path.IO

Associated Types

type AbsPath (Path b File) #

type RelPath (Path b File) #

Zeros (Path Abs File) Source # 
Instance details

Defined in Uniform.Filenames

Zeros (Path Rel File) Source # 
Instance details

Defined in Uniform.Filenames

Extensions (Path ar File) Source # 
Instance details

Defined in Uniform.Filenames

Associated Types

type ExtensionType (Path ar File) Source #

Filenames1 (Path ar File) Source # 
Instance details

Defined in Uniform.Filenames

Show (Path ar File) => FileOps (Path ar File) Source # 
Instance details

Defined in Uniform.FileStrings

Show (Path ar File) => FileOps2 (Path ar File) ByteString Source # 
Instance details

Defined in Uniform.FileStrings

Show (Path ar File) => FileOps2 (Path ar File) Text Source # 
Instance details

Defined in Uniform.FileStrings

Show (Path ar File) => FileOps2 (Path ar File) String Source # 
Instance details

Defined in Uniform.FileStrings

Filenames (Path ar File) (Path Rel File) Source # 
Instance details

Defined in Uniform.Filenames

FileOps2a (Path Abs Dir) (Path Abs File) Source # 
Instance details

Defined in Uniform.FileStrings

FileOps2a (Path Rel Dir) (Path Rel File) Source # 
Instance details

Defined in Uniform.FileStrings

type RelPath (Path b File) 
Instance details

Defined in Path.IO

type AbsPath (Path b File) 
Instance details

Defined in Path.IO

type ExtensionType (Path ar File) Source # 
Instance details

Defined in Uniform.Filenames

data Dir #

A directory path.

Instances

Instances details
Data Dir 
Instance details

Defined in Path.Posix

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Dir -> c Dir #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Dir #

toConstr :: Dir -> Constr #

dataTypeOf :: Dir -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Dir) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Dir) #

gmapT :: (forall b. Data b => b -> b) -> Dir -> Dir #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Dir -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Dir -> r #

gmapQ :: (forall d. Data d => d -> u) -> Dir -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Dir -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Dir -> m Dir #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Dir -> m Dir #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Dir -> m Dir #

FromJSON (SomeBase Dir) 
Instance details

Defined in Path.Posix

Read (Path Abs Dir) Source # 
Instance details

Defined in Uniform.PathShowCase

Read (Path Rel Dir) Source # 
Instance details

Defined in Uniform.PathShowCase

Show (Path Abs Dir) Source # 
Instance details

Defined in Uniform.PathShowCase

Show (Path Rel Dir) Source # 
Instance details

Defined in Uniform.PathShowCase

FromJSON (Path Abs Dir) 
Instance details

Defined in Path.Posix

FromJSON (Path Rel Dir) 
Instance details

Defined in Path.Posix

FromJSONKey (Path Abs Dir) 
Instance details

Defined in Path.Posix

FromJSONKey (Path Rel Dir) 
Instance details

Defined in Path.Posix

AnyPath (Path b Dir) 
Instance details

Defined in Path.IO

Associated Types

type AbsPath (Path b Dir) #

type RelPath (Path b Dir) #

Zeros (Path Abs Dir) Source # 
Instance details

Defined in Uniform.Filenames

Zeros (Path Rel Dir) Source # 
Instance details

Defined in Uniform.Filenames

Filenames1 (Path ar Dir) Source # 
Instance details

Defined in Uniform.Filenames

DirOps (Path Abs Dir) Source # 
Instance details

Defined in Uniform.FileStrings

DirOps (Path Rel Dir) Source # 
Instance details

Defined in Uniform.FileStrings

Filenames4 (Path b Dir) FilePath Source # 
Instance details

Defined in Uniform.Filenames

Associated Types

type FileResultT4 (Path b Dir) FilePath Source #

Filenames3 (Path b Dir) FilePath Source # 
Instance details

Defined in Uniform.Filenames

Associated Types

type FileResultT (Path b Dir) FilePath Source #

Filenames4 (Path b Dir) (Path Rel t) Source # 
Instance details

Defined in Uniform.Filenames

Associated Types

type FileResultT4 (Path b Dir) (Path Rel t) Source #

Methods

addDir :: Path b Dir -> Path Rel t -> FileResultT4 (Path b Dir) (Path Rel t) Source #

Filenames3 (Path b Dir) (Path Rel t) Source # 
Instance details

Defined in Uniform.Filenames

Associated Types

type FileResultT (Path b Dir) (Path Rel t) Source #

FileOps2a (Path Abs Dir) (Path Abs File) Source # 
Instance details

Defined in Uniform.FileStrings

FileOps2a (Path Rel Dir) (Path Rel File) Source # 
Instance details

Defined in Uniform.FileStrings

Filenames5 (Path b Dir) (Path b t) (Path Rel t) Source # 
Instance details

Defined in Uniform.Filenames

Methods

stripPrefix :: Path b Dir -> Path b t -> Maybe (Path Rel t) Source #

type RelPath (Path b Dir) 
Instance details

Defined in Path.IO

type RelPath (Path b Dir) = Path Rel Dir
type AbsPath (Path b Dir) 
Instance details

Defined in Path.IO

type AbsPath (Path b Dir) = Path Abs Dir
type FileResultT4 (Path b Dir) FilePath Source # 
Instance details

Defined in Uniform.Filenames

type FileResultT (Path b Dir) FilePath Source # 
Instance details

Defined in Uniform.Filenames

type FileResultT4 (Path b Dir) (Path Rel t) Source # 
Instance details

Defined in Uniform.Filenames

type FileResultT4 (Path b Dir) (Path Rel t) = Path b t
type FileResultT (Path b Dir) (Path Rel t) Source # 
Instance details

Defined in Uniform.Filenames

type FileResultT (Path b Dir) (Path Rel t) = Path b t

data Path b t #

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:

  1. File format: file.txt, foo/bar.txt, /foo/bar.txt
  2. Directory format: foo/, /foo/bar/

All directories end in a trailing separator. There are no duplicate path separators //, no .., no ./, no ~/, etc.

Instances

Instances details
(Typeable b, Typeable t) => Lift (Path b t :: Type) 
Instance details

Defined in Path.Internal.Posix

Methods

lift :: Path b t -> Q Exp #

liftTyped :: Path b t -> Q (TExp (Path b t)) #

Eq (Path b t)

String equality.

The following property holds:

show x == show y ≡ x == y
Instance details

Defined in Path.Internal.Posix

Methods

(==) :: Path b t -> Path b t -> Bool #

(/=) :: Path b t -> Path b t -> Bool #

(Data b, Data t) => Data (Path b t) 
Instance details

Defined in Path.Internal.Posix

Methods

gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Path b t -> c (Path b t) #

gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Path b t) #

toConstr :: Path b t -> Constr #

dataTypeOf :: Path b t -> DataType #

dataCast1 :: Typeable t0 => (forall d. Data d => c (t0 d)) -> Maybe (c (Path b t)) #

dataCast2 :: Typeable t0 => (forall d e. (Data d, Data e) => c (t0 d e)) -> Maybe (c (Path b t)) #

gmapT :: (forall b0. Data b0 => b0 -> b0) -> Path b t -> Path b t #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Path b t -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Path b t -> r #

gmapQ :: (forall d. Data d => d -> u) -> Path b t -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Path b t -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Path b t -> m (Path b t) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Path b t -> m (Path b t) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Path b t -> m (Path b t) #

Ord (Path b t)

String ordering.

The following property holds:

show x `compare` show y ≡ x `compare` y
Instance details

Defined in Path.Internal.Posix

Methods

compare :: Path b t -> Path b t -> Ordering #

(<) :: Path b t -> Path b t -> Bool #

(<=) :: Path b t -> Path b t -> Bool #

(>) :: Path b t -> Path b t -> Bool #

(>=) :: Path b t -> Path b t -> Bool #

max :: Path b t -> Path b t -> Path b t #

min :: Path b t -> Path b t -> Path b t #

Read (Path Abs File) Source # 
Instance details

Defined in Uniform.PathShowCase

Read (Path Abs Dir) Source # 
Instance details

Defined in Uniform.PathShowCase

Read (Path Rel File) Source # 
Instance details

Defined in Uniform.PathShowCase

Read (Path Rel Dir) Source # 
Instance details

Defined in Uniform.PathShowCase

Show (Path b t)

Same as 'show . Path.toFilePath'.

The following property holds:

x == y ≡ show x == show y
Instance details

Defined in Path.Internal.Posix

Methods

showsPrec :: Int -> Path b t -> ShowS #

show :: Path b t -> String #

showList :: [Path b t] -> ShowS #

Show (Path Abs File) Source # 
Instance details

Defined in Uniform.PathShowCase

Show (Path Abs Dir) Source # 
Instance details

Defined in Uniform.PathShowCase

Show (Path Rel File) Source # 
Instance details

Defined in Uniform.PathShowCase

Show (Path Rel Dir) Source # 
Instance details

Defined in Uniform.PathShowCase

Generic (Path b t) 
Instance details

Defined in Path.Internal.Posix

Associated Types

type Rep (Path b t) :: Type -> Type #

Methods

from :: Path b t -> Rep (Path b t) x #

to :: Rep (Path b t) x -> Path b t #

Hashable (Path b t) 
Instance details

Defined in Path.Internal.Posix

Methods

hashWithSalt :: Int -> Path b t -> Int #

hash :: Path b t -> Int #

ToJSON (Path b t) 
Instance details

Defined in Path.Internal.Posix

Methods

toJSON :: Path b t -> Value #

toEncoding :: Path b t -> Encoding #

toJSONList :: [Path b t] -> Value #

toEncodingList :: [Path b t] -> Encoding #

ToJSONKey (Path b t) 
Instance details

Defined in Path.Internal.Posix

FromJSON (Path Abs File) 
Instance details

Defined in Path.Posix

FromJSON (Path Abs Dir) 
Instance details

Defined in Path.Posix

FromJSON (Path Rel File) 
Instance details

Defined in Path.Posix

FromJSON (Path Rel Dir) 
Instance details

Defined in Path.Posix

FromJSONKey (Path Abs File) 
Instance details

Defined in Path.Posix

FromJSONKey (Path Abs Dir) 
Instance details

Defined in Path.Posix

FromJSONKey (Path Rel File) 
Instance details

Defined in Path.Posix

FromJSONKey (Path Rel Dir) 
Instance details

Defined in Path.Posix

NFData (Path b t) 
Instance details

Defined in Path.Internal.Posix

Methods

rnf :: Path b t -> () #

AnyPath (Path b File) 
Instance details

Defined in Path.IO

Associated Types

type AbsPath (Path b File) #

type RelPath (Path b File) #

AnyPath (Path b Dir) 
Instance details

Defined in Path.IO

Associated Types

type AbsPath (Path b Dir) #

type RelPath (Path b Dir) #

Zeros (Path Abs File) Source # 
Instance details

Defined in Uniform.Filenames

Zeros (Path Abs Dir) Source # 
Instance details

Defined in Uniform.Filenames

Zeros (Path Rel File) Source # 
Instance details

Defined in Uniform.Filenames

Zeros (Path Rel Dir) Source # 
Instance details

Defined in Uniform.Filenames

NiceStrings (Path a b) Source # 
Instance details

Defined in Uniform.PathShowCase

Methods

shownice :: Path a b -> Text #

showNice :: Path a b -> Text #

showlong :: Path a b -> Text #

PrettyStrings (Path a b) Source # 
Instance details

Defined in Uniform.PathShowCase

Methods

showPretty :: Path a b -> Text #

Extensions (Path ar File) Source # 
Instance details

Defined in Uniform.Filenames

Associated Types

type ExtensionType (Path ar File) Source #

Filenames1 (Path ar Dir) Source # 
Instance details

Defined in Uniform.Filenames

Filenames1 (Path ar File) Source # 
Instance details

Defined in Uniform.Filenames

Show (Path ar File) => FileOps (Path ar File) Source # 
Instance details

Defined in Uniform.FileStrings

DirOps (Path Abs Dir) Source # 
Instance details

Defined in Uniform.FileStrings

DirOps (Path Rel Dir) Source # 
Instance details

Defined in Uniform.FileStrings

FileSystemOps (Path ar df) Source # 
Instance details

Defined in Uniform.FileStrings

Filenames4 (Path b Dir) FilePath Source # 
Instance details

Defined in Uniform.Filenames

Associated Types

type FileResultT4 (Path b Dir) FilePath Source #

Filenames3 (Path b Dir) FilePath Source # 
Instance details

Defined in Uniform.Filenames

Associated Types

type FileResultT (Path b Dir) FilePath Source #

Show (Path ar File) => FileOps2 (Path ar File) ByteString Source # 
Instance details

Defined in Uniform.FileStrings

Show (Path ar File) => FileOps2 (Path ar File) Text Source # 
Instance details

Defined in Uniform.FileStrings

Show (Path ar File) => FileOps2 (Path ar File) String Source # 
Instance details

Defined in Uniform.FileStrings

Filenames4 (Path b Dir) (Path Rel t) Source # 
Instance details

Defined in Uniform.Filenames

Associated Types

type FileResultT4 (Path b Dir) (Path Rel t) Source #

Methods

addDir :: Path b Dir -> Path Rel t -> FileResultT4 (Path b Dir) (Path Rel t) Source #

Filenames3 (Path b Dir) (Path Rel t) Source # 
Instance details

Defined in Uniform.Filenames

Associated Types

type FileResultT (Path b Dir) (Path Rel t) Source #

Filenames (Path ar File) (Path Rel File) Source # 
Instance details

Defined in Uniform.Filenames

FileOps2a (Path Abs Dir) (Path Abs File) Source # 
Instance details

Defined in Uniform.FileStrings

FileOps2a (Path Rel Dir) (Path Rel File) Source # 
Instance details

Defined in Uniform.FileStrings

Filenames5 (Path b Dir) (Path b t) (Path Rel t) Source # 
Instance details

Defined in Uniform.Filenames

Methods

stripPrefix :: Path b Dir -> Path b t -> Maybe (Path Rel t) Source #

type Rep (Path b t) 
Instance details

Defined in Path.Internal.Posix

type Rep (Path b t) = D1 ('MetaData "Path" "Path.Internal.Posix" "path-0.9.2-DP3yj10INJZBwr6c0cEvTX" 'True) (C1 ('MetaCons "Path" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath)))
type RelPath (Path b Dir) 
Instance details

Defined in Path.IO

type RelPath (Path b Dir) = Path Rel Dir
type RelPath (Path b File) 
Instance details

Defined in Path.IO

type AbsPath (Path b Dir) 
Instance details

Defined in Path.IO

type AbsPath (Path b Dir) = Path Abs Dir
type AbsPath (Path b File) 
Instance details

Defined in Path.IO

type ExtensionType (Path ar File) Source # 
Instance details

Defined in Uniform.Filenames

type FileResultT4 (Path b Dir) FilePath Source # 
Instance details

Defined in Uniform.Filenames

type FileResultT (Path b Dir) FilePath Source # 
Instance details

Defined in Uniform.Filenames

type FileResultT4 (Path b Dir) (Path Rel t) Source # 
Instance details

Defined in Uniform.Filenames

type FileResultT4 (Path b Dir) (Path Rel t) = Path b t
type FileResultT (Path b Dir) (Path Rel t) Source # 
Instance details

Defined in Uniform.Filenames

type FileResultT (Path b Dir) (Path Rel t) = Path b t

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.

Orphan instances

Zeros (Path Abs File) Source # 
Instance details

Zeros (Path Abs Dir) Source # 
Instance details

Zeros (Path Rel File) Source # 
Instance details

Zeros (Path Rel Dir) Source # 
Instance details