polysemy-path-0.2.1.0: Polysemy versions of Path functions.
LicenseMIT
Maintainerdan.firth@homotopic.tech
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Polysemy.Path

Description

Polysemy versions of functions in the path library.

Synopsis

Documentation

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 #

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 #

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 -> () #

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.0-1XaDMm6hRGZI4vY8hKM6Gz" 'True) (C1 ('MetaCons "Path" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath)))

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
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

data Abs #

An absolute path.

Instances

Instances details
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

data File #

A file path.

Instances

Instances details
FromJSON (SomeBase File) 
Instance details

Defined in Path.Posix

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

data Dir #

A directory path.

Instances

Instances details
FromJSON (SomeBase Dir) 
Instance details

Defined in Path.Posix

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

data SomeBase t #

Path of some type. t represents the type, whether file or directory. Pattern match to find whether the path is absolute or relative.

Instances

Instances details
Eq (SomeBase t) 
Instance details

Defined in Path.Posix

Methods

(==) :: SomeBase t -> SomeBase t -> Bool #

(/=) :: SomeBase t -> SomeBase t -> Bool #

Ord (SomeBase t) 
Instance details

Defined in Path.Posix

Methods

compare :: SomeBase t -> SomeBase t -> Ordering #

(<) :: SomeBase t -> SomeBase t -> Bool #

(<=) :: SomeBase t -> SomeBase t -> Bool #

(>) :: SomeBase t -> SomeBase t -> Bool #

(>=) :: SomeBase t -> SomeBase t -> Bool #

max :: SomeBase t -> SomeBase t -> SomeBase t #

min :: SomeBase t -> SomeBase t -> SomeBase t #

Show (SomeBase t) 
Instance details

Defined in Path.Posix

Methods

showsPrec :: Int -> SomeBase t -> ShowS #

show :: SomeBase t -> String #

showList :: [SomeBase t] -> ShowS #

Generic (SomeBase t) 
Instance details

Defined in Path.Posix

Associated Types

type Rep (SomeBase t) :: Type -> Type #

Methods

from :: SomeBase t -> Rep (SomeBase t) x #

to :: Rep (SomeBase t) x -> SomeBase t #

Hashable (SomeBase t) 
Instance details

Defined in Path.Posix

Methods

hashWithSalt :: Int -> SomeBase t -> Int #

hash :: SomeBase t -> Int #

ToJSON (SomeBase t) 
Instance details

Defined in Path.Posix

FromJSON (SomeBase File) 
Instance details

Defined in Path.Posix

FromJSON (SomeBase Dir) 
Instance details

Defined in Path.Posix

NFData (SomeBase t) 
Instance details

Defined in Path.Posix

Methods

rnf :: SomeBase t -> () #

type Rep (SomeBase t) 
Instance details

Defined in Path.Posix

type Rep (SomeBase t) = D1 ('MetaData "SomeBase" "Path.Posix" "path-0.9.0-1XaDMm6hRGZI4vY8hKM6Gz" 'False) (C1 ('MetaCons "Abs" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Path Abs t))) :+: C1 ('MetaCons "Rel" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Path Rel t))))

data PathException #

Exceptions that can occur during path operations.

Since: path-0.6.0

absdir :: QuasiQuoter #

Construct a Path Abs Dir using QuasiQuotes.

[absdir|/|]

[absdir|/home/chris|]

Remember: due to the nature of absolute paths a path like [absdir|/home/chris|] may compile on your platform, but it may not compile on another platform (Windows).

Since: path-0.5.13

reldir :: QuasiQuoter #

Construct a Path Rel Dir using QuasiQuotes.

[absdir|/home|]</>[reldir|chris|]

Since: path-0.5.13

absfile :: QuasiQuoter #

Construct a Path Abs File using QuasiQuotes.

[absfile|/home/chris/foo.txt|]

Remember: due to the nature of absolute paths a path like [absdir|/home/chris/foo.txt|] may compile on your platform, but it may not compile on another platform (Windows).

Since: path-0.5.13

relfile :: QuasiQuoter #

Construct a Path Rel File using QuasiQuotes.

[absdir|/home/chris|]</>[relfile|foo.txt|]

Since: path-0.5.13

(</>) :: Path b Dir -> Path Rel t -> Path b t infixr 5 #

Append two paths.

The following cases are valid and the equalities hold:

