module Static.Resources
(
htmlImportList
, getResourceSetsForImport
, cleanResourceFiles
, ResourceSpec
, parseSpec
, check
, ImportType(..)
, ResourceSetsForImport(..)
, generateResources
, resourcesMTime
) where
import Static.Resources.Types
import Static.Resources.Spec
import Static.Resources.Checker
import Static.Resources.Generation
import Static.Resources.Import
import Control.Monad
import Control.Monad.Error
import Data.List
import Data.Maybe
import System.Directory
import System.FilePath
import Data.Time.Clock
import Data.Time.Calendar
getResourceSetsForImport :: ImportType
-> FilePath
-> FilePath
-> IO (Either String ResourceSetsForImport)
getResourceSetsForImport it fp pathPrefix = do
spec <- parseSpec fp
do
cleanResourceFiles (takeDirectory fp) spec
res <- runErrorT $ do
when (null $ sets spec) $ throwError "No resource sets are defined"
checkRes <- lift $ check (takeDirectory fp) spec
either (throwError . ("Error while checking spec. Error : " ++))
(const (return ()))
checkRes
lift $ generateResources it (takeDirectory fp) spec pathPrefix
case res of
Left s -> putStrLn $ "Static resource generation failed. " ++ s
Right (ResourceSetsForImport rs _) ->
putStrLn $ "Static resource generation done. Generated " ++
show (length rs) ++ " sets."
return res
cleanResourceFiles :: String -> ResourceSpec -> IO ()
cleanResourceFiles dir = getGeneratedFiles dir >=> mapM_ removeFile
getGeneratedFiles :: String -> ResourceSpec -> IO [FilePath]
getGeneratedFiles dir spec = do
mainFiles <- fmap (filter (\fn -> any (`isPrefixOf` fn) (map name (sets spec)) && isStaticResourceFile fn))
(getDirectoryContents dir)
let potentialCompiledLessLocalFiles = map (\r -> dir ++ "/" ++ (path r) ++ ".css") $ filter (\r -> LESS == rtype r) $ concatMap resources $ sets spec
compiledLessLocalFiles <- forM potentialCompiledLessLocalFiles $ \fn -> do
exists <- doesFileExist fn
if (exists)
then return $ Just fn
else return $ Nothing
return $ (map (\r -> dir ++ "/" ++ r) mainFiles) ++ (nub $ map fromJust $ filter isJust compiledLessLocalFiles)
resourcesMTime :: FilePath -> IO UTCTime
resourcesMTime fp = resourcesMTime' (takeDirectory fp)
resourcesMTime' :: FilePath -> IO UTCTime
resourcesMTime' fp = do
fs <- getDirectoryContents fp
let zeroTime = UTCTime (ModifiedJulianDay 0) 0
fmap maximum $ forM fs $ \f -> do
isDirectory <- doesDirectoryExist (fp ++ "/" ++f)
case ("." == f || ".." == f, isDirectory, isStaticResourceFile f) of
(True,_,_) -> return zeroTime
(_,True,_) -> resourcesMTime' $ fp ++ "/" ++f
(_,_,True) -> getModificationTime $ fp ++ "/" ++ f
(_,_,_) -> return zeroTime