Changeset 12675
- Timestamp:
- 2020-04-03T18:00:43+02:00 (3 years ago)
- Location:
- NEMO/branches/UKMO/NEMO_4.0.1_icesheet_and_river_coupling/src/OCE
- Files:
-
- 5 edited
Legend:
- Unmodified
- Added
- Removed
-
NEMO/branches/UKMO/NEMO_4.0.1_icesheet_and_river_coupling/src/OCE/ICB/icbclv.F90
r12576 r12675 53 53 ! 54 54 REAL(wp) :: zcalving_used, zdist, zfact 55 REAL(wp) :: zgreenland_calving_sum, zantarctica_calving_sum 55 REAL(wp), DIMENSION(1) :: zgreenland_calving_sum, zantarctica_calving_sum 56 LOGICAL :: ll_write 56 57 INTEGER :: jn, ji, jj ! loop counters 57 58 INTEGER :: imx ! temporary integer for max berg class … … 77 78 ! to preserve total freshwater conservation in coupled models without an active ice sheet model. 78 79 79 zgreenland_calving_sum = SUM( berg_grid%calving(:,:) * greenland_icesheet_mask(:,:) )80 IF( lk_mpp ) CALL mpp_sum( zgreenland_calving_sum )80 zgreenland_calving_sum(1) = SUM( berg_grid%calving(:,:) * greenland_icesheet_mask(:,:) ) 81 IF( lk_mpp ) CALL mpp_sum( 'icbclv', zgreenland_calving_sum ) 81 82 WHERE( greenland_icesheet_mask(:,:) == 1.0 ) & 82 83 & berg_grid%calving(:,:) = berg_grid%calving(:,:) * greenland_icesheet_mass_rate_of_change * rn_greenland_calving_fraction & 83 & / ( zgreenland_calving_sum + 1.0e-10_wp )84 & / ( zgreenland_calving_sum(1) + 1.0e-10_wp ) 84 85 85 86 ! check 86 IF(ll_write) WRITE(numout, *) 'Greenland iceberg calving climatology (kg/s) : ',zgreenland_calving_sum 87 zgreenland_calving_sum = SUM( berg_grid%calving(:,:) * greenland_icesheet_mask(:,:) )88 IF( lk_mpp ) CALL mpp_sum( zgreenland_calving_sum )89 IF(ll_write) WRITE(numout, *) 'Greenland iceberg calving adjusted value (kg/s) : ',zgreenland_calving_sum 90 91 zantarctica_calving_sum = SUM( berg_grid%calving(:,:) * antarctica_icesheet_mask(:,:) )92 IF( lk_mpp ) CALL mpp_sum( zantarctica_calving_sum )87 IF(ll_write) WRITE(numout, *) 'Greenland iceberg calving climatology (kg/s) : ',zgreenland_calving_sum(1) 88 zgreenland_calving_sum(1) = SUM( berg_grid%calving(:,:) * greenland_icesheet_mask(:,:) ) 89 IF( lk_mpp ) CALL mpp_sum( 'icbclv', zgreenland_calving_sum ) 90 IF(ll_write) WRITE(numout, *) 'Greenland iceberg calving adjusted value (kg/s) : ',zgreenland_calving_sum(1) 91 92 zantarctica_calving_sum(1) = SUM( berg_grid%calving(:,:) * antarctica_icesheet_mask(:,:) ) 93 IF( lk_mpp ) CALL mpp_sum( 'icbclv', zantarctica_calving_sum ) 93 94 WHERE( antarctica_icesheet_mask(:,:) == 1.0 ) & 94 95 berg_grid%calving(:,:) = berg_grid%calving(:,:) * antarctica_icesheet_mass_rate_of_change * rn_antarctica_calving_fraction & 95 & / ( zantarctica_calving_sum + 1.0e-10_wp )96 & / ( zantarctica_calving_sum(1) + 1.0e-10_wp ) 96 97 97 98 ! check 98 IF(ll_write) WRITE(numout, *) 'Antarctica iceberg calving climatology (kg/s) : ',zantarctica_calving_sum 99 zantarctica_calving_sum = SUM( berg_grid%calving(:,:) * antarctica_icesheet_mask(:,:) )100 IF( lk_mpp ) CALL mpp_sum( zantarctica_calving_sum )101 IF(ll_write) WRITE(numout, *) 'Antarctica iceberg calving adjusted value (kg/s) : ',zantarctica_calving_sum 99 IF(ll_write) WRITE(numout, *) 'Antarctica iceberg calving climatology (kg/s) : ',zantarctica_calving_sum(1) 100 zantarctica_calving_sum(1) = SUM( berg_grid%calving(:,:) * antarctica_icesheet_mask(:,:) ) 101 IF( lk_mpp ) CALL mpp_sum( 'icbclv', zantarctica_calving_sum ) 102 IF(ll_write) WRITE(numout, *) 'Antarctica iceberg calving adjusted value (kg/s) : ',zantarctica_calving_sum(1) 102 103 103 104 ENDIF -
NEMO/branches/UKMO/NEMO_4.0.1_icesheet_and_river_coupling/src/OCE/SBC/cpl_oasis3.F90
r12580 r12675 33 33 USE in_out_manager ! I/O manager 34 34 USE lbclnk ! ocean lateral boundary conditions (or mpp link) 35 USE lib_mpp 35 36 36 37 IMPLICIT NONE … … 52 53 PUBLIC cpl_finalize 53 54 55 #if defined key_mpp_mpi 56 INCLUDE 'mpif.h' 57 #endif 58 59 INTEGER, PARAMETER :: localRoot = 0 54 60 INTEGER, PUBLIC :: OASIS_Rcv = 1 !: return code if received field 55 61 INTEGER, PUBLIC :: OASIS_idle = 0 !: return code if nothing done by oasis … … 115 121 CHARACTER(len = *), INTENT(in ) :: cd_modname ! model name as set in namcouple file 116 122 INTEGER , INTENT( out) :: kl_comm ! local communicator of the model 123 INTEGER :: error 117 124 !!-------------------------------------------------------------------- 118 125 … … 627 634 WRITE(numout,*) ' - Start of data is ', pdata(1:number_to_print) 628 635 WRITE(numout,*) '****************' 629 IF(lflush) CALL flush(numout)630 636 ENDIF 631 637 … … 635 641 636 642 ENDDO 637 643 644 #if defined key_mpp_mpi 638 645 ! Set the precision that we want to broadcast using MPI_BCAST 639 646 SELECT CASE( wp ) … … 651 658 ! to deal with that w/o NEMO adopting a UM-style test mechanism 652 659 ! to determine active put/get timesteps. 653 CALL mpi_bcast( pdata, nitems, MPI_WORKING_PRECISION, localRoot, mpi_comm_opa, ierr ) 660 CALL mpi_bcast( pdata, nitems, MPI_WORKING_PRECISION, localRoot, mpi_comm_oce, ierr ) 661 #else 662 CALL oasis_abort( ncomp_id, "cpl_rcv_1d", "Unable to use mpi_bcast without key_mpp_mpi present. Please add key_mpp_mpi to your list of NEMO keys." ) 663 #endif 654 664 655 665 ! -
NEMO/branches/UKMO/NEMO_4.0.1_icesheet_and_river_coupling/src/OCE/SBC/cpl_rnf_1d.F90
r12580 r12675 19 19 USE lib_mpp ! MPP library 20 20 USE iom 21 USE wrk_nemo ! Memory allocation22 21 USE dom_oce ! Domain sizes (for grid box area e1e2t) 23 22 USE sbc_oce ! Surface boundary condition: ocean fields … … 31 30 32 31 TYPE, PUBLIC :: RIVERS_DATA !: Storage for river outflow data 33 INTEGER, POINTER, DIMENSION(:,:) :: river_number !: River outflow number34 REAL(wp), POINTER, DIMENSION(:) :: river_area ! 1D array listing areas of each river outflow (m2)35 COMPLEX(wp), POINTER, DIMENSION(:) :: river_area_c ! Comlex version of river_area for use in bit reproducible sums (m2)32 INTEGER, ALLOCATABLE, DIMENSION(:,:) :: river_number !: River outflow number 33 REAL(wp), ALLOCATABLE, DIMENSION(:) :: river_area ! 1D array listing areas of each river outflow (m2) 34 COMPLEX(wp), ALLOCATABLE, DIMENSION(:) :: river_area_c ! Comlex version of river_area for use in bit reproducible sums (m2) 36 35 END TYPE RIVERS_DATA 37 36 … … 60 59 INTEGER :: ii, jj, rr !: Loop indices 61 60 INTEGER :: max_river 62 REAL(wp), POINTER, DIMENSION(:,:):: river_number ! 2D array containing the river outflow numbers61 REAL(wp), DIMENSION(jpi,jpj) :: river_number ! 2D array containing the river outflow numbers 63 62 64 63 NAMELIST/nam_cpl_rnf_1d/file_riv_number, nn_cpl_river, ln_print_river_info 65 64 !!---------------------------------------------------------------------- 66 65 67 IF( nn_timing == 1) CALL timing_start('cpl_rnf_1d_init')66 IF( ln_timing ) CALL timing_start('cpl_rnf_1d_init') 68 67 69 68 IF(lwp) WRITE(numout,*) 70 69 IF(lwp) WRITE(numout,*) 'cpl_rnf_1d_init : initialization of river runoff coupling' 71 70 IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~' 72 IF(lwp .AND. lflush) CALL flush(numout)71 IF(lwp) CALL flush(numout) 73 72 74 73 REWIND(numnam_cfg) … … 76 75 ! Read the namelist 77 76 READ ( numnam_ref, nam_cpl_rnf_1d, IOSTAT = ios, ERR = 901) 78 901 IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_cpl_rnf_1d in reference namelist' , lwp)77 901 IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_cpl_rnf_1d in reference namelist' ) 79 78 READ ( numnam_cfg, nam_cpl_rnf_1d, IOSTAT = ios, ERR = 902 ) 80 902 IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_cpl_rnf_1d in configuration namelist' , lwp)79 902 IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_cpl_rnf_1d in configuration namelist' ) 81 80 IF(lwm .AND. nprint > 2) WRITE ( numond, nam_cpl_rnf_1d ) 82 81 … … 88 87 IF(lwp) WRITE(numout,*) ' Print river information = ',ln_print_river_info 89 88 IF(lwp) WRITE(numout,*) ' ' 90 IF(lwp .AND. lflush) CALL flush(numout)91 89 IF(lwp) CALL flush(numout) 90 92 91 ! Assign space for river numbers 93 92 ALLOCATE( rivers%river_number( jpi, jpj ) ) 94 CALL wrk_alloc( jpi, jpj, river_number )95 93 96 94 ! Read the river numbers from netcdf file … … 113 111 IF ( ln_print_river_info .AND. lwp) THEN 114 112 WRITE(numout,*) 'Maximum river number in input file = ',max_river 115 IF(lflush)CALL flush(numout)113 CALL flush(numout) 116 114 END IF 117 115 … … 132 130 133 131 ! Use mpp_sum to add together river areas on other processors 134 CALL mpp_sum( rivers%river_area_c, nn_cpl_river)132 CALL mpp_sum( 'cpl_rnf_1d', rivers%river_area_c ) 135 133 136 134 ! Convert from complex number to real … … 142 140 IF ( ln_print_river_info .AND. lwp) THEN 143 141 WRITE(numout,*) 'Area of rivers 1 to 10 are ',rivers%river_area(1:10) 144 IF(lflush)CALL flush(numout)142 CALL flush(numout) 145 143 END IF 146 144 -
NEMO/branches/UKMO/NEMO_4.0.1_icesheet_and_river_coupling/src/OCE/SBC/sbccpl.F90
r12580 r12675 262 262 & sn_rcv_icb , sn_rcv_isf , sn_rcv_wfreq , sn_rcv_tauw, nn_cats_cpl , & 263 263 & sn_rcv_ts_ice, sn_rcv_grnm , sn_rcv_antm , & 264 & nn_coupled_iceshelf_fluxes , ln_iceshelf_init_atmos 264 & nn_coupled_iceshelf_fluxes , ln_iceshelf_init_atmos , & 265 265 & rn_greenland_total_fw_flux , rn_greenland_calving_fraction , & 266 266 & rn_antarctica_total_fw_flux , rn_antarctica_calving_fraction , & … … 1185 1185 INTEGER :: ji, jj, jn ! dummy loop indices 1186 1186 INTEGER :: isec ! number of seconds since nit000 (assuming rdt did not change since nit000) 1187 REAL(wp) :: zcumulneg, zcumulpos ! temporary scalars 1187 REAL(wp) :: zcumulneg, zcumulpos ! temporary scalars 1188 REAL(wp) :: zcoef ! temporary scalar 1189 LOGICAL :: ll_wrtstp ! write diagnostics? 1190 REAL(wp) :: zrhoa = 1.22 ! Air density kg/m3 1191 REAL(wp) :: zcdrag = 1.5e-3 ! drag coefficient 1188 1192 REAL(wp) :: zgreenland_icesheet_mass_in, zantarctica_icesheet_mass_in 1189 1193 REAL(wp) :: zgreenland_icesheet_mass_b, zantarctica_icesheet_mass_b 1190 1194 REAL(wp) :: zmask_sum, zepsilon 1191 REAL(wp) :: zcoef ! temporary scalar1192 REAL(wp) :: zrhoa = 1.22 ! Air density kg/m31193 REAL(wp) :: zcdrag = 1.5e-3 ! drag coefficient1194 1195 REAL(wp) :: zzx, zzy ! temporary variables 1195 1196 REAL(wp), DIMENSION(jpi,jpj) :: ztx, zty, zmsk, zemp, zqns, zqsr 1196 1197 !!---------------------------------------------------------------------- 1198 ! 1199 ll_wrtstp = ( MOD( kt, sn_cfctl%ptimincr ) == 0 ) .OR. ( kt == nitend ) 1197 1200 ! 1198 1201 IF( ln_mixcpl ) zmsk(:,:) = 1. - xcplmask(:,:,0) … … 1574 1577 WRITE(numout,*) 'Greenland icesheet mass rate of change (kg/s) is ', greenland_icesheet_mass_rate_of_change 1575 1578 WRITE(numout,*) 'Greenland icesheet seconds lapsed since last change is ', greenland_icesheet_timelapsed 1576 IF(lflush) CALL flush(numout)1577 1579 ENDIF 1578 1580 ELSE IF ( nn_coupled_iceshelf_fluxes == 2 ) THEN … … 1612 1614 WRITE(numout,*) 'Antarctica icesheet mass rate of change (kg/s) is ', antarctica_icesheet_mass_rate_of_change 1613 1615 WRITE(numout,*) 'Antarctica icesheet seconds lapsed since last change is ', antarctica_icesheet_timelapsed 1614 IF(lflush) CALL flush(numout)1615 1616 ENDIF 1616 1617 ELSE IF ( nn_coupled_iceshelf_fluxes == 2 ) THEN -
NEMO/branches/UKMO/NEMO_4.0.1_icesheet_and_river_coupling/src/OCE/SBC/sbcisf.F90
r12576 r12675 96 96 REAL(wp), DIMENSION(:,:) , ALLOCATABLE :: zqhcisf2d 97 97 REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: zfwfisf3d, zqhcisf3d, zqlatisf3d 98 LOGICAL :: ll_wrtstp 98 99 !!--------------------------------------------------------------------- 99 100 ! 101 ll_wrtstp = ( MOD( kt, sn_cfctl%ptimincr ) == 0 ) .OR. ( kt == nitend ) 100 102 IF( MOD( kt-1, nn_fsbc) == 0 ) THEN ! compute salt and heat flux 101 103 ! … … 138 140 139 141 ! All related global sums must be done bit reproducibly 140 zgreenland_fwfisf_sum = glob_sum( fwfisf(:,:) * e1t(:,:) * e2t(:,:) * greenland_icesheet_mask(:,:) )142 zgreenland_fwfisf_sum = glob_sum( 'sbcisf', fwfisf(:,:) * e1t(:,:) * e2t(:,:) * greenland_icesheet_mask(:,:) ) 141 143 142 144 ! use ABS function because we need to preserve the sign of fwfisf … … 148 150 IF(lwp .AND. ll_wrtstp) WRITE(numout, *) 'Greenland iceshelf melting climatology (kg/s) : ',zgreenland_fwfisf_sum 149 151 150 zgreenland_fwfisf_sum = glob_sum( fwfisf(:,:) * e1t(:,:) * e2t(:,:) * greenland_icesheet_mask(:,:) )152 zgreenland_fwfisf_sum = glob_sum( 'sbcisf', fwfisf(:,:) * e1t(:,:) * e2t(:,:) * greenland_icesheet_mask(:,:) ) 151 153 152 154 IF(lwp .AND. ll_wrtstp) WRITE(numout, *) 'Greenland iceshelf melting adjusted value (kg/s) : ',zgreenland_fwfisf_sum 153 155 154 zantarctica_fwfisf_sum = glob_sum( fwfisf(:,:) * e1t(:,:) * e2t(:,:) * antarctica_icesheet_mask(:,:) )156 zantarctica_fwfisf_sum = glob_sum( 'sbcisf', fwfisf(:,:) * e1t(:,:) * e2t(:,:) * antarctica_icesheet_mask(:,:) ) 155 157 156 158 ! use ABS function because we need to preserve the sign of fwfisf … … 162 164 IF(lwp .AND. ll_wrtstp) WRITE(numout, *) 'Antarctica iceshelf melting climatology (kg/s) : ',zantarctica_fwfisf_sum 163 165 164 zantarctica_fwfisf_sum = glob_sum( fwfisf(:,:) * e1t(:,:) * e2t(:,:) * antarctica_icesheet_mask(:,:) )166 zantarctica_fwfisf_sum = glob_sum( 'sbcisf', fwfisf(:,:) * e1t(:,:) * e2t(:,:) * antarctica_icesheet_mask(:,:) ) 165 167 166 168 IF(lwp .AND. ll_wrtstp) WRITE(numout, *) 'Antarctica iceshelf melting adjusted value (kg/s) : ',zantarctica_fwfisf_sum … … 189 191 190 192 ! All related global sums must be done bit reproducibly 191 zgreenland_fwfisf_sum = glob_sum( fwfisf(:,:) * e1t(:,:) * e2t(:,:) * greenland_icesheet_mask(:,:) )193 zgreenland_fwfisf_sum = glob_sum( 'sbcisf', fwfisf(:,:) * e1t(:,:) * e2t(:,:) * greenland_icesheet_mask(:,:) ) 192 194 193 195 ! use ABS function because we need to preserve the sign of fwfisf … … 199 201 IF(lwp .AND. ll_wrtstp) WRITE(numout, *) 'Greenland iceshelf melting climatology (kg/s) : ',zgreenland_fwfisf_sum 200 202 201 zgreenland_fwfisf_sum = glob_sum( fwfisf(:,:) * e1t(:,:) * e2t(:,:) * greenland_icesheet_mask(:,:) )203 zgreenland_fwfisf_sum = glob_sum( 'sbcisf', fwfisf(:,:) * e1t(:,:) * e2t(:,:) * greenland_icesheet_mask(:,:) ) 202 204 203 205 IF(lwp .AND. ll_wrtstp) WRITE(numout, *) 'Greenland iceshelf melting adjusted value (kg/s) : ',zgreenland_fwfisf_sum 204 206 205 zantarctica_fwfisf_sum = glob_sum( fwfisf(:,:) * e1t(:,:) * e2t(:,:) * antarctica_icesheet_mask(:,:) )207 zantarctica_fwfisf_sum = glob_sum( 'sbcisf', fwfisf(:,:) * e1t(:,:) * e2t(:,:) * antarctica_icesheet_mask(:,:) ) 206 208 207 209 ! use ABS function because we need to preserve the sign of fwfisf … … 213 215 IF(lwp .AND. ll_wrtstp) WRITE(numout, *) 'Antarctica iceshelf melting climatology (kg/s) : ',zantarctica_fwfisf_sum 214 216 215 zantarctica_fwfisf_sum = glob_sum( fwfisf(:,:) * e1t(:,:) * e2t(:,:) * antarctica_icesheet_mask(:,:) )217 zantarctica_fwfisf_sum = glob_sum( 'sbcisf', fwfisf(:,:) * e1t(:,:) * e2t(:,:) * antarctica_icesheet_mask(:,:) ) 216 218 217 219 IF(lwp .AND. ll_wrtstp) WRITE(numout, *) 'Antarctica iceshelf melting adjusted value (kg/s) : ',zantarctica_fwfisf_sum
Note: See TracChangeset
for help on using the changeset viewer.