$(mkAbsDir x) </> $(mkRelDir y) = $(mkAbsDir (x ++ "/" ++ y))
$(mkAbsDir x) </> $(mkRelFile y) = $(mkAbsFile (x ++ "/" ++ y))
$(mkRelDir x) </> $(mkRelDir y) = $(mkRelDir (x ++ "/" ++ y))
$(mkRelDir x) </> $(mkRelFile y) = $(mkRelFile (x ++ "/" ++ y))

The following are proven not possible to express:

$(mkAbsFile …) </> x
$(mkRelFile …) </> x
x </> $(mkAbsFile …)
x </> $(mkAbsDir …)

stripProperPrefix :: Members '[Error PathException] r => Path b Dir -> Path b t -> Sem r (Path Rel t) Source #

Polysemy version of stripProperPrefix.

Since: 0.1.0.0

isProperPrefixOf :: Path b Dir -> Path b t -> Bool #

Determines if the path in the first parameter is a proper prefix of the path in the second parameter.

The following properties hold:

not (x `isProperPrefixOf` x)
x `isProperPrefixOf` (x </> y)

Since: path-0.6.0

parent :: Path b t -> Path b Dir #

Take the parent path component from a path.

The following properties hold:

parent (x </> y) == x
parent "/x" == "/"
parent "x" == "."

On the root (absolute or relative), getting the parent is idempotent:

parent "/" = "/"
parent "." = "."

filename :: Path b File -> Path Rel File #

Extract the file part of a path.

The following properties hold:

filename (p </> a) == filename a

dirname :: Path b Dir -> Path Rel Dir #

Extract the last directory name of a path.

The following properties hold:

dirname $(mkRelDir ".") == $(mkRelDir ".")
dirname (p </> a) == dirname a

addExtension :: Members '[Error PathException] r => String -> Path b File -> Sem r (Path b File) Source #

Polysemy version of addExtension.

Since: 0.2.0.0

splitExtension :: Members '[Error PathException] r => Path b File -> Sem r (Path b File, String) Source #

Polysemy version of splitExtension.

Since: 0.2.0.0

fileExtension :: Members '[Error PathException] r => Path b File -> Sem r String Source #

Polysemy version of fileExtension.

Since: 0.2.0.0

replaceExtension :: Members '[Error PathException] r => String -> Path b File -> Sem r (Path b File) Source #

Polysemy version of replaceExtension.

Since: 0.2.0.0

parseRelFile :: Members '[Error PathException] r => FilePath -> Sem r (Path Rel File) Source #

Polysemy version of parseRelFile.

Since: 0.1.0.0

parseAbsFile :: Members '[Error PathException] r => FilePath -> Sem r (Path Abs File) Source #

Polysemy version of parseAbsFile.

Since: 0.1.0.0

parseRelDir :: Members '[Error PathException] r => FilePath -> Sem r (Path Rel Dir) Source #

Polysemy version of parseRelDir.

Since: 0.1.0.0

parseAbsDir :: Members '[Error PathException] r => FilePath -> Sem r (Path Abs Dir) Source #

Polysemy version of parseAbsDir.

Since: 0.1.0.0

parseSomeDir :: Members '[Error PathException] r => FilePath -> Sem r (SomeBase Dir) Source #

Polysemy version of parseSomeDir.

Since: 0.2.0.0

parseSomeFile :: Members '[Error PathException] r => FilePath -> Sem r (SomeBase File) Source #

Polysemy version of parseSomeFile.

Since: 0.2.0.0

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.

fromAbsDir :: Path Abs Dir -> FilePath #

Convert absolute path to directory to FilePath type.

fromRelDir :: Path Rel Dir -> FilePath #

Convert relative path to directory to FilePath type.

fromAbsFile :: Path Abs File -> FilePath #

Convert absolute path to file to FilePath type.

fromRelFile :: Path Rel File -> FilePath #

Convert relative path to file to FilePath type.

fromSomeDir :: SomeBase Dir -> FilePath #

Convert a valid directory to a FilePath.

fromSomeFile :: SomeBase File -> FilePath #

Convert a valid file to a FilePath.

mkAbsDir :: FilePath -> Q Exp #

Make a Path Abs Dir.

Remember: due to the nature of absolute paths this (e.g. /home/foo) may compile on your platform, but it may not compile on another platform (Windows).

mkAbsFile :: FilePath -> Q Exp #

Make a Path Abs File.

Remember: due to the nature of absolute paths this (e.g. /home/foo) may compile on your platform, but it may not compile on another platform (Windows).