{-# LANGUAGE MultiWayIf #-} {-# LANGUAGE OverloadedStrings #-} -- | Paths are horrible, so they have their own module now. -- I just hope you are running this on some kind of Unix module Paths where import Data.Text (Text, isPrefixOf) import qualified Data.Text as T import System.FilePath (splitPath) import System.FilePath.Posix (()) import Text.Regex.TDFA import Util (PrettyPrint (prettyprint)) -- | a normalised path: a number of "upwards" steps, and -- a path without any . or .. in it. Also possibly a -- fragment, mostly for map links. data RelPath = Path Int Text (Maybe Text) deriving (Show, Eq, Ord) data PathResult = OkRelPath RelPath | AbsolutePath | NotAPath | UnderscoreMapLink | AtMapLink -- | horrible regex parsing for filepaths that is hopefully kinda safe parsePath :: Text -> PathResult parsePath text = if | rest =~ ("^([^/]*[^\\./]/)*[^/]*[^\\./]$" :: Text) -> OkRelPath (Path up path fragment) | "/_/" `isPrefixOf` text -> UnderscoreMapLink | "/@/" `isPrefixOf` text -> AtMapLink | "/" `isPrefixOf` text -> AbsolutePath | otherwise -> NotAPath where (_, prefix, rest, _) = text =~ ("^((\\.|\\.\\.)/)*" :: Text) :: (Text, Text, Text, [Text]) -- how many steps upwards in the tree? up = length . filter (".." ==) . T.splitOn "/" $ prefix parts = T.splitOn "#" rest path = head parts fragment = if length parts >= 2 then Just $ T.concat $ tail parts -- TODO! else Nothing instance PrettyPrint RelPath where prettyprint (Path up rest frag) = ups <> rest <> fragment where ups = T.concat $ replicate up "../" fragment = maybe mempty ("#" <>) frag -- | Normalises a path. -- -- It takes a `prefix`, and will "truncate" the .. operator -- at the end of the prefix, i.e. it will never return paths -- that lie (naïvely) outside of the prefix. normalise :: FilePath -> RelPath -> FilePath normalise prefix (Path 0 path _) = prefix T.unpack path normalise prefix (Path i path _) = concat (take (length dirs - i) dirs) T.unpack path where dirs = splitPath prefix normaliseWithFrag :: FilePath -> RelPath -> FilePath normaliseWithFrag prefix (Path i path frag) = normalise prefix (Path (i+1) path frag) <> T.unpack (maybe mempty ("#" <>) frag)