New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
Changeset 12576 for NEMO – NEMO

Changeset 12576 for NEMO


Ignore:
Timestamp:
2020-03-20T12:39:37+01:00 (4 years ago)
Author:
dancopsey
Message:

Merge in iceberg calving stuff from dev_r5518_coupling_GSI7_GSI8_landice from the start of the branch to revision 6023.

Location:
NEMO/branches/UKMO/NEMO_4.0.1_icesheet_and_river_coupling
Files:
7 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/UKMO/NEMO_4.0.1_icesheet_and_river_coupling/cfgs/SHARED/field_def_nemo-oce.xml

    r11536 r12576  
    264264 
    265265          <!-- * variable related to ice shelf forcing * --> 
     266          <field id="berg_calve"   long_name="Iceberg calving"                               unit="kg/m2/s"  />  
    266267          <field id="fwfisf"       long_name="Ice shelf melting"                             unit="kg/m2/s"  /> 
    267268          <field id="fwfisf3d"     long_name="Ice shelf melting"                             unit="kg/m2/s"  grid_ref="grid_T_3D" /> 
  • NEMO/branches/UKMO/NEMO_4.0.1_icesheet_and_river_coupling/cfgs/SHARED/namelist_ref

    r11715 r12576  
    290290   !                       !   -> file cplmask.nc with the float variable called cplmask (jpi,jpj,nn_cplmodel) 
    291291   nn_cats_cpl   =     5   !  Number of sea ice categories over which coupling is to be carried out (if not 1) 
     292   nn_coupled_iceshelf_fluxes = 0 ! =0 : total freshwater input from iceberg calving and ice shelf basal melting  
     293                                  ! taken from climatologies used (no action in coupling routines). 
     294                                  ! =1 :  use rate of change of mass of Greenland and Antarctic icesheets to set the  
     295                                  ! combined magnitude of the iceberg calving and iceshelf melting freshwater fluxes. 
     296                                  ! =2 :  specify constant freshwater inputs in this namelist to set the combined 
     297                                  ! magnitude of iceberg calving and iceshelf melting freshwater fluxes. 
     298   ln_iceshelf_init_atmos     = .true.  ! If true force ocean to initialise icesheet masses from atmospheric values rather than 
     299                                        ! from values in ocean restart file.  
     300   rn_greenland_total_fw_flux   = 0.0  ! Constant total rate of freshwater input (kg/s) for Greenland (if nn_coupled_iceshelf_fluxes=2)  
     301   rn_greenland_calving_fraction = 0.5  ! Set fraction of total freshwater flux for iceberg calving - remainder goes to iceshelf melting. 
     302   rn_antarctica_total_fw_flux  = 0.0  ! Constant total rate of freshwater input (kg/s) for Antarctica (if nn_coupled_iceshelf_fluxes=2) 
     303   rn_antarctica_calving_fraction = 0.5 ! Set fraction of total freshwater flux for iceberg calving - remainder goes to iceshelf melting. 
     304   rn_iceshelf_fluxes_tolerance = 1e-6  ! Fractional threshold for detecting differences in icesheet masses (must be positive definite). 
    292305 
    293306   !_____________!__________________________!____________!_____________!______________________!________! 
  • NEMO/branches/UKMO/NEMO_4.0.1_icesheet_and_river_coupling/src/OCE/ICB/icbclv.F90

    r11715 r12576  
    2626   USE icb_oce        ! iceberg parameters  
    2727 
     28   USE sbc_oce        ! for icesheet freshwater input variables  
     29   USE in_out_manager  
     30   USE iom  
     31 
    2832   IMPLICIT NONE 
    2933   PRIVATE 
     
    4953      ! 
    5054      REAL(wp)      ::   zcalving_used, zdist, zfact 
     55      REAL(wp)      ::   zgreenland_calving_sum, zantarctica_calving_sum  
    5156      INTEGER       ::   jn, ji, jj                    ! loop counters 
    5257      INTEGER       ::   imx                           ! temporary integer for max berg class 
     
    6368      ! Heat in units of W/m2, and mask (just in case) 
    6469      berg_grid%calving_hflx(:,:) = src_calving_hflx(:,:) * tmask_i(:,:) * tmask(:,:,1) 
     70 
     71      IF( lk_oasis) THEN 
     72        ! nn_coupled_iceshelf_fluxes uninitialised unless lk_oasis=true 
     73        IF( nn_coupled_iceshelf_fluxes .gt. 0 ) THEN 
     74          ll_write = ((MOD( kt, sn_cfctl%ptimincr ) == 0) .OR. ( kt == nitend )) .AND. lwp 
     75          ! Adjust total calving rates so that sum of iceberg calving and iceshelf melting in the northern 
     76          ! and southern hemispheres equals rate of increase of mass of greenland and antarctic ice sheets 
     77          ! to preserve total freshwater conservation in coupled models without an active ice sheet model. 
     78 
     79           zgreenland_calving_sum = SUM( berg_grid%calving(:,:) * greenland_icesheet_mask(:,:) ) 
     80           IF( lk_mpp ) CALL mpp_sum( zgreenland_calving_sum ) 
     81           WHERE( greenland_icesheet_mask(:,:) == 1.0 )                                                                                 & 
     82          &    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 
     85           ! 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 ) 
     93           WHERE( antarctica_icesheet_mask(:,:) == 1.0 )                                                                              & 
     94           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 
     97           ! 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 
     102 
     103        ENDIF 
     104      ENDIF 
     105    
     106      CALL iom_put( 'berg_calve', berg_grid%calving(:,:) ) 
     107 
    65108 
    66109      IF( ll_first_call .AND. .NOT. l_restarted_bergs ) THEN      ! This is a hack to simplify initialization 
  • NEMO/branches/UKMO/NEMO_4.0.1_icesheet_and_river_coupling/src/OCE/IOM/restart.F90

    r11715 r12576  
    2929   USE diurnal_bulk 
    3030   USE lib_mpp         ! distribued memory computing library 
     31   USE sbc_oce         ! for icesheet freshwater input variables  
    3132 
    3233   IMPLICIT NONE 
     
    161162                     CALL iom_rstput( kt, nitrst, numrow, 'sshn'   , sshn, ldxios = lwxios      ) 
    162163                     CALL iom_rstput( kt, nitrst, numrow, 'rhop'   , rhop, ldxios = lwxios      ) 
     164 
     165                     IF( lk_oasis) THEN 
     166                     ! nn_coupled_iceshelf_fluxes uninitialised unless lk_oasis=true 
     167                       IF( nn_coupled_iceshelf_fluxes .eq. 1 ) THEN 
     168                          CALL iom_rstput( kt, nitrst, numrow, 'greenland_icesheet_mass', greenland_icesheet_mass ) 
     169                          CALL iom_rstput( kt, nitrst, numrow, 'greenland_icesheet_timelapsed', greenland_icesheet_timelapsed ) 
     170                          CALL iom_rstput( kt, nitrst, numrow, 'greenland_icesheet_mass_roc', greenland_icesheet_mass_rate_of_change ) 
     171                          CALL iom_rstput( kt, nitrst, numrow, 'antarctica_icesheet_mass', antarctica_icesheet_mass ) 
     172                          CALL iom_rstput( kt, nitrst, numrow, 'antarctica_icesheet_timelapsed', antarctica_icesheet_timelapsed ) 
     173                          CALL iom_rstput( kt, nitrst, numrow, 'antarctica_icesheet_mass_roc', antarctica_icesheet_mass_rate_of_change ) 
     174                       ENDIF 
     175                     ENDIF 
    163176                  ! extra variable needed for the ice sheet coupling 
    164177                  IF ( ln_iscpl ) THEN  
     
    295308      ENDIF 
    296309      ! 
     310      IF( iom_varid( numror, 'greenland_icesheet_mass', ldstop = .FALSE. ) > 0 )   THEN 
     311         CALL iom_get( numror, 'greenland_icesheet_mass', greenland_icesheet_mass ) 
     312         CALL iom_get( numror, 'greenland_icesheet_timelapsed', greenland_icesheet_timelapsed ) 
     313         CALL iom_get( numror, 'greenland_icesheet_mass_roc', greenland_icesheet_mass_rate_of_change ) 
     314      ELSE 
     315         greenland_icesheet_mass = 0.0  
     316         greenland_icesheet_mass_rate_of_change = 0.0  
     317         greenland_icesheet_timelapsed = 0.0 
     318      ENDIF 
     319      IF( iom_varid( numror, 'antarctica_icesheet_mass', ldstop = .FALSE. ) > 0 )   THEN 
     320         CALL iom_get( numror, 'antarctica_icesheet_mass', antarctica_icesheet_mass ) 
     321         CALL iom_get( numror, 'antarctica_icesheet_timelapsed', antarctica_icesheet_timelapsed ) 
     322         CALL iom_get( numror, 'antarctica_icesheet_mass_roc', antarctica_icesheet_mass_rate_of_change ) 
     323      ELSE 
     324         antarctica_icesheet_mass = 0.0  
     325         antarctica_icesheet_mass_rate_of_change = 0.0  
     326         antarctica_icesheet_timelapsed = 0.0 
     327      ENDIF 
     328      ! 
    297329      IF( neuler == 0 ) THEN                                  ! Euler restart (neuler=0) 
    298330         tsb  (:,:,:,:) = tsn  (:,:,:,:)                             ! all before fields set to now values 
  • NEMO/branches/UKMO/NEMO_4.0.1_icesheet_and_river_coupling/src/OCE/SBC/sbc_oce.F90

    r11715 r12576  
    136136   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   atm_co2           !: atmospheric pCO2                             [ppm] 
    137137   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: xcplmask          !: coupling mask for ln_mixcpl (warning: allocated in sbccpl) 
     138   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   greenland_icesheet_mass_array, greenland_icesheet_mask  
     139   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   antarctica_icesheet_mass_array, antarctica_icesheet_mask  
    138140 
    139141   !!---------------------------------------------------------------------- 
     
    149151   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   frq_m     !: mean (nn_fsbc time-step) fraction of solar net radiation absorbed in the 1st T level [-] 
    150152 
     153   !!---------------------------------------------------------------------- 
     154   !!  Surface scalars of total ice sheet mass for Greenland and Antarctica,  
     155   !! passed from atmosphere to be converted to dvol and hence a freshwater  
     156   !! flux  by using old values. New values are saved in the dump, to become 
     157   !! old values next coupling timestep. Freshwater fluxes split between  
     158   !! sub iceshelf melting and iceberg calving, scalled to flux per second 
     159   !!---------------------------------------------------------------------- 
     160    
     161   REAL(wp), PUBLIC  :: greenland_icesheet_mass, greenland_icesheet_mass_rate_of_change, greenland_icesheet_timelapsed  
     162   REAL(wp), PUBLIC  :: antarctica_icesheet_mass, antarctica_icesheet_mass_rate_of_change, antarctica_icesheet_timelapsed 
     163 
     164   ! sbccpl namelist parameters associated with icesheet freshwater input code. Included here rather than in sbccpl.F90 to  
     165   ! avoid circular dependencies. 
     166   INTEGER, PUBLIC     ::   nn_coupled_iceshelf_fluxes     ! =0 : total freshwater input from iceberg calving and ice shelf basal melting  
     167                                                           ! taken from climatologies used (no action in coupling routines). 
     168                                                           ! =1 :  use rate of change of mass of Greenland and Antarctic icesheets to set the  
     169                                                           ! combined magnitude of the iceberg calving and iceshelf melting freshwater fluxes. 
     170                                                           ! =2 :  specify constant freshwater inputs in this namelist to set the combined 
     171                                                           ! magnitude of iceberg calving and iceshelf melting freshwater fluxes. 
     172   LOGICAL, PUBLIC     ::   ln_iceshelf_init_atmos         ! If true force ocean to initialise iceshelf masses from atmospheric values rather 
     173                                                           ! than values in ocean restart (applicable if nn_coupled_iceshelf_fluxes=1). 
     174   REAL(wp), PUBLIC    ::   rn_greenland_total_fw_flux    ! Constant total rate of freshwater input (kg/s) for Greenland (if nn_coupled_iceshelf_fluxes=2)  
     175   REAL(wp), PUBLIC    ::   rn_greenland_calving_fraction  ! Set fraction of total freshwater flux for iceberg calving - remainder goes to iceshelf melting. 
     176   REAL(wp), PUBLIC    ::   rn_antarctica_total_fw_flux   ! Constant total rate of freshwater input (kg/s) for Antarctica (if nn_coupled_iceshelf_fluxes=2)  
     177   REAL(wp), PUBLIC    ::   rn_antarctica_calving_fraction ! Set fraction of total freshwater flux for iceberg calving - remainder goes to iceshelf melting. 
     178   REAL(wp), PUBLIC    ::   rn_iceshelf_fluxes_tolerance   ! Absolute tolerance for detecting differences in icesheet masses.  
     179 
    151180   !! * Substitutions 
    152181#  include "vectopt_loop_substitute.h90" 
     
    182211         &      ssu_m  (jpi,jpj) , sst_m(jpi,jpj) , frq_m(jpi,jpj) ,      & 
    183212         &      ssv_m  (jpi,jpj) , sss_m(jpi,jpj) , ssh_m(jpi,jpj) , STAT=ierr(4) ) 
     213         ! 
     214      ALLOCATE( greenland_icesheet_mass_array(jpi,jpj) , antarctica_icesheet_mass_array(jpi,jpj) )  
     215      ALLOCATE( greenland_icesheet_mask(jpi,jpj) , antarctica_icesheet_mask(jpi,jpj) )  
    184216         ! 
    185217      ALLOCATE( e3t_m(jpi,jpj) , STAT=ierr(5) ) 
  • NEMO/branches/UKMO/NEMO_4.0.1_icesheet_and_river_coupling/src/OCE/SBC/sbccpl.F90

    r11715 r12576  
    116116   INTEGER, PARAMETER ::   jpr_tauwy  = 56   ! y component of the ocean stress from waves 
    117117   INTEGER, PARAMETER ::   jpr_ts_ice = 57   ! Sea ice surface temp 
    118  
    119    INTEGER, PARAMETER ::   jprcv      = 57   ! total number of fields received   
     118   INTEGER, PARAMETER ::   jpr_grnm   = 58   ! Greenland ice mass  
     119   INTEGER, PARAMETER ::   jpr_antm   = 59   ! Antarctic ice mass  
     120 
     121   INTEGER, PARAMETER ::   jprcv      = 59   ! total number of fields received   
    120122 
    121123   INTEGER, PARAMETER ::   jps_fice   =  1   ! ice fraction sent to the atmosphere 
     
    174176   TYPE(FLD_C) ::   sn_rcv_w10m, sn_rcv_taumod, sn_rcv_tau, sn_rcv_tauw, sn_rcv_dqnsdt, sn_rcv_qsr,  & 
    175177      &             sn_rcv_qns , sn_rcv_emp   , sn_rcv_rnf, sn_rcv_ts_ice 
    176    TYPE(FLD_C) ::   sn_rcv_cal, sn_rcv_iceflx, sn_rcv_co2, sn_rcv_mslp, sn_rcv_icb, sn_rcv_isf 
     178   TYPE(FLD_C) ::   sn_rcv_cal, sn_rcv_iceflx, sn_rcv_co2, sn_rcv_mslp, sn_rcv_icb, sn_rcv_isf,      & 
     179                    sn_rcv_grnm, sn_rcv_antm 
    177180   ! Send to waves  
    178181   TYPE(FLD_C) ::   sn_snd_ifrac, sn_snd_crtw, sn_snd_wlev  
     
    256259         &                  sn_rcv_iceflx, sn_rcv_co2   , nn_cplmodel , ln_usecplmask, sn_rcv_mslp ,   & 
    257260         &                  sn_rcv_icb   , sn_rcv_isf   , sn_rcv_wfreq , sn_rcv_tauw, nn_cats_cpl  ,   & 
    258          &                  sn_rcv_ts_ice 
     261         &                  sn_rcv_ts_ice, sn_rcv_grnm  , sn_rcv_antm  , nn_coupled_iceshelf_fluxes,   & 
     262         &                  rn_greenland_calving_fraction, rn_antarctica_calving_fraction,             & 
     263         &                  rn_iceshelf_fluxes_tolerance 
    259264 
    260265      !!--------------------------------------------------------------------- 
     
    292297         WRITE(numout,*)'      runoffs                         = ', TRIM(sn_rcv_rnf%cldes   ), ' (', TRIM(sn_rcv_rnf%clcat   ), ')' 
    293298         WRITE(numout,*)'      calving                         = ', TRIM(sn_rcv_cal%cldes   ), ' (', TRIM(sn_rcv_cal%clcat   ), ')' 
     299         WRITE(numout,*)'      Greenland ice mass              = ', TRIM(sn_rcv_grnm%cldes  ), ' (', TRIM(sn_rcv_grnm%clcat  ), ')'  
     300         WRITE(numout,*)'      Antarctica ice mass             = ', TRIM(sn_rcv_antm%cldes  ), ' (', TRIM(sn_rcv_antm%clcat  ), ')'  
    294301         WRITE(numout,*)'      iceberg                         = ', TRIM(sn_rcv_icb%cldes   ), ' (', TRIM(sn_rcv_icb%clcat   ), ')' 
    295302         WRITE(numout,*)'      ice shelf                       = ', TRIM(sn_rcv_isf%cldes   ), ' (', TRIM(sn_rcv_isf%clcat   ), ')' 
     
    330337         WRITE(numout,*)'  ln_usecplmask                       = ', ln_usecplmask 
    331338         WRITE(numout,*)'  nn_cats_cpl                         = ', nn_cats_cpl 
     339         WRITE(numout,*)'  nn_coupled_iceshelf_fluxes          = ', nn_coupled_iceshelf_fluxes  
     340         WRITE(numout,*)'  ln_iceshelf_init_atmos              = ', ln_iceshelf_init_atmos 
     341         WRITE(numout,*)'  rn_greenland_total_fw_flux         = ', rn_greenland_total_fw_flux 
     342         WRITE(numout,*)'  rn_antarctica_total_fw_flux        = ', rn_antarctica_total_fw_flux 
     343         WRITE(numout,*)'  rn_greenland_calving_fraction       = ', rn_greenland_calving_fraction  
     344         WRITE(numout,*)'  rn_antarctica_calving_fraction      = ', rn_antarctica_calving_fraction  
     345         WRITE(numout,*)'  rn_iceshelf_fluxes_tolerance        = ', rn_iceshelf_fluxes_tolerance  
    332346      ENDIF 
    333347 
     
    471485      ! 
    472486      srcv(jpr_cal)%clname = 'OCalving'   ;  IF( TRIM( sn_rcv_cal%cldes) == 'coupled' )   srcv(jpr_cal)%laction = .TRUE. 
     487      srcv(jpr_grnm  )%clname = 'OGrnmass'   ;   IF( TRIM( sn_rcv_grnm%cldes ) == 'coupled' )   srcv(jpr_grnm)%laction = .TRUE.  
     488      srcv(jpr_antm  )%clname = 'OAntmass'   ;   IF( TRIM( sn_rcv_antm%cldes ) == 'coupled' )   srcv(jpr_antm)%laction = .TRUE.  
    473489      srcv(jpr_isf)%clname = 'OIcshelf'   ;  IF( TRIM( sn_rcv_isf%cldes) == 'coupled' )   srcv(jpr_isf)%laction = .TRUE. 
    474490      srcv(jpr_icb)%clname = 'OIceberg'   ;  IF( TRIM( sn_rcv_icb%cldes) == 'coupled' )   srcv(jpr_icb)%laction = .TRUE. 
     
    10451061         &   CALL ctl_stop( 'sbc_cpl_init: diurnal cycle reconstruction (ln_dm2dc) needs daily couping for solar radiation' ) 
    10461062      IF( ln_dm2dc .AND. ln_cpl ) ncpl_qsr_freq = 86400 / ncpl_qsr_freq 
     1063 
     1064      IF( nn_coupled_iceshelf_fluxes .gt. 0 ) THEN  
     1065          ! Crude masks to separate the Antarctic and Greenland icesheets. Obviously something  
     1066          ! more complicated could be done if required.  
     1067          greenland_icesheet_mask = 0.0  
     1068          WHERE( gphit >= 0.0 ) greenland_icesheet_mask = 1.0  
     1069          antarctica_icesheet_mask = 0.0  
     1070          WHERE( gphit < 0.0 ) antarctica_icesheet_mask = 1.0  
     1071  
     1072          ! initialise other variables  
     1073          greenland_icesheet_mass_array(:,:) = 0.0  
     1074          antarctica_icesheet_mass_array(:,:) = 0.0  
     1075  
     1076          IF( .not. ln_rstart ) THEN  
     1077             greenland_icesheet_mass = 0.0   
     1078             greenland_icesheet_mass_rate_of_change = 0.0   
     1079             greenland_icesheet_timelapsed = 0.0  
     1080             antarctica_icesheet_mass = 0.0   
     1081             antarctica_icesheet_mass_rate_of_change = 0.0   
     1082             antarctica_icesheet_timelapsed = 0.0  
     1083          ENDIF  
     1084  
     1085      ENDIF  
    10471086      ! 
    10481087   END SUBROUTINE sbc_cpl_init 
     
    11031142      INTEGER  ::   ji, jj, jn             ! dummy loop indices 
    11041143      INTEGER  ::   isec                   ! number of seconds since nit000 (assuming rdt did not change since nit000) 
    1105       REAL(wp) ::   zcumulneg, zcumulpos   ! temporary scalars      
     1144      REAL(wp) ::   zcumulneg, zcumulpos   ! temporary scalars   
     1145      REAL(wp) ::   zgreenland_icesheet_mass_in, zantarctica_icesheet_mass_in  
     1146      REAL(wp) ::   zgreenland_icesheet_mass_b, zantarctica_icesheet_mass_b  
     1147      REAL(wp) ::   zmask_sum, zepsilon     
    11061148      REAL(wp) ::   zcoef                  ! temporary scalar 
    11071149      REAL(wp) ::   zrhoa  = 1.22          ! Air density kg/m3 
     
    14451487         IF( srcv(jpr_fice )%laction )   fr_i(:,:) = frcv(jpr_fice )%z3(:,:,1) 
    14461488         ! 
     1489      ENDIF 
     1490 
     1491      !                                                        ! land ice masses : Greenland 
     1492      zepsilon = rn_iceshelf_fluxes_tolerance 
     1493 
     1494      IF( srcv(jpr_grnm)%laction .AND. nn_coupled_iceshelf_fluxes == 1 ) THEN 
     1495       
     1496         ! This is a zero dimensional, single value field.  
     1497         zgreenland_icesheet_mass_in =  frcv(jpr_grnm)%z3(1,1,1) 
     1498            
     1499         greenland_icesheet_timelapsed = greenland_icesheet_timelapsed + rdt          
     1500 
     1501         IF( ln_iceshelf_init_atmos .AND. kt == 1 ) THEN 
     1502            ! On the first timestep (of an NRUN) force the ocean to ignore the icesheet masses in the ocean restart 
     1503            ! and take them from the atmosphere to avoid problems with using inconsistent ocean and atmosphere restarts. 
     1504            zgreenland_icesheet_mass_b = zgreenland_icesheet_mass_in 
     1505            greenland_icesheet_mass = zgreenland_icesheet_mass_in 
     1506         ENDIF 
     1507 
     1508         IF( ABS( zgreenland_icesheet_mass_in - greenland_icesheet_mass ) > zepsilon ) THEN 
     1509            zgreenland_icesheet_mass_b = greenland_icesheet_mass 
     1510             
     1511            ! Only update the mass if it has increased. 
     1512            IF ( (zgreenland_icesheet_mass_in - greenland_icesheet_mass) > 0.0 ) THEN 
     1513               greenland_icesheet_mass = zgreenland_icesheet_mass_in 
     1514            ENDIF 
     1515             
     1516            IF( zgreenland_icesheet_mass_b /= 0.0 ) & 
     1517           &     greenland_icesheet_mass_rate_of_change = ( greenland_icesheet_mass - zgreenland_icesheet_mass_b ) / greenland_icesheet_timelapsed  
     1518            greenland_icesheet_timelapsed = 0.0_wp        
     1519         ENDIF 
     1520         IF(lwp .AND. ll_wrtstp) THEN 
     1521            WRITE(numout,*) 'Greenland icesheet mass (kg) read in is ', zgreenland_icesheet_mass_in 
     1522            WRITE(numout,*) 'Greenland icesheet mass (kg) used is    ', greenland_icesheet_mass 
     1523            WRITE(numout,*) 'Greenland icesheet mass rate of change (kg/s) is ', greenland_icesheet_mass_rate_of_change 
     1524            WRITE(numout,*) 'Greenland icesheet seconds lapsed since last change is ', greenland_icesheet_timelapsed 
     1525            IF(lflush) CALL flush(numout) 
     1526         ENDIF 
     1527      ELSE IF ( nn_coupled_iceshelf_fluxes == 2 ) THEN 
     1528         greenland_icesheet_mass_rate_of_change = rn_greenland_total_fw_flux 
     1529      ENDIF 
     1530 
     1531      !                                                        ! land ice masses : Antarctica 
     1532      IF( srcv(jpr_antm)%laction .AND. nn_coupled_iceshelf_fluxes == 1 ) THEN 
     1533          
     1534         ! This is a zero dimensional, single value field.  
     1535         zantarctica_icesheet_mass_in = frcv(jpr_antm)%z3(1,1,1) 
     1536            
     1537         antarctica_icesheet_timelapsed = antarctica_icesheet_timelapsed + rdt          
     1538 
     1539         IF( ln_iceshelf_init_atmos .AND. kt == 1 ) THEN 
     1540            ! On the first timestep (of an NRUN) force the ocean to ignore the icesheet masses in the ocean restart 
     1541            ! and take them from the atmosphere to avoid problems with using inconsistent ocean and atmosphere restarts. 
     1542            zantarctica_icesheet_mass_b = zantarctica_icesheet_mass_in 
     1543            antarctica_icesheet_mass = zantarctica_icesheet_mass_in 
     1544         ENDIF 
     1545 
     1546         IF( ABS( zantarctica_icesheet_mass_in - antarctica_icesheet_mass ) > zepsilon ) THEN 
     1547            zantarctica_icesheet_mass_b = antarctica_icesheet_mass 
     1548             
     1549            ! Only update the mass if it has increased. 
     1550            IF ( (zantarctica_icesheet_mass_in - antarctica_icesheet_mass) > 0.0 ) THEN 
     1551               antarctica_icesheet_mass = zantarctica_icesheet_mass_in 
     1552            END IF 
     1553             
     1554            IF( zantarctica_icesheet_mass_b /= 0.0 ) & 
     1555          &      antarctica_icesheet_mass_rate_of_change = ( antarctica_icesheet_mass - zantarctica_icesheet_mass_b ) / antarctica_icesheet_timelapsed  
     1556            antarctica_icesheet_timelapsed = 0.0_wp        
     1557         ENDIF 
     1558         IF(lwp .AND. ll_wrtstp) THEN 
     1559            WRITE(numout,*) 'Antarctica icesheet mass (kg) read in is ', zantarctica_icesheet_mass_in 
     1560            WRITE(numout,*) 'Antarctica icesheet mass (kg) used is    ', antarctica_icesheet_mass 
     1561            WRITE(numout,*) 'Antarctica icesheet mass rate of change (kg/s) is ', antarctica_icesheet_mass_rate_of_change 
     1562            WRITE(numout,*) 'Antarctica icesheet seconds lapsed since last change is ', antarctica_icesheet_timelapsed 
     1563            IF(lflush) CALL flush(numout) 
     1564         ENDIF 
     1565      ELSE IF ( nn_coupled_iceshelf_fluxes == 2 ) THEN 
     1566         antarctica_icesheet_mass_rate_of_change = rn_antarctica_total_fw_flux 
    14471567      ENDIF 
    14481568      ! 
  • NEMO/branches/UKMO/NEMO_4.0.1_icesheet_and_river_coupling/src/OCE/SBC/sbcisf.F90

    r11715 r12576  
    9292      INTEGER ::   ji, jj, jk   ! loop index 
    9393      INTEGER ::   ikt, ikb     ! local integers 
     94      REAL(wp)                     ::   zgreenland_fwfisf_sum, zantarctica_fwfisf_sum  
    9495      REAL(wp), DIMENSION(jpi,jpj) ::   zt_frz, zdep   ! freezing temperature (zt_frz) at depth (zdep)  
    9596      REAL(wp), DIMENSION(:,:)  , ALLOCATABLE ::   zqhcisf2d 
     
    127128               fwfisf(:,:) = - sf_rnfisf(1)%fnow(:,:,1)         ! fresh water flux from the isf (fwfisf <0 mean melting)  
    128129            ENDIF 
     130 
     131            IF( lk_oasis) THEN 
     132              ! nn_coupled_iceshelf_fluxes uninitialised unless lk_oasis=true 
     133              IF( nn_coupled_iceshelf_fluxes .gt. 0 ) THEN 
     134 
     135                ! Adjust total iceshelf melt rates so that sum of iceberg calving and iceshelf melting in the northern 
     136                ! and southern hemispheres equals rate of increase of mass of greenland and antarctic ice sheets 
     137                ! to preserve total freshwater conservation in coupled models without an active ice sheet model. 
     138 
     139                ! All related global sums must be done bit reproducibly 
     140                 zgreenland_fwfisf_sum = glob_sum( fwfisf(:,:) * e1t(:,:) * e2t(:,:) * greenland_icesheet_mask(:,:) ) 
     141 
     142                 ! use ABS function because we need to preserve the sign of fwfisf 
     143                 WHERE( greenland_icesheet_mask(:,:) == 1.0 )                                                                  & 
     144                &    fwfisf(:,:) = fwfisf(:,:)  * ABS( greenland_icesheet_mass_rate_of_change * (1.0-rn_greenland_calving_fraction) & 
     145                &                           / ( zgreenland_fwfisf_sum + 1.0e-10_wp ) ) 
     146 
     147                 ! check 
     148                 IF(lwp .AND. ll_wrtstp) WRITE(numout, *) 'Greenland iceshelf melting climatology (kg/s) : ',zgreenland_fwfisf_sum 
     149 
     150                 zgreenland_fwfisf_sum = glob_sum( fwfisf(:,:) * e1t(:,:) * e2t(:,:) * greenland_icesheet_mask(:,:) ) 
     151 
     152                 IF(lwp .AND. ll_wrtstp) WRITE(numout, *) 'Greenland iceshelf melting adjusted value (kg/s) : ',zgreenland_fwfisf_sum 
     153 
     154                 zantarctica_fwfisf_sum = glob_sum( fwfisf(:,:) * e1t(:,:) * e2t(:,:) * antarctica_icesheet_mask(:,:) ) 
     155 
     156                 ! use ABS function because we need to preserve the sign of fwfisf 
     157                 WHERE( antarctica_icesheet_mask(:,:) == 1.0 ) & 
     158                &    fwfisf(:,:) = fwfisf(:,:)  * ABS( antarctica_icesheet_mass_rate_of_change * (1.0-rn_antarctica_calving_fraction) & 
     159                &                           / ( zantarctica_fwfisf_sum + 1.0e-10_wp ) ) 
     160 
     161                 ! check 
     162                 IF(lwp .AND. ll_wrtstp) WRITE(numout, *) 'Antarctica iceshelf melting climatology (kg/s) : ',zantarctica_fwfisf_sum 
     163 
     164                 zantarctica_fwfisf_sum = glob_sum( fwfisf(:,:) * e1t(:,:) * e2t(:,:) * antarctica_icesheet_mask(:,:) ) 
     165 
     166                 IF(lwp .AND. ll_wrtstp) WRITE(numout, *) 'Antarctica iceshelf melting adjusted value (kg/s) : ',zantarctica_fwfisf_sum 
     167 
     168              ENDIF 
     169            ENDIF 
     170 
    129171            qisf(:,:)   = fwfisf(:,:) * rLfusisf             ! heat flux 
    130172            stbl(:,:)   = soce 
     
    137179               fwfisf(:,:) = -sf_fwfisf(1)%fnow(:,:,1)            ! fwf 
    138180            ENDIF 
     181 
     182            IF( lk_oasis) THEN 
     183              ! nn_coupled_iceshelf_fluxes uninitialised unless lk_oasis=true 
     184              IF( nn_coupled_iceshelf_fluxes .gt. 0 ) THEN 
     185 
     186                ! Adjust total iceshelf melt rates so that sum of iceberg calving and iceshelf melting in the northern 
     187                ! and southern hemispheres equals rate of increase of mass of greenland and antarctic ice sheets 
     188                ! to preserve total freshwater conservation in coupled models without an active ice sheet model. 
     189 
     190                ! All related global sums must be done bit reproducibly 
     191                 zgreenland_fwfisf_sum = glob_sum( fwfisf(:,:) * e1t(:,:) * e2t(:,:) * greenland_icesheet_mask(:,:) ) 
     192 
     193                 ! use ABS function because we need to preserve the sign of fwfisf 
     194                 WHERE( greenland_icesheet_mask(:,:) == 1.0 )                                                                  & 
     195                &    fwfisf(:,:) = fwfisf(:,:)  * ABS( greenland_icesheet_mass_rate_of_change * (1.0-rn_greenland_calving_fraction) & 
     196                &                           / ( zgreenland_fwfisf_sum + 1.0e-10_wp ) ) 
     197 
     198                 ! check 
     199                 IF(lwp .AND. ll_wrtstp) WRITE(numout, *) 'Greenland iceshelf melting climatology (kg/s) : ',zgreenland_fwfisf_sum 
     200 
     201                 zgreenland_fwfisf_sum = glob_sum( fwfisf(:,:) * e1t(:,:) * e2t(:,:) * greenland_icesheet_mask(:,:) ) 
     202 
     203                 IF(lwp .AND. ll_wrtstp) WRITE(numout, *) 'Greenland iceshelf melting adjusted value (kg/s) : ',zgreenland_fwfisf_sum 
     204 
     205                 zantarctica_fwfisf_sum = glob_sum( fwfisf(:,:) * e1t(:,:) * e2t(:,:) * antarctica_icesheet_mask(:,:) ) 
     206 
     207                 ! use ABS function because we need to preserve the sign of fwfisf 
     208                 WHERE( antarctica_icesheet_mask(:,:) == 1.0 ) & 
     209                &    fwfisf(:,:) = fwfisf(:,:)  * ABS( antarctica_icesheet_mass_rate_of_change * (1.0-rn_antarctica_calving_fraction) & 
     210                &                           / ( zantarctica_fwfisf_sum + 1.0e-10_wp ) ) 
     211 
     212                 ! check 
     213                 IF(lwp .AND. ll_wrtstp) WRITE(numout, *) 'Antarctica iceshelf melting climatology (kg/s) : ',zantarctica_fwfisf_sum 
     214 
     215                 zantarctica_fwfisf_sum = glob_sum( fwfisf(:,:) * e1t(:,:) * e2t(:,:) * antarctica_icesheet_mask(:,:) ) 
     216 
     217                 IF(lwp .AND. ll_wrtstp) WRITE(numout, *) 'Antarctica iceshelf melting adjusted value (kg/s) : ',zantarctica_fwfisf_sum 
     218 
     219              ENDIF 
     220            ENDIF 
     221 
    139222            qisf(:,:)   = fwfisf(:,:) * rLfusisf               ! heat flux 
    140223            stbl(:,:)   = soce 
Note: See TracChangeset for help on using the changeset viewer.