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.
 
 
 
 

470 lines
13 KiB

  1. -- |
  2. -- Module : HPath
  3. -- Copyright : © 2015–2016 FP Complete, 2016 Julian Ospald
  4. -- License : BSD 3 clause
  5. --
  6. -- Maintainer : Julian Ospald <hasufell@posteo.de>
  7. -- Stability : experimental
  8. -- Portability : portable
  9. --
  10. -- Support for well-typed paths.
  11. {-# LANGUAGE CPP #-}
  12. {-# LANGUAGE DeriveDataTypeable #-}
  13. {-# LANGUAGE EmptyDataDecls #-}
  14. #if __GLASGOW_HASKELL__ >= 708
  15. {-# LANGUAGE PatternSynonyms #-}
  16. #endif
  17. {-# LANGUAGE QuasiQuotes #-}
  18. {-# LANGUAGE TemplateHaskell #-}
  19. module HPath
  20. (
  21. -- * Types
  22. Abs
  23. ,Path
  24. ,Rel
  25. ,PathParseException
  26. ,PathException
  27. #if __GLASGOW_HASKELL__ >= 708
  28. -- * PatternSynonyms/ViewPatterns
  29. ,pattern Path
  30. #endif
  31. -- * Path Construction
  32. ,parseAbs
  33. ,parseRel
  34. ,parseAny
  35. ,rootPath
  36. -- * Path Conversion
  37. ,fromAbs
  38. ,fromRel
  39. ,toFilePath
  40. ,fromAny
  41. -- * Path Operations
  42. ,(</>)
  43. ,basename
  44. ,dirname
  45. ,getAllParents
  46. ,getAllComponents
  47. ,getAllComponentsAfterRoot
  48. ,stripDir
  49. -- * Path Examination
  50. ,isParentOf
  51. ,isRootPath
  52. -- * Path IO helpers
  53. ,withAbsPath
  54. ,withRelPath
  55. -- * Quasiquoters
  56. ,abs
  57. ,rel
  58. )
  59. where
  60. import Control.Exception (Exception)
  61. import Control.Monad.Catch (MonadThrow(..))
  62. #if MIN_VERSION_bytestring(0,10,8)
  63. import Data.ByteString(ByteString, stripPrefix)
  64. #else
  65. import Data.ByteString(ByteString)
  66. import qualified Data.List as L
  67. #endif
  68. import qualified Data.ByteString as BS
  69. import Data.ByteString.UTF8
  70. import Data.Data
  71. import Data.Maybe
  72. import Data.Word8
  73. import HPath.Internal
  74. import Language.Haskell.TH
  75. import Language.Haskell.TH.Syntax (Exp(..), Lift(..), lift)
  76. import Language.Haskell.TH.Quote (QuasiQuoter(..))
  77. import Prelude hiding (abs, any)
  78. import System.Posix.FilePath hiding ((</>))
  79. --------------------------------------------------------------------------------
  80. -- Types
  81. -- | An absolute path.
  82. data Abs deriving (Typeable)
  83. -- | A relative path; one without a root.
  84. data Rel deriving (Typeable)
  85. -- | Exception when parsing a location.
  86. data PathParseException
  87. = InvalidAbs ByteString
  88. | InvalidRel ByteString
  89. | Couldn'tStripPrefixTPS ByteString ByteString
  90. deriving (Show,Typeable)
  91. instance Exception PathParseException
  92. data PathException = RootDirHasNoBasename
  93. deriving (Show,Typeable)
  94. instance Exception PathException
  95. --------------------------------------------------------------------------------
  96. -- PatternSynonyms
  97. #if __GLASGOW_HASKELL__ >= 710
  98. pattern Path :: ByteString -> Path a
  99. #endif
  100. #if __GLASGOW_HASKELL__ >= 708
  101. pattern Path x <- (MkPath x)
  102. #endif
  103. --------------------------------------------------------------------------------
  104. -- Path Parsers
  105. -- | Get a location for an absolute path. Produces a normalised path.
  106. --
  107. -- Throws: 'PathParseException'
  108. --
  109. -- >>> parseAbs "/abc" :: Maybe (Path Abs)
  110. -- Just "/abc"
  111. -- >>> parseAbs "/" :: Maybe (Path Abs)
  112. -- Just "/"
  113. -- >>> parseAbs "/abc/def" :: Maybe (Path Abs)
  114. -- Just "/abc/def"
  115. -- >>> parseAbs "/abc/def/.///" :: Maybe (Path Abs)
  116. -- Just "/abc/def"
  117. -- >>> parseAbs "abc" :: Maybe (Path Abs)
  118. -- Nothing
  119. -- >>> parseAbs "" :: Maybe (Path Abs)
  120. -- Nothing
  121. -- >>> parseAbs "/abc/../foo" :: Maybe (Path Abs)
  122. -- Nothing
  123. parseAbs :: MonadThrow m
  124. => ByteString -> m (Path Abs)
  125. parseAbs filepath =
  126. if isAbsolute filepath &&
  127. isValid filepath &&
  128. not (hasParentDir filepath)
  129. then return (MkPath . dropTrailingPathSeparator . normalise $ filepath)
  130. else throwM (InvalidAbs filepath)
  131. -- | Get a location for a relative path. Produces a normalised
  132. -- path.
  133. --
  134. -- Note that @filepath@ may contain any number of @./@ but may not consist
  135. -- solely of @./@. It also may not contain a single @..@ anywhere.
  136. --
  137. -- Throws: 'PathParseException'
  138. --
  139. -- >>> parseRel "abc" :: Maybe (Path Rel)
  140. -- Just "abc"
  141. -- >>> parseRel "def/" :: Maybe (Path Rel)
  142. -- Just "def"
  143. -- >>> parseRel "abc/def" :: Maybe (Path Rel)
  144. -- Just "abc/def"
  145. -- >>> parseRel "abc/def/." :: Maybe (Path Rel)
  146. -- Just "abc/def"
  147. -- >>> parseRel "/abc" :: Maybe (Path Rel)
  148. -- Nothing
  149. -- >>> parseRel "" :: Maybe (Path Rel)
  150. -- Nothing
  151. -- >>> parseRel "abc/../foo" :: Maybe (Path Rel)
  152. -- Nothing
  153. -- >>> parseRel "." :: Maybe (Path Rel)
  154. -- Nothing
  155. -- >>> parseRel ".." :: Maybe (Path Rel)
  156. -- Nothing
  157. parseRel :: MonadThrow m
  158. => ByteString -> m (Path Rel)
  159. parseRel filepath =
  160. if not (isAbsolute filepath) &&
  161. filepath /= BS.singleton _period &&
  162. filepath /= BS.pack [_period, _period] &&
  163. not (hasParentDir filepath) &&
  164. isValid filepath
  165. then return (MkPath . dropTrailingPathSeparator . normalise $ filepath)
  166. else throwM (InvalidRel filepath)
  167. -- | Parses a path, whether it's relative or absolute.
  168. --
  169. -- Excludes '.' and '..'.
  170. --
  171. -- Throws: 'PathParseException'
  172. --
  173. -- >>> parseAny "/abc" :: Maybe (Either (Path Abs) (Path Rel))
  174. -- Just (Left "/abc")
  175. -- >>> parseAny "..." :: Maybe (Either (Path Abs) (Path Rel))
  176. -- Just (Right "...")
  177. -- >>> parseAny "abc/def" :: Maybe (Either (Path Abs) (Path Rel))
  178. -- Just (Right "abc/def")
  179. -- >>> parseAny "abc/def/." :: Maybe (Either (Path Abs) (Path Rel))
  180. -- Just (Right "abc/def")
  181. -- >>> parseAny "/abc" :: Maybe (Either (Path Abs) (Path Rel))
  182. -- Just (Left "/abc")
  183. -- >>> parseAny "" :: Maybe (Either (Path Abs) (Path Rel))
  184. -- Nothing
  185. -- >>> parseAny "abc/../foo" :: Maybe (Either (Path Abs) (Path Rel))
  186. -- Nothing
  187. -- >>> parseAny "." :: Maybe (Either (Path Abs) (Path Rel))
  188. -- Nothing
  189. -- >>> parseAny ".." :: Maybe (Either (Path Abs) (Path Rel))
  190. -- Nothing
  191. parseAny :: MonadThrow m => ByteString -> m (Either (Path Abs) (Path Rel))
  192. parseAny filepath = case parseAbs filepath of
  193. Just p -> pure $ Left p
  194. Nothing -> case parseRel filepath of
  195. Just p -> pure $ Right p
  196. Nothing -> throwM (InvalidRel filepath)
  197. rootPath :: Path Abs
  198. rootPath = (MkPath (BS.singleton _slash))
  199. --------------------------------------------------------------------------------
  200. -- Path Conversion
  201. -- | Convert any Path to a ByteString type.
  202. toFilePath :: Path b -> ByteString
  203. toFilePath (MkPath l) = l
  204. -- | Convert an absolute Path to a ByteString type.
  205. fromAbs :: Path Abs -> ByteString
  206. fromAbs = toFilePath
  207. -- | Convert a relative Path to a ByteString type.
  208. fromRel :: Path Rel -> ByteString
  209. fromRel = toFilePath
  210. fromAny :: Either (Path Abs) (Path Rel) -> ByteString
  211. fromAny = either toFilePath toFilePath
  212. --------------------------------------------------------------------------------
  213. -- Path Operations
  214. -- | Append two paths.
  215. --
  216. -- The second argument must always be a relative path, which ensures
  217. -- that undefinable things like `"/abc" </> "/def"` cannot happen.
  218. --
  219. -- Technically, the first argument can be a path that points to a non-directory,
  220. -- because this library is IO-agnostic and makes no assumptions about
  221. -- file types.
  222. --
  223. -- >>> (MkPath "/") </> (MkPath "file" :: Path Rel)
  224. -- "/file"
  225. -- >>> (MkPath "/path/to") </> (MkPath "file" :: Path Rel)
  226. -- "/path/to/file"
  227. -- >>> (MkPath "/") </> (MkPath "file/lal" :: Path Rel)
  228. -- "/file/lal"
  229. -- >>> (MkPath "/") </> (MkPath "file" :: Path Rel)
  230. -- "/file"
  231. (</>) :: Path b -> Path Rel -> Path b
  232. (</>) (MkPath a) (MkPath b) = MkPath (a' `BS.append` b)
  233. where
  234. a' = if hasTrailingPathSeparator a
  235. then a
  236. else addTrailingPathSeparator a
  237. -- | Strip directory from path, making it relative to that directory.
  238. -- Throws 'Couldn'tStripPrefixDir' if directory is not a parent of the path.
  239. --
  240. -- The bases must match.
  241. --
  242. -- >>> (MkPath "/lal/lad") `stripDir` (MkPath "/lal/lad/fad") :: Maybe (Path Rel)
  243. -- Just "fad"
  244. -- >>> (MkPath "lal/lad") `stripDir` (MkPath "lal/lad/fad") :: Maybe (Path Rel)
  245. -- Just "fad"
  246. -- >>> (MkPath "/") `stripDir` (MkPath "/") :: Maybe (Path Rel)
  247. -- Nothing
  248. -- >>> (MkPath "/lal/lad/fad") `stripDir` (MkPath "/lal/lad") :: Maybe (Path Rel)
  249. -- Nothing
  250. -- >>> (MkPath "fad") `stripDir` (MkPath "fad") :: Maybe (Path Rel)
  251. -- Nothing
  252. stripDir :: MonadThrow m
  253. => Path b -> Path b -> m (Path Rel)
  254. stripDir (MkPath p) (MkPath l) =
  255. case stripPrefix p' l of
  256. Nothing -> throwM (Couldn'tStripPrefixTPS p' l)
  257. Just ok -> if BS.null ok
  258. then throwM (Couldn'tStripPrefixTPS p' l)
  259. else return (MkPath ok)
  260. where
  261. p' = addTrailingPathSeparator p
  262. -- |Get all parents of a path.
  263. --
  264. -- >>> getAllParents (MkPath "/abs/def/dod")
  265. -- ["/abs/def","/abs","/"]
  266. -- >>> getAllParents (MkPath "/foo")
  267. -- ["/"]
  268. -- >>> getAllParents (MkPath "/")
  269. -- []
  270. getAllParents :: Path Abs -> [Path Abs]
  271. getAllParents (MkPath p)
  272. | np == BS.singleton pathSeparator = []
  273. | otherwise = dirname (MkPath np) : getAllParents (dirname $ MkPath np)
  274. where
  275. np = normalise p
  276. -- | Gets all path components.
  277. --
  278. -- >>> getAllComponents (MkPath "abs/def/dod")
  279. -- ["abs","def","dod"]
  280. -- >>> getAllComponents (MkPath "abs")
  281. -- ["abs"]
  282. getAllComponents :: Path Rel -> [Path Rel]
  283. getAllComponents (MkPath p) = fmap MkPath . splitDirectories $ p
  284. -- | Gets all path components after the "/" root directory.
  285. --
  286. -- >>> getAllComponentsAfterRoot (MkPath "/abs/def/dod")
  287. -- ["abs","def","dod"]
  288. -- >>> getAllComponentsAfterRoot (MkPath "/abs")
  289. -- ["abs"]
  290. getAllComponentsAfterRoot :: Path Abs -> [Path Rel]
  291. getAllComponentsAfterRoot p = getAllComponents (fromJust $ stripDir rootPath p)
  292. -- | Extract the directory name of a path.
  293. --
  294. -- >>> dirname (MkPath "/abc/def/dod")
  295. -- "/abc/def"
  296. -- >>> dirname (MkPath "/")
  297. -- "/"
  298. dirname :: Path Abs -> Path Abs
  299. dirname (MkPath fp) = MkPath (takeDirectory fp)
  300. -- | Extract the file part of a path.
  301. --
  302. --
  303. -- The following properties hold:
  304. --
  305. -- @basename (p \<\/> a) == basename a@
  306. --
  307. -- Throws: `PathException` if given the root path "/"
  308. --
  309. -- >>> basename (MkPath "/abc/def/dod") :: Maybe (Path Rel)
  310. -- Just "dod"
  311. -- >>> basename (MkPath "abc/def/dod") :: Maybe (Path Rel)
  312. -- Just "dod"
  313. -- >>> basename (MkPath "dod") :: Maybe (Path Rel)
  314. -- Just "dod"
  315. -- >>> basename (MkPath "/") :: Maybe (Path Rel)
  316. -- Nothing
  317. basename :: MonadThrow m => Path b -> m (Path Rel)
  318. basename (MkPath l)
  319. | not (isAbsolute rl) = return $ MkPath rl
  320. | otherwise = throwM RootDirHasNoBasename
  321. where
  322. rl = last . splitPath $ l
  323. --------------------------------------------------------------------------------
  324. -- Path Examination
  325. -- | Is p a parent of the given location? Implemented in terms of
  326. -- 'stripDir'. The bases must match.
  327. --
  328. -- >>> (MkPath "/lal/lad") `isParentOf` (MkPath "/lal/lad/fad")
  329. -- True
  330. -- >>> (MkPath "lal/lad") `isParentOf` (MkPath "lal/lad/fad")
  331. -- True
  332. -- >>> (MkPath "/") `isParentOf` (MkPath "/")
  333. -- False
  334. -- >>> (MkPath "/lal/lad/fad") `isParentOf` (MkPath "/lal/lad")
  335. -- False
  336. -- >>> (MkPath "fad") `isParentOf` (MkPath "fad")
  337. -- False
  338. isParentOf :: Path b -> Path b -> Bool
  339. isParentOf p l = isJust (stripDir p l :: Maybe (Path Rel))
  340. -- | Check whether the given Path is the root "/" path.
  341. --
  342. -- >>> isRootPath (MkPath "/lal/lad")
  343. -- False
  344. -- >>> isRootPath (MkPath "/")
  345. -- True
  346. isRootPath :: Path Abs -> Bool
  347. isRootPath = (== rootPath)
  348. --------------------------------------------------------------------------------
  349. -- Path IO helpers
  350. withAbsPath :: Path Abs -> (ByteString -> IO a) -> IO a
  351. withAbsPath (MkPath p) action = action p
  352. withRelPath :: Path Rel -> (ByteString -> IO a) -> IO a
  353. withRelPath (MkPath p) action = action p
  354. ------------------------
  355. -- ByteString helpers
  356. #if MIN_VERSION_bytestring(0,10,8)
  357. #else
  358. stripPrefix :: ByteString -> ByteString -> Maybe ByteString
  359. stripPrefix a b = BS.pack `fmap` L.stripPrefix (BS.unpack a) (BS.unpack b)
  360. #endif
  361. ------------------------
  362. -- QuasiQuoters
  363. instance Lift (Path a) where
  364. lift (MkPath bs) = AppE <$> [| MkPath . BS.pack |] <*> lift (BS.unpack bs)
  365. qq :: (ByteString -> Q Exp) -> QuasiQuoter
  366. qq quoteExp' =
  367. QuasiQuoter
  368. { quoteExp = (\s -> quoteExp' . fromString $ s)
  369. , quotePat = \_ ->
  370. fail "illegal QuasiQuote (allowed as expression only, used as a pattern)"
  371. , quoteType = \_ ->
  372. fail "illegal QuasiQuote (allowed as expression only, used as a type)"
  373. , quoteDec = \_ ->
  374. fail "illegal QuasiQuote (allowed as expression only, used as a declaration)"
  375. }
  376. mkAbs :: ByteString -> Q Exp
  377. mkAbs = either (error . show) lift . parseAbs
  378. mkRel :: ByteString -> Q Exp
  379. mkRel = either (error . show) lift . parseRel
  380. -- | Quasiquote an absolute Path. This accepts Unicode Chars and will encode as UTF-8.
  381. --
  382. -- >>> [abs|/etc/profile|] :: Path Abs
  383. -- "/etc/profile"
  384. -- >>> [abs|/|] :: Path Abs
  385. -- "/"
  386. -- >>> [abs|/|] :: Path Abs
  387. -- "/\239\131\144"
  388. abs :: QuasiQuoter
  389. abs = qq mkAbs
  390. -- | Quasiquote a relative Path. This accepts Unicode Chars and will encode as UTF-8.
  391. --
  392. -- >>> [rel|etc|] :: Path Rel
  393. -- "etc"
  394. -- >>> [rel|bar/baz|] :: Path Rel
  395. -- "bar/baz"
  396. -- >>> [rel||] :: Path Rel
  397. -- "\239\131\144"
  398. rel :: QuasiQuoter
  399. rel = qq mkRel