File: PreferredContent.hs

package info (click to toggle)
git-annex 10.20250416-2
  • links: PTS, VCS
  • area: main
  • in suites: trixie
  • size: 73,572 kB
  • sloc: haskell: 90,656; javascript: 9,103; sh: 1,469; makefile: 211; perl: 137; ansic: 44
file content (153 lines) | stat: -rw-r--r-- 5,955 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
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
{- git-annex preferred content matcher configuration
 -
 - Copyright 2012-2024 Joey Hess <id@joeyh.name>
 -
 - Licensed under the GNU AGPL version 3 or higher.
 -}

module Logs.PreferredContent (
	preferredContentSet,
	requiredContentSet,
	groupPreferredContentSet,
	isPreferredContent,
	isRequiredContent,
	preferredContentMap,
	preferredContentMapRaw,
	requiredContentMap,
	requiredContentMapRaw,
	groupPreferredContentMapRaw,
	checkPreferredContentExpression,
	setStandardGroup,
	defaultStandardGroup,
	preferredRequiredMapsLoad,
	preferredRequiredMapsLoad',
	introspectPreferredRequiredContent,
	prop_standardGroups_parse,
) where

import Annex.Common
import Logs.PreferredContent.Raw
import qualified Annex.Branch
import qualified Annex
import Logs
import Logs.UUIDBased
import Utility.Matcher
import Annex.FileMatcher
import Annex.UUID
import Logs.Group
import Logs.Remote
import Types.StandardGroups
import Limit

import qualified Data.Map as M
import qualified Data.Set as S
import qualified Data.Attoparsec.ByteString.Lazy as A

{- Checks if a file is preferred content (or required content) for the
 - specified repository (or the current repository if none is specified). -}
isPreferredContent :: LiveUpdate -> Maybe UUID -> AssumeNotPresent -> Maybe Key -> AssociatedFile -> Bool -> Annex Bool
isPreferredContent = checkMap preferredContentMap

isRequiredContent :: LiveUpdate -> Maybe UUID -> AssumeNotPresent -> Maybe Key -> AssociatedFile -> Bool -> Annex Bool
isRequiredContent = checkMap requiredContentMap

checkMap :: Annex (FileMatcherMap Annex) -> LiveUpdate -> Maybe UUID -> AssumeNotPresent -> Maybe Key -> AssociatedFile -> Bool -> Annex Bool
checkMap getmap lu mu notpresent mkey afile d = do
	u <- maybe getUUID return mu
	m <- getmap
	case M.lookup u m of
		Nothing -> return d
		Just matcher -> checkMatcher matcher mkey afile lu notpresent (return d) (return d)

{- Checks if the preferred or required content for the specified repository
 - (or the current repository if none is specified) contains any terms
 - that meet the condition. -}
introspectPreferredRequiredContent :: (MatchFiles Annex -> Bool) -> Maybe UUID -> Annex Bool
introspectPreferredRequiredContent c mu = do
	u <- maybe getUUID return mu
	check u preferredContentMap <||> check u requiredContentMap
  where
	check u mk = mk >>= return . maybe False (any c . fst) . M.lookup u

preferredContentMap :: Annex (FileMatcherMap Annex)
preferredContentMap = maybe (fst <$> preferredRequiredMapsLoad preferredContentTokens) return
	=<< Annex.getState Annex.preferredcontentmap

requiredContentMap :: Annex (FileMatcherMap Annex)
requiredContentMap = maybe (snd <$> preferredRequiredMapsLoad preferredContentTokens) return
	=<< Annex.getState Annex.requiredcontentmap

preferredRequiredMapsLoad :: (PreferredContentData -> [ParseToken (MatchFiles Annex)]) -> Annex (FileMatcherMap Annex, FileMatcherMap Annex)
preferredRequiredMapsLoad mktokens = do
	(pc, rc) <- preferredRequiredMapsLoad' id mktokens
	let pc' = handleunknown (MatcherDesc "preferred content") pc
	let rc' = handleunknown (MatcherDesc "required content") rc
	Annex.changeState $ \s -> s
		{ Annex.preferredcontentmap = Just pc'
		, Annex.requiredcontentmap = Just rc'
		}
	return (pc', rc')
  where
	handleunknown matcherdesc = M.mapWithKey $ \u v ->
		(either (const $ unknownMatcher u) id v, matcherdesc)

preferredRequiredMapsLoad' :: (Matcher (MatchFiles Annex) -> Matcher (MatchFiles Annex)) -> (PreferredContentData -> [ParseToken (MatchFiles Annex)]) -> Annex (M.Map UUID (Either String (Matcher (MatchFiles Annex))), M.Map UUID (Either String (Matcher (MatchFiles Annex))))
preferredRequiredMapsLoad' matcherf mktokens = do
	groupmap <- groupMap
	configmap <- remoteConfigMap
	let genmap l gm = 
		let mk u = makeMatcher groupmap configmap
			gm u matcherf mktokens (Right (unknownMatcher u))
		in simpleMap
			. parseLogOldWithUUID (\u -> mk u . decodeBS <$> A.takeByteString)
			<$> Annex.Branch.get l
	gm <- groupPreferredContentMapRaw
	pc <- genmap preferredContentLog gm
	rc <- genmap requiredContentLog gm
	-- Required content is implicitly also preferred content, so combine.
	let pc' = M.unionWith combiner pc rc
	return (pc', rc)
  where
	combiner (Right a) (Right b) = Right (combineMatchers a b)
	combiner (Left a)  (Left b)  = Left (a ++ " " ++ b)
	combiner (Left a)  (Right _) = Left a
	combiner (Right _) (Left b)  = Left b

{- Parsing preferred content expressions intentionally never fails,
 - because the configuration is shared among repositories and newer
 - versions of git-annex may add new features.
 -
 - When a preferred content expression cannot be parsed, but is already
 - in the log (eg, put there by a newer version of git-annex),
 - the fallback behavior is to match only files that are currently present.
 -
 - This avoid unwanted/expensive changes to the content, until the problem
 - is resolved. -}
unknownMatcher :: UUID -> Matcher (MatchFiles Annex)
unknownMatcher u = generate [present]
  where
	present = Operation $ limitPresent (Just u)

{- Puts a UUID in a standard group, and sets its preferred content to use
 - the standard expression for that group (unless preferred content is
 - already set). -}
setStandardGroup :: UUID -> StandardGroup -> Annex ()
setStandardGroup u g = do
	groupSet u $ S.singleton $ fromStandardGroup g
	unlessM (isJust . M.lookup u <$> preferredContentMap) $
		preferredContentSet u "standard"

{- Avoids overwriting the UUID's standard group or preferred content
 - when it's already been configured. -}
defaultStandardGroup :: UUID -> StandardGroup -> Annex ()
defaultStandardGroup u g = 
	unlessM (hasgroup <||> haspc) $
		setStandardGroup u g
  where
	hasgroup = not . S.null <$> lookupGroups u
	haspc = isJust . M.lookup u <$> preferredContentMap

prop_standardGroups_parse :: Bool
prop_standardGroups_parse = 
	all (isNothing . checkPreferredContentExpression . standardPreferredContent)
		[ minBound .. maxBound]