{-# LINE 1 "System/Posix/PosixPath/FilePath.hsc" #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE PatternSynonyms #-}
module System.Posix.PosixPath.FilePath (
     withFilePath, peekFilePath, peekFilePathLen,
     throwErrnoPathIfMinus1Retry,
     throwErrnoPathIfMinus1Retry_,
     throwErrnoPathIfNullRetry,
     throwErrnoPathIfRetry,
     throwErrnoPath,
     throwErrnoPathIf,
     throwErrnoPathIf_,
     throwErrnoPathIfNull,
     throwErrnoPathIfMinus1,
     throwErrnoPathIfMinus1_,
     throwErrnoTwoPathsIfMinus1_
  ) where
import Foreign hiding ( void )
import Foreign.C hiding (
     throwErrnoPath,
     throwErrnoPathIf,
     throwErrnoPathIf_,
     throwErrnoPathIfNull,
     throwErrnoPathIfMinus1,
     throwErrnoPathIfMinus1_ )
import System.OsPath.Types
import Data.ByteString.Internal (c_strlen)
import Control.Monad
import Control.Exception
import System.OsPath.Posix as PS
import System.OsPath.Data.ByteString.Short as BSS
import Prelude hiding (FilePath)
import System.OsString.Internal.Types (PosixString(..), pattern PS)
import GHC.IO.Exception
{-# LINE 56 "System/Posix/PosixPath/FilePath.hsc" #-}
withFilePath :: PosixPath -> (CString -> IO a) -> IO a
withFilePath :: forall a. PosixPath -> (CString -> IO a) -> IO a
withFilePath PosixPath
path = PosixPath -> (CString -> IO a) -> IO a
forall a. PosixPath -> (CString -> IO a) -> IO a
useAsCStringSafe PosixPath
path
peekFilePath :: CString -> IO PosixPath
peekFilePath :: CString -> IO PosixPath
peekFilePath = (ShortByteString -> PosixPath)
-> IO ShortByteString -> IO PosixPath
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ShortByteString -> PosixPath
PosixString (IO ShortByteString -> IO PosixPath)
-> (CString -> IO ShortByteString) -> CString -> IO PosixPath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CString -> IO ShortByteString
packCString
peekFilePathLen :: CStringLen -> IO PosixPath
peekFilePathLen :: CStringLen -> IO PosixPath
peekFilePathLen = (ShortByteString -> PosixPath)
-> IO ShortByteString -> IO PosixPath
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ShortByteString -> PosixPath
PosixString (IO ShortByteString -> IO PosixPath)
-> (CStringLen -> IO ShortByteString) -> CStringLen -> IO PosixPath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CStringLen -> IO ShortByteString
packCStringLen
throwErrnoPathIfMinus1Retry :: (Eq a, Num a)
                            => String -> PosixPath -> IO a -> IO a
throwErrnoPathIfMinus1Retry :: forall a. (Eq a, Num a) => String -> PosixPath -> IO a -> IO a
throwErrnoPathIfMinus1Retry String
loc PosixPath
path IO a
f = do
  (a -> Bool) -> String -> PosixPath -> IO a -> IO a
forall a. (a -> Bool) -> String -> PosixPath -> IO a -> IO a
throwErrnoPathIfRetry (a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== -a
1) String
loc PosixPath
path IO a
f
throwErrnoPathIfMinus1Retry_ :: (Eq a, Num a)
                             => String -> PosixPath -> IO a -> IO ()
throwErrnoPathIfMinus1Retry_ :: forall a. (Eq a, Num a) => String -> PosixPath -> IO a -> IO ()
throwErrnoPathIfMinus1Retry_ String
loc PosixPath
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 -> PosixPath -> IO a -> IO a
forall a. (a -> Bool) -> String -> PosixPath -> IO a -> IO a
throwErrnoPathIfRetry (a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== -a
1) String
loc PosixPath
path IO a
f
throwErrnoPathIfNullRetry :: String -> PosixPath -> IO (Ptr a) -> IO (Ptr a)
throwErrnoPathIfNullRetry :: forall a. String -> PosixPath -> IO (Ptr a) -> IO (Ptr a)
throwErrnoPathIfNullRetry String
loc PosixPath
path IO (Ptr a)
f =
  (Ptr a -> Bool) -> String -> PosixPath -> IO (Ptr a) -> IO (Ptr a)
forall a. (a -> Bool) -> String -> PosixPath -> 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 PosixPath
path IO (Ptr a)
f
throwErrnoPathIfRetry :: (a -> Bool) -> String -> PosixPath -> IO a -> IO a
throwErrnoPathIfRetry :: forall a. (a -> Bool) -> String -> PosixPath -> IO a -> IO a
throwErrnoPathIfRetry a -> Bool
pr String
loc PosixPath
rpath IO a
f =
  do
    a
res <- IO a
f
    if a -> Bool
pr a
res
      then do
        Errno
err <- IO Errno
getErrno
        if Errno
err Errno -> Errno -> Bool
forall a. Eq a => a -> a -> Bool
== Errno
eINTR
          then (a -> Bool) -> String -> PosixPath -> IO a -> IO a
forall a. (a -> Bool) -> String -> PosixPath -> IO a -> IO a
throwErrnoPathIfRetry a -> Bool
pr String
loc PosixPath
rpath IO a
f
          else String -> PosixPath -> IO a
forall a. String -> PosixPath -> IO a
throwErrnoPath String
loc PosixPath
rpath
      else a -> IO a
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return a
res
throwErrnoPath :: String -> PosixPath -> IO a
throwErrnoPath :: forall a. String -> PosixPath -> IO a
throwErrnoPath String
loc PosixPath
path =
  do
    Errno
errno <- IO Errno
getErrno
    String
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 (PosixPath -> String
_toStr PosixPath
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 (PosixPath -> IO String
PS.decodeFS PosixPath
path)
    IOException -> IO a
forall a. IOException -> IO a
ioError (String -> Errno -> Maybe Handle -> Maybe String -> IOException
errnoToIOError String
loc Errno
errno Maybe Handle
forall a. Maybe a
Nothing (String -> Maybe String
forall a. a -> Maybe a
Just String
path'))
throwErrnoPathIf :: (a -> Bool) -> String -> PosixPath -> IO a -> IO a
throwErrnoPathIf :: forall a. (a -> Bool) -> String -> PosixPath -> IO a -> IO a
throwErrnoPathIf a -> Bool
cond String
loc PosixPath
path IO a
f =
  do
    a
res <- IO a
f
    if a -> Bool
cond a
res then String -> PosixPath -> IO a
forall a. String -> PosixPath -> IO a
throwErrnoPath String
loc PosixPath
path else a -> IO a
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return a
res
throwErrnoPathIf_ :: (a -> Bool) -> String -> PosixPath -> IO a -> IO ()
throwErrnoPathIf_ :: forall a. (a -> Bool) -> String -> PosixPath -> IO a -> IO ()
throwErrnoPathIf_ a -> Bool
cond String
loc PosixPath
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 -> PosixPath -> IO a -> IO a
forall a. (a -> Bool) -> String -> PosixPath -> IO a -> IO a
throwErrnoPathIf a -> Bool
cond String
loc PosixPath
path IO a
f
throwErrnoPathIfNull :: String -> PosixPath -> IO (Ptr a) -> IO (Ptr a)
throwErrnoPathIfNull :: forall a. String -> PosixPath -> IO (Ptr a) -> IO (Ptr a)
throwErrnoPathIfNull  = (Ptr a -> Bool) -> String -> PosixPath -> IO (Ptr a) -> IO (Ptr a)
forall a. (a -> Bool) -> String -> PosixPath -> IO a -> IO a
throwErrnoPathIf (Ptr a -> Ptr a -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr a
forall a. Ptr a
nullPtr)
throwErrnoPathIfMinus1 :: (Eq a, Num a) => String -> PosixPath -> IO a -> IO a
throwErrnoPathIfMinus1 :: forall a. (Eq a, Num a) => String -> PosixPath -> IO a -> IO a
throwErrnoPathIfMinus1 = (a -> Bool) -> String -> PosixPath -> IO a -> IO a
forall a. (a -> Bool) -> String -> PosixPath -> IO a -> IO a
throwErrnoPathIf (a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== -a
1)
throwErrnoPathIfMinus1_ :: (Eq a, Num a) => String -> PosixPath -> IO a -> IO ()
throwErrnoPathIfMinus1_ :: forall a. (Eq a, Num a) => String -> PosixPath -> IO a -> IO ()
throwErrnoPathIfMinus1_  = (a -> Bool) -> String -> PosixPath -> IO a -> IO ()
forall a. (a -> Bool) -> String -> PosixPath -> IO a -> IO ()
throwErrnoPathIf_ (a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== -a
1)
throwErrnoTwoPathsIfMinus1_ :: (Eq a, Num a) => String -> PosixPath -> PosixPath -> IO a -> IO ()
throwErrnoTwoPathsIfMinus1_ :: forall a.
(Eq a, Num a) =>
String -> PosixPath -> PosixPath -> IO a -> IO ()
throwErrnoTwoPathsIfMinus1_ String
loc PosixPath
path1 PosixPath
path2 IO a
action = do
    String
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 (PosixPath -> String
_toStr PosixPath
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 (PosixPath -> IO String
PS.decodeFS PosixPath
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 (PosixPath -> String
_toStr PosixPath
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 (PosixPath -> IO String
PS.decodeFS PosixPath
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
_toStr :: PosixPath -> String
_toStr :: PosixPath -> String
_toStr = (PosixChar -> Char) -> [PosixChar] -> String
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PosixChar -> Char
PS.toChar ([PosixChar] -> String)
-> (PosixPath -> [PosixChar]) -> PosixPath -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PosixPath -> [PosixChar]
PS.unpack
useAsCStringSafe :: PosixPath -> (CString -> IO a) -> IO a
useAsCStringSafe :: forall a. PosixPath -> (CString -> IO a) -> IO a
useAsCStringSafe pp :: PosixPath
pp@(PS ShortByteString
path) CString -> IO a
f = ShortByteString -> (CString -> IO a) -> IO a
forall a. ShortByteString -> (CString -> IO a) -> IO a
useAsCString ShortByteString
path ((CString -> IO a) -> IO a) -> (CString -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \CString
ptr -> do
    let len :: Int
len = ShortByteString -> Int
BSS.length ShortByteString
path
    CSize
clen <- CString -> IO CSize
c_strlen CString
ptr
    if CSize
clen CSize -> CSize -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len
        then CString -> IO a
f CString
ptr
        else do
          String
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 (PosixPath -> String
_toStr PosixPath
pp)) 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 (PosixPath -> IO String
PS.decodeFS PosixPath
pp)
          IOException -> IO a
forall a. IOException -> IO a
ioError (String -> IOException
err String
path')
  where
    err :: 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
Just String
path'
          }