{-# LINE 1 "System/Posix/ByteString/FilePath.hsc" #-}{-# LANGUAGE Trustworthy #-}{-# LANGUAGE TypeApplications #-}------------------------------------------------------------------------------- |-- Module : System.Posix.ByteString.FilePath-- Copyright : (c) The University of Glasgow 2002-- License : BSD-style (see the file libraries/base/LICENSE)---- Maintainer : libraries@haskell.org-- Stability : provisional-- Portability : non-portable (requires POSIX)---- Internal stuff: support for ByteString FilePaths-------------------------------------------------------------------------------moduleSystem.Posix.ByteString.FilePath(RawFilePath ,withFilePath ,peekFilePath ,peekFilePathLen ,throwErrnoPathIfMinus1Retry ,throwErrnoPathIfMinus1Retry_ ,throwErrnoPathIfNullRetry ,throwErrnoPathIfRetry ,throwErrnoPath ,throwErrnoPathIf ,throwErrnoPathIf_ ,throwErrnoPathIfNull ,throwErrnoPathIfMinus1 ,throwErrnoPathIfMinus1_ ,throwErrnoTwoPathsIfMinus1_ )whereimportForeignhiding(void)importForeign.Chiding(throwErrnoPath,throwErrnoPathIf,throwErrnoPathIf_,throwErrnoPathIfNull,throwErrnoPathIfMinus1,throwErrnoPathIfMinus1_)importControl.MonadimportControl.ExceptionimportData.ByteString.Internal(c_strlen)importGHC.ForeignasGHC(peekCStringLen)importGHC.IO.Encoding(getFileSystemEncoding)importGHC.IO.ExceptionimportData.ByteStringasBimportData.ByteString.Char8asBCimportPreludehiding(FilePath){-# LINE 54 "System/Posix/ByteString/FilePath.hsc" #-}-- | A literal POSIX file pathtypeRawFilePath =ByteStringwithFilePath ::RawFilePath ->(CString->IOa )->IOa withFilePath :: forall a. RawFilePath -> (CString -> IO a) -> IO a withFilePath RawFilePath path =RawFilePath -> (CString -> IO a) -> IO a forall a. RawFilePath -> (CString -> IO a) -> IO a useAsCStringSafe RawFilePath path peekFilePath ::CString->IORawFilePath peekFilePath :: CString -> IO RawFilePath peekFilePath =CString -> IO RawFilePath packCStringpeekFilePathLen ::CStringLen->IORawFilePath peekFilePathLen :: CStringLen -> IO RawFilePath peekFilePathLen =CStringLen -> IO RawFilePath packCStringLenthrowErrnoPathIfMinus1Retry ::(Eqa ,Numa )=>String->RawFilePath ->IOa ->IOa throwErrnoPathIfMinus1Retry :: forall a. (Eq a, Num a) => String -> RawFilePath -> IO a -> IO a throwErrnoPathIfMinus1Retry String loc RawFilePath path IO a f =do(a -> Bool) -> String -> RawFilePath -> IO a -> IO a forall a. (a -> Bool) -> String -> RawFilePath -> IO a -> IO a throwErrnoPathIfRetry (a -> a -> Bool forall a. Eq a => a -> a -> Bool ==-a 1)String loc RawFilePath path IO a f throwErrnoPathIfMinus1Retry_ ::(Eqa ,Numa )=>String->RawFilePath ->IOa ->IO()throwErrnoPathIfMinus1Retry_ :: forall a. (Eq a, Num a) => String -> RawFilePath -> IO a -> IO () throwErrnoPathIfMinus1Retry_ String loc RawFilePath path IO a f =IO a -> IO () forall (f :: * -> *) a. Functor f => f a -> f () void(IO a -> IO ()) -> IO a -> IO () forall a b. (a -> b) -> a -> b $(a -> Bool) -> String -> RawFilePath -> IO a -> IO a forall a. (a -> Bool) -> String -> RawFilePath -> IO a -> IO a throwErrnoPathIfRetry (a -> a -> Bool forall a. Eq a => a -> a -> Bool ==-a 1)String loc RawFilePath path IO a f throwErrnoPathIfNullRetry ::String->RawFilePath ->IO(Ptra )->IO(Ptra )throwErrnoPathIfNullRetry :: forall a. String -> RawFilePath -> IO (Ptr a) -> IO (Ptr a) throwErrnoPathIfNullRetry String loc RawFilePath path IO (Ptr a) f =(Ptr a -> Bool) -> String -> RawFilePath -> IO (Ptr a) -> IO (Ptr a) forall a. (a -> Bool) -> String -> RawFilePath -> IO a -> IO a throwErrnoPathIfRetry (Ptr a -> Ptr a -> Bool forall a. Eq a => a -> a -> Bool ==Ptr a forall a. Ptr a nullPtr)String loc RawFilePath path IO (Ptr a) f throwErrnoPathIfRetry ::(a ->Bool)->String->RawFilePath ->IOa ->IOa throwErrnoPathIfRetry :: forall a. (a -> Bool) -> String -> RawFilePath -> IO a -> IO a throwErrnoPathIfRetry a -> Bool pr String loc RawFilePath rpath IO a f =doa res <-IO a f ifa -> Bool pr a res thendoErrno err <-IO Errno getErrnoifErrno err Errno -> Errno -> Bool forall a. Eq a => a -> a -> Bool ==Errno eINTRthen(a -> Bool) -> String -> RawFilePath -> IO a -> IO a forall a. (a -> Bool) -> String -> RawFilePath -> IO a -> IO a throwErrnoPathIfRetry a -> Bool pr String loc RawFilePath rpath IO a f elseString -> RawFilePath -> IO a forall a. String -> RawFilePath -> IO a throwErrnoPath String loc RawFilePath rpath elsea -> IO a forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a returna res -- | as 'throwErrno', but exceptions include the given path when appropriate.--throwErrnoPath ::String->RawFilePath ->IOa throwErrnoPath :: forall a. String -> RawFilePath -> IO a throwErrnoPath String loc RawFilePath path =doErrno errno <-IO Errno getErrnoString path' <-(IOException -> String) -> (String -> String) -> Either IOException String -> String forall a c b. (a -> c) -> (b -> c) -> Either a b -> c either(String -> IOException -> String forall a b. a -> b -> a const(RawFilePath -> String BC.unpackRawFilePath path ))String -> String forall a. a -> a id(Either IOException String -> String) -> IO (Either IOException String) -> IO String forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$>forall e a. Exception e => IO a -> IO (Either e a) try@IOException(RawFilePath -> IO String decodeWithBasePosix RawFilePath path )IOException -> IO a forall a. IOException -> IO a ioError(String -> Errno -> Maybe Handle -> Maybe String -> IOException errnoToIOErrorString loc Errno errno Maybe Handle forall a. Maybe a Nothing(String -> Maybe String forall a. a -> Maybe a JustString path' ))-- | as 'throwErrnoIf', but exceptions include the given path when-- appropriate.--throwErrnoPathIf ::(a ->Bool)->String->RawFilePath ->IOa ->IOa throwErrnoPathIf :: forall a. (a -> Bool) -> String -> RawFilePath -> IO a -> IO a throwErrnoPathIf a -> Bool cond String loc RawFilePath path IO a f =doa res <-IO a f ifa -> Bool cond a res thenString -> RawFilePath -> IO a forall a. String -> RawFilePath -> IO a throwErrnoPath String loc RawFilePath path elsea -> IO a forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a returna res -- | as 'throwErrnoIf_', but exceptions include the given path when-- appropriate.--throwErrnoPathIf_ ::(a ->Bool)->String->RawFilePath ->IOa ->IO()throwErrnoPathIf_ :: forall a. (a -> Bool) -> String -> RawFilePath -> IO a -> IO () throwErrnoPathIf_ a -> Bool cond String loc RawFilePath path IO a f =IO a -> IO () forall (f :: * -> *) a. Functor f => f a -> f () void(IO a -> IO ()) -> IO a -> IO () forall a b. (a -> b) -> a -> b $(a -> Bool) -> String -> RawFilePath -> IO a -> IO a forall a. (a -> Bool) -> String -> RawFilePath -> IO a -> IO a throwErrnoPathIf a -> Bool cond String loc RawFilePath path IO a f -- | as 'throwErrnoIfNull', but exceptions include the given path when-- appropriate.--throwErrnoPathIfNull ::String->RawFilePath ->IO(Ptra )->IO(Ptra )throwErrnoPathIfNull :: forall a. String -> RawFilePath -> IO (Ptr a) -> IO (Ptr a) throwErrnoPathIfNull =(Ptr a -> Bool) -> String -> RawFilePath -> IO (Ptr a) -> IO (Ptr a) forall a. (a -> Bool) -> String -> RawFilePath -> IO a -> IO a throwErrnoPathIf (Ptr a -> Ptr a -> Bool forall a. Eq a => a -> a -> Bool ==Ptr a forall a. Ptr a nullPtr)-- | as 'throwErrnoIfMinus1', but exceptions include the given path when-- appropriate.--throwErrnoPathIfMinus1 ::(Eqa ,Numa )=>String->RawFilePath ->IOa ->IOa throwErrnoPathIfMinus1 :: forall a. (Eq a, Num a) => String -> RawFilePath -> IO a -> IO a throwErrnoPathIfMinus1 =(a -> Bool) -> String -> RawFilePath -> IO a -> IO a forall a. (a -> Bool) -> String -> RawFilePath -> IO a -> IO a throwErrnoPathIf (a -> a -> Bool forall a. Eq a => a -> a -> Bool ==-a 1)-- | as 'throwErrnoIfMinus1_', but exceptions include the given path when-- appropriate.--throwErrnoPathIfMinus1_ ::(Eqa ,Numa )=>String->RawFilePath ->IOa ->IO()throwErrnoPathIfMinus1_ :: forall a. (Eq a, Num a) => String -> RawFilePath -> IO a -> IO () throwErrnoPathIfMinus1_ =(a -> Bool) -> String -> RawFilePath -> IO a -> IO () forall a. (a -> Bool) -> String -> RawFilePath -> IO a -> IO () throwErrnoPathIf_ (a -> a -> Bool forall a. Eq a => a -> a -> Bool ==-a 1)-- | as 'throwErrnoTwoPathsIfMinus1_', but exceptions include two paths when appropriate.--throwErrnoTwoPathsIfMinus1_ ::(Eqa ,Numa )=>String->RawFilePath ->RawFilePath ->IOa ->IO()throwErrnoTwoPathsIfMinus1_ :: forall a. (Eq a, Num a) => String -> RawFilePath -> RawFilePath -> IO a -> IO () throwErrnoTwoPathsIfMinus1_ String loc RawFilePath path1 RawFilePath path2 IO a action =doString path1' <-(IOException -> String) -> (String -> String) -> Either IOException String -> String forall a c b. (a -> c) -> (b -> c) -> Either a b -> c either(String -> IOException -> String forall a b. a -> b -> a const(RawFilePath -> String BC.unpackRawFilePath path1 ))String -> String forall a. a -> a id(Either IOException String -> String) -> IO (Either IOException String) -> IO String forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$>forall e a. Exception e => IO a -> IO (Either e a) try@IOException(RawFilePath -> IO String decodeWithBasePosix RawFilePath path1 )String path2' <-(IOException -> String) -> (String -> String) -> Either IOException String -> String forall a c b. (a -> c) -> (b -> c) -> Either a b -> c either(String -> IOException -> String forall a b. a -> b -> a const(RawFilePath -> String BC.unpackRawFilePath path2 ))String -> String forall a. a -> a id(Either IOException String -> String) -> IO (Either IOException String) -> IO String forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$>forall e a. Exception e => IO a -> IO (Either e a) try@IOException(RawFilePath -> IO String decodeWithBasePosix RawFilePath path2 )String -> IO a -> IO () forall a. (Eq a, Num a) => String -> IO a -> IO () throwErrnoIfMinus1_(String loc String -> String -> String forall a. Semigroup a => a -> a -> a <>String " '"String -> String -> String forall a. Semigroup a => a -> a -> a <>String path1' String -> String -> String forall a. Semigroup a => a -> a -> a <>String "' to '"String -> String -> String forall a. Semigroup a => a -> a -> a <>String path2' String -> String -> String forall a. Semigroup a => a -> a -> a <>String "'")IO a action -- | This mimics the filepath decoder base uses on unix,-- with the small distinction that we're not truncating at NUL bytes (because we're not at-- the outer FFI layer).decodeWithBasePosix ::RawFilePath ->IOStringdecodeWithBasePosix :: RawFilePath -> IO String decodeWithBasePosix RawFilePath ba =RawFilePath -> (CStringLen -> IO String) -> IO String forall a. RawFilePath -> (CStringLen -> IO a) -> IO a B.useAsCStringLenRawFilePath ba ((CStringLen -> IO String) -> IO String) -> (CStringLen -> IO String) -> IO String forall a b. (a -> b) -> a -> b $\CStringLen fp ->CStringLen -> IO String peekFilePathPosix CStringLen fp wherepeekFilePathPosix ::CStringLen->IOStringpeekFilePathPosix :: CStringLen -> IO String peekFilePathPosix CStringLen fp =IO TextEncoding getFileSystemEncodingIO TextEncoding -> (TextEncoding -> IO String) -> IO String forall a b. IO a -> (a -> IO b) -> IO b forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b >>=\TextEncoding enc ->TextEncoding -> CStringLen -> IO String GHC.peekCStringLenTextEncoding enc CStringLen fp -- | Wrapper around 'useAsCString', checking the encoded 'FilePath' for internal NUL octets as these are-- disallowed in POSIX filepaths. See https://gitlab.haskell.org/ghc/ghc/-/issues/13660useAsCStringSafe ::RawFilePath ->(CString->IOa )->IOa useAsCStringSafe :: forall a. RawFilePath -> (CString -> IO a) -> IO a useAsCStringSafe RawFilePath path CString -> IO a f =RawFilePath -> (CString -> IO a) -> IO a forall a. RawFilePath -> (CString -> IO a) -> IO a useAsCStringRawFilePath path ((CString -> IO a) -> IO a) -> (CString -> IO a) -> IO a forall a b. (a -> b) -> a -> b $\CString ptr ->doletlen :: Int len =RawFilePath -> Int B.lengthRawFilePath path CSize clen <-CString -> IO CSize c_strlenCString ptr ifCSize clen CSize -> CSize -> Bool forall a. Eq a => a -> a -> Bool ==Int -> CSize forall a b. (Integral a, Num b) => a -> b fromIntegralInt len thenCString -> IO a f CString ptr elsedoString path' <-(IOException -> String) -> (String -> String) -> Either IOException String -> String forall a c b. (a -> c) -> (b -> c) -> Either a b -> c either(String -> IOException -> String forall a b. a -> b -> a const(RawFilePath -> String BC.unpackRawFilePath path ))String -> String forall a. a -> a id(Either IOException String -> String) -> IO (Either IOException String) -> IO String forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$>forall e a. Exception e => IO a -> IO (Either e a) try@IOException(RawFilePath -> IO String decodeWithBasePosix RawFilePath path )IOException -> IO a forall a. IOException -> IO a ioError(String -> IOException err String path' )whereerr :: String -> IOException err String path' =IOError{ioe_handle :: Maybe Handle ioe_handle =Maybe Handle forall a. Maybe a Nothing,ioe_type :: IOErrorType ioe_type =IOErrorType InvalidArgument,ioe_location :: String ioe_location =String "checkForInteriorNuls",ioe_description :: String ioe_description =String "POSIX filepaths must not contain internal NUL octets.",ioe_errno :: Maybe CInt ioe_errno =Maybe CInt forall a. Maybe a Nothing,ioe_filename :: Maybe String ioe_filename =String -> Maybe String forall a. a -> Maybe a JustString path' }