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 14995 for NEMO/trunk/tests/ISOMIP+/MY_SRC/sbcfwb.F90 – NEMO

Ignore:
Timestamp:
2021-06-15T19:15:26+02:00 (3 years ago)
Author:
mathiot
Message:

ticket #2669 : merge ticket2669_isf_fluxes into trunk

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/trunk/tests/ISOMIP+/MY_SRC/sbcfwb.F90

    r13583 r14995  
    2424   ! 
    2525   USE in_out_manager ! I/O manager 
     26   USE iom            ! IOM 
    2627   USE lib_mpp        ! distribued memory computing library 
    2728   USE timing         ! Timing 
     
    3435   PUBLIC   sbc_fwb    ! routine called by step 
    3536 
    36    REAL(wp) ::   a_fwb_b   ! annual domain averaged freshwater budget 
    37    REAL(wp) ::   a_fwb     ! for 2 year before (_b) and before year. 
    38    REAL(wp) ::   fwfold    ! fwfold to be suppressed 
     37   REAL(wp) ::   rn_fwb0   ! initial freshwater adjustment flux [kg/m2/s] (nn_fwb = 2 only) 
     38   REAL(wp) ::   a_fwb     ! annual domain averaged freshwater budget from the 
     39                           ! previous year 
    3940   REAL(wp) ::   area      ! global mean ocean surface (interior domain) 
    4041 
     
    6566      INTEGER, INTENT( in ) ::   Kmm      ! ocean time level index 
    6667      ! 
    67       INTEGER  ::   inum, ikty, iyear     ! local integers 
     68      INTEGER  ::   ios, inum, ikty       ! local integers 
    6869      REAL(wp) ::   z_fwf, z_fwf_nsrf, zsum_fwf, zsum_erp                ! local scalars 
    6970      REAL(wp) ::   zsurf_neg, zsurf_pos, zsurf_tospread, zcoef          !   -      - 
     
    7273      REAL(wp)   ,DIMENSION(1) ::   z_fwfprv   
    7374      COMPLEX(dp),DIMENSION(1) ::   y_fwfnow   
     75      ! 
     76      NAMELIST/namsbc_fwb/rn_fwb0 
    7477      !!---------------------------------------------------------------------- 
    7578      ! 
    7679      IF( kt == nit000 ) THEN 
     80         READ( numnam_ref, namsbc_fwb, IOSTAT = ios, ERR = 901 ) 
     81901      IF( ios /= 0 ) CALL ctl_nam( ios, 'namsbc_fwb in reference namelist'     ) 
     82         READ( numnam_cfg, namsbc_fwb, IOSTAT = ios, ERR = 902 ) 
     83902      IF( ios >  0 ) CALL ctl_nam( ios, 'namsbc_fwb in configuration namelist' ) 
     84         IF(lwm) WRITE( numond, namsbc_fwb ) 
    7785         IF(lwp) THEN 
    7886            WRITE(numout,*) 
     
    8088            WRITE(numout,*) '~~~~~~~' 
    8189            IF( kn_fwb == 1 )   WRITE(numout,*) '          instantaneously set to zero' 
    82             IF( kn_fwb == 2 )   WRITE(numout,*) '          adjusted from previous year budget' 
     90            IF( kn_fwb == 4 )   WRITE(numout,*) '          instantaneously set to zero with heat and salt flux correction (ISOMIP+)' 
    8391            IF( kn_fwb == 3 )   WRITE(numout,*) '          fwf set to zero and spread out over erp area' 
    84             IF( kn_fwb == 4 )   WRITE(numout,*) '          instantaneously set to zero with heat and salt flux correction (ISOMIP+)' 
     92            IF( kn_fwb == 2 ) THEN 
     93               WRITE(numout,*) '          adjusted from previous year budget' 
     94               WRITE(numout,*) 
     95               WRITE(numout,*) '   Namelist namsbc_fwb' 
     96               WRITE(numout,*) '      Initial freshwater adjustment flux [kg/m2/s] = ', rn_fwb0 
     97            END IF 
    8598         ENDIF 
    8699         ! 
     
    111124            emp(:,:) = emp(:,:) - z_fwfprv(1)        * tmask(:,:,1) 
    112125            qns(:,:) = qns(:,:) + zcoef * sst_m(:,:) * tmask(:,:,1) ! account for change to the heat budget due to fw correction 
     126            ! outputs 
     127            IF( iom_use('hflx_fwb_cea') )  CALL iom_put( 'hflx_fwb_cea', zcoef * sst_m(:,:) * tmask(:,:,1) ) 
     128            IF( iom_use('vflx_fwb_cea') )  CALL iom_put( 'vflx_fwb_cea', z_fwfprv(1)        * tmask(:,:,1) ) 
    113129         ENDIF 
    114130         ! 
     
    131147            qns(:,:) = qns(:,:) + zcoef * sst_m(:,:) * tmask(:,:,1) ! (Eq. 35 AD2015) ! use sst_m to avoid generation of any bouyancy fluxes 
    132148            sfx(:,:) = sfx(:,:) + z_fwf * sss_m(:,:) * tmask(:,:,1) ! (Eq. 36 AD2015) ! use sss_m to avoid generation of any bouyancy fluxes 
    133             !qns(:,:) = qns(:,:) + zcoef * ( -1.9 ) * tmask(:,:,1) ! (Eq. 35 AD2015) ! could be sst_m if we don't want any bouyancy fluxes 
    134             !sfx(:,:) = sfx(:,:) + z_fwf * ( 33.8 ) * tmask(:,:,1) ! (Eq. 36 AD2015) ! could be sss_m if we don't want any bouyancy fluxes 
    135             !qns(:,:) = qns(:,:) + zcoef * ( -1.0 ) * tmask(:,:,1) ! use for ISOMIP+ coupling sanity check (keep ssh cst while playing with cpl conservation option) 
    136             !sfx(:,:) = sfx(:,:) + z_fwf * ( 34.2 ) * tmask(:,:,1) ! use for ISOMIP+ coupling sanity check (keep ssh cst while playing with cpl conservation option) 
    137          ENDIF 
    138          ! 
    139       CASE ( 2 )                             !==  fwf budget adjusted from the previous year  ==! 
    140          ! 
    141          IF( kt == nit000 ) THEN                      ! initialisation 
    142             !                                         ! Read the corrective factor on precipitations (fwfold) 
    143             CALL ctl_opn( inum, 'EMPave_old.dat', 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. ) 
    144             READ ( inum, "(24X,I8,2ES24.16)" ) iyear, a_fwb_b, a_fwb 
    145             CLOSE( inum ) 
    146             fwfold = a_fwb                            ! current year freshwater budget correction 
    147             !                                         ! estimate from the previous year budget 
     149         ENDIF 
     150         ! 
     151      CASE ( 2 )                             !==  fw adjustment based on fw budget at the end of the previous year  ==! 
     152         ! 
     153         IF( kt == nit000 ) THEN                                                                    ! initialisation 
     154            !                                                                                       ! set the fw adjustment (a_fwb) 
     155            IF ( ln_rstart .AND. iom_varid( numror, 'a_fwb',   ldstop = .FALSE. ) > 0 ) THEN        !    as read from restart file 
     156               IF(lwp) WRITE(numout,*) 'sbc_fwb : reading FW-budget adjustment from restart file' 
     157               CALL iom_get( numror, 'a_fwb',   a_fwb ) 
     158            ELSE                                                                                    !    as specified in namelist 
     159               a_fwb = rn_fwb0 
     160            END IF 
     161            ! 
    148162            IF(lwp)WRITE(numout,*) 
    149             IF(lwp)WRITE(numout,*)'sbc_fwb : year = ',iyear  , ' freshwater budget correction = ', fwfold 
    150             IF(lwp)WRITE(numout,*)'          year = ',iyear-1, ' freshwater budget read       = ', a_fwb 
    151             IF(lwp)WRITE(numout,*)'          year = ',iyear-2, ' freshwater budget read       = ', a_fwb_b 
     163            IF(lwp)WRITE(numout,*)'sbc_fwb : initial freshwater-budget adjustment = ', a_fwb, 'kg/m2/s' 
     164            ! 
    152165         ENDIF    
    153          !                                         ! Update fwfold if new year start 
     166         !                                         ! Update a_fwb if new year start 
    154167         ikty = 365 * 86400 / rn_Dt                  !!bug  use of 365 days leap year or 360d year !!!!!!! 
    155168         IF( MOD( kt, ikty ) == 0 ) THEN 
    156             a_fwb_b = a_fwb                           ! mean sea level taking into account the ice+snow 
     169                                                      ! mean sea level taking into account the ice+snow 
    157170                                                      ! sum over the global domain 
    158171            a_fwb   = glob_sum( 'sbcfwb', e1e2t(:,:) * ( ssh(:,:,Kmm) + snwice_mass(:,:) * r1_rho0 ) ) 
    159172            a_fwb   = a_fwb * 1.e+3 / ( area * rday * 365. )     ! convert in Kg/m3/s = mm/s 
    160173!!gm        !                                                      !!bug 365d year  
    161             fwfold =  a_fwb                           ! current year freshwater budget correction 
    162             !                                         ! estimate from the previous year budget 
    163174         ENDIF 
    164175         !  
    165176         IF( MOD( kt-1, kn_fsbc ) == 0 ) THEN         ! correct the freshwater fluxes 
    166             zcoef = fwfold * rcp 
    167             emp(:,:) = emp(:,:) + fwfold             * tmask(:,:,1) 
     177            zcoef = a_fwb * rcp 
     178            emp(:,:) = emp(:,:) + a_fwb              * tmask(:,:,1) 
    168179            qns(:,:) = qns(:,:) - zcoef * sst_m(:,:) * tmask(:,:,1) ! account for change to the heat budget due to fw correction 
    169          ENDIF 
    170          ! 
    171          IF( kt == nitend .AND. lwm ) THEN            ! save fwfold value in a file (only one required) 
    172             CALL ctl_opn( inum, 'EMPave.dat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE., narea ) 
    173             WRITE( inum, "(24X,I8,2ES24.16)" ) nyear, a_fwb_b, a_fwb 
    174             CLOSE( inum ) 
    175          ENDIF 
     180            ! outputs 
     181            IF( iom_use('hflx_fwb_cea') )  CALL iom_put( 'hflx_fwb_cea', -zcoef * sst_m(:,:) * tmask(:,:,1) ) 
     182            IF( iom_use('vflx_fwb_cea') )  CALL iom_put( 'vflx_fwb_cea', -a_fwb              * tmask(:,:,1) ) 
     183         ENDIF 
     184         ! Output restart information 
     185         IF( lrst_oce ) THEN 
     186            IF(lwp) WRITE(numout,*) 
     187            IF(lwp) WRITE(numout,*) 'sbc_fwb : writing FW-budget adjustment to ocean restart file at it = ', kt 
     188            IF(lwp) WRITE(numout,*) '~~~~' 
     189            CALL iom_rstput( kt, nitrst, numrow, 'a_fwb',   a_fwb ) 
     190         END IF 
     191         ! 
     192         IF( kt == nitend .AND. lwp ) WRITE(numout,*) 'sbc_fwb : final freshwater-budget adjustment = ', a_fwb, 'kg/m2/s' 
    176193         ! 
    177194      CASE ( 3 )                             !==  global fwf set to zero and spread out over erp area  ==! 
     
    211228            qns(:,:) = qns(:,:) - zerp_cor(:,:) * rcp * sst_m(:,:)  ! account for change to the heat budget due to fw correction 
    212229            erp(:,:) = erp(:,:) + zerp_cor(:,:) 
     230            ! outputs 
     231            IF( iom_use('hflx_fwb_cea') )  CALL iom_put( 'hflx_fwb_cea', -zerp_cor(:,:) * rcp * sst_m(:,:) ) 
     232            IF( iom_use('vflx_fwb_cea') )  CALL iom_put( 'vflx_fwb_cea', -zerp_cor(:,:) ) 
    213233            ! 
    214234            IF( lwp ) THEN                   ! control print 
Note: See TracChangeset for help on using the changeset viewer.