aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--cabal-helper.cabal1
-rw-r--r--lib/Distribution/Helper/Discover.hs38
-rw-r--r--src/CabalHelper/Compiletime/Compat/Directory.hs26
3 files changed, 63 insertions, 2 deletions
diff --git a/cabal-helper.cabal b/cabal-helper.cabal
index 9cc7215..cb43f72 100644
--- a/cabal-helper.cabal
+++ b/cabal-helper.cabal
@@ -131,6 +131,7 @@ library c-h-internal
import: build-deps, extensions
exposed-modules:
CabalHelper.Compiletime.Cabal
+ CabalHelper.Compiletime.Compat.Directory
CabalHelper.Compiletime.Compat.Environment
CabalHelper.Compiletime.Compat.ProgramDb
CabalHelper.Compiletime.Compat.Version
diff --git a/lib/Distribution/Helper/Discover.hs b/lib/Distribution/Helper/Discover.hs
index d4abe69..a748b25 100644
--- a/lib/Distribution/Helper/Discover.hs
+++ b/lib/Distribution/Helper/Discover.hs
@@ -14,6 +14,8 @@
-- You should have received a copy of the GNU General Public License
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
+{-# LANGUAGE GADTs #-}
+
{-|
Module : Distribution.Helper.Discover
Description : Finding project contexts
@@ -30,12 +32,44 @@ module Distribution.Helper.Discover
, findDistDirsWithHints
) where
+import Control.Monad.Writer
+import Data.List
+import System.Directory
+import System.FilePath
+
import CabalHelper.Compiletime.Types
+import CabalHelper.Compiletime.Cabal
+import CabalHelper.Compiletime.Compat.Directory
findProjects :: FilePath -> IO [Ex ProjLoc]
findDistDirs :: ProjLoc pt -> [DistDir pt]
findDistDirsWithHints :: ProjLoc pt -> [FilePath] -> [DistDir pt]
-findProjects = undefined
-findDistDirs = undefined
+findProjects dir = execWriterT $ do
+ let cabalProject = dir </> "cabal.project"
+ whenM (liftIO $ doesFileExist cabalProject) $
+ tell [Ex $ ProjLocV2File cabalProject]
+ let stackYaml = dir </> "stack.yaml"
+ whenM (liftIO $ doesFileExist stackYaml) $
+ tell [Ex $ ProjLocStackYaml stackYaml]
+ join $ traverse (tell . pure . Ex . ProjLocV1CabalFile) <$>
+ liftIO (findCabalFiles dir)
+
+findDistDirs (ProjLocV1CabalFile cabal) =
+ [DistDirV1 $ replaceFileName cabal "dist/"]
+findDistDirs (ProjLocV1Dir dir) = [DistDirV1 $ dir </> "dist/"]
+findDistDirs (ProjLocV2File cabal) =
+ [DistDirV2 $ replaceFileName cabal "dist-newstyle/"]
+findDistDirs (ProjLocV2Dir dir) = [DistDirV2 $ dir </> "dist-newstyle/"]
+findDistDirs (ProjLocStackYaml _) = [DistDirStack Nothing]
+
findDistDirsWithHints = undefined
+
+findCabalFiles :: FilePath -> IO [FilePath]
+findCabalFiles dir = do
+ fs <- listDirectory dir
+ let cs = filter (".cabal" `isSuffixOf`) fs
+ filterM doesFileExist cs
+
+whenM :: Monad m => m Bool -> m () -> m ()
+whenM p x = p >>= (`when` x)
diff --git a/src/CabalHelper/Compiletime/Compat/Directory.hs b/src/CabalHelper/Compiletime/Compat/Directory.hs
new file mode 100644
index 0000000..0a65164
--- /dev/null
+++ b/src/CabalHelper/Compiletime/Compat/Directory.hs
@@ -0,0 +1,26 @@
+-- cabal-helper: Simple interface to Cabal's configuration state
+-- Copyright (C) 2019 Daniel Gröber <cabal-helper@dxld.at>
+--
+-- This program is free software: you can redistribute it and/or modify
+-- it under the terms of the GNU General Public License as published by
+-- the Free Software Foundation, either version 3 of the License, or
+-- (at your option) any later version.
+--
+-- This program is distributed in the hope that it will be useful,
+-- but WITHOUT ANY WARRANTY; without even the implied warranty of
+-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
+-- GNU General Public License for more details.
+--
+-- You should have received a copy of the GNU General Public License
+-- along with this program. If not, see <http://www.gnu.org/licenses/>.
+
+{-# LANGUAGE CPP #-}
+module CabalHelper.Compiletime.Compat.Directory where
+
+import System.Directory (getDirectoryContents)
+
+#if !MIN_VERSION_directory(1,2,5)
+listDirectory :: FilePath -> IO [FilePath]
+listDirectory path =
+ filter (\f -> f /= "." && f /= "..") <$> getDirectoryContents path
+#endif