{- This file is part of Vervis. - - Written in 2016 by fr33domlover . - - ♡ Copying is an act of love. Please copy, reuse and share. - - The author(s) have dedicated all copyright and related and neighboring - rights to this software to the public domain worldwide. This software is - distributed without any warranty. - - You should have received a copy of the CC0 Public Domain Dedication along - with this software. If not, see - . -} module Vervis.Git ( readSourceView , readChangesView ) where import Prelude import Data.Foldable (find) import Data.Git import Data.Git.Graph import Data.Git.Harder import Data.Git.Ref (toHex) import Data.Git.Storage (getObject_) import Data.Git.Storage.Object (Object (..)) import Data.Git.Types (GitTime (..)) import Data.Graph.Inductive.Graph (noNodes) import Data.Graph.Inductive.Query.Topsort import Data.Set (Set) import Data.String (fromString) import Data.Text (Text) import Data.Text.Encoding (encodeUtf8) import System.Hourglass (timeCurrent) import Time.Types (Elapsed (..)) import qualified Data.ByteString.Lazy as BL (ByteString) import qualified Data.DList as D (DList, empty, snoc, toList) import qualified Data.Set as S (member, mapMonotonic) import qualified Data.Text as T (pack, unpack) import qualified Data.Text.Encoding as TE (decodeUtf8With) import qualified Data.Text.Encoding.Error as TE (lenientDecode) import Data.ByteString.Char8.Local (takeLine) import Data.EventTime.Local import Data.Git.Local import Vervis.Changes import Vervis.Foundation (Widget) import Vervis.Readme import Vervis.SourceTree matchReadme :: (ModePerm, ObjId, Text, EntObjType) -> Bool matchReadme (_, _, name, EntObjBlob) = isReadme name matchReadme _ = False -- | Find a README file in a directory. Return the filename and the file -- content. findReadme :: Git -> TreeRows -> IO (Maybe (Text, BL.ByteString)) findReadme git rows = case find matchReadme rows of Nothing -> return Nothing Just (_perm, oid, name, _etype) -> do obj <- getObject_ git (unObjId oid) True return $ case obj of ObjBlob b -> Just (name, blobGetContent b) _ -> Nothing matchType :: EntObjType -> EntryType matchType EntObjBlob = TypeBlob matchType EntObjTree = TypeTree rowToEntry :: (ModePerm, ObjId, Text, EntObjType) -> DirEntry rowToEntry (_, _, name, etype) = DirEntry (matchType etype) name loadSourceView :: Git -> Text -> [Text] -> IO (Set RefName, Set RefName, Maybe (SourceView BL.ByteString)) loadSourceView git refT dir = do branches <- branchList git tags <- tagList git let refS = T.unpack refT refN = RefName refS msv <- if refN `S.member` branches || refN `S.member` tags then do tipOid <- resolveName git refS mtree <- resolveTreeish git $ unObjId tipOid case mtree of Nothing -> return Nothing Just tree -> do let dir' = map (entName . encodeUtf8) dir view <- viewPath git tree dir' Just <$> case view of RootView rows -> do mreadme <- findReadme git rows let ents = map rowToEntry rows return $ SourceDir $ DirectoryView Nothing ents mreadme TreeView name _ rows -> do mreadme <- findReadme git rows let ents = map rowToEntry rows return $ SourceDir $ DirectoryView (Just name) ents mreadme BlobView name _ body -> return $ SourceFile $ FileView name body else return Nothing return (branches, tags, msv) readSourceView :: FilePath -- ^ Repository path -> Text -- ^ Name of branch or tag -> [Text] -- ^ Path in the source tree pointing to a file or directory -> IO (Set Text, Set Text, Maybe (SourceView Widget)) -- ^ Branches, tags, view of the selected item readSourceView path ref dir = do (bs, ts, msv) <- withRepo (fromString path) $ \ git -> loadSourceView git ref dir let toTexts = S.mapMonotonic $ T.pack . refNameRaw return (toTexts bs, toTexts ts, renderSources dir <$> msv) instance ResultList D.DList where emptyList = D.empty appendItem = flip D.snoc readChangesView :: FilePath -- ^ Repository path -> Text -- ^ Name of branch or tag -> IO (Set Text, Set Text, Maybe [LogEntry]) -- ^ Branches, tags, view of selected ref's change log readChangesView path ref = withRepo (fromString path) $ \ git -> do let toTexts = S.mapMonotonic $ T.pack . refNameRaw branches <- toTexts <$> branchList git tags <- toTexts <$> tagList git ml <- if ref `S.member` branches || ref `S.member` tags then do oid <- resolveName git $ T.unpack ref graph <- loadCommitGraphPT git [oid] let mnodes = topsortUnmixOrder graph (NodeStack [noNodes graph]) nodes = case mnodes of Nothing -> error "commit graph contains a cycle" Just ns -> ns pairs = D.toList $ fmap (nodeLabel graph) nodes toText = TE.decodeUtf8With TE.lenientDecode Elapsed now <- timeCurrent let mkrow oid commit = LogEntry { leAuthor = toText $ personName $ commitAuthor commit , leHash = toText $ toHex $ unObjId oid , leMessage = toText $ takeLine $ commitMessage commit , leTime = intervalToEventTime $ FriendlyConvert $ now - t } where Elapsed t = gitTimeUTC $ personTime $ commitAuthor commit return $ Just $ map (uncurry mkrow) pairs else return Nothing return (branches, tags, ml)