Cabal-syntax-3.14.0.0: A library for working with .cabal files
Safe HaskellNone
LanguageHaskell2010

Distribution.Utils.Path

Synopsis

Symbolic path endpoints

data FileOrDir Source #

A type-level symbolic name, to an abstract file or directory (e.g. the Cabal package directory).

Constructors

File

A file (with no further information).

Dir Type

The abstract name of a directory or category of directories, e.g. the package directory or a source directory.

data AllowAbsolute Source #

Is this symbolic path allowed to be absolute, or must it be relative?

Constructors

AllowAbsolute

The path may be absolute, or it may be relative.

OnlyRelative

The path must be relative.

Abstract directory locations

data CWD Source #

Abstract directory: current working directory.

See Note [Symbolic paths] in Distribution.Utils.Path.

data Pkg Source #

Abstract directory: package directory (e.g. a directory containing the .cabal file).

See Note [Symbolic paths] in Distribution.Utils.Path.

data Dist Source #

Abstract directory: dist directory (e.g. dist-newstyle).

See Note [Symbolic paths] in Distribution.Utils.Path.

data Source Source #

Abstract directory: source directory (a search directory for source files).

See Note [Symbolic paths] in Distribution.Utils.Path.

data Include Source #

Abstract directory: include directory (a search directory for CPP includes like header files, e.g. with ghc -I).

See Note [Symbolic paths] in Distribution.Utils.Path.

data Lib Source #

Abstract directory: search directory for extra libraries.

See Note [Symbolic paths] in Distribution.Utils.Path.

data Framework Source #

Abstract directory: MacOS framework directory.

See Note [Symbolic paths] in Distribution.Utils.Path.

data Build Source #

Abstract directory: build directory.

See Note [Symbolic paths] in Distribution.Utils.Path.

data Artifacts Source #

Abstract directory: directory for build artifacts, such as documentation or .hie files.

See Note [Symbolic paths] in Distribution.Utils.Path.

data PkgDB Source #

Abstract directory: package database directory.

See Note [Symbolic paths] in Distribution.Utils.Path.

data DataDir Source #

Abstract directory: data files directory.

See Note [Symbolic paths] in Distribution.Utils.Path.

data Mix Source #

Abstract directory: directory for HPC .mix files.

See Note [Symbolic paths] in Distribution.Utils.Path.

data Tix Source #

Abstract directory: directory for HPC .tix files.

See Note [Symbolic paths] in Distribution.Utils.Path.

data Tmp Source #

Abstract directory: a temporary directory.

See Note [Symbolic paths] in Distribution.Utils.Path.

data Response Source #

Abstract directory: directory for response files.

See Note [Symbolic paths] in Distribution.Utils.Path.

data PkgConf Source #

Abstract directory: directory for pkg-config files.

See Note [Symbolic paths] in Distribution.Utils.Path.

Symbolic paths

type RelativePath = SymbolicPathX 'OnlyRelative Source #

A symbolic relative path, relative to an abstract location specified by the from type parameter.

They are *symbolic*, which means we cannot perform any IO until we interpret them (using e.g. interpretSymbolicPath).

type SymbolicPath = SymbolicPathX 'AllowAbsolute Source #

A symbolic path which is allowed to be absolute.

They are *symbolic*, which means we cannot perform any IO until we interpret them (using e.g. interpretSymbolicPath).

newtype AbsolutePath (to :: FileOrDir) Source #

Constructors

AbsolutePath (forall from. SymbolicPath from to) 

data SymbolicPathX (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir) Source #

A symbolic path, possibly relative to an abstract location specified by the from type parameter.

They are *symbolic*, which means we cannot perform any IO until we interpret them (using e.g. interpretSymbolicPath).

Instances

