Eventually-decentralized project hosting and management platform

[[ 🗃 ^WvWbo vervis ]] :: [📥 Inbox] [📤 Outbox] [🐤 Followers] [🤝 Collaborators] [🛠 Changes]

Clone

HTTPS: darcs clone https://vervis.peers.community/repos/WvWbo

SSH: darcs clone USERNAME@vervis.peers.community:WvWbo

Tags

TODO

src / Vervis /

Git.hs

1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
{- This file is part of Vervis.
 -
 - Written in 2016, 2018, 2019, 2020, 2022
 - 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.Git
    ( readSourceView
    , readChangesView
    , listRefs
    , readPatch
    --, lastCommitTime
    , writePostReceiveHooks
    , generateGitPatches
    , canApplyGitPatches
    , applyGitPatches
    )
where

import Control.Arrow ((***))
import Control.Exception.Base
import Control.Monad.IO.Class
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Except
import Patience (diff, Item (..))
import Data.Foldable
import Data.Git.Diff
import Data.Git.Graph
import Data.Git.Harder
import Data.Git.Monad
import Data.Git.Ref (SHA1, fromHex, toHex)
import Data.Git.Storage (getObject_)
import Data.Git.Storage.Object (Object (..))
import Data.Git.Types hiding (ObjectType (..))
import Data.Graph.Inductive.Graph (noNodes)
import Data.Graph.Inductive.Query.Topsort
import Data.List.NonEmpty (NonEmpty ((:|)))
import Data.Set (Set)
import Data.String (fromString)
import Data.Text (Text)
import Data.Text.Encoding (encodeUtf8, decodeUtf8)
import Data.Time.Calendar (Day (..))
import Data.Time.Clock (UTCTime (..))
import Data.Time.Clock.POSIX (posixSecondsToUTCTime)
import Data.Traversable (for)
import Data.Word (Word32)
import Database.Persist
import System.Exit
import System.FilePath
import System.Hourglass (timeCurrent)
import System.Process.Typed
import Text.Email.Validate (emailAddress)
import Time.Types (Elapsed (..), Seconds (..))

import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as BL
import qualified Data.DList as D (DList, empty, snoc, toList)
import qualified Data.Git as G
import qualified Data.List.NonEmpty as NE
import qualified Data.Set as S (member, mapMonotonic, toList)
import qualified Data.Text as T
import qualified Data.Text.Encoding as TE
import qualified Data.Text.Encoding.Error as TE (lenientDecode)
import qualified Data.Vector as V (fromList)
import qualified Database.Esqueleto as E

import Network.FedURI
import Yesod.ActivityPub
import Yesod.Hashids
import Yesod.MonadSite

import Control.Monad.Trans.Except.Local
import Data.ByteString.Char8.Local (takeLine)
import Data.DList.Local
import Data.EventTime.Local
import Data.Git.Local
import Data.List.Local
import Data.Patch.Local hiding (Patch)
import System.Process.Typed.Local

import qualified Data.Patch.Local as P
import qualified Data.Text.UTF8.Local as TU

import Vervis.Changes
import Vervis.Foundation
import Vervis.Model
import Vervis.Model.Ident
import Development.PatchMediaType
import Vervis.Path
import Vervis.Readme
import Vervis.Settings
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 SHA1 -> 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 SHA1
    -> Text
    -> [Text]
    -> IO (Set RefName, Set RefName, Maybe (SourceView BL.ByteString))
loadSourceView git refT dir = do
    branches <- G.branchList git
    tags <- G.tagList git
    let refS = T.unpack refT
        refN = RefName refS
    msv <-
        if null branches
            then return $ Just $ SourceDir $ DirectoryView Nothing [] Nothing
            else if refN `S.member` branches || refN `S.member` tags
                then do
                    tipOid <- resolveName git refS
                    mtree <- G.resolveTreeish git $ unObjId tipOid
                    for mtree $ \ tree -> do
                        let dir' = map (G.entName . encodeUtf8) dir
                        view <- viewPath git tree dir'
                        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) <-
        G.withRepo (fromString path) $ \ git -> loadSourceView git ref dir
    let toTexts = S.mapMonotonic $ T.pack . refNameRaw
    return (toTexts bs, toTexts ts, renderSources dir <$> msv)

