Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Path s b t
- data Dir dir
- data File file
- data Abs
- data Rel dir
- data Posix
- data Windows
- data System
- type Path' = Path System
- type Rel' = Rel ()
- type Dir' = Dir ()
- type File' = File ()
- parseRelDir :: MonadThrow m => FilePath -> m (Path System (Rel d1) (Dir d2))
- parseRelFile :: MonadThrow m => FilePath -> m (Path System (Rel d) (File f))
- parseAbsDir :: MonadThrow m => FilePath -> m (Path System Abs (Dir d))
- parseAbsFile :: MonadThrow m => FilePath -> m (Path System Abs (File f))
- parseRelDirW :: MonadThrow m => FilePath -> m (Path Windows (Rel d1) (Dir d2))
- parseRelFileW :: MonadThrow m => FilePath -> m (Path Windows (Rel d) (File f))
- parseAbsDirW :: MonadThrow m => FilePath -> m (Path Windows Abs (Dir d))
- parseAbsFileW :: MonadThrow m => FilePath -> m (Path Windows Abs (File f))
- parseRelDirP :: MonadThrow m => FilePath -> m (Path Posix (Rel d1) (Dir d2))
- parseRelFileP :: MonadThrow m => FilePath -> m (Path Posix (Rel d) (File f))
- parseAbsDirP :: MonadThrow m => FilePath -> m (Path Posix Abs (Dir d))
- parseAbsFileP :: MonadThrow m => FilePath -> m (Path Posix Abs (File f))
- toFilePath :: Path s b t -> FilePath
- fromRelDir :: Path System (Rel r) (Dir d) -> FilePath
- fromRelFile :: Path System (Rel r) (File f) -> FilePath
- fromAbsDir :: Path System Abs (Dir d) -> FilePath
- fromAbsFile :: Path System Abs (File f) -> FilePath
- fromRelDirP :: Path Posix (Rel r) (Dir d) -> FilePath
- fromRelFileP :: Path Posix (Rel r) (File f) -> FilePath
- fromAbsDirP :: Path Posix Abs (Dir d) -> FilePath
- fromAbsFileP :: Path Posix Abs (File f) -> FilePath
- fromRelDirW :: Path Windows (Rel r) (Dir d) -> FilePath
- fromRelFileW :: Path Windows (Rel r) (File f) -> FilePath
- fromAbsDirW :: Path Windows Abs (Dir d) -> FilePath
- fromAbsFileW :: Path Windows Abs (File f) -> FilePath
- (</>) :: Path s b (Dir d) -> Path s (Rel d) t -> Path s b t
- parent :: Path s b t -> Path s b (Dir d)
- basename :: Path s b t -> Path s (Rel d) t
- castRel :: Path s (Rel d1) a -> Path s (Rel d2) a
- castDir :: Path s a (Dir d1) -> Path s a (Dir d2)
- castFile :: Path s a (File f1) -> Path s a (File f2)
- relDirToPosix :: MonadThrow m => Path s (Rel d1) (Dir d2) -> m (Path Posix (Rel d1) (Dir d2))
- relFileToPosix :: MonadThrow m => Path s (Rel d1) (File f) -> m (Path Posix (Rel d1) (File f))
- absdir :: QuasiQuoter
- absdirP :: QuasiQuoter
- absdirW :: QuasiQuoter
- absfile :: QuasiQuoter
- absfileP :: QuasiQuoter
- absfileW :: QuasiQuoter
- reldir :: QuasiQuoter
- reldirP :: QuasiQuoter
- reldirW :: QuasiQuoter
- relfile :: QuasiQuoter
- relfileP :: QuasiQuoter
- relfileW :: QuasiQuoter
Overview
This library provides a strongly typed representation of file paths, providing more safety during compile time while also making code more readable, compared to the standard solution (System.FilePath).
Example of using System.FilePath vs using StrongPath to get the path to bash profile file (relative to the home directory):
-- Using FilePath getBashProfilePath :: IO FilePath
This leaves many questions open. Is returned path relative or absolute? If relative, what is it relative to? Is it normalized? Is it maybe invalid? What kind of separators (win, posix) does it use?
-- Using StrongPath getBashProfilePath :: IO (Path System (Rel HomeDir) (File BashProfile))
With StrongPath, you can read from type that it is relative to home directory, you are guaranteed it is normalized and valid, and type also tells you it is using separators of the OS your program is running on.
Some more examples:
-- System path to "foo" directory, relative to "bar" directory. dirFooInDirBar :: Path System (Rel BarDir) (Dir FooDir) dirFooInDirBar = [reldir|somedir/foo|] -- This path is parsed during compile time, ensuring it is valid. -- Absolute system path to "bar" directory. `Path'` is just alias for `Path System`. dirBarAbsPath :: Path' Abs (Dir BarDir) dirBarAbsPath = [absdir|/bar/|] -- Absolute path to "foo" directory, calculated by concatenating two paths from above. -- If path on the right was not relative to the path on the left, StrongPath would throw compile error upon concatenation. dirFooAbsPath :: Path' Abs (Dir FooDir) dirFooAbsPath = dirBarAbsPath </> dirFooInDirBar -- Posix path to "unnamed" file, relative to "foo" directory. someFile :: Path Posix (Rel FooDir) File () someFile = [relfileP|some/file.txt|] dirHome :: Path System Abs (Dir HomeDir) dirHome :: [absdir|/home/john/|] dirFooCopiedToHomeAsInBar :: Path System Abs (Dir FooDir) dirFooCopiedToHomeAsInBar = dirHome </> castRel dirFooInDirBar data BarDir -- Represents Bar directory. data FooDir -- Represents Foo directory. data HomeDir -- Represents Home directory.
Basic idea is that working with FilePath
(which is just an alias for String
and is a default type for representing file paths in Haskell) is too clumsy
and can easily lead to errors in runtime, while those errors could have been caught
in the compile time if more advanced approach for representing file paths was used.
This is where StrongPath with its Path
type comes in: by encoding
more information about the file path into the type (e.g. is it relative or
absolute, if it is relative what is it relative to, is it file or dir), we
can achieve that additional safety and catch many potential errors during compile time,
while also making code more readable.
Some examples:
- If you have absolute path to directory on the disk such as
/home/john/Music
, with StrongPath you could represent it asPath System Abs (Dir MusicDir)
, capturing its details in the type. - If you have relative (to home) path to file on the disk such as
john/.gitconfig
, you could represent it asPath System (Rel HomeDir) (File JohnsGitConfigFile)
. - If you have
../index.js
path, coming from the Javascript import statementimport Stuff from "../index.js"
, you could represent it asPath Posix (Rel ()) (File IndexFile)
.
Notice that StrongPath will not allow you to, for example, represent /foo/bar.txt
, which is an
absolute path, as Path System (Rel SomeDir) (File BarFile)
, because the parser function (in
this case parseRelFile
) will detect that path is absolute and not relative
and will throw compile error.
Therefore, due to the checks that parser functions perform,
once you get FilePath
converted into Path
, you can be pretty sure that it
is exactly what the type says it is.
Once you have your file path represented as Path
, you can perform safe operations like
</>
(concatenation of two paths) where types really shine.
Specifically, </>
will allow you to concatenate two paths only if they use the same standard,
right path is relative to the left path and the left path is a directory.
If these conditions are not satisfied, the code will not compile!
Function naming
In StrongPath you will find groups of (usually 12) functions that all do the same thing really but each one of them is specialized for specific type of path.
In such case, we usually name them via following scheme: <function_name_prefix><base><type><standard>
, where
<base>
can beRel
orAbs
.<type>
can beFile
orDir
.<standard>
can beP
(Posix),W
(Windows) or nothing (System).
This results in 12 functions, for all 12 combinations of path type.
For example, from their name, we can say for the following functions that:
parseAbsFile
does something withPath System Abs (File f)
parseRelFileP
does something withPath Posix (Rel r) (File f)
parseRelDirW
does something withPath Windows (Rel r) (Dir d)
Common examples
Below we will go through most important features of StrongPath by going through some simple code examples that build upon each other.
Typical import
import StrongPath (Path, System, Abs, Rel, File, Dir, (</>)) import qualified StrongPath as SP
Absolute path to home dir
Let's say that you want to ask user for absolute path to their home directory. With StrongPath, you could do it like this:
data HomeDir getHomeDirPath :: IO (Path System Abs (Dir HomeDir)) getHomeDirPath = getLine >>= fromJust . SP.parseAbsDir
Notice how you captured all the important information in type, plus
you ensure it is indeed valid path by parsing it (with parseAbsDir
)!
For the simplicity we didn't handle error properly and just used fromJust
,
but normally you would probably want to do something more fancy.
Relative path to .gitconfig
Next, let's write a function that asks user for a relative path to .gitconfig file in their home directory.
data UserGitConfig getUserGitConfigPath :: IO (Path System (Rel HomeDir) (File UserGitConfig)) getUserGitConfigPath = getLine >>= fromJust . SP.parseRelFile
Absolute path to .gitconfig
If user inputed both abs path to home dir and rel path to .gitconfig, we can compute abs path to .gitconfig:
absHomeDirPath <- getHomeDirPath relGitConfigPath <- getUserGitConfigPath let absGitConfigPath = absHomeDirPath </> relGitConfigPath
Cool thing here is that you can be sure that absGitConfigPath
makes sense, because </>
would not allow
you (at compile time) to concatenate relGitConfigPath
with anything else than path to home dir, since it knows
that is what it is relative to!
Copying .gitconfig
Let's say that for some reason, we want to copy this .gitconfig to home dir of another user, and we want it to have the same relative position in that home dir as it has in the current home dir.
Let's assume we already have
anotherHomeDir :: IO (Path System Abs (Dir AnotherHomeDir))
then we can do smth like this:
let absAnotherGitConfigPath = anotherHomeDir </> (SP.castRel relGitConfigPath)
We used castRel
to "loosen up" relGitConfigPath
's type, so it does not require to be relative
to HomeDir
and instead accepts AnotherHomeDir
.
Similar to castRel
, there are also castFile
and castDir
.
Now we could do the copying like this:
copyFile (fromAbsFile absGitConfigPath) (fromAbsFile absAnotherGitConfigPath)
Notice that while converting Path
to FilePath
, we could have used toFilePath
instead of
fromAbsFile
, but fromAbsFile
gives us more type safety by demanding given Path
to be
of specific type (absolute file). For example, if somehow variable absGitConfigPath
got to be of type
Path System (Rel ()) (Dir ())
, fromAbsFile
would cause compile time error, while toFilePath
would just happily go on.
Extracting from
path from a JS import statement.
What if we wanted to extract from
path from a Javascript import statement and return it as a Path
?
Example of Javascript import statement:
import Bar from "../foo/bar" // We want to extract "../foo/bar" path.
Let's assume that we know that this statement is relative to some ProjectDir
(because that is where the
JS file we got the statement from is located), but we don't know upfront the name of the file being imported.
Such function could have the following signature:
parseJsImportFrom :: String -> Maybe (Path Posix (Rel (ProjectDir)) (File ()))
Notice how we used Posix
to specify that the path is following posix standard
no matter on which OS we are running this code, while in examples above we
used System
, which meant paths follow whatever is the standard of the OS we are running on.
Next, also notice how we used File ()
to specify that file is "unnamed".
While you could use some other approach to specify this, we found this to be convenient way to do it.
That is why we also introduce File'
and Dir'
aliases, to make this even simpler.
Defining a path via string literal during compile time
Let's say we want to define default file path from user's home directory to user's VLC config directory, and we already know it while writing our program. With StrongPath, we could do it like this:
defaultUserVlcConfigDir :: Path System (Rel UserHomeDir) (Dir UserVlcConfigDir) defaultUserVlcConfigDir = [SP.reldir|.config/vlc|]
where we need QuasiQuotes language extension for reldir
quasi quoter to work.
This will parse the path during compile-time, ensuring it is valid.
Paths starting with "../"
Relative paths in StrongPath can start with one or multiple "../". "../" is taken into account and appropriately managed when performing operations on paths.
someRelPath :: Path System (Rel SomeDir) (File SomeFle) someRelPath = [SP.relfile|../foo/myfile.txt|]
Inspiration
This library is greatly inspired by path library and is really a layer on top of it, replicating most of its API and using it for implementation details, while also adding to it, with main additions being:
- Differentiation between path standards (system, posix and windows) at type level, they can't be accidentally mixed.
- "Naming" of directories and files at type level.
- Support at type level for describing what are relative paths exactly relative to, so you e.g. can't concatenate wrong paths.
- Support for
../
at start of relative path.
StrongPath in practice
- StrongPath is used extensively in wasp-lang.
Similar libraries
- path - Inspiration for StrongPath. Has less information encoded in types than StrongPath but is therefore somewhat simpler to use.
- data-filepath - Similar to
path
. Check https://github.com/commercialhaskell/path#data-filepath for detailed comparison topath
. - pathtype - Similar to
path
. Check https://github.com/commercialhaskell/path#pathtype for detailed comparison topath
. - paths - Focused on capturing if path is relative or absolute, and to what.
- hpath - Uses ByteString under the hood (instead of String), written only for Posix, has no File/Dir distinction.
API
Types
Path
Strongly typed file path. Central type of the StrongPath.
s
- Standard: Posix or windows. Can be fixed (
Posix
,Windows
) or determined by the system (System
). b
- Base: Absolute (
Abs
) or relative (Rel
). t
- Type: File (
File
) or directory (Dir
).
Some examples:
Path System (Dir HomeDir) (File FooFile) Path System Abs (Dir HomeDir) Path Posix (Rel ProjectRoot) (File ())
Instances
Lift (Path s b t :: Type) Source # | |
Eq (Path s b t) Source # | |
(Data s, Data b, Data t) => Data (Path s b t) Source # | |
Defined in StrongPath.Internal gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Path s b t -> c (Path s b t) # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Path s b t) # toConstr :: Path s b t -> Constr # dataTypeOf :: Path s b t -> DataType # dataCast1 :: Typeable t0 => (forall d. Data d => c (t0 d)) -> Maybe (c (Path s b t)) # dataCast2 :: Typeable t0 => (forall d e. (Data d, Data e) => c (t0 d e)) -> Maybe (c (Path s b t)) # gmapT :: (forall b0. Data b0 => b0 -> b0) -> Path s b t -> Path s b t # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Path s b t -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Path s b t -> r # gmapQ :: (forall d. Data d => d -> u) -> Path s b t -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Path s b t -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Path s b t -> m (Path s b t) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Path s b t -> m (Path s b t) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Path s b t -> m (Path s b t) # | |
Ord (Path s b t) Source # | |
Show (Path s b t) Source # | |
Hashable (Path s b t) Source # | Caveat: For two relative Paths, that only differ in the Directory, that they are relative to, this Hashable instance will return the same hash even though they are different paths. |
Defined in StrongPath.Instances |
Path
type
Means that path points to a directory dir
.
To use as a type in place of dir
, we recommend creating an empty
data type representing the specific directory, e.g. data ProjectRootDir
.
Instances
Lift (Dir dir :: Type) Source # | |
Data dir => Data (Dir dir) Source # | |
Defined in StrongPath.Internal gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Dir dir -> c (Dir dir) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Dir dir) # toConstr :: Dir dir -> Constr # dataTypeOf :: Dir dir -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Dir dir)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Dir dir)) # gmapT :: (forall b. Data b => b -> b) -> Dir dir -> Dir dir # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Dir dir -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Dir dir -> r # gmapQ :: (forall d. Data d => d -> u) -> Dir dir -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Dir dir -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Dir dir -> m (Dir dir) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Dir dir -> m (Dir dir) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Dir dir -> m (Dir dir) # |
Means that path points to a file file
.
To use as a type in place of file
, we recommend creating an empty
data type representing the specific file, e.g. data ProjectManifestFile
.
Instances
Lift (File file :: Type) Source # | |
Data file => Data (File file) Source # | |
Defined in StrongPath.Internal gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> File file -> c (File file) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (File file) # toConstr :: File file -> Constr # dataTypeOf :: File file -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (File file)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (File file)) # gmapT :: (forall b. Data b => b -> b) -> File file -> File file # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> File file -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> File file -> r # gmapQ :: (forall d. Data d => d -> u) -> File file -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> File file -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> File file -> m (File file) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> File file -> m (File file) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> File file -> m (File file) # |
Path
base
Describes Path
base as absolute.
Instances
Data Abs Source # | |
Defined in StrongPath.Internal 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 # | |
Lift Abs Source # | |
Describes Path
base as relative to the directory dir
.
Instances
Lift (Rel dir :: Type) Source # | |
Data dir => Data (Rel dir) Source # | |
Defined in StrongPath.Internal gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Rel dir -> c (Rel dir) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Rel dir) # toConstr :: Rel dir -> Constr # dataTypeOf :: Rel dir -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Rel dir)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Rel dir)) # gmapT :: (forall b. Data b => b -> b) -> Rel dir -> Rel dir # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Rel dir -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Rel dir -> r # gmapQ :: (forall d. Data d => d -> u) -> Rel dir -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Rel dir -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Rel dir -> m (Rel dir) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Rel dir -> m (Rel dir) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Rel dir -> m (Rel dir) # |
Path
standard
TLDR: If you are not sure which standard to use, go with System
since that is the most
common use case, and you will likely recognize the situation in which you need
system-indepenent behaviour (Posix
, Windows
) when it happens.
Describes Path
standard as posix (e.g. /path/to/foobar
).
This makes Path
behave in system-independent fashion: code behaves the same
regardless of the system it is running on.
You will normally want to use it when dealing with paths from some external source,
or with paths that have explicitely fixed standard.
For example, if you are running your Haskell program on Windows and parsing logs which
were obtained from the Linux server, or maybe you are parsing Javascript import statements,
you will want to use Posix
.
Instances
Data Posix Source # | |
Defined in StrongPath.Internal gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Posix -> c Posix # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Posix # dataTypeOf :: Posix -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Posix) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Posix) # gmapT :: (forall b. Data b => b -> b) -> Posix -> Posix # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Posix -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Posix -> r # gmapQ :: (forall d. Data d => d -> u) -> Posix -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Posix -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Posix -> m Posix # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Posix -> m Posix # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Posix -> m Posix # | |
Lift Posix Source # | |
Describes Path
standard as windows (e.g. C:\path\to\foobar
).
Check Posix
for more details, everything is analogous.
Instances
Data Windows Source # | |
Defined in StrongPath.Internal gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Windows -> c Windows # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Windows # toConstr :: Windows -> Constr # dataTypeOf :: Windows -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Windows) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Windows) # gmapT :: (forall b. Data b => b -> b) -> Windows -> Windows # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Windows -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Windows -> r # gmapQ :: (forall d. Data d => d -> u) -> Windows -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Windows -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Windows -> m Windows # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Windows -> m Windows # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Windows -> m Windows # | |
Lift Windows Source # | |
Describes Path
standard to be determined by the system/OS.
If the system is Windows, it will resolve to Windows
internally, and if not,
it will resolve to Posix
.
However, keep in mind that even if running on Windows, Path Windows b t
and Path System b t
are still considered to be different types,
even though Path System b t
internally uses Windows standard.
You will normally want to use System
if you are dealing with the paths on the disk of the host OS
(where your code is running), for example if user is providing you with the path to the file on the disk
that you will be doing something with.
Keep in mind that System
causes the behaviour of Path
to be system/platform-dependant.
Instances
Data System Source # | |
Defined in StrongPath.Internal gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> System -> c System # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c System # toConstr :: System -> Constr # dataTypeOf :: System -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c System) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c System) # gmapT :: (forall b. Data b => b -> b) -> System -> System # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> System -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> System -> r # gmapQ :: (forall d. Data d => d -> u) -> System -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> System -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> System -> m System # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> System -> m System # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> System -> m System # | |
Lift System Source # | |
Path
aliases
type Path' = Path System Source #
System
is the most commonly used standard, so we provide you with a type alias for it.
When you don't want your path to be relative to anything specific,
it is convenient to use unit ()
.
When you don't want your directory path to be named,
it is convenient to use unit ()
.
When you don't want your file path to be named,
it is convenient to use unit ()
.
Parsers (from FilePath
to Path
)
Path can be constructed from FilePath
:
parse<base><type><standard> :: MonadThrow m => FilePath -> m (<corresponding_path_type>)
There are 12 parser functions, each of them parsing FilePath
into a specific Path
type.
All of them work in the same fashion and will throw an error (via MonadThrow
)
if given FilePath
can't be parsed into the specific Path
type.
For example, if path is absolute, parseRelDir
will throw an error.
Not all parsers accept all types of separators, for example
parseRelDirP
parser will fail to parse paths using Windows separators,
while parseRelDirW
will accept both Windows and Posix separators.
Below is a table describing, for all the parser functions, which path standard (separators) do they accept as input and to what path standard they parse it.
Parsers | From | To |
---|---|---|
parse[Abs|Rel][Dir|File] | System/Posix | System |
parse[Abs|Rel][Dir|File]W | Win/Posix | Win |
parse[Abs|Rel][Dir|File]P | Posix | Posix |
NOTE: Root of parseAbs...
input always has to match its path standard!
e.g., parseAbsDirW
can parse "C:\foo/bar"
but it can't parse "/foo/bar"
.
Examples:
parseAbsFile "C:\foo\bar.txt"
is valid if system is Windows, and gives the same result asparseAbsFile "C:\foo/bar.txt"
. On the other hand, both are invalid if system is Linux.parseRelFile "foo/bar.txt"
is valid independent of the system.parseRelFile "foo\bar.txt"
is valid only if system is Windows.parseRelDirW "foo\bar\test"
is valid, independent of the system, and gives the same result asparseRelDirW "foo\bar/test"
orparseRelDirW "foo/bar/test"
.
Basically, all of the parsers accept their "native" standard AND Posix,
which enables you to hardcode paths as Posix in the code that will compile
and work both on Linux and Windows when using System
as a standard.
So Posix becames a kind of "universal" language for hardcoding the paths.
parseRelDir :: MonadThrow m => FilePath -> m (Path System (Rel d1) (Dir d2)) Source #
parseRelFile :: MonadThrow m => FilePath -> m (Path System (Rel d) (File f)) Source #
parseAbsDir :: MonadThrow m => FilePath -> m (Path System Abs (Dir d)) Source #
parseAbsFile :: MonadThrow m => FilePath -> m (Path System Abs (File f)) Source #
parseRelDirW :: MonadThrow m => FilePath -> m (Path Windows (Rel d1) (Dir d2)) Source #
parseRelFileW :: MonadThrow m => FilePath -> m (Path Windows (Rel d) (File f)) Source #
parseAbsDirW :: MonadThrow m => FilePath -> m (Path Windows Abs (Dir d)) Source #
parseAbsFileW :: MonadThrow m => FilePath -> m (Path Windows Abs (File f)) Source #
parseRelDirP :: MonadThrow m => FilePath -> m (Path Posix (Rel d1) (Dir d2)) Source #
parseRelFileP :: MonadThrow m => FilePath -> m (Path Posix (Rel d) (File f)) Source #
parseAbsDirP :: MonadThrow m => FilePath -> m (Path Posix Abs (Dir d)) Source #
parseAbsFileP :: MonadThrow m => FilePath -> m (Path Posix Abs (File f)) Source #
Conversion (from Path
to FilePath
)
Path
can be converted into FilePath
via polymorphic function toFilePath
or via any of the 12 functions that accept specific path type.
We recommend using specific functions instead of toFilePath
,
because that way you are explicit about which path you expect
and if that expectancy is not met, type system will catch it.
toFilePath :: Path s b t -> FilePath Source #
Operations
(</>) :: Path s b (Dir d) -> Path s (Rel d) t -> Path s b t Source #
Concatenates two paths, same as FilePath.</>
, but only if the second path is relative
to the directory that first path leads to, and if both paths use the same path standard.
How "../"
s are resolved (examples are pseudocode):
- For each
"../"
at the start of the right hand path, one most right entry is removed from the left hand path.
"a/b" </> "../c" == "a/c"
- If left path is absolute and right path has too many
"../"
s, they go "over" the root and are effectively ignored.
"/a/b" </> "../../../../../c" == "/c"
- If left path is relative and right path has more
"../"
s then left has entries, the leftover"../"
s are carried over.
"a/b" </> "../../../../../c" == "../../../c"
parent :: Path s b t -> Path s b (Dir d) Source #
Gets parent dir of the path.
Either removes last entry in the path or if there are no entries and just "../"
s, adds one more "../"
.
If path is absolute root and it has no parent, it will return unchanged path.
Examples (pseudocode):
parent "a/b/c" == "a/b" parent "/a" == "/" parent "/" == "/" parent "../a/b" == "../a" parent ".." == "../.." parent (parent "../a") == "../.."
basename :: Path s b t -> Path s (Rel d) t Source #
Returns the most right member of the path once split by separators.
If path is pointing to file, basename will be name of the file.
If path is pointing to a directory, basename will be name of the directory.
Check examples below to see how are special paths like ..
, .
, /
and similar resolved.
Examples (pseudocode): > basename "ab/c" == "c" > basename "file.txt" == "file.txt" > basename "../file.txt" == "file.txt" > basename "../.." == ".." > basename ".." == ".." > basename "." == "." > basename "/" == "."
Casting
castRel :: Path s (Rel d1) a -> Path s (Rel d2) a Source #
Enables you to redefine which dir is the path relative to.
Conversion of path standard
relDirToPosix :: MonadThrow m => Path s (Rel d1) (Dir d2) -> m (Path Posix (Rel d1) (Dir d2)) Source #
Converts relative dir path to posix by replacing current path separators with posix path separators. If path is already posix, it will not change.
Works well for "normal" relative paths like "a\b\c"
(Win) or "a/b/c"
(Posix).
If path is weird but still considered relative, like just "C:"
on Win,
results can be unexpected, most likely resulting with error thrown.
relFileToPosix :: MonadThrow m => Path s (Rel d1) (File f) -> m (Path Posix (Rel d1) (File f)) Source #
Converts relative file path to posix, if it is not already posix.
Check relDirToPosix
for more details, they behave the same.
QuasiQuoters
StrongPath provides quasi quoters that enable you to construct Path
in compile time.
You will need to enable QuasiQuotes
language extension in order to use them.
With quasi quoters, you can define paths like this:
dirFooAbsPath :: Path System Abs (Dir FooDir) dirFooAbsPath = [absdir|/foo/bar|]
someFile :: Path Posix (Rel FooDir) File () someFile = [relfileP|some/file.txt|]
These will run at compile-time and underneath use the appropriate parser, ensuring that paths are valid and throwing compile-time error if not.
absdir :: QuasiQuoter Source #
reldir :: QuasiQuoter Source #
Working with Path library
If you are using Path library alongside StrongPath, you can import module StrongPath.Path,
which contains functions for converting StrongPath Path
into Path
and vice versa.