You can not select more than 25 topics Topics must start with a letter or number, can include dashes ('-') and can be up to 35 characters long.
 
 
 
 

291 lines
6.9 KiB

  1. {-# LANGUAGE OverloadedStrings #-}
  2. {-# LANGUAGE PackageImports #-}
  3. module Utils where
  4. import Control.Applicative
  5. (
  6. (<$>)
  7. )
  8. import Control.Monad
  9. (
  10. forM_
  11. , void
  12. )
  13. import Control.Monad.IfElse
  14. (
  15. whenM
  16. )
  17. import qualified Data.ByteString as BS
  18. import Data.IORef
  19. (
  20. newIORef
  21. , readIORef
  22. , writeIORef
  23. , IORef
  24. )
  25. import HPath.IO
  26. import HPath.IO.Errors
  27. import Prelude hiding (appendFile, readFile, writeFile)
  28. import Data.Maybe
  29. (
  30. fromJust
  31. )
  32. import qualified HPath as P
  33. import System.IO.Unsafe
  34. (
  35. unsafePerformIO
  36. )
  37. import qualified System.Posix.Directory.Traversals as DT
  38. import Data.ByteString
  39. (
  40. ByteString
  41. )
  42. import qualified Data.ByteString.Lazy as L
  43. import System.Posix.Files.ByteString
  44. (
  45. groupExecuteMode
  46. , groupReadMode
  47. , nullFileMode
  48. , otherExecuteMode
  49. , otherReadMode
  50. , ownerExecuteMode
  51. , ownerReadMode
  52. , setFileMode
  53. , unionFileModes
  54. )
  55. baseTmpDir :: IORef (Maybe ByteString)
  56. {-# NOINLINE baseTmpDir #-}
  57. baseTmpDir = unsafePerformIO (newIORef Nothing)
  58. tmpDir :: IORef (Maybe ByteString)
  59. {-# NOINLINE tmpDir #-}
  60. tmpDir = unsafePerformIO (newIORef Nothing)
  61. -----------------
  62. --[ Utilities ]--
  63. -----------------
  64. setTmpDir :: ByteString -> IO ()
  65. {-# NOINLINE setTmpDir #-}
  66. setTmpDir bs = do
  67. tmp <- fromJust <$> readIORef baseTmpDir
  68. writeIORef tmpDir (Just (tmp `BS.append` bs))
  69. createTmpDir :: IO ()
  70. {-# NOINLINE createTmpDir #-}
  71. createTmpDir = do
  72. tmp <- P.parseAbs =<< (fromJust <$> readIORef tmpDir)
  73. void $ createDir newDirPerms tmp
  74. deleteTmpDir :: IO ()
  75. {-# NOINLINE deleteTmpDir #-}
  76. deleteTmpDir = do
  77. tmp <- P.parseAbs =<< (fromJust <$> readIORef tmpDir)
  78. void $ deleteDir tmp
  79. deleteBaseTmpDir :: IO ()
  80. {-# NOINLINE deleteBaseTmpDir #-}
  81. deleteBaseTmpDir = do
  82. tmp <- (fromJust <$> readIORef baseTmpDir) >>= P.parseAbs
  83. contents <- getDirsFiles tmp
  84. forM_ contents deleteDir
  85. void $ deleteDir tmp
  86. withRawTmpDir :: (P.Path P.Abs -> IO a) -> IO a
  87. {-# NOINLINE withRawTmpDir #-}
  88. withRawTmpDir f = do
  89. tmp <- P.parseAbs =<< (fromJust <$> readIORef tmpDir)
  90. f tmp
  91. getRawTmpDir :: IO ByteString
  92. {-# NOINLINE getRawTmpDir #-}
  93. getRawTmpDir = withRawTmpDir (return . flip BS.append "/" . P.fromAbs)
  94. withTmpDir :: ByteString -> (P.Path P.Abs -> IO a) -> IO a
  95. {-# NOINLINE withTmpDir #-}
  96. withTmpDir ip f = do
  97. tmp <- P.parseAbs =<< (fromJust <$> readIORef tmpDir)
  98. p <- (tmp P.</>) <$> P.parseRel ip
  99. f p
  100. withTmpDir' :: ByteString
  101. -> ByteString
  102. -> (P.Path P.Abs -> P.Path P.Abs -> IO a)
  103. -> IO a
  104. {-# NOINLINE withTmpDir' #-}
  105. withTmpDir' ip1 ip2 f = do
  106. tmp <- P.parseAbs =<< (fromJust <$> readIORef tmpDir)
  107. p1 <- (tmp P.</>) <$> P.parseRel ip1
  108. p2 <- (tmp P.</>) <$> P.parseRel ip2
  109. f p1 p2
  110. removeFileIfExists :: ByteString -> IO ()
  111. {-# NOINLINE removeFileIfExists #-}
  112. removeFileIfExists bs =
  113. withTmpDir bs $ \p -> whenM (doesFileExist p) (deleteFile p)
  114. removeDirIfExists :: ByteString -> IO ()
  115. {-# NOINLINE removeDirIfExists #-}
  116. removeDirIfExists bs =
  117. withTmpDir bs $ \p -> whenM (doesDirectoryExist p) (deleteDirRecursive p)
  118. copyFile' :: ByteString -> ByteString -> CopyMode -> IO ()
  119. {-# NOINLINE copyFile' #-}
  120. copyFile' inputFileP outputFileP cm =
  121. withTmpDir' inputFileP outputFileP (\p1 p2 -> copyFile p1 p2 cm)
  122. copyDirRecursive' :: ByteString -> ByteString
  123. -> CopyMode -> RecursiveErrorMode -> IO ()
  124. {-# NOINLINE copyDirRecursive' #-}
  125. copyDirRecursive' inputDirP outputDirP cm rm =
  126. withTmpDir' inputDirP outputDirP (\p1 p2 -> copyDirRecursive p1 p2 cm rm)
  127. createDir' :: ByteString -> IO ()
  128. {-# NOINLINE createDir' #-}
  129. createDir' dest = withTmpDir dest (createDir newDirPerms)
  130. createDirRecursive' :: ByteString -> IO ()
  131. {-# NOINLINE createDirRecursive' #-}
  132. createDirRecursive' dest = withTmpDir dest (createDirRecursive newDirPerms)
  133. createRegularFile' :: ByteString -> IO ()
  134. {-# NOINLINE createRegularFile' #-}
  135. createRegularFile' dest = withTmpDir dest (createRegularFile newFilePerms)
  136. createSymlink' :: ByteString -> ByteString -> IO ()
  137. {-# NOINLINE createSymlink' #-}
  138. createSymlink' dest sympoint = withTmpDir dest
  139. (\x -> createSymlink x sympoint)
  140. renameFile' :: ByteString -> ByteString -> IO ()
  141. {-# NOINLINE renameFile' #-}
  142. renameFile' inputFileP outputFileP =
  143. withTmpDir' inputFileP outputFileP $ \i o -> do
  144. renameFile i o
  145. renameFile o i
  146. moveFile' :: ByteString -> ByteString -> CopyMode -> IO ()
  147. {-# NOINLINE moveFile' #-}
  148. moveFile' inputFileP outputFileP cm =
  149. withTmpDir' inputFileP outputFileP $ \i o -> do
  150. moveFile i o cm
  151. moveFile o i Strict
  152. recreateSymlink' :: ByteString -> ByteString -> CopyMode -> IO ()
  153. {-# NOINLINE recreateSymlink' #-}
  154. recreateSymlink' inputFileP outputFileP cm =
  155. withTmpDir' inputFileP outputFileP (\p1 p2 -> recreateSymlink p1 p2 cm)
  156. noWritableDirPerms :: ByteString -> IO ()
  157. {-# NOINLINE noWritableDirPerms #-}
  158. noWritableDirPerms path = withTmpDir path $ \p ->
  159. setFileMode (P.fromAbs p) perms
  160. where
  161. perms = ownerReadMode
  162. `unionFileModes` ownerExecuteMode
  163. `unionFileModes` groupReadMode
  164. `unionFileModes` groupExecuteMode
  165. `unionFileModes` otherReadMode
  166. `unionFileModes` otherExecuteMode
  167. noPerms :: ByteString -> IO ()
  168. {-# NOINLINE noPerms #-}
  169. noPerms path = withTmpDir path $ \p -> setFileMode (P.fromAbs p) nullFileMode
  170. normalDirPerms :: ByteString -> IO ()
  171. {-# NOINLINE normalDirPerms #-}
  172. normalDirPerms path =
  173. withTmpDir path $ \p -> setFileMode (P.fromAbs p) newDirPerms
  174. normalFilePerms :: ByteString -> IO ()
  175. {-# NOINLINE normalFilePerms #-}
  176. normalFilePerms path =
  177. withTmpDir path $ \p -> setFileMode (P.fromAbs p) newFilePerms
  178. getFileType' :: ByteString -> IO FileType
  179. {-# NOINLINE getFileType' #-}
  180. getFileType' path = withTmpDir path getFileType
  181. getDirsFiles' :: ByteString -> IO [P.Path P.Abs]
  182. {-# NOINLINE getDirsFiles' #-}
  183. getDirsFiles' path = withTmpDir path getDirsFiles
  184. deleteFile' :: ByteString -> IO ()
  185. {-# NOINLINE deleteFile' #-}
  186. deleteFile' p = withTmpDir p deleteFile
  187. deleteDir' :: ByteString -> IO ()
  188. {-# NOINLINE deleteDir' #-}
  189. deleteDir' p = withTmpDir p deleteDir
  190. deleteDirRecursive' :: ByteString -> IO ()
  191. {-# NOINLINE deleteDirRecursive' #-}
  192. deleteDirRecursive' p = withTmpDir p deleteDirRecursive
  193. canonicalizePath' :: ByteString -> IO (P.Path P.Abs)
  194. {-# NOINLINE canonicalizePath' #-}
  195. canonicalizePath' p = withTmpDir p canonicalizePath
  196. writeFile' :: ByteString -> ByteString -> IO ()
  197. {-# NOINLINE writeFile' #-}
  198. writeFile' ip bs =
  199. withTmpDir ip $ \p -> writeFile p bs
  200. appendFile' :: ByteString -> ByteString -> IO ()
  201. {-# NOINLINE appendFile' #-}
  202. appendFile' ip bs =
  203. withTmpDir ip $ \p -> appendFile p bs
  204. allDirectoryContents' :: ByteString -> IO [ByteString]
  205. {-# NOINLINE allDirectoryContents' #-}
  206. allDirectoryContents' ip =
  207. withTmpDir ip $ \p -> DT.allDirectoryContents' (P.fromAbs p)
  208. readFile' :: ByteString -> IO ByteString
  209. {-# NOINLINE readFile' #-}
  210. readFile' p = withTmpDir p readFile
  211. readFileEOF' :: ByteString -> IO L.ByteString
  212. {-# NOINLINE readFileEOF' #-}
  213. readFileEOF' p = withTmpDir p readFileEOF