path-sing-0.1.0.0: A singleton wrapper for the `path` library.
Copyright(c) 2023 Yamada Ryo
LicenseMPL-2.0 (see the file LICENSE)
Maintainerymdfield@outlook.jp
Stabilityexperimental
Portabilityportable
Safe HaskellSafe-Inferred
LanguageGHC2021

Path.Sing

Description

 
Synopsis

Documentation

data Base Source #

A DataKind that indicates whether the path is absolute or relative.

Constructors

Abs 
Rel 

data FsType Source #

A DataKind that indicates whether the path reveals a file or a directory.

Constructors

File 
Dir 

type family PathBase b where ... Source #

Mapping to the tag representing the path's base in the Path library.

Equations

PathBase 'Abs = Abs 
PathBase 'Rel = Rel 

type family PathFsType t where ... Source #

Mapping to the tag representing the path's type in the Path library.

Equations

PathFsType 'File = File 
PathFsType 'Dir = Dir 

data SBase b where Source #

A singleton tag that indicates whether the path is absolute or relative.

Constructors

SAbs :: SBase 'Abs 
SRel :: SBase 'Rel 

Instances

Instances details
Show (SBase b) Source # 
Instance details

Defined in Path.Sing

Methods

showsPrec :: Int -> SBase b -> ShowS #

show :: SBase b -> String #

showList :: [SBase b] -> ShowS #

Eq (SBase b) Source # 
Instance details

Defined in Path.Sing

Methods

(==) :: SBase b -> SBase b -> Bool #

(/=) :: SBase b -> SBase b -> Bool #

Hashable (SBase b) Source # 
Instance details

Defined in Path.Sing

Methods

hashWithSalt :: Int -> SBase b -> Int #

hash :: SBase b -> Int #

data SFsType t where Source #

A singleton tag that indicates whether the path reveals a file or a directory.

Constructors

SFile :: SFsType 'File 
SDir :: SFsType 'Dir 

Instances

Instances details
Show (SFsType t) Source # 
Instance details

Defined in Path.Sing

Methods

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

show :: SFsType t -> String #

showList :: [SFsType t] -> ShowS #

Eq (SFsType b) Source # 
Instance details

Defined in Path.Sing

Methods

(==) :: SFsType b -> SFsType b -> Bool #

(/=) :: SFsType b -> SFsType b -> Bool #

Hashable (SFsType b) Source # 
Instance details

Defined in Path.Sing

Methods

hashWithSalt :: Int -> SFsType b -> Int #

hash :: SFsType b -> Int #

data Path b t Source #

A singleton-type wrapper of the original Path type.

Constructors

Path (SBase b) (SFsType t) (Path (PathBase b) (PathFsType t)) 

Instances

Instances details
Generic (Path b t) Source # 
Instance details

Defined in Path.Sing

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 #

Eq (Path b t) Source # 
Instance details

Defined in Path.Sing

Methods

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

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

Hashable (Path b t) Source # 
Instance details

Defined in Path.Sing

Methods

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

hash :: Path b t -> Int #

type Rep (Path b t) Source # 
Instance details

Defined in Path.Sing

data SomePath Source #

Path of some type.

Constructors

forall b t. SomePath (Path b t) 

data SomeBase t Source #

Path of some base.

Constructors

forall b. SomeBase (Path b t) 

data SomeFsType b Source #

Path of some type.

Constructors

forall t. SomeFsType (Path b t) 

data UnknownFsType b Source #

Path of some type. The difference with SomeFsType is that information on whether the path is a file or directory is not distinguished here and is ambiguous.

Constructors

UnknownFsType (SBase b) (Path (PathBase b) File) 

pathToString :: Path b t -> String Source #

Convert to a String.

(</>) :: Path b 'Dir -> Path 'Rel t -> Path b t Source #

Append two paths.

fileToDirPath :: forall b. Path b 'File -> Path b 'Dir Source #

Reinterpret file paths as directory paths. It is also the operation of adding a / at the end.