Skip to content

Commit

Permalink
Merge pull request #232 from derpycode/_DEV_ORBITS_masterupdated
Browse files Browse the repository at this point in the history
merge into master
  • Loading branch information
derpycode authored Nov 16, 2023
2 parents 58c922e + 6c1f947 commit 7ab755e
Show file tree
Hide file tree
Showing 44 changed files with 13,225 additions and 124 deletions.
5 changes: 3 additions & 2 deletions genie-biogem/src/fortran/biogem.f90
Original file line number Diff line number Diff line change
Expand Up @@ -4025,13 +4025,14 @@ SUBROUTINE diag_biogem_timeseries( &
end if
! solar insolation (and orbitally-related information)
! NOTE: apply ocean mask (@ surface)
! NOTE [PV 24/07/23]: apply ocean-atmosphere mask
! (1) mean global properties
int_misc_ocn_solfor_sig = int_misc_ocn_solfor_sig + &
& loc_dtyr*loc_ocn_rtot_A*sum(phys_ocn(ipo_A,:,:,n_k)*phys_ocnatm(ipoa_solfor,:,:))
& loc_dtyr*loc_ocnatm_rtot_A*sum(phys_ocnatm(ipoa_A,:,:)*phys_ocnatm(ipoa_solfor,:,:))
int_misc_opn_solfor_sig = int_misc_opn_solfor_sig + &
& loc_dtyr*loc_opn_rtot_A*sum(phys_ocn(ipo_A,:,:,n_k)*phys_ocnatm(ipoa_solfor,:,:))
int_misc_ocn_fxsw_sig = int_misc_ocn_fxsw_sig + &
& loc_dtyr*loc_ocn_rtot_A*sum(phys_ocn(ipo_A,:,:,n_k)*phys_ocnatm(ipoa_fxsw,:,:))
& loc_dtyr*loc_ocnatm_rtot_A*sum(phys_ocnatm(ipoa_A,:,:)*phys_ocnatm(ipoa_fxsw,:,:))
int_misc_opn_fxsw_sig = int_misc_opn_fxsw_sig + &
& loc_dtyr*loc_opn_rtot_A*sum(phys_ocn(ipo_A,:,:,n_k)*phys_ocnatm(ipoa_fxsw,:,:))
! (2) latitudinal/seasonal properties
Expand Down
26 changes: 13 additions & 13 deletions genie-biogem/src/fortran/biogem_data_ascii.f90
Original file line number Diff line number Diff line change
Expand Up @@ -518,10 +518,10 @@ SUBROUTINE sub_init_data_save_runtime()
call check_iostat(ios,__LINE__,__FILE__)
CLOSE(unit=out,iostat=ios)
call check_iostat(ios,__LINE__,__FILE__)
! insolation (wet grid only)
! insolation
loc_filename=fun_data_timeseries_filename( &
& loc_t,par_outdir_name,trim(par_outfile_name)//'_series','misc_ocn_insol',string_results_ext)
loc_string = '% time (yr) / mean (wet grid) insolation (W m-2) / ' // &
& loc_t,par_outdir_name,trim(par_outfile_name)//'_series','misc_insol',string_results_ext)
loc_string = '% time (yr) / mean insolation (W m-2) / ' // &
& 'N mean zonal insolation (W m-2) @ j=' // fun_conv_num_char_n(2,par_sig_j_N) // &
& ' and BIOGEM time-step: ' // fun_conv_num_char_n(2,par_t_sig_count_N) // &
& ' / ' // &
Expand All @@ -535,8 +535,8 @@ SUBROUTINE sub_init_data_save_runtime()
CLOSE(unit=out,iostat=ios)
call check_iostat(ios,__LINE__,__FILE__)
loc_filename=fun_data_timeseries_filename( &
& loc_t,par_outdir_name,trim(par_outfile_name)//'_series','misc_ocn_swflux',string_results_ext)
loc_string = '% time (yr) / mean annual Sw flux at ocean surface (W m-2)'
& loc_t,par_outdir_name,trim(par_outfile_name)//'_series','misc_swflux',string_results_ext)
loc_string = '% time (yr) / mean annual SW flux at surface (W m-2)'
call check_unit(out,__LINE__,__FILE__)
OPEN(unit=out,file=loc_filename,action='write',status='replace',iostat=ios)
call check_iostat(ios,__LINE__,__FILE__)
Expand Down Expand Up @@ -817,8 +817,8 @@ SUBROUTINE sub_init_data_save_runtime()
end if
! insolation (wet grid only)
loc_filename=fun_data_timeseries_filename( &
& loc_t,par_outdir_name,trim(par_outfile_name)//'_series','misc_ocn_insol',string_results_ext)
loc_string = '% time (yr) / mean (wet grid) insolation (W m-2) / ' // &
& loc_t,par_outdir_name,trim(par_outfile_name)//'_series','misc_insol',string_results_ext)
loc_string = '% time (yr) / mean insolation (W m-2) / ' // &
& 'N mean zonal insolation (W m-2) @ j=' // fun_conv_num_char_n(2,par_sig_j_N) // &
& ' and BIOGEM time-step: ' // fun_conv_num_char_n(2,par_t_sig_count_N) // &
& ' / ' // &
Expand All @@ -832,8 +832,8 @@ SUBROUTINE sub_init_data_save_runtime()
CLOSE(unit=out,iostat=ios)
call check_iostat(ios,__LINE__,__FILE__)
loc_filename=fun_data_timeseries_filename( &
& loc_t,par_outdir_name,trim(par_outfile_name)//'_series','misc_ocn_swflux',string_results_ext)
loc_string = '% time (yr) / mean annual Sw flux at ocean surface (W m-2)'
& loc_t,par_outdir_name,trim(par_outfile_name)//'_series','misc_swflux',string_results_ext)
loc_string = '% time (yr) / mean annual SW flux at surface (W m-2)'
call check_unit(out,__LINE__,__FILE__)
OPEN(unit=out,file=loc_filename,action='write',status='replace',iostat=ios)
call check_iostat(ios,__LINE__,__FILE__)
Expand Down Expand Up @@ -2171,9 +2171,9 @@ SUBROUTINE sub_data_save_runtime(dum_yr_save,dum_t)
call check_iostat(ios,__LINE__,__FILE__)
CLOSE(unit=out,iostat=ios)
call check_iostat(ios,__LINE__,__FILE__)
! insolation (wet grid only)
! insolation (ocnatm grid) at top of atmosphere
loc_filename=fun_data_timeseries_filename( &
& dum_t,par_outdir_name,trim(par_outfile_name)//'_series','misc_ocn_insol',string_results_ext)
& dum_t,par_outdir_name,trim(par_outfile_name)//'_series','misc_insol',string_results_ext)
call check_unit(out,__LINE__,__FILE__)
OPEN(unit=out,file=loc_filename,action='write',status='old',position='append',iostat=ios)
call check_iostat(ios,__LINE__,__FILE__)
Expand All @@ -2185,9 +2185,9 @@ SUBROUTINE sub_data_save_runtime(dum_yr_save,dum_t)
call check_iostat(ios,__LINE__,__FILE__)
CLOSE(unit=out,iostat=ios)
call check_iostat(ios,__LINE__,__FILE__)
! SW flux at surface (wet grid only)
! SW flux (ocnatm grid) at surface (accounted for albedo)
loc_filename=fun_data_timeseries_filename( &
& dum_t,par_outdir_name,trim(par_outfile_name)//'_series','misc_ocn_swflux',string_results_ext)
& dum_t,par_outdir_name,trim(par_outfile_name)//'_series','misc_swflux',string_results_ext)
call check_unit(out,__LINE__,__FILE__)
OPEN(unit=out,file=loc_filename,action='write',status='old',position='append',iostat=ios)
call check_iostat(ios,__LINE__,__FILE__)
Expand Down
Loading

0 comments on commit 7ab755e

Please sign in to comment.