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 7034 – NEMO

Changeset 7034


Ignore:
Timestamp:
2016-10-17T18:02:09+02:00 (8 years ago)
Author:
kuniko
Message:

Initial commit

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/dev_r5518_fa_am_dt_deltadelta_toa/NEMOGCM/NEMO/OPA_SRC/SBC/sbcflx_adj.F90

    r7031 r7034  
    3232   PUBLIC   sbc_flx_adj_init   ! routine called in sbcmod 
    3333 
     34   !ky 16/10/2016 commented out below two lines 
    3435   !ky 06/09/2016 uncommented below two lines for FA test 
    3536   !ky 11/12/2015 recommented below two lines 
    3637   !!ky 3/12/2015 uncommented below two lines for FA test! 
    37    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   erp   !: evaporation damping   [kg/m2/s] 
    38    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   qrp   !: heat flux damping        [w/m2] 
     38   !REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   erp   !: evaporation damping   [kg/m2/s] 
     39   !REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   qrp   !: heat flux damping        [w/m2] 
    3940 
    4041   !                                   !!* Namelist namsbc_flx_adj * 
     
    4344   LOGICAL         ::   ln_sssr_bnd     ! flag to bound erp term  
    4445   REAL(wp)        ::   rn_sssr_bnd     ! ABS(Max./Min.) value of erp term [mm/day] 
     46   REAL(wp)        ::   delta_toa       ! global mean annual mean TOA for FA to perturbed ensemble [W/m2] 
     47   REAL(wp)        ::   delta_delta_toa ! perturbation to delta_toa [W/m2] 
    4548 
    4649   REAL(wp) , ALLOCATABLE, DIMENSION(:) ::   buffer   ! Temporary buffer for exchange 
     
    8386      !!---------------------------------------------------------------------- 
    8487      ! 
    85       !!write(numout,*) '*** In sbcflx_adj ***' 
     88      write(numout,*) '*** In sbcflx_adj *** delta_toa, delta_delta_toa=', & 
     89         & delta_toa, delta_delta_toa 
    8690 
    8791      IF( nn_timing == 1 )  CALL timing_start('sbc_flx_adj') 
     
    101105                     ! K.Y. 16/03/2016 Apply Arctic mask to heat flux adjustment 
    102106                     zqrp = ( 1. - 2.*only_arcmsk(ji,jj) )  & 
    103                         &        * sf_qrp(1)%fnow(ji,jj,1) 
     107                        &        * sf_qrp(1)%fnow(ji,jj,1)  & 
     108                        &        + delta_toa + delta_delta_toa 
     109                     ! K.Y. 16/10/2016 added "&" to 2 lines above and  
     110                     !   delta_toa, delta_delta_toa to above line 
    104111                     !zqrp = sf_qrp(1)%fnow(ji,jj,1) 
    105112                     !ky 07/09/2016 copied 1 line below for FA test 
     
    108115                     !qrp(ji,jj) = sf_qrp(1)%fnow(ji,jj,1) 
    109116                     !ky 07/09/2016 copied 1 line above and modified as below for FA test 
    110                      qrp(ji,jj) = zqrp 
     117                     !ky 16/10/2016 commented out 1 line below 
     118                     !qrp(ji,jj) = zqrp 
    111119                     qns(ji,jj) = qns(ji,jj) + zqrp 
    112120                  END DO 
    113121               END DO 
     122               !ky 16/10/2016 commented out below 1 line below 
    114123               !ky 06/09/2016 uncommented below 1 line below for FA test! 
    115124               !ky 11/12/2015 recommented out below 1 line below 
    116125               !!ky 3/12/2015 uncommented below 1 line below for FA test! 
    117                CALL iom_put( "qrp", qrp )                             ! heat flux damping 
     126               !CALL iom_put( "qrp", qrp )                             ! heat flux damping 
    118127            ENDIF 
    119128            ! 
     
    132141                     !!ky 3/12/2015 1 line below for FA test! 
    133142                     !erp(ji,jj) = sf_erp(1)%fnow(ji,jj,1) 
     143                     !ky 16/10/2016 commented out below two lines 
    134144                     !ky 06/09/2016 copied line above and changed to below two lines for FA test! 
    135                      erp(ji,jj) = ( 1. - 2.*rnfmsk_arcmsk(ji,jj) )  &        ! No damping in vicinity of river mouths 
    136                         &        * sf_erp(1)%fnow(ji,jj,1)  
     145                     !erp(ji,jj) = ( 1. - 2.*rnfmsk_arcmsk(ji,jj) )  &        ! No damping in vicinity of river mouths 
     146                     !   &        * sf_erp(1)%fnow(ji,jj,1)  
    137147                     sfx(ji,jj) = sfx(ji,jj) + zerp                 ! salt flux 
    138148                  END DO 
    139149               END DO 
     150               !ky 16/10/2016 commented out below one line 
    140151               !ky 06/09/2016 uncommented below one line for FA test! 
    141152               !ky 11/12/2015 recommented out below one line 
    142153               !!ky 3/12/2015 uncommented below one line for FA test! 
    143                CALL iom_put( "erp", erp )                             ! freshwater flux damping 
     154               !CALL iom_put( "erp", erp )                             ! freshwater flux damping 
    144155               ! 
    145156            ELSEIF( nn_flxadjfw == 2 ) THEN                               !* Salinity damping term (volume flux (emp) and associated heat flux (qns) 
     
    155166                     !erp(ji,jj) = sf_erp(1)%fnow(ji,jj,1) 
    156167                     !ky 06/09/2016 copied line above and changed to below line for FA test! 
    157                      erp(ji,jj) = zerp 
     168                     !ky 16/10/2016 commented out below line 
     169                     !erp(ji,jj) = zerp 
    158170                     emp(ji,jj) = emp (ji,jj) + zerp 
    159171                     qns(ji,jj) = qns(ji,jj) - zerp * rcp * sst_m(ji,jj) 
    160172                  END DO 
    161173               END DO 
     174               !ky 16/10/2016 commented out below 1 line 
    162175               !ky 06/09/2016 uncommented below 1 line for FA test! 
    163176               !ky 11/12/2015 recommented out below 1 line 
    164177               !!ky 3/12/2015 uncommented below 1 line for FA test! 
    165                CALL iom_put( "erp", erp )                             ! freshwater flux damping 
     178               !CALL iom_put( "erp", erp )                             ! freshwater flux damping 
    166179            ENDIF 
    167180            ! 
     
    193206      TYPE(FLD_N) ::   sn_qrp, sn_erp        ! informations about the fields to be read 
    194207      NAMELIST/namsbc_flx_adj/ cn_dir, nn_flxadjht, nn_flxadjfw, sn_qrp, sn_erp,   & 
    195          &                     ln_sssr_bnd, rn_sssr_bnd 
     208         &                     ln_sssr_bnd, rn_sssr_bnd, delta_toa, delta_delta_toa 
    196209      INTEGER     ::  ios 
    197210      !!---------------------------------------------------------------------- 
     
    219232         WRITE(numout,*) '      flag to bound erp term                 ln_sssr_bnd = ', ln_sssr_bnd 
    220233         WRITE(numout,*) '      ABS(Max./Min.) erp threshold           rn_sssr_bnd = ', rn_sssr_bnd, ' mm/day' 
     234         WRITE(numout,*) '      global mean, annual mean TOA to supplement FA delta_toa = ', delta_toa, ' W/m2' 
     235         WRITE(numout,*) '      perturbation to delta_toa = ', delta_delta_toa, ' W/m2' 
    221236      ENDIF 
    222237      ! 
    223238      !                            !* Allocate erp and qrp array 
     239      !ky 16/10/2016 commented out below two lines 
    224240      !ky 06/09/2016 uncommented below two lines for FA test! 
    225241      !ky 11/12/2015 recommented out below two lines 
    226242      !!ky 3/12/2015 uncommented below two lines for FA test! 
    227       ALLOCATE( qrp(jpi,jpj), erp(jpi,jpj), STAT=ierror ) 
    228       IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'sbc_ssr: unable to allocate erp and qrp array' ) 
     243      !ALLOCATE( qrp(jpi,jpj), erp(jpi,jpj), STAT=ierror ) 
     244      !IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'sbc_ssr: unable to allocate erp and qrp array' ) 
    229245      ! 
    230246      IF( nn_flxadjht == 1 ) THEN      !* set sf_qrp structure & allocate arrays 
     
    257273      ! 
    258274      !ky!!                            !* Initialize qrp and erp if no restoring  
     275      !ky 16/10/2016 commented out below two lines 
    259276      !ky 06/09/2016 below two lines for FA test! 
    260277      !ky 11/12/2015 commented out below two lines 
    261278      !!ky 3/12/2015 below two lines for FA test! 
    262       IF( nn_flxadjht /= 1                   )   qrp(:,:) = 0._wp 
    263       IF( nn_flxadjfw /= 1 .OR. nn_flxadjfw /= 2 )   erp(:,:) = 0._wp 
     279      !IF( nn_flxadjht /= 1                   )   qrp(:,:) = 0._wp 
     280      !IF( nn_flxadjfw /= 1 .OR. nn_flxadjfw /= 2 )   erp(:,:) = 0._wp 
    264281      !!ky!!IF( nn_sstr /= 1                   )   qrp(:,:) = 0._wp 
    265282      !!ky!!IF( nn_sssr /= 1 .OR. nn_sssr /= 2 )   erp(:,:) = 0._wp 
Note: See TracChangeset for help on using the changeset viewer.