summaryrefslogtreecommitdiff
path: root/Git/Construct.hs
blob: 3f3ea974762c098925f9d52eafd517ea5051c97c (plain)
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
{- Construction of Git Repo objects
 -
 - Copyright 2010,2011 Joey Hess <joey@kitenet.net>
 -
 - Licensed under the GNU GPL version 3 or higher.
 -}

module Git.Construct (
	fromCurrent,
	fromCwd,
	fromAbsPath,
	fromPath,
	fromUrl,
	fromUnknown,
	localToUrl,
	remoteNamed,
	remoteNamedFromKey,
	fromRemotes,
	fromRemoteLocation,
	repoAbsPath,
) where

import System.Posix.User
import System.Posix.Env (getEnv, unsetEnv)
import System.Posix.Directory (changeWorkingDirectory)
import qualified Data.Map as M hiding (map, split)
import Network.URI

import Common
import Git.Types
import Git
import qualified Git.Url as Url

{- Finds the current git repository.
 -
 - GIT_DIR can override the location of the .git directory.
 -
 - When GIT_WORK_TREE is set, chdir to it, so that anything using
 - this repository runs in the right location. However, this chdir is
 - done after determining GIT_DIR; git does not let GIT_WORK_TREE
 - influence the git directory.
 -
 - Both environment variables are unset, to avoid confusing other git
 - commands that also look at them. This would particularly be a problem
 - when GIT_DIR is relative and we chdir for GIT_WORK_TREE. Instead,
 - the Git module passes --work-tree and --git-dir to git commands it runs.
 -}
fromCurrent :: IO Repo
fromCurrent = do
	r <- maybe fromCwd fromPath =<< getEnv "GIT_DIR"
	maybe noop changeWorkingDirectory =<< getEnv "GIT_WORK_TREE"
	unsetEnv "GIT_DIR"
	unsetEnv "GIT_WORK_TREE"
	return r

{- Finds the git repository used for the Cwd, which may be in a parent
 - directory. -}
fromCwd :: IO Repo
fromCwd = getCurrentDirectory >>= seekUp isRepoTop >>= maybe norepo makerepo
	where
		makerepo = newFrom . Dir
		norepo = error "Not in a git repository."

{- Local Repo constructor, accepts a relative or absolute path. -}
fromPath :: FilePath -> IO Repo
fromPath dir = fromAbsPath =<< absPath dir

{- Local Repo constructor, requires an absolute path to the repo be
 - specified. -}
fromAbsPath :: FilePath -> IO Repo
fromAbsPath dir
	| "/" `isPrefixOf` dir =
		ifM (doesDirectoryExist dir') ( ret dir' , hunt )
	| otherwise =
		error $ "internal error, " ++ dir ++ " is not absolute"
	where
		ret = newFrom . Dir
 		{- Git always looks for "dir.git" in preference to
		 - to "dir", even if dir ends in a "/". -}
		canondir = dropTrailingPathSeparator dir
		dir' = canondir ++ ".git"
		{- When dir == "foo/.git", git looks for "foo/.git/.git",
		 - and failing that, uses "foo" as the repository. -}
		hunt
			| "/.git" `isSuffixOf` canondir =
				ifM (doesDirectoryExist $ dir </> ".git")
					( ret dir
					, ret $ takeDirectory canondir
					)
			| otherwise = ret dir

{- Remote Repo constructor. Throws exception on invalid url.
 -
 - Git is somewhat forgiving about urls to repositories, allowing
 - eg spaces that are not normally allowed unescaped in urls.
 -}
fromUrl :: String -> IO Repo
fromUrl url
	| not (isURI url) = fromUrlStrict $ escapeURIString isUnescapedInURI url
	| otherwise = fromUrlStrict url

fromUrlStrict :: String -> IO Repo
fromUrlStrict url
	| startswith "file://" url = fromAbsPath $ uriPath u
	| otherwise = newFrom $ Url u
	where
		u = fromMaybe bad $ parseURI url
		bad = error $ "bad url " ++ url

{- Creates a repo that has an unknown location. -}
fromUnknown :: IO Repo
fromUnknown = newFrom Unknown

{- Converts a local Repo into a remote repo, using the reference repo
 - which is assumed to be on the same host. -}
localToUrl :: Repo -> Repo -> Repo
localToUrl reference r
	| not $ repoIsUrl reference = error "internal error; reference repo not url"
	| repoIsUrl r = r
	| otherwise = r { location = Url $ fromJust $ parseURI absurl }
	where
		absurl =
			Url.scheme reference ++ "//" ++
			Url.authority reference ++
			workTree r

