Have you added the get_env
function to your module/project?
Click to see source code
! Copyright (c) 2020 fpm contributors
!
! This work is licensed under the terms of the MIT license.
! For a copy, see <https://opensource.org/licenses/MIT>.
!> get named environment variable value. It it is blank or
!! not set return the optional default value
function get_env(NAME,DEFAULT) result(VALUE)
implicit none
!> name of environment variable to get the value of
character(len=*),intent(in) :: NAME
!> default value to return if the requested value is undefined or blank
character(len=*),intent(in),optional :: DEFAULT
!> the returned value
character(len=:),allocatable :: VALUE
integer :: howbig
integer :: stat
integer :: length
! get length required to hold value
length=0
if(NAME.ne.'')then
call get_environment_variable(NAME, length=howbig,status=stat,trim_name=.true.)
select case (stat)
case (1)
!*!print *, NAME, " is not defined in the environment. Strange..."
VALUE=''
case (2)
!*!print *, "This processor doesn't support environment variables. Boooh!"
VALUE=''
case default
! make string to hold value of sufficient size
allocate(character(len=max(howbig,1)) :: VALUE)
! get value
call get_environment_variable(NAME,VALUE,status=stat,trim_name=.true.)
if(stat.ne.0)VALUE=''
end select
else
VALUE=''
endif
if(VALUE.eq.''.and.present(DEFAULT))VALUE=DEFAULT
end function get_env
Concerning the workflow, I agree that using configure to append an environment variable to the .bashrc config is murky. It’s best to confront the user about it in the usage instructions and fail elegantly at runtime if the variable is not set (with a nice message how to fix this). After-all, there is no need to recompile, only to set the environment variable. Hence you could get rid of the conditional compilation logic entirely, and also remove the -DIRVSPDATA
flag in the Makefile.
As an extra precaution you could add the following to the Makefile:
ifndef IRVSPDATA
$(warning Warning - Environment variable 'IRVSPDATA' has not been set.)
endif
You could also promote the warning into an error, which would cause make to fail. But I don’t think it’s of that much help. (It’s also not fail-proof, as a user can silence the warning by issuing the command make IRVSPDATA=0
, leaving the actual environment variable unchanged.)
IMO, the conditional compilation would make sense if you attempt to insert the directory path directly into your Fortran code. This would however require a rebuild if you’d like to change the folder. To pass the path you could do make IRVSPDATA=$(pwd)
or use the exported environment variable. In case you’d want to insert the path directly, you’d also need to quote the preprocessor define flag -D'IRVSPDATA="$(IRVSPDATA)"'
, and the string it contains. Personally, I think the runtime version is adequate.