{-# OPTIONS_GHC -fno-warn-orphans #-} ----------------------------------------------------------------------------- -- | -- Module : Lentil.File -- Copyright : © 2015 Francesco Ariis -- License : GPLv3 (see the LICENSE file) -- -- File operations ----------------------------------------------------------------------------- module Lentil.File where import Lentil.Types import Lentil.Parse.Issue import System.FilePath import System.FilePath.Find import Data.Monoid import Control.Applicative import qualified Data.List as L --------------- -- INSTANCES -- --------------- instance Monoid a => Monoid (FindClause a) where mempty = pure mempty mappend = liftA2 mappend -------------- -- FILESCAN -- -------------- findIssues :: [FilePath] -> [FilePath] -> IO [Issue] findIssues is xs = find always (findClause is xs) "." >>= issueFinder -- fp to include, fp to exclude, clause findClause :: [FilePath] -> [FilePath] -> FindClause Bool findClause i x = let ic = mconcat $ map fp2fc i xc = mconcat $ map fp2fc x in fmap getAny ic &&? (not <$> fmap getAny xc) where fp2fc :: FilePath -> FindClause Any fp2fc f = Any . L.isPrefixOf (combine "." f) <$> filePath -- TODO: combine funziona su windows? [feature:intermediate]