Skip to content

Commit a5d9c70

Browse files
authored
Change git directory using work-tree / git-dir (#747)
1 parent e2f00d8 commit a5d9c70

File tree

1 file changed

+8
-6
lines changed

1 file changed

+8
-6
lines changed

src/fpm/git.f90

Lines changed: 8 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
!> Implementation for interacting with git repositories.
22
module fpm_git
33
use fpm_error, only: error_t, fatal_error
4-
use fpm_filesystem, only : get_temp_filename, getline
4+
use fpm_filesystem, only : get_temp_filename, getline, join_path
55
implicit none
66

77
public :: git_target_t
@@ -141,13 +141,14 @@ subroutine checkout(self, local_path, error)
141141
type(error_t), allocatable, intent(out) :: error
142142

143143
integer :: stat
144-
character(len=:), allocatable :: object
144+
character(len=:), allocatable :: object, workdir
145145

146146
if (allocated(self%object)) then
147147
object = self%object
148148
else
149149
object = 'HEAD'
150150
end if
151+
workdir = "--work-tree="//local_path//" --git-dir="//join_path(local_path, ".git")
151152

152153
call execute_command_line("git init "//local_path, exitstat=stat)
153154

@@ -156,15 +157,15 @@ subroutine checkout(self, local_path, error)
156157
return
157158
end if
158159

159-
call execute_command_line("git -C "//local_path//" fetch --depth=1 "// &
160+
call execute_command_line("git "//workdir//" fetch --depth=1 "// &
160161
self%url//" "//object, exitstat=stat)
161162

162163
if (stat /= 0) then
163164
call fatal_error(error,'Error while fetching git repository for remote dependency')
164165
return
165166
end if
166167

167-
call execute_command_line("git -C "//local_path//" checkout -qf FETCH_HEAD", exitstat=stat)
168+
call execute_command_line("git "//workdir//" checkout -qf FETCH_HEAD", exitstat=stat)
168169

169170
if (stat /= 0) then
170171
call fatal_error(error,'Error while checking out git repository for remote dependency')
@@ -186,11 +187,12 @@ subroutine git_revision(local_path, object, error)
186187
type(error_t), allocatable, intent(out) :: error
187188

188189
integer :: stat, unit, istart, iend
189-
character(len=:), allocatable :: temp_file, line, iomsg
190+
character(len=:), allocatable :: temp_file, line, iomsg, workdir
190191
character(len=*), parameter :: hexdigits = '0123456789abcdef'
191192

193+
workdir = "--work-tree="//local_path//" --git-dir="//join_path(local_path, ".git")
192194
allocate(temp_file, source=get_temp_filename())
193-
line = "git -C "//local_path//" log -n 1 > "//temp_file
195+
line = "git "//workdir//" log -n 1 > "//temp_file
194196
call execute_command_line(line, exitstat=stat)
195197

196198
if (stat /= 0) then

0 commit comments

Comments
 (0)