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

Changeset 8393


Ignore:
Timestamp:
2017-07-28T17:26:12+02:00 (7 years ago)
Author:
jgraham
Message:

Updated to include 25hourm mldzint diagnostics.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/AMM15_v3_6_STABLE_package/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfmxl.F90

    r8059 r8393  
    4848   END TYPE MXL_ZINT 
    4949 
     50!Used for 25h mean 
     51   LOGICAL, PRIVATE :: mld_25h_init = .TRUE.    !Logical used to initalise 25h 
     52                                                !outputs. Necassary, because we need to 
     53                                                !initalise the mld_25h on the zeroth 
     54                                                !timestep (i.e in the nemogcm_init call) 
     55   LOGICAL, PRIVATE :: mld_25h_write = .FALSE.  !Logical confirm 25h calculating/processing 
     56 
     57   INTEGER, SAVE :: i_cnt_25h                   ! Counter for 25 hour means 
     58 
     59   REAL(wp),SAVE, ALLOCATABLE, DIMENSION(:,:,:) ::   hmld_zint_25h 
     60 
    5061   !! * Substitutions 
    5162#  include "domzgr_substitute.h90" 
     
    441452      INTEGER :: nn_mld_diag = 0    ! number of diagnostics 
    442453 
     454      INTEGER :: i_steps          ! no of timesteps per hour 
     455      INTEGER :: ierror             ! logical error message    
     456 
     457      REAL(wp) :: zdt             ! timestep variable   
     458 
    443459      CHARACTER(len=1) :: cmld 
    444460 
     
    496512                  CALL iom_put( "mldhtc_"//cmld , htc_mld(:,:)   ) 
    497513               ENDIF 
     514 
     515               IF( iom_use( "mldzint25h_"//cmld ) ) THEN 
     516                  IF( .NOT. mld_25h_write ) mld_25h_write = .TRUE. 
     517                  zdt = rdt 
     518                  IF( nacc == 1 ) zdt = rdtmin 
     519                  IF( MOD( 3600,INT(zdt) ) == 0 ) THEN 
     520                     i_steps = 3600/INT(zdt) 
     521                  ELSE 
     522                     CALL ctl_stop('STOP', 'zdf_mxl_zint 25h: timestep must give MOD(3600,rdt) = 0 otherwise no hourly values are possible') 
     523                  ENDIF 
     524                  IF( ( mld_25h_init ) .OR. ( kt == nit000 ) ) THEN 
     525                     i_cnt_25h = 1 
     526                     IF( .NOT. ALLOCATED(hmld_zint_25h) ) THEN 
     527                        ALLOCATE( hmld_zint_25h(jpi,jpj,nn_mld_diag), STAT=ierror ) 
     528                        IF( ierror > 0 )  CALL ctl_stop( 'zdf_mxl_zint 25h: unable to allocate hmld_zint_25h' )    
     529                     ENDIF 
     530                     hmld_zint_25h(:,:,jn) = hmld_zint(:,:) 
     531                  ENDIF 
     532                  IF( MOD( kt, i_steps ) == 0 .AND.  kt .NE. nn_it000 ) THEN 
     533                     hmld_zint_25h(:,:,jn) = hmld_zint_25h(:,:,jn) + hmld_zint(:,:) 
     534                  ENDIF 
     535                  IF( i_cnt_25h .EQ. 25 .AND.  MOD( kt, i_steps*24) == 0 .AND. kt .NE. nn_it000 ) THEN 
     536                     CALL iom_put( "mldzint25h_"//cmld , hmld_zint_25h(:,:,jn) / 25._wp   ) 
     537                  ENDIF 
     538               ENDIF 
     539 
    498540            ENDIF 
    499541         END DO 
     542                   
     543         IF(  mld_25h_write  ) THEN 
     544            IF( ( MOD( kt, i_steps ) == 0 ) .OR.  mld_25h_init ) THEN 
     545               IF (lwp) THEN 
     546                  WRITE(numout,*) 'zdf_mxl_zint (25h) : Summed the following number of hourly values so far',i_cnt_25h 
     547          ENDIF 
     548               i_cnt_25h = i_cnt_25h + 1 
     549               IF( mld_25h_init ) mld_25h_init = .FALSE. 
     550            ENDIF 
     551            IF( i_cnt_25h .EQ. 25 .AND.  MOD( kt, i_steps*24) == 0 .AND. kt .NE. nn_it000 ) THEN 
     552               i_cnt_25h = 1  
     553            ENDIF 
     554         ENDIF 
     555                   
    500556      ENDIF 
    501557 
Note: See TracChangeset for help on using the changeset viewer.