module Distribution.Hup.Parse
(
module Distribution.Hup.Parse
, module Distribution.Hup.Types
)
where
import Control.Monad.Except (MonadError(..),when)
import Data.Char (isDigit, toLower, isSpace)
import Data.List (dropWhileEnd,isSuffixOf,stripPrefix
,intercalate)
import Data.List.Split (splitOn)
import Data.Maybe (listToMaybe)
import Data.String
import System.Directory (getDirectoryContents)
import System.FilePath (splitExtension, splitFileName, takeExtension)
import Distribution.Hup.Types (IsCandidate(..), IsDocumentation(..)
,Package(..), Upload(..) )
rstrip :: String -> String
rstrip = dropWhileEnd isSpace
lstrip :: String -> String
lstrip = dropWhile isSpace
replace :: Eq a => [a] -> [a] -> [a] -> [a]
replace [] _ _ = error "Extra.replace, first argument cannot be empty"
replace from to xs | Just xs <- stripPrefix from xs = to ++ replace from to xs
replace from to (x:xs) = x : replace from to xs
replace _from _to [] = []
takeWhileEnd :: (a -> Bool) -> [a] -> [a]
takeWhileEnd p = reverse . takeWhile p . reverse
spanEnd :: (a -> Bool) -> [a] -> ([a], [a])
spanEnd p xs = (dropWhileEnd p xs, takeWhileEnd p xs)
breakEnd :: (a -> Bool) -> [a] -> ([a], [a])
breakEnd p = spanEnd (not . p)
findCabal :: IO (Maybe Prelude.FilePath)
findCabal = do
x <- getDirectoryContents "."
return $ listToMaybe $ filter ((==) ".cabal" . takeExtension) x
readCabal :: IO String
readCabal = do
file <- findCabal
case file of
Nothing -> return []
Just file -> readFile file
extractCabal :: String -> String -> String
extractCabal find = f . words . replace ":" " : "
where
f (name:":":val:_) | map toLower find == map toLower name = val
f (_x:xs) = f xs
f [] = error "Failed to find the Cabal key " ++ find
parseTgzFilename
:: (IsString s, MonadError s m) =>
Prelude.FilePath -> m (IsDocumentation, Package)
parseTgzFilename f = do
let (base, ext) = splitExtension f
ext `shouldBe` ".gz"
(base, ext) <- return $ splitExtension base
ext `shouldBe` ".tar"
base <- return $ snd $ splitFileName base
(base, isDocco) <- return $ if "-docs" `isSuffixOf` base
then let base' = intercalate "-" $
init $ splitOn "-" base
in (base', IsDocumentation)
else (base, IsPackage)
let (pkg, ver) = spanVersion base
pkg <- return $ dropWhileEnd (=='-') pkg
return (isDocco, Package pkg ver)
where
ext `shouldBe` expected =
when (ext /= expected) $
throwError $ fromString $ unwords ["Expected filename with extension"
,"'.tar.gz', but got", f]
spanVersion = spanEnd (\x -> isDigit x || x == '.')
parseTgzFilename'
:: (IsString s) =>
Prelude.FilePath -> Either s (IsDocumentation, Package)
parseTgzFilename' = parseTgzFilename