File: Util.hs

package info (click to toggle)
git-annex 10.20251029-1
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid
  • size: 75,300 kB
  • sloc: haskell: 91,492; javascript: 9,103; sh: 1,593; makefile: 216; perl: 137; ansic: 44
file content (70 lines) | stat: -rw-r--r-- 2,263 bytes parent folder | download | duplicates (3)
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
{- git-annex remote list utils
 -
 - Copyright 2011-2025 Joey Hess <id@joeyh.name>
 -
 - Licensed under the GNU AGPL version 3 or higher.
 -}

module Remote.List.Util where

import Annex.Common
import qualified Annex
import qualified Git.Config
import Annex.UUID
import Types.Remote
import Config.DynamicConfig

import Data.Ord

{- Call when remotes have changed. Re-reads the git config, and
 - invalidates the cache so the remoteList will be re-generated next time
 - it's used. -}
remotesChanged :: Annex ()
remotesChanged = do
	newg <- inRepo Git.Config.reRead
	Annex.changeState $ \s -> s 
		{ Annex.remotes = []
		, Annex.gitremotes = Nothing
		, Annex.repo = newg
		}

{- Whether to include remotes that have annex-ignore set. -}
newtype IncludeIgnored = IncludeIgnored Bool

keyPossibilities'
	:: IncludeIgnored
	-> Key
	-> [UUID]
	-- ^ uuids of remotes that are recorded to have the key
	-> [Remote]
	-- ^ all remotes
	-> Annex [Remote]
keyPossibilities' ii _key remotelocations rs = do
	u <- getUUID
	let locations = filter (/= u) remotelocations
	let speclocations = map uuid
		$ filter (remoteAnnexSpeculatePresent . gitconfig) rs
	-- there are unlikely to be many speclocations, so building a Set
	-- is not worth the expense
	let locations' = speclocations ++ filter (`notElem` speclocations) locations
	fst <$> remoteLocations' ii locations' [] rs

remoteLocations' :: IncludeIgnored -> [UUID] -> [UUID] -> [Remote] -> Annex ([Remote], [UUID])
remoteLocations' (IncludeIgnored ii) locations trusted rs = do
	let validtrustedlocations = nub locations `intersect` trusted

	-- remotes that match uuids that have the key
	allremotes <- if not ii
		then filterM (not <$$> liftIO . getDynamicConfig . remoteAnnexIgnore . gitconfig) rs
		else return rs
	let validremotes = remotesWithUUID allremotes locations

	return (sortBy (comparing cost) validremotes, validtrustedlocations)

{- Filters a list of remotes to ones that have the listed uuids. -}
remotesWithUUID :: [Remote] -> [UUID] -> [Remote]
remotesWithUUID rs us = filter (\r -> uuid r `elem` us) rs

{- Filters a list of remotes to ones that do not have the listed uuids. -}
remotesWithoutUUID :: [Remote] -> [UUID] -> [Remote]
remotesWithoutUUID rs us = filter (\r -> uuid r `notElem` us) rs