module Storage.Hashed.AnchoredPath ( Name(..), AnchoredPath(..), appendPath, anchorPath , isPrefix, parent, parents, catPaths -- * Unsafe functions. , nameToFilePath, nameFromFilePath , floatBS, anchorBS ) where import qualified Data.ByteString.Char8 as BS import Data.List( isPrefixOf, inits ) import System.FilePath( () ) ------------------------------- -- AnchoredPath utilities -- newtype Name = Name BS.ByteString deriving (Eq, Show, Ord) newtype AnchoredPath = AnchoredPath [Name] deriving (Eq, Show, Ord) -- Both unsafe. nameToFilePath :: Name -> FilePath nameToFilePath (Name p) = BS.unpack p nameFromFilePath :: FilePath -> Name nameFromFilePath p = Name $ BS.pack p isPrefix :: AnchoredPath -> AnchoredPath -> Bool (AnchoredPath a) `isPrefix` (AnchoredPath b) = a `isPrefixOf` b -- | Append an element to the end of a path. appendPath :: AnchoredPath -> Name -> AnchoredPath appendPath (AnchoredPath p) n = case n of (Name s) | s == BS.empty -> AnchoredPath p | otherwise -> AnchoredPath $ p ++ [n] catPaths :: AnchoredPath -> AnchoredPath -> AnchoredPath catPaths (AnchoredPath p) (AnchoredPath n) = AnchoredPath $ p ++ n parent :: AnchoredPath -> AnchoredPath parent (AnchoredPath x) = AnchoredPath (init x) parents :: AnchoredPath -> [AnchoredPath] parents (AnchoredPath x) = case x of [] -> [] [_] -> [AnchoredPath []] _ -> map AnchoredPath $ tail $ inits (init x) -- | Take a "root" directory and an anchored path and produce a full path. anchorPath :: FilePath -> AnchoredPath -> FilePath anchorPath dir (AnchoredPath p) = dir path where path = BS.unpack (flatten p) flatten = BS.intercalate (BS.singleton '/') . map (\(Name x) -> x) {-# INLINE anchorPath #-} floatBS :: BS.ByteString -> AnchoredPath floatBS = AnchoredPath . map Name . takeWhile (not . BS.null) . BS.split '/' anchorBS :: AnchoredPath -> BS.ByteString anchorBS (AnchoredPath p) = BS.intercalate (BS.singleton '/') [ n | (Name n) <- p ]