summaryrefslogtreecommitdiff
path: root/lib/Paths.hs
blob: 49c029582dd498eb9a2ea469230c6b6110c1f1a5 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
{-# LANGUAGE OverloadedStrings #-}

-- |

module Paths where

import           Data.Text             (Text)
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
data RelPath = Path Int Text (Maybe Text)
  deriving (Show, Eq, Ord)

-- | horrible regex parsing for filepaths that is hopefully kinda safe
parsePath :: Text -> Maybe RelPath
parsePath text =
  if rest =~ ("^([^/]*[^\\./]/)*[^/]*[^\\./]$" :: Text) :: Bool
  then Just $ Path up path fragment
  else Nothing
  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 _) = ups <> rest
    where ups = T.concat $ replicate up "../"

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