Skip to content

Commit

Permalink
change pointers to allocatables and add back intents to several schem…
Browse files Browse the repository at this point in the history
…es for AQM production code
  • Loading branch information
grantfirl committed Nov 28, 2023
1 parent d6563b5 commit 89cf283
Show file tree
Hide file tree
Showing 24 changed files with 70 additions and 66 deletions.
4 changes: 2 additions & 2 deletions physics/GFS_DCNV_generic_post.F90
Original file line number Diff line number Diff line change
Expand Up @@ -38,10 +38,10 @@ subroutine GFS_DCNV_generic_post_run (im, levs, lssav, ldiag3d, qdiag3d, ras, &
logical, intent(in) :: satmedmf, trans_trac

real(kind=kind_phys), dimension(:), intent(inout) :: rainc, cldwrk
real(kind=kind_phys), dimension(:,:), pointer :: upd_mf, dwn_mf, det_mf
real(kind=kind_phys), dimension(:,:), intent(inout), allocatable :: upd_mf, dwn_mf, det_mf
real(kind=kind_phys), dimension(:,:), intent(inout) :: cnvw, cnvc

real(kind=kind_phys), dimension(:,:,:), pointer :: dtend
real(kind=kind_phys), dimension(:,:,:), intent(inout), allocatable :: dtend
integer, intent(in) :: dtidx(:,:), index_of_process_dcnv, index_of_temperature, &
index_of_x_wind, index_of_y_wind, ntqv
integer, intent(in) :: ntcw,ntiw,ntclamt,ntrw,ntsw,ntrnc,ntsnc,ntgl, &
Expand Down
2 changes: 1 addition & 1 deletion physics/GFS_GWD_generic_post.F90
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,7 @@ subroutine GFS_GWD_generic_post_run(lssav, ldiag3d, dtf, dusfcg, dvsfcg, dudt, d
real(kind=kind_phys), intent(inout) :: dugwd(:), dvgwd(:)

! dtend only allocated only if ldiag3d is .true.
real(kind=kind_phys), pointer :: dtend(:,:,:)
real(kind=kind_phys), intent(inout), allocatable :: dtend(:,:,:)
integer, intent(in) :: dtidx(:,:), index_of_temperature, &
& index_of_x_wind, index_of_y_wind, index_of_process_orographic_gwd

Expand Down
4 changes: 2 additions & 2 deletions physics/GFS_GWD_generic_pre.F90
Original file line number Diff line number Diff line change
Expand Up @@ -29,13 +29,13 @@ subroutine GFS_GWD_generic_pre_run( &
real(kind=kind_phys), intent(out) :: &
& oc(:), oa4(:,:), clx(:,:), &
& theta(:), sigma(:), gamma(:), elvmax(:)
real(kind=kind_phys), pointer :: &
real(kind=kind_phys), intent(out), allocatable :: &
& varss(:), ocss(:), oa4ss(:,:), clxss(:,:)

logical, intent(in) :: lssav, ldiag3d, flag_for_gwd_generic_tend
real(kind=kind_phys), intent(in) :: dtdt(:,:), dudt(:,:), dvdt(:,:)
! dtend only allocated only if ldiag3d is .true.
real(kind=kind_phys), pointer :: dtend(:,:,:)
real(kind=kind_phys), intent(inout), allocatable :: dtend(:,:,:)
integer, intent(in) :: dtidx(:,:), index_of_temperature, &
& index_of_x_wind, index_of_y_wind, index_of_process_orographic_gwd
real(kind=kind_phys), intent(in) :: dtf
Expand Down
30 changes: 15 additions & 15 deletions physics/GFS_MP_generic_post.F90
Original file line number Diff line number Diff line change
Expand Up @@ -55,35 +55,35 @@ subroutine GFS_MP_generic_post_run(
real(kind=kind_phys), dimension(:,:), intent(in) :: prsi, phii
real(kind=kind_phys), dimension(:,:,:), intent(in) :: gq0, save_q

real(kind=kind_phys), dimension(:,:,:), pointer :: dfi_radar_tten
real(kind=kind_phys), dimension(:,:,:), intent(in), allocatable :: dfi_radar_tten

real(kind=kind_phys), dimension(:), intent(in ) :: sr
real(kind=kind_phys), dimension(:), intent(inout) :: rain, domr_diag, domzr_diag, domip_diag, doms_diag, tprcp, &
srflag, cnvprcp, totprcp, totice, totsnw, totgrp, cnvprcpb, &
totprcpb, toticeb, totsnwb, totgrpb, pwat
real(kind=kind_phys), dimension(:), intent(inout) :: rain_cpl, rainc_cpl, snow_cpl

real(kind=kind_phys), dimension(:,:,:), pointer :: dtend
real(kind=kind_phys), dimension(:,:,:), intent(inout), allocatable :: dtend
integer, dimension(:,:), intent(in) :: dtidx

! Stochastic physics / surface perturbations
real(kind=kind_phys), dimension(:), intent(inout) :: drain_cpl, dsnow_cpl

! Rainfall variables previous time step
integer, intent(in) :: lsm, lsm_ruc, lsm_noahmp
real(kind=kind_phys), dimension(:), pointer :: raincprv
real(kind=kind_phys), dimension(:), pointer :: rainncprv
real(kind=kind_phys), dimension(:), pointer :: iceprv
real(kind=kind_phys), dimension(:), pointer :: snowprv
real(kind=kind_phys), dimension(:), pointer :: graupelprv
real(kind=kind_phys), dimension(:), pointer :: draincprv
real(kind=kind_phys), dimension(:), pointer :: drainncprv
real(kind=kind_phys), dimension(:), pointer :: diceprv
real(kind=kind_phys), dimension(:), pointer :: dsnowprv
real(kind=kind_phys), dimension(:), pointer :: dgraupelprv
real(kind=kind_phys), dimension(:,:), pointer :: dqdt_qmicro
real(kind=kind_phys), dimension(:,:), intent(inout) :: prevsq
real(kind=kind_phys), intent(in) :: dtp
real(kind=kind_phys), dimension(:), intent(inout), allocatable :: raincprv
real(kind=kind_phys), dimension(:), intent(inout), allocatable :: rainncprv
real(kind=kind_phys), dimension(:), intent(inout), allocatable :: iceprv
real(kind=kind_phys), dimension(:), intent(inout), allocatable :: snowprv
real(kind=kind_phys), dimension(:), intent(inout), allocatable :: graupelprv
real(kind=kind_phys), dimension(:), intent(inout), allocatable :: draincprv
real(kind=kind_phys), dimension(:), intent(inout), allocatable :: drainncprv
real(kind=kind_phys), dimension(:), intent(inout), allocatable :: diceprv
real(kind=kind_phys), dimension(:), intent(inout), allocatable :: dsnowprv
real(kind=kind_phys), dimension(:), intent(inout), allocatable :: dgraupelprv
real(kind=kind_phys), dimension(:,:), intent(inout), allocatable :: dqdt_qmicro
real(kind=kind_phys), dimension(:,:), intent(inout) :: prevsq
real(kind=kind_phys), intent(in) :: dtp

! CCPP error handling
character(len=*), intent(out) :: errmsg
Expand Down
6 changes: 3 additions & 3 deletions physics/GFS_PBL_generic_post.F90
Original file line number Diff line number Diff line change
Expand Up @@ -47,7 +47,7 @@ subroutine GFS_PBL_generic_post_run (im, levs, nvdiff, ntrac,
real(kind=kind_phys), intent(in) :: rd, cp, fvirt, hvap, huge
real(kind=kind_phys), dimension(:), intent(in) :: t1, q1, hflx, oceanfrac
real(kind=kind_phys), dimension(:,:), intent(in) :: prsl
real(kind=kind_phys), dimension(:), pointer :: dusfc_cice, dvsfc_cice, dtsfc_cice, dqsfc_cice, &
real(kind=kind_phys), dimension(:), intent(in), allocatable :: dusfc_cice, dvsfc_cice, dtsfc_cice, dqsfc_cice, &
dtsfc_med, dqsfc_med, dusfc_med, dvsfc_med
real(kind=kind_phys), dimension(:), intent(in) :: wind, stress_wat, hflx_wat, evap_wat, ugrs1, vgrs1

Expand All @@ -64,9 +64,9 @@ subroutine GFS_PBL_generic_post_run (im, levs, nvdiff, ntrac,
! Since Intel 15 crashes when passing unallocated arrays to arrays defined with explicit shape,
! use assumed-shape arrays. Note that Intel 18 and GNU 6.2.0-8.1.0 tolerate explicit-shape arrays
! as long as these do not get used when not allocated.
real(kind=kind_phys), dimension(:), pointer :: dusfc_cpl, dvsfc_cpl, dtsfc_cpl, dqsfc_cpl, dusfci_cpl, dvsfci_cpl, &
real(kind=kind_phys), dimension(:), intent(inout), allocatable :: dusfc_cpl, dvsfc_cpl, dtsfc_cpl, dqsfc_cpl, dusfci_cpl, dvsfci_cpl, &
dtsfci_cpl, dqsfci_cpl, dusfc_diag, dvsfc_diag, dtsfc_diag, dqsfc_diag, dusfci_diag, dvsfci_diag, dtsfci_diag, dqsfci_diag
real(kind=kind_phys), pointer , optional :: dtend(:,:,:)
real(kind=kind_phys), intent(inout), allocatable, optional :: dtend(:,:,:)
integer, intent(in) :: dtidx(:,:)
integer, intent(in) :: index_of_temperature, index_of_x_wind, index_of_y_wind, index_of_process_pbl

Expand Down
2 changes: 1 addition & 1 deletion physics/GFS_SCNV_generic_post.F90
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,7 @@ subroutine GFS_SCNV_generic_post_run (im, levs, nn, lssav, ldiag3d, qdiag3d, &
real(kind=kind_phys), dimension(:,:,:), intent(in) :: save_q, gq0

! dtend only allocated if ldiag3d == .true.
real(kind=kind_phys), pointer :: dtend(:,:,:)
real(kind=kind_phys), intent(inout), allocatable :: dtend(:,:,:)
integer, intent(in) :: dtidx(:,:)
integer, intent(in) :: index_of_temperature, index_of_x_wind, index_of_y_wind, index_of_process_scnv
real(kind=kind_phys), dimension(:,:,:), intent(in) :: clw
Expand Down
6 changes: 3 additions & 3 deletions physics/GFS_radiation_surface.F90
Original file line number Diff line number Diff line change
Expand Up @@ -81,9 +81,9 @@ subroutine GFS_radiation_surface_run ( &
hprime, tsfg, tsfa, tisfc, &
coszen, alvsf, alnsf, alvwf, &
alnwf, facsf, facwf, snoalb
real(kind=kind_phys), dimension(:), pointer :: lndp_prt_list
character(len=3) , dimension(:), pointer :: lndp_var_list
real(kind=kind_phys), dimension(:), pointer :: albdvis_ice, albdnir_ice, &
real(kind=kind_phys), dimension(:), intent(in), allocatable :: lndp_prt_list
character(len=3) , dimension(:), intent(in), allocatable :: lndp_var_list
real(kind=kind_phys), dimension(:), intent(in), allocatable :: albdvis_ice, albdnir_ice, &
albivis_ice, albinir_ice

real(kind=kind_phys), dimension(:), intent(inout) :: albdvis_lnd, albdnir_lnd, &
Expand Down
10 changes: 5 additions & 5 deletions physics/GFS_rrtmg_pre.F90
Original file line number Diff line number Diff line change
Expand Up @@ -119,17 +119,17 @@ subroutine GFS_rrtmg_pre_run (im, levs, lm, lmk, lmp, lextop, ltp, &
integer, intent(in) :: ntdu1, ntdu2, ntdu3, ntdu4, ntdu5, ntss1, ntss2, ntss3, &
ntss4, ntss5, ntsu, ntbcb, ntbcl, ntocb, ntocl, ntchm

character(len=3), dimension(:), pointer :: lndp_var_list
character(len=3), dimension(:), intent(in), allocatable :: lndp_var_list

logical, intent(in) :: lextop, lsswr, lslwr, ltaerosol, lgfdlmprad, &
uni_cld, effr_in, do_mynnedmf, &
lmfshal, lmfdeep2, pert_clds, mraerosol
logical, intent(in) :: aero_dir_fdb
real(kind=kind_phys), dimension(:,:), pointer :: smoke_ext, dust_ext
real(kind=kind_phys), dimension(:,:), intent(in), allocatable :: smoke_ext, dust_ext

logical, intent(in) :: nssl_ccn_on, nssl_invertccn
integer, intent(in) :: spp_rad
real(kind_phys), pointer :: spp_wts_rad(:,:)
real(kind_phys), intent(in), allocatable :: spp_wts_rad(:,:)

real(kind=kind_phys), intent(in) :: fhswr, fhlwr, solhr, sup, julian, sppt_amp
real(kind=kind_phys), intent(in) :: con_eps, epsm1, fvirt, rog, rocp, con_rd
Expand All @@ -142,7 +142,7 @@ subroutine GFS_rrtmg_pre_run (im, levs, lm, lmk, lmp, lextop, ltp, &
tgrs, &
mg_cld, effrr_in, &
cnvw_in, cnvc_in
real(kind=kind_phys), dimension(:,:), pointer :: sfc_wts, sppt_wts
real(kind=kind_phys), dimension(:,:), intent(in), allocatable :: sfc_wts, sppt_wts

real(kind=kind_phys), dimension(:,:,:), intent(in) :: qgrs
real(kind=kind_phys), dimension(:,:,:), intent(inout) :: aer_nm
Expand All @@ -155,7 +155,7 @@ subroutine GFS_rrtmg_pre_run (im, levs, lm, lmk, lmp, lextop, ltp, &
real(kind=kind_phys), dimension(:,:), intent(inout) :: clouds1, &
clouds2, clouds3, &
clouds4, clouds5
real(kind=kind_phys), dimension(:,:), pointer :: qci_conv
real(kind=kind_phys), dimension(:,:), intent(in), allocatable :: qci_conv
real(kind=kind_phys), dimension(:), intent(out) :: lwp_ex,iwp_ex, &
lwp_fc,iwp_fc

Expand Down
4 changes: 2 additions & 2 deletions physics/GFS_suite_interstitial_2.F90
Original file line number Diff line number Diff line change
Expand Up @@ -30,9 +30,9 @@ subroutine GFS_suite_interstitial_2_run (im, levs, lssav, ldiag3d, lsidea, flag_
logical, intent(in ), dimension(:) :: flag_cice
real(kind=kind_phys), intent(in ), dimension(:) :: ctei_rm
real(kind=kind_phys), intent(in ), dimension(:) :: xcosz, adjsfcdsw, adjsfcdlw, pgr, xmu, work1, work2
real(kind=kind_phys), pointer , dimension(:) :: ulwsfc_cice
real(kind=kind_phys), intent(in ), dimension(:), allocatable :: ulwsfc_cice
real(kind=kind_phys), intent(in ), dimension(:) :: cice
real(kind=kind_phys), pointer , dimension(:,:) :: htrlwu
real(kind=kind_phys), intent(in ), dimension(:,:), allocatable :: htrlwu
real(kind=kind_phys), intent(in ), dimension(:,:) :: htrsw, htrlw, tgrs, prsl, qgrs_water_vapor, qgrs_cloud_water, prslk
real(kind=kind_phys), intent(in ), dimension(:,:) :: prsi
real(kind=kind_phys), intent(in ), dimension(:,:,:) :: lwhd
Expand Down
2 changes: 1 addition & 1 deletion physics/GFS_suite_interstitial_3.F90
Original file line number Diff line number Diff line change
Expand Up @@ -54,7 +54,7 @@ subroutine GFS_suite_interstitial_3_run (otsptflag, &

real(kind=kind_phys), intent(inout ), dimension(:,:) :: sigmain
real(kind=kind_phys), intent(inout ), dimension(:,:) :: sigmaout
real(kind=kind_phys), pointer , dimension(:,:) :: qmicro
real(kind=kind_phys), intent(inout ), dimension(:,:), allocatable :: qmicro
real(kind=kind_phys), intent(inout), dimension(:,:) :: rhc, save_qc
! save_qi is not allocated for Zhao-Carr MP
real(kind=kind_phys), intent(inout), dimension(:,:) :: save_qi
Expand Down
2 changes: 1 addition & 1 deletion physics/GFS_suite_interstitial_4.F90
Original file line number Diff line number Diff line change
Expand Up @@ -37,7 +37,7 @@ subroutine GFS_suite_interstitial_4_run (im, levs, ltaerosol, tracers_total, ntr

! dtend and dtidx are only allocated if ldiag3d
logical, intent(in) :: ldiag3d, qdiag3d
real(kind=kind_phys), dimension(:,:,:), pointer :: dtend
real(kind=kind_phys), dimension(:,:,:), intent(inout), allocatable :: dtend
integer, dimension(:,:), intent(in) :: dtidx
integer, intent(in) :: index_of_process_conv_trans,ntk,ntke

Expand Down
6 changes: 3 additions & 3 deletions physics/GFS_surface_generic_post.F90
Original file line number Diff line number Diff line change
Expand Up @@ -66,14 +66,14 @@ subroutine GFS_surface_generic_post_run (im, cplflx, cplaqm, cplchm, cplwav, cpl
real(kind=kind_phys), dimension(:), intent(in) :: ep1d, gflx, tgrs_1, qgrs_1, ugrs_1, vgrs_1, adjsfcdlw, adjsfcdsw, &
adjnirbmd, adjnirdfd, adjvisbmd, adjvisdfd, adjsfculw, adjsfculw_wat, adjnirbmu, adjnirdfu, adjvisbmu, adjvisdfu, &
t2m, q2m, u10m, v10m, tsfc, tsfc_wat, pgr, xcosz, evbs, evcw, trans, sbsno, snowc, snohf, pah, ecan, etran, edir

real(kind=kind_phys), dimension(:), intent(in), allocatable :: waxy
real(kind=kind_phys), dimension(:), intent(inout) :: epi, gfluxi, t1, q1, u1, v1, gflux, evbsa, evcwa, transa, sbsnoa,&
snowca, snohfa, ep, tecan, tetran, tedir

real(kind=kind_phys), dimension(:), pointer :: dlwsfci_cpl, dswsfci_cpl, dlwsfc_cpl, &
real(kind=kind_phys), dimension(:), intent(inout), allocatable :: dlwsfci_cpl, dswsfci_cpl, dlwsfc_cpl, &
dswsfc_cpl, dnirbmi_cpl, dnirdfi_cpl, dvisbmi_cpl, dvisdfi_cpl, dnirbm_cpl, dnirdf_cpl, dvisbm_cpl, dvisdf_cpl, &
nlwsfci_cpl, nlwsfc_cpl, t2mi_cpl, q2mi_cpl, u10mi_cpl, v10mi_cpl, tsfci_cpl, psurfi_cpl, nnirbmi_cpl, nnirdfi_cpl, &
nvisbmi_cpl, nvisdfi_cpl, nswsfci_cpl, nswsfc_cpl, nnirbm_cpl, nnirdf_cpl, nvisbm_cpl, nvisdf_cpl, pahi, paha, twa, waxy
nvisbmi_cpl, nvisdfi_cpl, nswsfci_cpl, nswsfc_cpl, nnirbm_cpl, nnirdf_cpl, nvisbm_cpl, nvisdf_cpl, pahi, paha, twa

real(kind=kind_phys), dimension(:), intent(inout) :: runoff, srunoff
real(kind=kind_phys), dimension(:), intent(in) :: drain, runof
Expand Down
8 changes: 4 additions & 4 deletions physics/GFS_surface_generic_pre.F90
Original file line number Diff line number Diff line change
Expand Up @@ -91,9 +91,9 @@ subroutine GFS_surface_generic_pre_run (nthreads, im, levs, vfrac, islmsk, isot,
real(kind=kind_phys), dimension(:), intent(in) :: rain_cpl
real(kind=kind_phys), dimension(:), intent(in) :: snow_cpl
integer, intent(in) :: lndp_type, n_var_lndp
character(len=3), dimension(:), pointer :: lndp_var_list
real(kind=kind_phys), dimension(:), pointer :: lndp_prt_list
real(kind=kind_phys), dimension(:,:), pointer :: sfc_wts
character(len=3), dimension(:), intent(in), allocatable :: lndp_var_list
real(kind=kind_phys), dimension(:), intent(in), allocatable :: lndp_prt_list
real(kind=kind_phys), dimension(:,:), intent(in), allocatable :: sfc_wts
real(kind=kind_phys), dimension(:), intent(out) :: z01d
real(kind=kind_phys), dimension(:), intent(out) :: zt1d
real(kind=kind_phys), dimension(:), intent(out) :: bexp1d
Expand All @@ -102,7 +102,7 @@ subroutine GFS_surface_generic_pre_run (nthreads, im, levs, vfrac, islmsk, isot,
real(kind=kind_phys), intent(out) :: lndp_vgf

logical, intent(in) :: cplflx
real(kind=kind_phys), dimension(:), pointer :: slimskin_cpl
real(kind=kind_phys), dimension(:), intent(in), allocatable :: slimskin_cpl
logical, dimension(:), intent(inout) :: flag_cice
integer, dimension(:), intent(out) :: islmsk_cice

Expand Down
12 changes: 6 additions & 6 deletions physics/cires_ugwp.F90
Original file line number Diff line number Diff line change
Expand Up @@ -230,22 +230,22 @@ subroutine cires_ugwp_run(do_ugwp, me, master, im, levs, ntrac, dtp, kdt, lonr
real(kind=kind_phys), intent(out), dimension(:) :: tau_mtb, tau_ogw, tau_tofd, tau_ngw
real(kind=kind_phys), intent(out), dimension(:, :):: gw_dudt, gw_dvdt, gw_dtdt, gw_kdis
real(kind=kind_phys), intent(out), dimension(:, :):: dudt_mtb, dudt_ogw, dudt_tms
real(kind=kind_phys), pointer , dimension(:) :: dusfc_ms, dvsfc_ms, dusfc_bl, dvsfc_bl
real(kind=kind_phys), pointer , dimension(:, :) :: dtauy2d_ms
real(kind=kind_phys), pointer , dimension(:, :) :: dtaux2d_bl, dtauy2d_bl
real(kind=kind_phys), intent(out), dimension(:) , allocatable :: dusfc_ms, dvsfc_ms, dusfc_bl, dvsfc_bl
real(kind=kind_phys), intent(out), dimension(:, :), allocatable :: dtauy2d_ms
real(kind=kind_phys), intent(out), dimension(:, :), allocatable :: dtaux2d_bl, dtauy2d_bl

! dtend is only allocated if ldiag=.true.
real(kind=kind_phys), optional, pointer :: dtend(:,:,:)
real(kind=kind_phys), intent(inout), optional, allocatable :: dtend(:,:,:)
integer, intent(in) :: dtidx(:,:), &
index_of_x_wind, index_of_y_wind, index_of_temperature, &
index_of_process_orographic_gwd, index_of_process_nonorographic_gwd

logical, intent(in) :: ldiag3d, lssav

! These arrays only allocated if ldiag_ugwp = .true.
real(kind=kind_phys), pointer , dimension(:,:) :: du3dt_mtb, du3dt_ogw, du3dt_tms
real(kind=kind_phys), intent(inout), dimension(:,:), alloctable :: du3dt_mtb, du3dt_ogw, du3dt_tms

real(kind=kind_phys), intent(inout), dimension(:, :):: dudt, dvdt, dtdt
real(kind=kind_phys), intent(inout), dimension(:,:) :: dudt, dvdt, dtdt

real(kind=kind_phys), intent(in) :: con_g, con_pi, con_cp, con_rd, con_rv, con_fvirt, con_omega

Expand Down
2 changes: 1 addition & 1 deletion physics/cires_ugwp_post.F90
Original file line number Diff line number Diff line change
Expand Up @@ -34,7 +34,7 @@ subroutine cires_ugwp_post_run (ldiag_ugwp, dtf, im, levs, &
real(kind=kind_phys), intent(inout), dimension(:) :: tot_mtb, tot_ogw, tot_tofd, tot_ngw
real(kind=kind_phys), intent(inout), dimension(:) :: tot_zmtb, tot_zlwb, tot_zogw
real(kind=kind_phys), intent(in), dimension(:,:) :: gw_dtdt, gw_dudt, gw_dvdt, dudt_mtb, dudt_ogw, dudt_tms
real(kind=kind_phys), pointer , dimension(:,:) :: du3dt_mtb, du3dt_ogw, du3dt_tms, du3dt_ngw, dv3dt_ngw
real(kind=kind_phys), intent(inout), dimension(:,:), allocatable :: du3dt_mtb, du3dt_ogw, du3dt_tms, du3dt_ngw, dv3dt_ngw
real(kind=kind_phys), intent(inout), dimension(:,:) :: dtdt, dudt, dvdt

character(len=*), intent(out) :: errmsg
Expand Down
Loading

0 comments on commit 89cf283

Please sign in to comment.