From 04b98e4d62fe33b4fa357f2b52ffcc4f2c413302 Mon Sep 17 00:00:00 2001
From: stuebinm <stuebinm@disroot.org>
Date: Thu, 23 Sep 2021 03:11:28 +0200
Subject: [PATCH] some documentation

---
 lib/CheckDir.hs | 13 +++++++++++--
 lib/Paths.hs    | 12 +++++++++---
 2 files changed, 20 insertions(+), 5 deletions(-)

diff --git a/lib/CheckDir.hs b/lib/CheckDir.hs
index 753d5ab..f551e6a 100644
--- a/lib/CheckDir.hs
+++ b/lib/CheckDir.hs
@@ -32,11 +32,13 @@ setFromList  = M.fromList . flip zip (repeat ())
 listFromSet :: Set a -> [a]
 listFromSet = map fst . M.toList
 
+-- | Result of linting an entire directory / repository
 data DirResult = DirResult
   { dirresultMaps :: Map FilePath MapResult
   , dirresultDeps :: [Text]
   } deriving (Generic, ToJSON)
 
+
 instance PrettyPrint DirResult where
   prettyprint res = T.concat
     (map (\(p,lints) -> "\nin " <> T.pack p <> ":\n" <> prettyprint lints) $ M.toList $ dirresultMaps res)
@@ -54,11 +56,18 @@ instance Monoid DirResult where
     }
 
 
--- TODO: options?
+-- | The nice function to check an entire repository with.
+-- gets a prefix (i.e. the bare path to the repository) and
+-- a root (i.e. the name of the file containing the entrypoint
+-- map within that file)
 recursiveCheckDir :: FilePath -> FilePath -> IO DirResult
 recursiveCheckDir prefix root = recursiveCheckDir' prefix [root] mempty mempty
 
-
+-- | The less-nice function for checking an entire repository.
+--
+-- Strictly speaking it probably doesn't need to have `done` and
+-- `acc` since they are essentially the same thing, but doing it
+-- like this seemed convenient at the time
 recursiveCheckDir' :: FilePath -> [FilePath] -> Set FilePath -> DirResult -> IO DirResult
 recursiveCheckDir' prefix paths done acc = do
   putStrLn $ "linting " <> show paths
diff --git a/lib/Paths.hs b/lib/Paths.hs
index 49c0295..5044673 100644
--- a/lib/Paths.hs
+++ b/lib/Paths.hs
@@ -1,7 +1,7 @@
 {-# 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)
@@ -12,7 +12,8 @@ import           Text.Regex.TDFA
 import           Util                  (PrettyPrint (prettyprint))
 
 -- | a normalised path: a number of "upwards" steps, and
--- a path without any . or .. in it
+-- 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)
 
@@ -37,6 +38,11 @@ instance PrettyPrint RelPath where
   prettyprint (Path up rest _) = ups <> rest
     where ups = T.concat $ replicate up "../"
 
+-- | 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 _) =
-- 
GitLab