File: AddComputed.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 (253 lines) | stat: -rw-r--r-- 7,901 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
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
{- git-annex command
 -
 - Copyright 2025 Joey Hess <id@joeyh.name>
 -
 - Licensed under the GNU AGPL version 3 or higher.
 -}

{-# LANGUAGE OverloadedStrings #-}

module Command.AddComputed where

import Command
import qualified Git
import qualified Git.Types as Git
import qualified Git.Ref as Git
import qualified Annex
import qualified Remote.Compute
import qualified Types.Remote as Remote
import Backend
import Annex.CatFile
import Annex.Content.Presence
import Annex.Ingest
import Annex.UUID
import Annex.GitShaKey
import Types.KeySource
import Types.Key
import Annex.FileMatcher
import Messages.Progress
import Logs.Location
import Logs.EquivilantKeys
import Utility.Metered
import Backend.URL (fromUrl)
import Git.FilePath

import qualified Data.Map as M
import Data.Time.Clock

cmd :: Command
cmd = notBareRepo $ withAnnexOptions [backendOption, jsonOptions] $
	command "addcomputed" SectionCommon "add computed files to annex"
		(paramRepeating paramExpression)
		(seek <$$> optParser)

data AddComputedOptions = AddComputedOptions
	{ computeParams :: CmdParams
	, computeRemote :: DeferredParse Remote
	, reproducible :: Maybe Reproducible
	}

optParser :: CmdParamsDesc -> Parser AddComputedOptions
optParser desc = AddComputedOptions
	<$> cmdParams desc
	<*> (mkParseRemoteOption <$> parseToOption)
	<*> parseReproducible

newtype Reproducible = Reproducible { isReproducible :: Bool }
	deriving (Show, Eq)

parseReproducible :: Parser (Maybe Reproducible)
parseReproducible = r <|> unr
  where
	r  = flag Nothing (Just (Reproducible True))
		( long "reproducible"
		<> short 'r'
		<> help "computation is fully reproducible"
		)
	unr = flag Nothing (Just (Reproducible False))
		( long "unreproducible"
		<> short 'u'
		<> help "computation is not fully reproducible"
		)

seek :: AddComputedOptions -> CommandSeek
seek o = startConcurrency commandStages (seek' o)

seek' :: AddComputedOptions -> CommandSeek
seek' o = do
	addunlockedmatcher <- addUnlockedMatcher
	r <- getParsed (computeRemote o)
	unless (Remote.Compute.isComputeRemote r) $
		giveup "That is not a compute remote."

	commandAction $ start o r addunlockedmatcher

start :: AddComputedOptions -> Remote -> AddUnlockedMatcher -> CommandStart
start o r = starting "addcomputed" ai si . perform o r
  where
	ai = ActionItemUUID (Remote.uuid r) (UnquotedString (Remote.name r))
	si = SeekInput (computeParams o)

perform :: AddComputedOptions -> Remote -> AddUnlockedMatcher -> CommandPerform
perform o r addunlockedmatcher = do
	program <- Remote.Compute.getComputeProgram r
	repopath <- fromRepo Git.repoPath
	subdir <- liftIO $ relPathDirToFile repopath (literalOsPath ".")
	let state = Remote.Compute.ComputeState
		{ Remote.Compute.computeParams = computeParams o ++
			Remote.Compute.defaultComputeParams r
		, Remote.Compute.computeInputs = mempty
		, Remote.Compute.computeOutputs = mempty
		, Remote.Compute.computeSubdir = subdir
		}
	fast <- Annex.getRead Annex.fast
	Remote.Compute.runComputeProgram program state
		(Remote.Compute.ImmutableState False)
		(getInputContent fast)
		Nothing
		(go fast)
	next $ return True
  where
	go fast = addComputed (Just "adding") r (reproducible o)
		chooseBackend Just fast (Right addunlockedmatcher)

addComputed
	:: Maybe StringContainingQuotedPath
	-> Remote
	-> Maybe Reproducible
	-> (OsPath -> Annex Backend)
	-> (OsPath -> Maybe OsPath)
	-> Bool
	-> Either Bool AddUnlockedMatcher
	-> Remote.Compute.ComputeProgramResult
	-> OsPath
	-> NominalDiffTime
	-> Annex ()
addComputed maddaction r reproducibleconfig choosebackend destfile fast addunlockedmatcher result tmpdir ts = do
	when (M.null outputs) $
		giveup "The computation succeeded, but it did not generate any files."
	oks <- forM (M.keys outputs) $ \outputfile -> do
		case maddaction of
			Just addaction -> showAction $
				addaction <> " " <> QuotedPath outputfile
			Nothing -> noop
		k <- catchNonAsync (addfile outputfile)
			(\err -> giveup $ "Failed to ingest output file " ++ fromOsPath outputfile ++ ": " ++ show err)
		return (outputfile, Just k)
	let state' = state
		{ Remote.Compute.computeOutputs = M.fromList oks
		}
	forM_ (mapMaybe snd oks) $ \k -> do
		Remote.Compute.setComputeState
			(Remote.remoteStateHandle r)
			k ts state'

		let u = Remote.uuid r
		unlessM (elem u <$> loggedLocations k) $
			logChange NoLiveUpdate k u InfoPresent
  where
	state = Remote.Compute.computeState result
	
	outputs = Remote.Compute.computeOutputs state
	
	addfile outputfile
		| fast = do
			case destfile outputfile of
				Nothing -> noop
				Just f -> addSymlink f stateurlk Nothing
			return stateurlk
		| isreproducible = do
			sz <- liftIO $ getFileSize outputfile'
			metered Nothing sz Nothing $ \_ p ->
				case destfile outputfile of
					Just f -> ingesthelper f p Nothing
					Nothing -> genkey outputfile p
		| otherwise = case destfile outputfile of
			Just f -> ingesthelper f nullMeterUpdate
				(Just stateurlk)
			Nothing -> return stateurlk
	  where
	  	stateurl = Remote.Compute.computeStateUrl r state outputfile
		stateurlk = fromUrl stateurl Nothing True
		outputfile' = tmpdir </> outputfile
		genkey f p = do
			backend <- choosebackend outputfile
			let ks = KeySource
				{ keyFilename = f
				, contentLocation = outputfile'
				, inodeCache = Nothing
				}
			fst <$> genKey ks p backend
		ingesthelper f p mk = ingestwith $ do
			k <- maybe (genkey f p) return mk
			topf <- inRepo $ toTopFilePath f
			let fi = FileInfo
				{ contentFile = outputfile'
				, matchFile = getTopFilePath topf
				, matchKey = Just k
				}
			lockingfile <- case addunlockedmatcher of
				Right addunlockedmatcher' -> 
					not <$> addUnlocked addunlockedmatcher'
						(MatchingFile fi)
						(not fast)
				Left v -> pure v
			let ldc = LockDownConfig
				{ lockingFile = lockingfile
				, hardlinkFileTmpDir = Nothing
				, checkWritePerms = True
				}
			liftIO $ createDirectoryIfMissing True $
				takeDirectory f
			liftIO $ moveFile outputfile' f
			let ks = KeySource
				{ keyFilename = f
				, contentLocation = f
				, inodeCache = Nothing
				}
			let ld = LockedDown ldc ks
			ingestAdd' p (Just ld) (Just k)
		ingestwith a = a >>= \case
			Nothing -> giveup "ingestion failed"
			Just k -> do
				u <- getUUID
				unlessM (elem u <$> loggedLocations k) $
					logStatus NoLiveUpdate k InfoPresent
				when (fromKey keyVariety k == VURLKey) $ do
					hb <- hashBackend
					void $ addEquivilantKey hb k 
						=<< calcRepo (gitAnnexLocation k)
				return k
	
	isreproducible = case reproducibleconfig of
		Just v -> isReproducible v
		Nothing -> Remote.Compute.computeReproducible result
	
getInputContent :: Bool -> OsPath -> Bool -> Annex (Key, Maybe (Either Git.Sha OsPath))
getInputContent fast p required = catKeyFile p >>= \case
	Just inputkey -> getInputContent' fast inputkey required filedesc
	Nothing -> inRepo (Git.fileRef p) >>= \case
		Just fileref -> catObjectMetaData fileref >>= \case
			Just (sha, _, t)
				| t == Git.BlobObject ->
					getInputContent' fast (gitShaKey sha) required filedesc
				| otherwise ->
					badinput $ ", not a git " ++ decodeBS (Git.fmtObjectType t)
			Nothing -> notcheckedin
		Nothing -> notcheckedin
  where
	filedesc = fromOsPath p
	badinput s = giveup $ "The computation needs an input file " ++ s ++ ": " ++ fromOsPath p
	notcheckedin = badinput "that is not checked into the git repository"

getInputContent' :: Bool -> Key -> Bool -> String -> Annex (Key, Maybe (Either Git.Sha OsPath))
getInputContent' fast inputkey required filedesc
	| fast && not required = return (inputkey, Nothing)
	| otherwise = case keyGitSha inputkey of
		Nothing -> ifM (inAnnex inputkey)
			( do
				obj <- calcRepo (gitAnnexLocation inputkey)
				return (inputkey, Just (Right obj))
			, giveup $ "The computation needs the content of an annexed file which is not present: " ++ filedesc
			)
		Just sha -> return (inputkey, Just (Left sha))