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 5602 for branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/trcstp.F90 – NEMO

Ignore:
Timestamp:
2015-07-16T13:55:15+02:00 (9 years ago)
Author:
cbricaud
Message:

merge change from trunk rev 5003 to 5519 ( rev where branche 3.6_stable were created )

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/trcstp.F90

    r5601 r5602  
    3131   PUBLIC   trc_stp    ! called by step 
    3232 
     33   REAL(wp), DIMENSION(:,:,:), SAVE, ALLOCATABLE ::   qsr_arr ! save qsr during TOP time-step 
     34   REAL(wp) :: rdt_sampl 
     35   INTEGER  :: nb_rec_per_days 
     36   INTEGER  :: isecfst, iseclast 
     37   LOGICAL  :: llnew 
     38 
    3339   !! * Substitutions 
    3440#  include "domzgr_substitute.h90" 
     
    5561      CHARACTER (len=25)    ::  charout  
    5662 
    57       REAL(wp), DIMENSION(:,:), POINTER ::   zqsr_tmp ! save qsr during TOP time-step 
    5863      !!------------------------------------------------------------------- 
    5964      ! 
     
    6974         areatot         = glob_sum( cvol(:,:,:) ) 
    7075      ENDIF 
    71       !     
    72       IF( ltrcdm2dc ) THEN 
    73          ! When Diurnal cycle, core bulk and LIM2  are activated, put daily mean qsr in qsr for TOP/biogeochemistery time-step 
    74          ! and save qsr with diurnal cycle in qsr_tmp 
    75          CALL wrk_alloc( jpi,jpj, zqsr_tmp ) 
    76          zqsr_tmp(:,:) = qsr     (:,:) 
    77          qsr     (:,:) = qsr_mean(:,:)     
    78       ENDIF 
     76      ! 
     77      IF( l_trcdm2dc )   CALL trc_mean_qsr( kt ) 
    7978      !     
    8079      IF( nn_dttrc /= 1 )   CALL trc_sub_stp( kt )  ! averaging physical variables for sub-stepping 
     
    107106      ENDIF 
    108107      ! 
    109       IF( ltrcdm2dc ) THEN 
    110          ! put back qsr with diurnal cycle in qsr 
    111          qsr(:,:) = zqsr_tmp(:,:) 
    112          CALL wrk_dealloc( jpi,jpj, zqsr_tmp ) 
    113       ENDIF 
    114       ! 
    115108      ztrai = 0._wp                                                   !  content of all tracers 
    116109      DO jn = 1, jptra 
     
    123116      ! 
    124117   END SUBROUTINE trc_stp 
     118 
     119   SUBROUTINE trc_mean_qsr( kt ) 
     120      !!---------------------------------------------------------------------- 
     121      !!             ***  ROUTINE trc_mean_qsr  *** 
     122      !! 
     123      !! ** Purpose :  Compute daily mean qsr for biogeochemical model in case 
     124      !!               of diurnal cycle 
     125      !! 
     126      !! ** Method  : store in TOP the qsr every hour ( or every time-step the latter  
     127      !!              is greater than 1 hour ) and then, compute the  mean with  
     128      !!              a moving average over 24 hours.  
     129      !!              In coupled mode, the sampling is done at every coupling frequency  
     130      !!---------------------------------------------------------------------- 
     131      INTEGER, INTENT(in) ::   kt 
     132      INTEGER  :: jn 
     133 
     134      IF( kt == nittrc000 ) THEN 
     135         IF( ln_cpl )  THEN   
     136            rdt_sampl = 86400. / ncpl_qsr_freq 
     137            nb_rec_per_days = ncpl_qsr_freq 
     138         ELSE   
     139            rdt_sampl = MAX( 3600., rdt * nn_dttrc ) 
     140            nb_rec_per_days = INT( 86400 / rdt_sampl ) 
     141         ENDIF 
     142         ! 
     143         IF( lwp ) THEN 
     144            WRITE(numout,*)  
     145            WRITE(numout,*) ' Sampling frequency dt = ', rdt_sampl, 's','   Number of sampling per day  nrec = ', nb_rec_per_days 
     146            WRITE(numout,*)  
     147         ENDIF 
     148         ! 
     149         ALLOCATE( qsr_arr(jpi,jpj,nb_rec_per_days ) ) 
     150         DO jn = 1, nb_rec_per_days 
     151            qsr_arr(:,:,jn) = qsr(:,:) 
     152         ENDDO 
     153         qsr_mean(:,:) = qsr(:,:) 
     154         ! 
     155         isecfst  = nsec_year + nsec1jan000   !   number of seconds between Jan. 1st 00h of nit000 year and the middle of time step 
     156         iseclast = isecfst 
     157         ! 
     158      ENDIF 
     159      ! 
     160      iseclast = nsec_year + nsec1jan000 
     161      llnew   = ( iseclast - isecfst )  > INT( rdt_sampl )   !   new shortwave to store 
     162      IF( kt /= nittrc000 .AND. llnew ) THEN 
     163          IF( lwp ) WRITE(numout,*) ' New shortwave to sample for TOP at time kt = ', kt, & 
     164             &                      ' time = ', (iseclast+rdt*nn_dttrc/2.)/3600.,'hours ' 
     165          isecfst = iseclast 
     166          DO jn = 1, nb_rec_per_days - 1 
     167             qsr_arr(:,:,jn) = qsr_arr(:,:,jn+1) 
     168          ENDDO 
     169          qsr_arr (:,:,nb_rec_per_days) = qsr(:,:) 
     170          qsr_mean(:,:                ) = SUM( qsr_arr(:,:,:), 3 ) / nb_rec_per_days 
     171      ENDIF 
     172      ! 
     173   END SUBROUTINE trc_mean_qsr 
    125174 
    126175#else 
Note: See TracChangeset for help on using the changeset viewer.