{-# LANGUAGE OverloadedStrings #-}
module Futhark.Pkg.Types
( PkgPath
, pkgPathFilePath
, PkgRevDeps(..)
, module Data.Versions
, commitVersion
, isCommitVersion
, parseVersion
, PkgManifest(..)
, newPkgManifest
, pkgRevDeps
, pkgDir
, addRequiredToManifest
, removeRequiredFromManifest
, prettyPkgManifest
, Comment
, Commented(..)
, Required(..)
, futharkPkg
, parsePkgManifest
, parsePkgManifestFromFile
, errorBundlePretty
, BuildList(..)
, prettyBuildList
) where
import Control.Applicative
import Control.Monad
import Data.Either
import Data.Foldable
import Data.List
import Data.Maybe
import Data.Traversable
import Data.Void
import qualified Data.Text as T
import qualified Data.Text.IO as T
import qualified Data.Map as M
import System.FilePath
import qualified System.FilePath.Posix as Posix
import Data.Versions (SemVer(..), VUnit(..), prettySemVer)
import Text.Megaparsec hiding (many, some)
import Text.Megaparsec.Char
import Prelude
type PkgPath = T.Text
pkgPathFilePath :: PkgPath -> FilePath
pkgPathFilePath = joinPath . Posix.splitPath . T.unpack
isCommitVersion :: SemVer -> Maybe T.Text
isCommitVersion (SemVer 0 0 0 [_] [[Str s]]) = Just s
isCommitVersion _ = Nothing
commitVersion :: T.Text -> T.Text -> SemVer
commitVersion time commit =
SemVer 0 0 0 [[Str time]] [[Str commit]]
parseVersion :: T.Text -> Either (ParseErrorBundle T.Text Void) SemVer
parseVersion = parse (semver' <* eof) "Semantic Version"
semver' :: Parsec Void T.Text SemVer
semver' = SemVer <$> majorP <*> minorP <*> patchP <*> preRel <*> metaData
where majorP = digitsP <* char '.'
minorP = majorP
patchP = digitsP
digitsP = read <$> ((T.unpack <$> string "0") <|> some digitChar)
preRel = maybe [] pure <$> optional preRel'
preRel' = char '-' *> (pure . Str . T.pack <$> some digitChar)
metaData = maybe [] pure <$> optional metaData'
metaData' = char '+' *> (pure . Str . T.pack <$> some alphaNumChar)
newtype PkgRevDeps = PkgRevDeps (M.Map PkgPath (SemVer, Maybe T.Text))
deriving (Show)
instance Semigroup PkgRevDeps where
PkgRevDeps x <> PkgRevDeps y = PkgRevDeps $ x <> y
instance Monoid PkgRevDeps where
mempty = PkgRevDeps mempty
type Comment = T.Text
data Commented a = Commented { comments :: [Comment]
, commented :: a
}
deriving (Show, Eq)
instance Functor Commented where
fmap = fmapDefault
instance Foldable Commented where
foldMap = foldMapDefault
instance Traversable Commented where
traverse f (Commented cs x) = Commented cs <$> f x
data Required = Required
{ requiredPkg :: PkgPath
, requiredPkgRev :: SemVer
, requiredHash :: Maybe T.Text
}
deriving (Show, Eq)
futharkPkg :: FilePath
futharkPkg = "futhark.pkg"
data PkgManifest = PkgManifest { manifestPkgPath :: Commented (Maybe PkgPath)
, manifestRequire :: Commented [Either Comment Required]
, manifestEndComments :: [Comment]
}
deriving (Show, Eq)
newPkgManifest :: Maybe PkgPath -> PkgManifest
newPkgManifest p =
PkgManifest (Commented mempty p) (Commented mempty mempty) mempty
prettyPkgManifest :: PkgManifest -> T.Text
prettyPkgManifest (PkgManifest name required endcs) =
T.unlines $ concat [ prettyComments name
, maybe [] (pure . ("package "<>) . (<>"\n")) $ commented name
, prettyComments required
, ["require {"]
, map ((" "<>) . prettyRequired) $ commented required
, ["}"]
, map prettyComment endcs
]
where prettyComments = map prettyComment . comments
prettyComment = ("--"<>)
prettyRequired (Left c) = prettyComment c
prettyRequired (Right (Required p r h)) =
T.unwords $ catMaybes [Just p,
Just $ prettySemVer r,
("#"<>) <$> h]
pkgRevDeps :: PkgManifest -> PkgRevDeps
pkgRevDeps = PkgRevDeps . M.fromList . mapMaybe onR .
commented . manifestRequire
where onR (Right r) = Just (requiredPkg r, (requiredPkgRev r, requiredHash r))
onR (Left _) = Nothing
pkgDir :: PkgManifest -> Maybe Posix.FilePath
pkgDir = fmap (Posix.addTrailingPathSeparator . ("lib" Posix.</>) .
T.unpack) . commented . manifestPkgPath
addRequiredToManifest :: Required -> PkgManifest -> (PkgManifest, Maybe Required)
addRequiredToManifest new_r pm =
let (old, requires') = mapAccumL add Nothing $ commented $ manifestRequire pm
in (if isJust old
then pm { manifestRequire = const requires' <$> manifestRequire pm }
else pm { manifestRequire = (++[Right new_r]) <$> manifestRequire pm },
old)
where add acc (Left c) = (acc, Left c)
add acc (Right r)
| requiredPkg r == requiredPkg new_r = (Just r, Right new_r)
| otherwise = (acc, Right r)
requiredInManifest :: PkgPath -> PkgManifest -> Maybe Required
requiredInManifest p =
find ((==p) . requiredPkg) . rights . commented . manifestRequire
removeRequiredFromManifest :: PkgPath -> PkgManifest -> Maybe (PkgManifest, Required)
removeRequiredFromManifest p pm = do
r <- requiredInManifest p pm
return (pm { manifestRequire = filter (not . matches) <$> manifestRequire pm },
r)
where matches = either (const False) ((==p) . requiredPkg)
type Parser = Parsec Void T.Text
pPkgManifest :: Parser PkgManifest
pPkgManifest = do
c1 <- pComments
p <- optional $ lexstr "package" *> pPkgPath
space
c2 <- pComments
required <- (lexstr "require" *>
braces (many $ (Left <$> pComment) <|> (Right <$> pRequired)))
<|> pure []
c3 <- pComments
eof
return $ PkgManifest (Commented c1 p) (Commented c2 required) c3
where lexeme :: Parser a -> Parser a
lexeme p = p <* space
lexeme' p = p <* spaceNoEol
lexstr :: T.Text -> Parser ()
lexstr = void . try . lexeme . string
braces :: Parser a -> Parser a
braces p = lexstr "{" *> p <* lexstr "}"
spaceNoEol = many $ oneOf (" \t" :: String)
pPkgPath = T.pack <$> some (alphaNumChar <|> oneOf ("@-/.:" :: String))
<?> "package path"
pRequired = space *> (Required <$> lexeme' pPkgPath
<*> lexeme' semver'
<*> optional (lexeme' pHash)) <* space
<?> "package requirement"
pHash = char '#' *> (T.pack <$> some alphaNumChar)
pComment = lexeme $ T.pack <$> (string "--" >> anySingle `manyTill` (void eol <|> eof))
pComments :: Parser [Comment]
pComments = catMaybes <$> many (comment <|> blankLine)
where comment = Just <$> pComment
blankLine = some spaceChar >> pure Nothing
parsePkgManifest :: FilePath -> T.Text -> Either (ParseErrorBundle T.Text Void) PkgManifest
parsePkgManifest = parse pPkgManifest
parsePkgManifestFromFile :: FilePath -> IO PkgManifest
parsePkgManifestFromFile f = do
s <- T.readFile f
case parsePkgManifest f s of
Left err -> fail $ errorBundlePretty err
Right m -> return m
newtype BuildList = BuildList { unBuildList :: M.Map PkgPath SemVer }
deriving (Eq, Show)
prettyBuildList :: BuildList -> T.Text
prettyBuildList (BuildList m) = T.unlines $ map f $ sortOn fst $ M.toList m
where f (p, v) = T.unwords [p, "=>", prettySemVer v]