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 4901 for branches/2014/dev_CNRS_2014/NEMOGCM/NEMO/OPA_SRC/TRA/traqsr.F90 – NEMO

Ignore:
Timestamp:
2014-11-27T16:41:22+01:00 (10 years ago)
Author:
cetlod
Message:

2014/dev_CNRS_2014 : merge the 3rd branch onto dev_CNRS_2014, see ticket #1415

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2014/dev_CNRS_2014/NEMOGCM/NEMO/OPA_SRC/TRA/traqsr.F90

    r4897 r4901  
    1010   !!             -   !  2005-11  (G. Madec) zco, zps, sco coordinate 
    1111   !!            3.2  !  2009-04  (G. Madec & NEMO team)  
    12    !!            3.6  !  2012-05  (C. Rousset) store attenuation coef for use in ice model  
     12   !!            4.0  !  2012-05  (C. Rousset) store attenuation coef for use in ice model  
    1313   !!---------------------------------------------------------------------- 
    1414 
     
    1717   !!   tra_qsr_init : solar radiation penetration initialization 
    1818   !!---------------------------------------------------------------------- 
    19    USE oce            ! ocean dynamics and active tracers 
    20    USE dom_oce        ! ocean space and time domain 
    21    USE sbc_oce        ! surface boundary condition: ocean 
    22    USE trc_oce        ! share SMS/Ocean variables 
    23    USE trd_oce        ! trends: ocean variables 
    24    USE trdtra         ! trends manager: tracers  
    25    USE phycst         ! physical constants 
    26    USE sbc_ice,  ONLY : lk_lim3 
    27    ! 
    28    USE in_out_manager ! I/O manager 
    29    USE prtctl         ! Print control 
    30    USE iom            ! I/O manager 
    31    USE fldread        ! read input fields 
    32    USE lib_mpp        ! MPP library 
     19   USE oce             ! ocean dynamics and active tracers 
     20   USE dom_oce         ! ocean space and time domain 
     21   USE sbc_oce         ! surface boundary condition: ocean 
     22   USE trc_oce         ! share SMS/Ocean variables 
     23   USE trdmod_oce      ! ocean variables trends 
     24   USE trdtra          ! ocean active tracers trends  
     25   USE in_out_manager  ! I/O manager 
     26   USE phycst          ! physical constants 
     27   USE prtctl          ! Print control 
     28   USE iom             ! I/O manager 
     29   USE fldread         ! read input fields 
     30   USE restart         ! ocean restart 
     31   USE lib_mpp         ! MPP library 
    3332   USE wrk_nemo       ! Memory Allocation 
    3433   USE timing         ! Timing 
     34   USE sbc_ice, ONLY : lk_lim3 
    3535 
    3636   IMPLICIT NONE 
     
    5151   REAL(wp), PUBLIC ::   rn_si1       !: deepest depth of extinction (water type I)       (2 bands) 
    5252    
    53    INTEGER , PUBLIC ::   nksr   !: levels below which the light cannot penetrate ( depth larger than 391 m) 
    54  
    55    REAL(wp)                  ::   xsi0r, xsi1r        ! inverse of rn_si0 and rn_si1, resp. 
    56    REAL(wp), DIMENSION(3,61) ::   rkrgb               ! tabulated attenuation coefficients for RGB absorption 
     53   ! Module variables 
     54   REAL(wp) ::   xsi0r                           !: inverse of rn_si0 
     55   REAL(wp) ::   xsi1r                           !: inverse of rn_si1 
    5756   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_chl   ! structure of input Chl (file informations, fields read) 
     57   INTEGER, PUBLIC ::   nksr              ! levels below which the light cannot penetrate ( depth larger than 391 m) 
     58   REAL(wp), DIMENSION(3,61) ::   rkrgb   !: tabulated attenuation coefficients for RGB absorption 
    5859 
    5960   !! * Substitutions 
     
    8990      !! 
    9091      !! ** Action  : - update ta with the penetrative solar radiation trend 
    91       !!              - send the trend to trdtra (l_trdtra=T) 
     92      !!              - save the trend in ttrd ('key_trdtra') 
    9293      !! 
    9394      !! Reference  : Jerlov, N. G., 1968 Optical Oceanography, Elsevier, 194pp. 
    9495      !!              Lengaigne et al. 2007, Clim. Dyn., V28, 5, 503-516. 
    9596      !!---------------------------------------------------------------------- 
     97      ! 
    9698      INTEGER, INTENT(in) ::   kt     ! ocean time-step 
    9799      ! 
     
    118120      ENDIF 
    119121 
    120       IF( l_trdtra ) THEN      ! Save temperature trends 
     122      IF( l_trdtra ) THEN      ! Save ta and sa trends 
    121123         CALL wrk_alloc( jpi, jpj, jpk, ztrdt )  
    122124         ztrdt(:,:,:) = tsa(:,:,:,jp_tem) 
     
    143145      !                                        Compute now qsr tracer content field 
    144146      !                                        ************************************ 
     147       
    145148      !                                           ! ============================================== ! 
    146149      IF( lk_qsr_bio .AND. ln_qsr_bio ) THEN      !  bio-model fluxes  : all vertical coordinates  ! 
     
    164167               DO ji = 1, jpi 
    165168                  IF ( qsr(ji,jj) /= 0._wp ) THEN 
    166                      oatte(ji,jj) = ( qsr_hc(ji,jj,1) / ( r1_rau0_rcp * qsr(ji,jj) ) ) 
    167                      iatte(ji,jj) = oatte(ji,jj) 
     169                     fraqsr_1lev(ji,jj) = ( qsr_hc(ji,jj,1) / ( r1_rau0_rcp * qsr(ji,jj) ) ) 
    168170                  ENDIF 
    169171               END DO 
     
    180182            IF( nn_chldta == 1 .OR. lk_vvl ) THEN            !*  Variable Chlorophyll or ocean volume 
    181183               ! 
    182                IF( nn_chldta == 1 ) THEN                             !- Variable Chlorophyll 
     184               IF( nn_chldta == 1 ) THEN                             !* Variable Chlorophyll 
    183185                  ! 
    184186                  CALL fld_read( kt, 1, sf_chl )                         ! Read Chl data and provides it at the current time step 
     
    196198                     END DO 
    197199                  END DO 
    198                ELSE                                                  !- Variable ocean volume but constant chrlorophyll 
    199                   zchl = 0.05                                           ! constant chlorophyll 
     200               ELSE                                            ! Variable ocean volume but constant chrlorophyll 
     201                  zchl = 0.05                                     ! constant chlorophyll 
    200202                  irgb = NINT( 41 + 20.*LOG10( zchl ) + 1.e-15 ) 
    201                   zekb(:,:) = rkrgb(1,irgb)                             ! Separation in R-G-B depending of the chlorophyll  
     203                  zekb(:,:) = rkrgb(1,irgb)                       ! Separation in R-G-B depending of the chlorophyll  
    202204                  zekg(:,:) = rkrgb(2,irgb) 
    203205                  zekr(:,:) = rkrgb(3,irgb) 
    204206               ENDIF 
    205207               ! 
    206                zcoef  = ( 1. - rn_abs ) / 3.e0                       !- equi-partition in R-G-B 
    207                ze0(:,:,1) = rn_abs * qsr(:,:) 
    208                ze1(:,:,1) =  zcoef * qsr(:,:) 
    209                ze2(:,:,1) =  zcoef * qsr(:,:) 
    210                ze3(:,:,1) =  zcoef * qsr(:,:) 
    211                zea(:,:,1) =          qsr(:,:) 
     208               zcoef  = ( 1. - rn_abs ) / 3.e0                        ! equi-partition in R-G-B 
     209               ze0(:,:,1) = rn_abs  * qsr(:,:) 
     210               ze1(:,:,1) = zcoef * qsr(:,:) 
     211               ze2(:,:,1) = zcoef * qsr(:,:) 
     212               ze3(:,:,1) = zcoef * qsr(:,:) 
     213               zea(:,:,1) =         qsr(:,:) 
    212214               ! 
    213215               DO jk = 2, nksr+1 
     
    236238                        zzc2 = zcoef  * EXP( - fse3t(ji,jj,1) * zekg(ji,jj) ) 
    237239                        zzc3 = zcoef  * EXP( - fse3t(ji,jj,1) * zekr(ji,jj) ) 
    238                         oatte(ji,jj) = 1.0 - ( zzc0 + zzc1 + zzc2  + zzc3  ) * tmask(ji,jj,2)  
    239                         iatte(ji,jj) = 1.0 - ( zzc0 + zzc1 + zcoef + zcoef ) * tmask(ji,jj,2) 
     240                        fraqsr_1lev(ji,jj) = 1.0 - ( zzc0 + zzc1 + zzc2  + zzc3  ) * tmask(ji,jj,2)  
    240241                     END DO 
    241242                  END DO 
     
    254255               ! clem: store attenuation coefficient of the first ocean level 
    255256               IF ( lk_lim3 .AND. ln_qsr_ice ) THEN 
    256                 
    257 !!gm  BUG ??????   ? ?  ? 
    258                   oatte(:,:) = etot3(:,:,1) / r1_rau0_rcp 
    259                   iatte(:,:) = oatte(:,:) 
     257                  fraqsr_1lev(:,:) = etot3(:,:,1) / r1_rau0_rcp 
    260258               ENDIF 
    261259           ENDIF 
     
    284282                        zc0 = zz0 * EXP( -fsdepw(ji,jj,1)*xsi0r ) + zz1 * EXP( -fsdepw(ji,jj,1)*xsi1r ) 
    285283                        zc1 = zz0 * EXP( -fsdepw(ji,jj,2)*xsi0r ) + zz1 * EXP( -fsdepw(ji,jj,2)*xsi1r ) 
    286                         oatte(ji,jj) = ( zc0*tmask(ji,jj,1) - zc1*tmask(ji,jj,2) ) / r1_rau0_rcp 
    287                         iatte(ji,jj) = oatte(ji,jj) 
     284                        fraqsr_1lev(ji,jj) = ( zc0*tmask(ji,jj,1) - zc1*tmask(ji,jj,2) ) / r1_rau0_rcp 
    288285                     END DO 
    289286                  END DO 
     
    299296               ! clem: store attenuation coefficient of the first ocean level 
    300297               IF ( lk_lim3 .AND. ln_qsr_ice ) THEN 
    301                   oatte(:,:) = etot3(:,:,1) / r1_rau0_rcp 
    302                   iatte(:,:) = oatte(:,:) 
     298                  fraqsr_1lev(:,:) = etot3(:,:,1) / r1_rau0_rcp 
    303299               ENDIF 
    304300               ! 
     
    331327      IF( l_trdtra ) THEN     ! qsr tracers trends saved for diagnostics 
    332328         ztrdt(:,:,:) = tsa(:,:,:,jp_tem) - ztrdt(:,:,:) 
    333          CALL trd_tra( kt, 'TRA', jp_tem, jptra_qsr, ztrdt ) 
     329         CALL trd_tra( kt, 'TRA', jp_tem, jptra_trd_qsr, ztrdt ) 
    334330         CALL wrk_dealloc( jpi, jpj, jpk, ztrdt )  
    335331      ENDIF 
     
    362358      !! Reference : Jerlov, N. G., 1968 Optical Oceanography, Elsevier, 194pp. 
    363359      !!---------------------------------------------------------------------- 
     360      ! 
    364361      INTEGER  ::   ji, jj, jk                   ! dummy loop indices 
    365362      INTEGER  ::   irgb, ierror, ioptio, nqsr   ! local integer 
     
    380377      IF( nn_timing == 1 )  CALL timing_start('tra_qsr_init') 
    381378      ! 
    382       ! clem init for oatte and iatte 
     379      ! Default value for fraqsr_1lev 
    383380      IF( .NOT. ln_rstart ) THEN 
    384          oatte(:,:) = 1._wp 
    385          iatte(:,:) = 1._wp 
     381         fraqsr_1lev(:,:) = 1._wp 
    386382      ENDIF 
    387383      ! 
Note: See TracChangeset for help on using the changeset viewer.