{- Calculates a list of a repo's configured remotes, by parsing its config. -}
fromRemotes :: Repo -> IO [Repo]
fromRemotes repo = mapM construct remotepairs
	where
		filterconfig f = filter f $ M.toList $ config repo
		filterkeys f = filterconfig (\(k,_) -> f k)
		remotepairs = filterkeys isremote
		isremote k = startswith "remote." k && endswith ".url" k
		construct (k,v) = remoteNamedFromKey k $ fromRemoteLocation v repo

{- Sets the name of a remote when constructing the Repo to represent it. -}
remoteNamed :: String -> IO Repo -> IO Repo
remoteNamed n constructor = do
	r <- constructor
	return $ r { remoteName = Just n }

{- Sets the name of a remote based on the git config key, such as
   "remote.foo.url". -}
remoteNamedFromKey :: String -> IO Repo -> IO Repo
remoteNamedFromKey k = remoteNamed basename
	where
		basename = join "." $ reverse $ drop 1 $
				reverse $ drop 1 $ split "." k

{- Constructs a new Repo for one of a Repo's remotes using a given
 - location (ie, an url). -}
fromRemoteLocation :: String -> Repo -> IO Repo
fromRemoteLocation s repo = gen $ calcloc s
	where
		gen v	
			| scpstyle v = fromUrl $ scptourl v
			| urlstyle v = fromUrl v
			| otherwise = fromRemotePath v repo
		-- insteadof config can rewrite remote location
		calcloc l
			| null insteadofs = l
			| otherwise = replacement ++ drop (length bestvalue) l
			where
				replacement = drop (length prefix) $
					take (length bestkey - length suffix) bestkey
				(bestkey, bestvalue) = maximumBy longestvalue insteadofs
				longestvalue (_, a) (_, b) = compare b a
				insteadofs = filterconfig $ \(k, v) -> 
					startswith prefix k &&
					endswith suffix k &&
					startswith v l
				filterconfig f = filter f $
					concatMap splitconfigs $
						M.toList $ fullconfig repo
				splitconfigs (k, vs) = map (\v -> (k, v)) vs
				(prefix, suffix) = ("url." , ".insteadof")
		urlstyle v = isURI v || ":" `isInfixOf` v && "//" `isInfixOf` v
		-- git remotes can be written scp style -- [user@]host:dir
		scpstyle v = ":" `isInfixOf` v && not ("//" `isInfixOf` v)
		scptourl v = "ssh://" ++ host ++ slash dir
			where
				(host, dir) = separate (== ':') v
				slash d	| d == "" = "/~/" ++ d
					| "/" `isPrefixOf` d = d
					| "~" `isPrefixOf` d = '/':d
					| otherwise = "/~/" ++ d

{- Constructs a Repo from the path specified in the git remotes of
 - another Repo. -}
fromRemotePath :: FilePath -> Repo -> IO Repo
fromRemotePath dir repo = do
	dir' <- expandTilde dir
	fromAbsPath $ workTree repo </> dir'

{- Git remotes can have a directory that is specified relative
 - to the user's home directory, or that contains tilde expansions.
 - This converts such a directory to an absolute path.
 - Note that it has to run on the system where the remote is.
 -}
repoAbsPath :: FilePath -> IO FilePath
repoAbsPath d = do
	d' <- expandTilde d
	h <- myHomeDir
	return $ h </> d'

expandTilde :: FilePath -> IO FilePath
expandTilde = expandt True
	where
		expandt _ [] = return ""
		expandt _ ('/':cs) = do
			v <- expandt True cs
			return ('/':v)
		expandt True ('~':'/':cs) = do
			h <- myHomeDir
			return $ h </> cs
		expandt True ('~':cs) = do
			let (name, rest) = findname "" cs
			u <- getUserEntryForName name
			return $ homeDirectory u </> rest
		expandt _ (c:cs) = do
			v <- expandt False cs
			return (c:v)
		findname n [] = (n, "")
		findname n (c:cs)
			| c == '/' = (n, cs)
			| otherwise = findname (n++[c]) cs

seekUp :: (FilePath -> IO Bool) -> FilePath -> IO (Maybe FilePath)
seekUp want dir =
	ifM (want dir)
		( return $ Just dir
		, case parentDir dir of
			"" -> return Nothing
			d -> seekUp want d
		)

isRepoTop :: FilePath -> IO Bool
isRepoTop dir = ifM isRepo ( return True , isBareRepo )
	where
		isRepo = gitSignature (".git" </> "config")
		isBareRepo = ifM (doesDirectoryExist $ dir </> "objects")
			( gitSignature "config" , return False )
		gitSignature file = doesFileExist (dir </> file)

newFrom :: RepoLocation -> IO Repo
newFrom l = return Repo
	{ location = l
	, config = M.empty
	, fullconfig = M.empty
	, remotes = []
	, remoteName = Nothing
	}