2016-05-13 19:11:17 +09:00
|
|
|
{- This file is part of Vervis.
|
|
|
|
-
|
|
|
|
- Written in 2016 by fr33domlover <fr33domlover@riseup.net>.
|
|
|
|
-
|
|
|
|
- ♡ 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
|
|
|
|
- <http://creativecommons.org/publicdomain/zero/1.0/>.
|
|
|
|
-}
|
|
|
|
|
|
|
|
module Vervis.Handler.Repo.Git
|
|
|
|
( getGitRepoSource
|
|
|
|
, getGitRepoHeadChanges
|
|
|
|
, getGitRepoChanges
|
|
|
|
)
|
|
|
|
where
|
|
|
|
|
2016-05-23 21:24:14 +09:00
|
|
|
import Prelude
|
2016-05-13 19:11:17 +09:00
|
|
|
|
2016-05-24 05:46:54 +09:00
|
|
|
import Control.Monad.IO.Class (liftIO)
|
2016-05-13 19:11:17 +09:00
|
|
|
import Data.Git.Graph
|
|
|
|
import Data.Git.Harder
|
|
|
|
import Data.Git.Named (RefName (..))
|
|
|
|
import Data.Git.Ref (toHex)
|
|
|
|
import Data.Git.Repository
|
|
|
|
import Data.Git.Storage (withRepo)
|
|
|
|
import Data.Git.Storage.Object (Object (..))
|
|
|
|
import Data.Git.Types (Blob (..), Commit (..), Person (..), entName)
|
|
|
|
import Data.Graph.Inductive.Graph (noNodes)
|
|
|
|
import Data.Graph.Inductive.Query.Topsort
|
|
|
|
import Data.List (inits)
|
2016-05-24 05:46:54 +09:00
|
|
|
import Data.Maybe (fromMaybe)
|
|
|
|
import Data.Text (Text, unpack)
|
2016-05-13 19:11:17 +09:00
|
|
|
import Data.Text.Encoding (decodeUtf8With)
|
|
|
|
import Data.Text.Encoding.Error (lenientDecode)
|
|
|
|
import Database.Esqueleto
|
|
|
|
import Data.Hourglass (timeConvert)
|
|
|
|
import System.Directory (createDirectoryIfMissing)
|
|
|
|
import System.Hourglass (dateCurrent)
|
2016-05-24 05:46:54 +09:00
|
|
|
import Text.Blaze.Html (Html)
|
|
|
|
import Yesod.Core (defaultLayout)
|
|
|
|
import Yesod.Core.Handler (notFound)
|
2016-05-13 19:11:17 +09:00
|
|
|
|
|
|
|
import qualified Data.DList as D
|
|
|
|
import qualified Data.Set as S (member)
|
|
|
|
import qualified Data.Text.Lazy.Encoding as L (decodeUtf8With)
|
|
|
|
|
|
|
|
import Data.ByteString.Char8.Local (takeLine)
|
|
|
|
import Data.Git.Local
|
|
|
|
import Text.FilePath.Local (breakExt)
|
|
|
|
import Vervis.Form.Repo
|
|
|
|
import Vervis.Foundation
|
|
|
|
import Vervis.Path
|
|
|
|
import Vervis.MediaType (chooseMediaType)
|
|
|
|
import Vervis.Model
|
2016-05-24 05:46:54 +09:00
|
|
|
import Vervis.Model.Ident
|
2016-05-13 19:11:17 +09:00
|
|
|
import Vervis.Model.Repo
|
|
|
|
import Vervis.Paginate
|
|
|
|
import Vervis.Readme
|
|
|
|
import Vervis.Render
|
|
|
|
import Vervis.Settings
|
|
|
|
import Vervis.SourceTree
|
|
|
|
import Vervis.Style
|
|
|
|
import Vervis.Widget.Repo
|
|
|
|
|
|
|
|
import qualified Data.ByteString.Lazy as BL (ByteString)
|
|
|
|
import qualified Data.Git.Local as G (createRepo)
|
|
|
|
import qualified Vervis.Git as G (readSourceView, readChangesView, listRefs)
|
|
|
|
|
2016-05-23 21:24:14 +09:00
|
|
|
getGitRepoSource :: Repo -> ShrIdent -> RpIdent -> Text -> [Text] -> Handler Html
|
2016-05-13 19:11:17 +09:00
|
|
|
getGitRepoSource repository user repo ref dir = do
|
|
|
|
path <- askRepoDir user repo
|
|
|
|
(branches, tags, msv) <- liftIO $ G.readSourceView path ref dir
|
|
|
|
case msv of
|
|
|
|
Nothing -> notFound
|
|
|
|
Just sv -> do
|
|
|
|
let parent = if null dir then [] else init dir
|
|
|
|
dirs = zip parent (tail $ inits parent)
|
|
|
|
defaultLayout $(widgetFile "repo/source-git")
|
|
|
|
|
2016-05-23 21:24:14 +09:00
|
|
|
getGitRepoHeadChanges :: Repo -> ShrIdent -> RpIdent -> Handler Html
|
2016-05-13 19:11:17 +09:00
|
|
|
getGitRepoHeadChanges repository shar repo =
|
|
|
|
getGitRepoChanges shar repo $ repoMainBranch repository
|
|
|
|
|
2016-05-23 21:24:14 +09:00
|
|
|
getGitRepoChanges :: ShrIdent -> RpIdent -> Text -> Handler Html
|
2016-05-13 19:11:17 +09:00
|
|
|
getGitRepoChanges shar repo ref = do
|
|
|
|
path <- askRepoDir shar repo
|
|
|
|
(branches, tags) <- liftIO $ G.listRefs path
|
|
|
|
if ref `S.member` branches || ref `S.member` tags
|
|
|
|
then do
|
|
|
|
(entries, navModel) <- getPageAndNav $
|
|
|
|
\ o l -> liftIO $ G.readChangesView path ref o l
|
|
|
|
let refSelect = refSelectW shar repo branches tags
|
|
|
|
changes = changesW entries
|
|
|
|
pageNav = navWidget navModel
|
|
|
|
defaultLayout $(widgetFile "repo/changes-git")
|
|
|
|
else notFound
|