Instances details
Newtype [RelativePath Pkg 'File] CompatLicenseFile Source # 
Instance details

Defined in Distribution.PackageDescription.FieldGrammar

Newtype (SymbolicPath Pkg ('Dir DataDir)) CompatDataDir Source # 
Instance details

Defined in Distribution.PackageDescription.FieldGrammar

Newtype (RelativePath from to) (RelativePathNT from to) Source # 
Instance details

Defined in Distribution.FieldGrammar.Newtypes

Methods

pack :: RelativePath from to -> RelativePathNT from to Source #

unpack :: RelativePathNT from to -> RelativePath from to Source #

Newtype (SymbolicPath from to) (SymbolicPathNT from to) Source # 
Instance details

Defined in Distribution.FieldGrammar.Newtypes

Methods

pack :: SymbolicPath from to -> SymbolicPathNT from to Source #

unpack :: SymbolicPathNT from to -> SymbolicPath from to Source #

Parsec (SymbolicPathX 'AllowAbsolute from to) Source # 
Instance details

Defined in Distribution.Utils.Path

Parsec (SymbolicPathX 'OnlyRelative from to) Source # 
Instance details

Defined in Distribution.Utils.Path

Pretty (SymbolicPathX allowAbsolute from to) Source # 
Instance details

Defined in Distribution.Utils.Path

Methods

pretty :: SymbolicPathX allowAbsolute from to -> Doc Source #

prettyVersioned :: CabalSpecVersion -> SymbolicPathX allowAbsolute from to -> Doc Source #

(Typeable allowAbsolute, Typeable from, Typeable to) => Structured (SymbolicPathX allowAbsolute from to) Source # 
Instance details

Defined in Distribution.Utils.Path

Methods

structure :: Proxy (SymbolicPathX allowAbsolute from to) -> Structure Source #

structureHash' :: Tagged (SymbolicPathX allowAbsolute from to) MD5

Binary (SymbolicPathX allowAbsolute from to) Source # 
Instance details

Defined in Distribution.Utils.Path

Methods

put :: SymbolicPathX allowAbsolute from to -> Put Source #

get :: Get (SymbolicPathX allowAbsolute from to) Source #

putList :: [SymbolicPathX allowAbsolute from to] -> Put Source #

NFData (SymbolicPathX allowAbsolute from to) Source # 
Instance details

Defined in Distribution.Utils.Path

Methods

rnf :: SymbolicPathX allowAbsolute from to -> () Source #

(Typeable from, Typeable allowAbsolute, Typeable to) => Data (SymbolicPathX allowAbsolute from to) Source # 
Instance details

Defined in Distribution.Utils.Path

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SymbolicPathX allowAbsolute from to -> c (SymbolicPathX allowAbsolute from to) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SymbolicPathX allowAbsolute from to) #

toConstr :: SymbolicPathX allowAbsolute from to -> Constr #

dataTypeOf :: SymbolicPathX allowAbsolute from to -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (SymbolicPathX allowAbsolute from to)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SymbolicPathX allowAbsolute from to)) #

gmapT :: (forall b. Data b => b -> b) -> SymbolicPathX allowAbsolute from to -> SymbolicPathX allowAbsolute from to #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SymbolicPathX allowAbsolute from to -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SymbolicPathX allowAbsolute from to -> r #

gmapQ :: (forall d. Data d => d -> u) -> SymbolicPathX allowAbsolute from to -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SymbolicPathX allowAbsolute from to -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SymbolicPathX allowAbsolute from to -> m (SymbolicPathX allowAbsolute from to) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SymbolicPathX allowAbsolute from to -> m (SymbolicPathX allowAbsolute from to) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SymbolicPathX allowAbsolute from to -> m (SymbolicPathX allowAbsolute from to) #

Generic (SymbolicPathX allowAbsolute from to) Source # 
Instance details

Defined in Distribution.Utils.Path

Associated Types

type Rep (SymbolicPathX allowAbsolute from to) 
Instance details

Defined in Distribution.Utils.Path

type Rep (SymbolicPathX allowAbsolute from to) = D1 ('MetaData "SymbolicPathX" "Distribution.Utils.Path" "Cabal-syntax-3.14.0.0-395c" 'True) (C1 ('MetaCons "SymbolicPath" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath)))

Methods

from :: SymbolicPathX allowAbsolute from to -> Rep (SymbolicPathX allowAbsolute from to) x #

to :: Rep (SymbolicPathX allowAbsolute from to) x -> SymbolicPathX allowAbsolute from to #

Read (SymbolicPathX allowAbsolute from to) Source # 
Instance details

Defined in Distribution.Utils.Path

Methods

readsPrec :: Int -> ReadS (SymbolicPathX allowAbsolute from to) #

readList :: ReadS [SymbolicPathX allowAbsolute from to] #

readPrec :: ReadPrec (SymbolicPathX allowAbsolute from to) #

readListPrec :: ReadPrec [SymbolicPathX allowAbsolute from to] #

Show (SymbolicPathX allowAbsolute from to) Source # 
Instance details

Defined in Distribution.Utils.Path

Methods

showsPrec :: Int -> SymbolicPathX allowAbsolute from to -> ShowS #

show :: SymbolicPathX allowAbsolute from to -> String #

showList :: [SymbolicPathX allowAbsolute from to] -> ShowS #

Eq (SymbolicPathX allowAbsolute from to) Source # 
Instance details

Defined in Distribution.Utils.Path

Methods

(==) :: SymbolicPathX allowAbsolute from to -> SymbolicPathX allowAbsolute from to -> Bool #

(/=) :: SymbolicPathX allowAbsolute from to -> SymbolicPathX allowAbsolute from to -> Bool #

Ord (SymbolicPathX allowAbsolute from to) Source # 
Instance details

Defined in Distribution.Utils.Path

Methods

compare :: SymbolicPathX allowAbsolute from to -> SymbolicPathX allowAbsolute from to -> Ordering #

(<) :: SymbolicPathX allowAbsolute from to -> SymbolicPathX allowAbsolute from to -> Bool #

(<=) :: SymbolicPathX allowAbsolute from to -> SymbolicPathX allowAbsolute from to -> Bool #

(>) :: SymbolicPathX allowAbsolute from to -> SymbolicPathX allowAbsolute from to -> Bool #

(>=) :: SymbolicPathX allowAbsolute from to -> SymbolicPathX allowAbsolute from to -> Bool #

max :: SymbolicPathX allowAbsolute from to -> SymbolicPathX allowAbsolute from to -> SymbolicPathX allowAbsolute from to #

min :: SymbolicPathX allowAbsolute from to -> SymbolicPathX allowAbsolute from to -> SymbolicPathX allowAbsolute from to #

type Rep (SymbolicPathX allowAbsolute from to) Source # 
Instance details

Defined in Distribution.Utils.Path

type Rep (SymbolicPathX allowAbsolute from to) = D1 ('MetaData "SymbolicPathX" "Distribution.Utils.Path" "Cabal-syntax-3.14.0.0-395c" 'True) (C1 ('MetaCons "SymbolicPath" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath)))

Symbolic path API

getSymbolicPath :: forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir). SymbolicPathX allowAbsolute from to -> FilePath Source #

Extract the FilePath underlying a SymbolicPath or RelativePath, without interpreting it.

Use this function e.g. to validate the underlying filepath.

When interacting with the file system, you should instead use interpretSymbolicPath or interpretSymbolicPathCWD.

See Note [Symbolic paths] in Distribution.Utils.Path.

sameDirectory :: forall (allowAbsolute :: AllowAbsolute) from to. SymbolicPathX allowAbsolute from ('Dir to) Source #

A symbolic path from a directory to itself.

makeRelativePathEx :: forall from (to :: FileOrDir). HasCallStack => FilePath -> RelativePath from to Source #

Make a RelativePath, ensuring the path is not absolute, but performing no further checks.

makeSymbolicPath :: forall from (to :: FileOrDir). FilePath -> SymbolicPath from to Source #

Make a SymbolicPath, which may be relative or absolute.

unsafeMakeSymbolicPath :: forall (allowAbs :: AllowAbsolute) from (to :: FileOrDir). FilePath -> SymbolicPathX allowAbs from to Source #

Make a SymbolicPath which may be relative or absolute, without performing any checks.

Avoid using this function in new code.

coerceSymbolicPath :: forall (allowAbsolute :: AllowAbsolute) from (to1 :: FileOrDir) (to2 :: FileOrDir). SymbolicPathX allowAbsolute from to1 -> SymbolicPathX allowAbsolute from to2 Source #

Change what a symbolic path is pointing to.

unsafeCoerceSymbolicPath :: forall (allowAbsolute :: AllowAbsolute) from1 (to1 :: FileOrDir) from2 (to2 :: FileOrDir). SymbolicPathX allowAbsolute from1 to1 -> SymbolicPathX allowAbsolute from2 to2 Source #

Change both what a symbolic path is pointing from and pointing to.

Avoid using this in new code.

relativeSymbolicPath :: forall from (to :: FileOrDir). RelativePath from to -> SymbolicPath from to Source #

Weakening: convert a relative symbolic path to a symbolic path, "forgetting" that it is relative.

symbolicPathRelative_maybe :: forall from (to :: FileOrDir). SymbolicPath from to -> Maybe (RelativePath from to) Source #

Is this symbolic path a relative symbolic path?

interpretSymbolicPath :: forall from (allowAbsolute :: AllowAbsolute) (to :: FileOrDir). Maybe (SymbolicPath CWD ('Dir from)) -> SymbolicPathX allowAbsolute from to -> FilePath Source #

Interpret a symbolic path with respect to the given directory.

Use this function before directly interacting with the file system in order to take into account a working directory argument.

NB: when invoking external programs (such as GHC), it is preferable to set the working directory of the process and use interpretSymbolicPathCWD rather than calling this function, as this function will turn relative paths into absolute paths if the working directory is an absolute path. This can degrade error messages, or worse, break the behaviour entirely (because the program might expect certain paths to be relative).

See Note [Symbolic paths] in Distribution.Utils.Path.

interpretSymbolicPathAbsolute :: forall (allowAbsolute :: AllowAbsolute) (to :: FileOrDir). AbsolutePath ('Dir Pkg) -> SymbolicPathX allowAbsolute Pkg to -> FilePath Source #

General filepath API

(</>) :: PathLike p q r => p -> q -> r infixr 5 Source #

Like </>, but also supporting symbolic paths.

(<.>) :: FileLike p => p -> String -> p infixr 7 Source #

Like <.>, but also supporting symbolic paths.

takeDirectorySymbolicPath :: forall (allowAbsolute :: AllowAbsolute) from to'. SymbolicPathX allowAbsolute from 'File -> SymbolicPathX allowAbsolute from ('Dir to') Source #

Like takeDirectory, for symbolic paths.

dropExtensionsSymbolicPath :: forall (allowAbsolute :: AllowAbsolute) from. SymbolicPathX allowAbsolute from 'File -> SymbolicPathX allowAbsolute from 'File Source #

Like dropExtensions, for symbolic paths.

replaceExtensionSymbolicPath :: forall (allowAbsolute :: AllowAbsolute) from. SymbolicPathX allowAbsolute from 'File -> String -> SymbolicPathX allowAbsolute from 'File Source #

Like replaceExtension, for symbolic paths.

normaliseSymbolicPath :: forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir). SymbolicPathX allowAbsolute from to -> SymbolicPathX allowAbsolute from to Source #

Like normalise, for symbolic paths.

Working directory handling

interpretSymbolicPathCWD :: forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir). SymbolicPathX allowAbsolute from to -> FilePath Source #

Interpret a symbolic path, **under the assumption that the working directory is the package directory**.

Use interpretSymbolicPath instead if you need to take into account a working directory argument before directly interacting with the file system.

Use this function instead of interpretSymbolicPath when invoking a child process: set the working directory of the sub-process, and use this function, e.g.:

callGhc :: Maybe (SymbolicPath CWD (Dir Pkg))
        -> SymbolicPath (Dir Pkg) File
        -> IO ()
callGhc mbWorkDir inputFile =
  runProgramInvocation $
    programInvocationCwd mbWorkDir ghcProg [interpretSymbolicPathCWD inputFile]

In this example, programInvocationCwd sets the working directory, so it is appropriate to use interpretSymbolicPathCWD to provide its arguments.

See Note [Symbolic paths] in Distribution.Utils.Path.

absoluteWorkingDir :: forall (to :: FileOrDir). Maybe (SymbolicPath CWD to) -> IO (AbsolutePath to) Source #

Absolute path to the current working directory.

tryMakeRelative :: forall dir (to :: FileOrDir). Maybe (SymbolicPath CWD ('Dir dir)) -> SymbolicPath dir to -> IO (SymbolicPath dir to) Source #

Try to make a symbolic path relative.

This function does nothing if the path is already relative.

NB: this function may fail to make the path relative.

Module names

moduleNameSymbolicPath :: forall (allowAbsolute :: AllowAbsolute). ModuleName -> SymbolicPathX allowAbsolute Source 'File Source #

Retrieve the relative symbolic path to a Haskell module.