| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Path.Internal.Posix
Description
Internal types and functions.
Documentation
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
| (Typeable b, Typeable t) => Lift (Path b t :: Type) Source # | |
| Eq (Path b t) Source # | String equality. The following property holds: show x == show y ≡ x == y | 
| (Data b, Data t) => Data (Path b t) Source # | |
| 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) Source # | String ordering. The following property holds: show x `compare` show y ≡ x `compare` y | 
| Defined in Path.Internal.Posix | |
| Show (Path b t) Source # | Same as 'show . Path.toFilePath'. The following property holds: x == y ≡ show x == show y | 
| Generic (Path b t) Source # | |
| Hashable (Path b t) Source # | |
| Defined in Path.Internal.Posix | |
| ToJSON (Path b t) Source # | |
| Defined in Path.Internal.Posix | |
| ToJSONKey (Path b t) Source # | |
| Defined in Path.Internal.Posix | |
| FromJSON (Path Rel Dir) Source # | |
| FromJSON (Path Rel File) Source # | |
| FromJSON (Path Abs Dir) Source # | |
| FromJSON (Path Abs File) Source # | |
| FromJSONKey (Path Rel Dir) Source # | |
| Defined in Path.Posix Methods | |
| FromJSONKey (Path Rel File) Source # | |
| Defined in Path.Posix Methods | |
| FromJSONKey (Path Abs Dir) Source # | |
| Defined in Path.Posix Methods | |
| FromJSONKey (Path Abs File) Source # | |
| Defined in Path.Posix Methods | |
| NFData (Path b t) Source # | |
| Defined in Path.Internal.Posix | |
| type Rep (Path b t) Source # | |
| Defined in Path.Internal.Posix | |
toFilePath :: Path b t -> FilePath Source #
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.
hasParentDir :: FilePath -> Bool Source #
Helper function: check if the filepath has any parent directories in it. This handles the logic of checking for different path separators on Windows.