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

Ignore:
Timestamp:
2015-04-24T14:08:11+02:00 (9 years ago)
Author:
cetlod
Message:

NEMOGCM_dev_r5204_CNRS_PISCES_dcy : update routines according to the new strategy, see ticket #1484

File:
1 edited

Legend:

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

    r5206 r5236  
    3030   PUBLIC   trc_stp    ! called by step 
    3131 
     32   REAL(wp), DIMENSION(:,:,:), SAVE, ALLOCATABLE ::   qsr_arr ! save qsr during TOP time-step 
     33   REAL(wp) :: rdt_sampl 
     34   INTEGER  :: nb_rec_per_days 
     35   INTEGER  :: isecfst, iseclast 
     36   LOGICAL  :: llnew 
     37 
    3238   !! * Substitutions 
    3339#  include "domzgr_substitute.h90" 
     
    5460      CHARACTER (len=25)    ::  charout  
    5561 
    56       REAL(wp), DIMENSION(:,:), POINTER ::   zqsr_tmp ! save qsr during TOP time-step 
    5762      !!------------------------------------------------------------------- 
    5863      ! 
     
    6873         areatot         = glob_sum( cvol(:,:,:) ) 
    6974      ENDIF 
     75      ! 
     76      IF( l_trcdm2dc )   CALL trc_mean_qsr( kt ) 
    7077      !     
    7178      IF( nn_dttrc /= 1 )   CALL trc_sub_stp( kt )  ! averaging physical variables for sub-stepping 
     
    109116   END SUBROUTINE trc_stp 
    110117 
     118   SUBROUTINE trc_mean_qsr( kt ) 
     119      !!---------------------------------------------------------------------- 
     120      !!             ***  ROUTINE trc_mean_qsr  *** 
     121      !! 
     122      !! ** Purpose :  Compute daily mean qsr for biogeochmeical model in case 
     123      !!               of diurnal cycle 
     124      !! 
     125      !! ** Method  :  Store qsr coming from ocean every at 1 hour of every 
     126      !!               coupling frequency  in coupled mode, in one day 
     127      !!               Compute the daily mean qsr 
     128      !!---------------------------------------------------------------------- 
     129      INTEGER, INTENT(in) ::   kt 
     130      INTEGER  :: jn 
     131 
     132      IF( kt == nittrc000 ) THEN 
     133         IF( lk_cpl )  THEN   
     134            rdt_sampl = 86400. / ncpl_qsr_freq 
     135            nb_rec_per_days = ncpl_qsr_freq 
     136         ELSE   
     137            rdt_sampl = MAX( 3600., rdt * nn_dttrc ) 
     138            nb_rec_per_days = INT( 86400 / rdt_sampl ) 
     139         ENDIF 
     140         ! 
     141         IF( lwp ) THEN 
     142            WRITE(numout,*)  
     143            WRITE(numout,*) ' Sampling frequency dt = ', rdt_sampl, 's','   Number of sampling per day  nrec = ', nb_rec_per_days 
     144            WRITE(numout,*)  
     145         ENDIF 
     146         ! 
     147         ALLOCATE( qsr_arr(jpi,jpj,nb_rec_per_days ) ) 
     148         DO jn = 1, nb_rec_per_days 
     149            qsr_arr(:,:,jn) = qsr(:,:) 
     150         ENDDO 
     151         qsr_mean(:,:) = qsr(:,:) 
     152         ! 
     153         isecfst  = nsec_year + nsec1jan000   !   number of seconds between Jan. 1st 00h of nit000 year and the middle of time step 
     154         iseclast = isecfst 
     155         ! 
     156      ENDIF 
     157      ! 
     158      iseclast = nsec_year + nsec1jan000 
     159      llnew   = ( iseclast - isecfst )  > INT( rdt_sampl )   !   new shortwave to store 
     160      IF( kt /= nittrc000 .AND. llnew ) THEN 
     161          IF( lwp ) WRITE(numout,9000) ' New shortwave to sample for TOP at time kt = ', kt, & 
     162             &                      ' time = ', (iseclast+rdt*nn_dttrc/2.)/3600.,'hours ' 
     163          isecfst = iseclast 
     164          DO jn = 1, nb_rec_per_days - 1 
     165             qsr_arr(:,:,jn) = qsr_arr(:,:,jn+1) 
     166          ENDDO 
     167          qsr_arr (:,:,nb_rec_per_days) = qsr(:,:) 
     168          qsr_mean(:,:                ) = SUM( qsr_arr(:,:,:) , 3 ) / nb_rec_per_days 
     169      ENDIF 
     170      ! 
     171 9000 FORMAT(i10,f10.1) 
     172      ! 
     173   END SUBROUTINE trc_mean_qsr 
     174 
    111175#else 
    112176   !!---------------------------------------------------------------------- 
Note: See TracChangeset for help on using the changeset viewer.