readChangesView
    :: FilePath
    -- ^ Repository path
    -> Text
    -- ^ Name of branch or tag
    -> Int
    -- ^ Offset, i.e. latest commits to skip
    -> Int
    -- ^ Limit, i.e. how many latest commits to take after the offset
    -> IO (Int, [LogEntry])
    -- ^ Total number of ref's changes, and view of selected ref's change log
readChangesView path ref off lim = G.withRepo (fromString path) $ \ git -> 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
        pairs' = take lim $ drop off pairs
        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    =
                ( utc t
                , intervalToEventTime $
                  FriendlyConvert $
                  now - t
                )
            }
            where
            Elapsed t = gitTimeUTC $ personTime $ commitAuthor commit
            utc (Seconds i) = posixSecondsToUTCTime $ fromIntegral i
    return (noNodes graph, map (uncurry mkrow) pairs')

listRefs :: FilePath -> IO (Set Text, Set Text)
listRefs path = G.withRepo (fromString path) $ \ git ->
    (,) <$> listBranches git <*> listTags git

patch :: [Edit] -> Commit SHA1 -> P.Patch
patch edits c = P.Patch
    { patchWritten     = makeAuthor $ commitAuthor c
    , patchCommitted   =
        if commitAuthor c == commitCommitter c
            then Nothing
            else Just $ makeAuthor $ commitCommitter c
    , patchTitle       = title
    , patchDescription = desc
    , patchDiff        = edits
    }
    where
    split t =
        let (l, r) = T.break (\ c -> c == '\n' || c == '\r') t
        in  (T.strip l, T.strip r)
    (title, desc) = split $ decodeUtf8 $ commitMessage c

    makeAuthor (G.Person name email time) =
        ( Author
            { authorName  = decodeUtf8 name
            , authorEmail =
                case emailAddress email of
                    Nothing ->
                        error $ "Invalid email " ++ T.unpack (decodeUtf8 email)
                    Just e  -> e
            }
        , let Elapsed (Seconds t) = gitTimeUTC time
          in  posixSecondsToUTCTime $ fromIntegral t
        )

ep2fp :: EntPath -> FilePath
ep2fp = T.unpack . decodeUtf8 . B.intercalate "/" . map getEntNameBytes

unModePerm :: ModePerm -> Word32
unModePerm (ModePerm w) = w

data Line = Line
    { lineNumber :: Int
    , lineText   :: Text
    }

instance Eq Line where
    Line _ t == Line _ s = t == s

instance Ord Line where
    Line _ t `compare` Line _ s = t `compare` s

mkdiff :: [Text] -> [Text] -> [(Bool, Int, Hunk)]
mkdiff old new =
    let eitherOldNew (Old a)    = Just $ Left a
        eitherOldNew (New a)    = Just $ Right a
        eitherOldNew (Both _ _) = Nothing
        stripLineNumber = fmap lineText
        mkhunk' (adds, pairs, rems) = Hunk
            { hunkAddFirst   = stripLineNumber adds
            , hunkRemoveAdd  = map (stripLineNumber *** stripLineNumber) pairs
            , hunkRemoveLast = stripLineNumber rems
            }
        line ((Line n _):_, _                     , _)            = (True, n)
        line ([]          , ((Line n _) :| _, _):_, _)            = (False, n)
        line ([]          , []                    , (Line n _):_) = (False, n)
        line ([]          , []                    , [])           = error "empty hunk"
        mkhunk h =
            let (n, l) = line h
            in  (n, l, mkhunk' h)
    in  map (mkhunk . groupEithers . NE.toList) $
        groupJusts $
        map eitherOldNew $
        diff (zipWith Line [1..] old) (zipWith Line [1..] new)

accumEdits :: BlobStateDiff SHA1 -> [Edit] -> [Edit]
accumEdits (OnlyOld bs) es =
    case bsContent bs of
        FileContent lines -> RemoveTextFile (ep2fp $ bsFilename bs) (unModePerm $ bsMode bs) (map (decodeUtf8 . BL.toStrict) lines) : es
        BinaryContent b   -> RemoveBinaryFile (ep2fp $ bsFilename bs) (unModePerm $ bsMode bs) (BL.length b) : es
accumEdits (OnlyNew bs) es =
    case bsContent bs of
        FileContent lines -> AddTextFile (ep2fp $ bsFilename bs) (unModePerm $ bsMode bs) (map (decodeUtf8 . BL.toStrict) lines) : es
        BinaryContent b   -> AddBinaryFile (ep2fp $ bsFilename bs) (unModePerm $ bsMode bs) (BL.length b) : es
accumEdits (OldAndNew old new) es =
    if bsFilename old == bsFilename new
        then if bsRef old == bsRef new
                then if bsMode old == bsMode new
                        then es
                        else ChmodFile (ep2fp $ bsFilename new) (unModePerm $ bsMode old) (unModePerm $ bsMode new) : es
                else case (bsContent old, bsContent new) of
                        (FileContent ols, FileContent nls) ->
                            case mkdiff (map (decodeUtf8 . BL.toStrict) ols) (map (decodeUtf8 . BL.toStrict) nls) of
                                [] -> error "file ref changed, diff is empty?"
                                h:hs -> EditTextFile (ep2fp $ bsFilename new) (V.fromList $ map (decodeUtf8 . BL.toStrict) ols) (h :| hs) (unModePerm $ bsMode old) (unModePerm $ bsMode new) : es
                        (BinaryContent b, FileContent nls) -> BinaryToText (ep2fp $ bsFilename new) (BL.length b) (unModePerm $ bsMode old) (map (decodeUtf8 . BL.toStrict) nls) (unModePerm $ bsMode new) : es
                        (FileContent ols, BinaryContent b) -> TextToBinary (ep2fp $ bsFilename new) (map (decodeUtf8 . BL.toStrict) ols) (unModePerm $ bsMode old) (BL.length b) (unModePerm $ bsMode new) : es
                        (BinaryContent from, BinaryContent to) -> EditBinaryFile (ep2fp $ bsFilename new) (BL.length from) (unModePerm $ bsMode old) (BL.length to) (unModePerm $ bsMode new) : es
        else error "getDiffWith gave OldAndNew with different file paths"

readPatch :: FilePath -> Text -> IO (P.Patch, [Text])
readPatch path hash = G.withRepo (fromString path) $ \ git -> do
    let ref = fromHex $ encodeUtf8 hash
    c <- G.getCommit git ref
    medits <- case commitParents c of
        []  -> error "Use the tree to generate list of AddFile diff parts?"
        [p] -> Right <$> getDiffWith accumEdits [] p ref git
        ps  -> fmap Left $ for ps $ \ p ->
                    decodeUtf8 . takeLine . commitMessage <$> G.getCommit git p
    return $ case medits of
        Left parents -> (patch []    c, parents)
        Right edits  -> (patch edits c, [])

{-
lastCommitTime :: FilePath -> IO (Maybe UTCTime)
lastCommitTime repo =
    (either fail return =<<) $ fmap join $ withRepo (fromString repo) $ runExceptT $ do
        branches <- S.toList <$> lift branchList
        lct <- foldlM' utc0 branches $ \ time branch -> do
            mcommit <- lift $ getCommit branch
            case mcommit of
                Nothing ->
                    throwE $
                        "lastCommitTime: Failed to get commit for branch " ++
                        refNameRaw branch
                Just c ->
                    return $ max time $
                    utc $ gitTimeUTC $ personTime $ commitCommitter c
        return $ if null branches
            then Nothing
            else Just lct
    where
    utc (Elapsed (Seconds i)) = posixSecondsToUTCTime $ fromIntegral i
    utc0 = UTCTime (ModifiedJulianDay 0) 0
    foldlM' i l f = foldlM f i l
-}

writePostReceiveHooks :: WorkerDB ()
writePostReceiveHooks = do
    hook <- asksSite $ appPostReceiveHookFile . appSettings
    authority <- asksSite $ renderAuthority . siteInstanceHost
    repos <- selectKeysList [RepoVcs ==. VCSGit] []
    for_ repos $ \ repoID -> do
        repoHash <- encodeKeyHashid repoID
        path <- askRepoDir repoHash
        liftIO $ writeHookFile path hook authority (keyHashidText repoHash)

-- | Given a temporary directory to use freely for this operation, generate
-- patches from the difference between the origin branch and the target branch
-- (origin branch must be an ancestor of target branch)
--
-- Target repo must be local, origin repo may be remote on the network
generateGitPatches
    :: FilePath -- ^ Absolute path to target repo
    -> String   -- ^ Target branch
    -> String   -- ^ Absolute path or HTTP URI of origin repo
    -> String   -- ^ Origin branch
    -> FilePath -- ^ Temporary directory to use for the operation
    -> ExceptT Text IO (NonEmpty Text)
generateGitPatches targetRepoPath targetBranch originRepoURI originBranch tempDir = do
    runProcessE "git clone" $ proc "git" ["clone", "--bare", "--verbose", "--single-branch", "--branch", targetBranch, "--", targetRepoPath, tempDir]
    runProcessE "git remote add" $ proc "git" ["-C", tempDir, "remote", "--verbose", "add", "-t", originBranch, "real-origin", originRepoURI]
    runProcessE "git fetch" $ proc "git" ["-C", tempDir, "fetch", "real-origin", originBranch]
    runProcessE "git merge-base --is-ancestor" $ proc "git" ["-C", tempDir, "merge-base", "--is-ancestor", targetBranch, "real-origin/" ++ originBranch]
    patchFileNames <- do
        names <- T.lines <$> readProcessE "git format-patch" (proc "git" ["-C", tempDir, "format-patch", targetBranch ++ "..real-origin/" ++ originBranch])
        fromMaybeE (NE.nonEmpty names) "No new patches found in origin branch"
    for patchFileNames $ \ name -> do
        b <- lift $ B.readFile $ tempDir </> T.unpack name
        case TE.decodeUtf8' b of
            Left e -> throwE $ T.concat
                [ "UTF-8 decoding error while reading Git patch file "
                , name, ": " , T.pack $ displayException e
                ]
            Right t -> return t

canApplyGitPatches repoPath branch patches tempDir = do
    runProcessE "git clone" $ proc "git" ["clone", "--verbose", "--single-branch", "--branch", branch, "--", repoPath, tempDir]
    runProcessE "git config" $ proc "git" ["-C", tempDir, "config", "user.name", "vervis"]
    runProcessE "git config" $ proc "git" ["-C", tempDir, "config", "user.email", "vervis@vervis.vervis"]
    let input = BL.concat $ NE.toList $ NE.map (BL.fromStrict . TE.encodeUtf8) patches
    exitCode <- lift $ runProcess $ setStdin (byteStringInput input) $ proc "git" ["-C", tempDir, "am"]
    return $ exitCode == ExitSuccess

-- Since 'git am' doesn't work on a bare repo, clone target repo into the given
-- temporary directory, apply there, and finally push
applyGitPatches repoPath branch patches tempDir = do
    runProcessE "git clone" $ proc "git" ["clone", "--verbose", "--single-branch", "--branch", branch, "--", repoPath, tempDir]
    runProcessE "git config" $ proc "git" ["-C", tempDir, "config", "user.name", "vervis"]
    runProcessE "git config" $ proc "git" ["-C", tempDir, "config", "user.email", "vervis@vervis.vervis"]
    let input = BL.concat $ NE.toList $ NE.map (BL.fromStrict . TE.encodeUtf8) patches
    runProcessE "git am" $ setStdin (byteStringInput input) $ proc "git" ["-C", tempDir, "am"]
    runProcessE "git push" $ proc "git" ["-C", tempDir, "push"]
[See repo JSON]