Agda-2.5.3.20180519: A dependently typed functional programming language and proof assistant

Safe HaskellNone
LanguageHaskell2010

Agda.Utils.FileName

Description

Operations on file names.

Synopsis

Documentation

newtype AbsolutePath Source #

Paths which are known to be absolute.

Note that the Eq and Ord instances do not check if different paths point to the same files or directories.

Constructors

AbsolutePath Text 

Instances

Eq AbsolutePath Source # 
Data AbsolutePath Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AbsolutePath -> c AbsolutePath #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AbsolutePath #

toConstr :: AbsolutePath -> Constr #

dataTypeOf :: AbsolutePath -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AbsolutePath) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AbsolutePath) #

gmapT :: (forall b. Data b => b -> b) -> AbsolutePath -> AbsolutePath #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AbsolutePath -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AbsolutePath -> r #

gmapQ :: (forall d. Data d => d -> u) -> AbsolutePath -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AbsolutePath -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AbsolutePath -> m AbsolutePath #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AbsolutePath -> m AbsolutePath #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AbsolutePath -> m AbsolutePath #

Ord AbsolutePath Source # 
Show AbsolutePath Source # 
Hashable AbsolutePath Source # 
Pretty AbsolutePath Source # 
KillRange Range Source # 
SetRange Range Source # 

Methods

setRange :: Range -> Range -> Range Source #

HasRange Range Source # 

Methods

getRange :: Range -> Range Source #

HasRange Interval Source # 
FreshName Range Source # 

Methods

freshName_ :: MonadState TCState m => Range -> m Name Source #

PrettyTCM Range Source # 

Methods

prettyTCM :: Range -> TCM Doc Source #

FreshName (Range, String) Source # 

Methods

freshName_ :: MonadState TCState m => (Range, String) -> m Name Source #

filePath :: AbsolutePath -> FilePath Source #

Extract the AbsolutePath to be used as FilePath.

mkAbsolute :: FilePath -> AbsolutePath Source #

Constructs AbsolutePaths.

Precondition: The path must be absolute and valid.

absolute :: FilePath -> IO AbsolutePath Source #

Makes the path absolute.

This function may raise an __IMPOSSIBLE__ error if canonicalizePath does not return an absolute path.

(===) :: AbsolutePath -> AbsolutePath -> Bool infix 4 Source #

Tries to establish if the two file paths point to the same file (or directory).

doesFileExistCaseSensitive :: FilePath -> IO Bool Source #

Case-sensitive doesFileExist for Windows.

This is case-sensitive only on the file name part, not on the directory part. (Ideally, path components coming from module name components should be checked case-sensitively and the other path components should be checked case insensitively.)