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

Changeset 15357


Ignore:
Timestamp:
2021-10-12T19:02:36+02:00 (3 years ago)
Author:
hadjt
Message:

Region means
IOM_use to only process variables in use.
namelist parameter to control whether hourly means, or instanteous values
Instantaneous values of heat, salt mass and volume.

Location:
NEMO/branches/UKMO/NEMO_4.0.4_CO9_shelf_climate/src/OCE
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/UKMO/NEMO_4.0.4_CO9_shelf_climate/src/OCE/DIA/diaregmean.F90

    r15353 r15357  
    4040   LOGICAL :: ln_diaregmean_karamld     ! region mean calculation including kara mld terms 
    4141   LOGICAL :: ln_diaregmean_pea         ! region mean calculation including pea terms 
     42   INTEGER :: nn_diaregmean_nhourlymean ! region mean number of hours in mean (normally 1., <0 = instantanous (slower)) 
    4243 
    4344 
     
    5253    
    5354   REAL(wp),  ALLOCATABLE,   DIMENSION(:,:,:) ::   tmp_field_mat !: temporary region_mask 
     55   REAL(wp),  ALLOCATABLE,   DIMENSION(:,:,:) ::   tmp_field_HSVM_mat !: temporary region_mask 
    5456   REAL(wp),  ALLOCATABLE,   DIMENSION(:,:,:) ::   tmp_field_AR5_mat !: temporary region_mask 
    5557   REAL(wp),  ALLOCATABLE,   DIMENSION(:,:,:) ::   tmp_field_SBC_mat !: temporary region_mask 
     
    98100#if defined key_fabm 
    99101      NAMELIST/nam_diaregmean/ ln_diaregmean,nn_regions_output,ln_diaregmean_ascii,ln_diaregmean_bin,ln_diaregmean_nc,& 
    100         & ln_diaregmean_karamld, ln_diaregmean_pea,ln_diaregmean_diaar5,ln_diaregmean_diasbc,ln_diaregmean_bgc 
     102        & ln_diaregmean_karamld, ln_diaregmean_pea,ln_diaregmean_diaar5,ln_diaregmean_diasbc,ln_diaregmean_bgc,nn_diaregmean_nhourlymean 
    101103#else 
    102104      NAMELIST/nam_diaregmean/ ln_diaregmean,nn_regions_output,ln_diaregmean_ascii,ln_diaregmean_bin,ln_diaregmean_nc,& 
    103         & ln_diaregmean_karamld, ln_diaregmean_pea,ln_diaregmean_diaar5,ln_diaregmean_diasbc 
     105        & ln_diaregmean_karamld, ln_diaregmean_pea,ln_diaregmean_diaar5,ln_diaregmean_diasbc,nn_diaregmean_nhourlymean 
    104106#endif 
    105107       
     
    137139          IF( ierr /= 0 )   CALL ctl_stop( 'tmp_field_mat: failed to allocate tmp_field_mat array' ) 
    138140      tmp_field_mat(:,:,:) = 0. 
    139       tmp_field_cnt = 0 
     141 
     142      ALLOCATE( tmp_field_HSVM_mat(jpi,jpj,4),  STAT= ierr ) !SS/NB/DT/ZA/VA T/S, SSH, MLD, PEA, PEAT, PEAS 
     143          IF( ierr /= 0 )   CALL ctl_stop( 'tmp_field_mat: failed to allocate tmp_field_mat array' ) 
     144      tmp_field_HSVM_mat(:,:,:) = 0. 
    140145       
    141146      IF(ln_diaregmean_diaar5) THEN    
     
    150155        tmp_field_SBC_mat(:,:,:) = 0. 
    151156      ENDIF 
     157 
     158 
     159      tmp_field_cnt = 0 
    152160 
    153161 
     
    457465      REAL(wp), POINTER, DIMENSION(:,:,:) :: zwtmbS    ! temporary S workspace  
    458466      REAL(wp), POINTER, DIMENSION(:,:,:) :: zwtmb1    ! temporary density workspace  
    459       REAL(wp)                            ::   zmdi       ! set masked values 
     467      REAL(wp)                            ::   zmdi    ! set masked values 
    460468      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index 
    461469       
     
    469477      CHARACTER (len=120), DIMENSION(4)  ::    name_AR5_mat 
    470478      CHARACTER (len=120), DIMENSION(7)  ::    name_SBC_mat 
     479      CHARACTER (len=120), DIMENSION(4)  ::    name_HSCM_mat 
    471480      INTEGER                            ::    vi      
    472481      LOGICAL                            ::    do_reg_mean 
     
    474483      REAL(wp), DIMENSION(4)             ::    output_mulitpler_AR5_mat 
    475484      REAL(wp), DIMENSION(7)             ::    output_mulitpler_SBC_mat 
     485      REAL(wp), DIMENSION(4)             ::    output_mulitpler_HSVM_mat 
    476486 
    477487 
     
    497507        !JT Not sure what this is??  IF( nacc == 1 ) zdt = rdtmin 
    498508 
    499         IF( MOD( 3600,INT(zdt) ) == 0 ) THEN 
    500             i_steps = 3600/INT(zdt) 
     509 
     510        IF (nn_diaregmean_nhourlymean <= 0) THEN 
     511            ! 22 mins with instanteous values, 13 mins with hourly mean 
     512            IF(lwp ) WRITE(numout,*) 'dia_wri_region_mean instantaneous values!!!' 
     513            i_steps = 1 
     514            IF(lwp ) WRITE(numout,*) 'dia_wri_region_mean instantaneous values!!!' 
    501515        ELSE 
    502             CALL ctl_stop('STOP', 'dia_regmean: timestep must give MOD(3600,rdt) = 0 otherwise no hourly values are possible') 
     516 
     517            IF( MOD( (nn_diaregmean_nhourlymean*3600),INT(zdt) ) == 0 ) THEN 
     518                i_steps = (3600*nn_diaregmean_nhourlymean)/INT(zdt) 
     519            ELSE 
     520                CALL ctl_stop('STOP', 'dia_regmean: timestep must give MOD(3600,rdt) = 0 otherwise no hourly values are possible') 
     521            ENDIF 
     522 
    503523        ENDIF 
    504  
    505         !!IF(lwp ) WRITE(numout,*) 'JT! test! dia_wri_region_mean instantaneous values!!!' 
    506         !!i_steps = 1 
    507         !!IF(lwp ) WRITE(numout,*) 'JT! test! dia_wri_region_mean instantaneous values!!!' 
     524         
     525 
     526 
     527 
     528 
    508529         
    509530        ! Every time step, add physical, SBC, PEA, MLD terms to create hourly sums. 
     
    527548        ALLOCATE (zwtmb1(jpi , jpj, 6),  STAT= ierr ) 
    528549        IF( ierr /= 0 )   CALL ctl_stop( 'dia_regmean: failed to allocate zwtmb1 array' ) 
     550 
    529551             
    530552        CALL dia_calctmb_region_mean(  tsn(:,:,:,jp_tem),zwtmbT) 
     
    548570        !JT CALL wrk_dealloc( jpi , jpj, jpk , tmp1mat ) 
    549571        DEALLOCATE(  tmp1mat ) 
     572 
     573        tmp_field_HSVM_mat(:,:,1) = (zwtmbT(:,:,6)*tmask(:,:,1)*3850.) !heat 4200 is value for FW, 3850 is the value for sea water.  
     574        tmp_field_HSVM_mat(:,:,2) = (zwtmbS(:,:,6)*tmask(:,:,1))       !salt 
     575        tmp_field_HSVM_mat(:,:,3) = (zwtmb1(:,:,5)*tmask(:,:,1))       !vol 
     576        tmp_field_HSVM_mat(:,:,4) = (zwtmb1(:,:,6)*tmask(:,:,1))       !mass 
     577 
     578        name_HSCM_mat(1) = 'heat' 
     579        name_HSCM_mat(2) = 'salt' 
     580        name_HSCM_mat(3) = 'vol' 
     581        name_HSCM_mat(4) = 'mass' 
     582 
     583        output_mulitpler_HSVM_mat(:) = 1 
     584        output_mulitpler_HSVM_mat(1) = 1e-12 
     585        output_mulitpler_HSVM_mat(2) = 1e-12 
     586 
     587 
    550588  
    551589        ! Add 2d fields every time step to the hourly total. 
     
    562600        tmp_field_mat(:,:,5) = tmp_field_mat(:,:,5) + (zwtmbT(:,:,5)*tmask(:,:,1)) !vat 
    563601        name_dat_mat(5) = 'vat' 
    564         tmp_field_mat(:,:,6) = tmp_field_mat(:,:,6) + ((zwtmbT(:,:,6)*tmask(:,:,1)*4.2e3))! heat 
     602        tmp_field_mat(:,:,6) = tmp_field_mat(:,:,6) + (tmp_field_HSVM_mat(:,:,1))! heat 
    565603        name_dat_mat(6) = 'heat' 
    566604 
     
    576614        tmp_field_mat(:,:,11) = tmp_field_mat(:,:,11) + (zwtmbS(:,:,5)*tmask(:,:,1)) !vas 
    577615        name_dat_mat(11) = 'vas' 
    578         tmp_field_mat(:,:,12) = tmp_field_mat(:,:,12) + (zwtmbS(:,:,6)*tmask(:,:,1)) !salt 
     616        tmp_field_mat(:,:,12) = tmp_field_mat(:,:,12) + (tmp_field_HSVM_mat(:,:,2)) !salt 
    579617        name_dat_mat(12) = 'salt' 
    580618 
    581         tmp_field_mat(:,:,13) = tmp_field_mat(:,:,13) + (zwtmb1(:,:,5)*tmask(:,:,1))!vol 
     619        tmp_field_mat(:,:,13) = tmp_field_mat(:,:,13) + (tmp_field_HSVM_mat(:,:,3))!vol 
    582620        name_dat_mat(13) = 'vol' 
    583         tmp_field_mat(:,:,14) = tmp_field_mat(:,:,14) + (zwtmb1(:,:,6)*tmask(:,:,1))!mass 
     621        tmp_field_mat(:,:,14) = tmp_field_mat(:,:,14) + (tmp_field_HSVM_mat(:,:,4))!mass 
    584622        name_dat_mat(14) = 'mass' 
    585623 
     
    587625        name_dat_mat(15) = 'ssh' 
    588626         
    589         !JT CALL wrk_dealloc( jpi , jpj, 6 , zwtmbT ) 
    590         !JT CALL wrk_dealloc( jpi , jpj, 6 , zwtmbS ) 
    591         !JT CALL wrk_dealloc( jpi , jpj, 6 , zwtmb1 ) 
    592627 
    593628        DEALLOCATE (zwtmbT, zwtmbS, zwtmb1 ) 
     
    639674 
    640675        output_mulitpler_dat_mat(:) = 1. 
    641         output_mulitpler_dat_mat(6) = 1e-12 
    642         output_mulitpler_dat_mat(12) = 1e-12 
     676        output_mulitpler_dat_mat(6)  = output_mulitpler_HSVM_mat(1) ! 1e-12 
     677        output_mulitpler_dat_mat(12) = output_mulitpler_HSVM_mat(2) ! 1e-12 
    643678        output_mulitpler_AR5_mat(:) = 1. 
    644679        output_mulitpler_SBC_mat(:) = 1. 
    645680 
    646         IF(lwp) THEN  
    647  
    648          
     681        ! On the hour, calculate hourly means from the hourly total,and process the regional means.  
     682 
     683        tmp_field_cnt = tmp_field_cnt + 1 
     684 
     685         
     686        IF ( MOD( kt, i_steps ) == 0 .and. kt .ne. nn_it000 ) THEN 
     687 
     688            
    649689            DO vi=1,19 ! State loop 
    650                WRITE(numout,*)  'JT dia_regmean SBC variable : ',TRIM( name_dat_mat(vi) ) 
     690 
     691               do_reg_mean = .TRUE. 
     692 
     693               IF (vi == 16) THEN 
     694                 IF( .not. ln_diaregmean_karamld ) do_reg_mean = .FALSE.    
     695               ENDIF  
     696 
     697               IF ((vi == 17) .OR. (vi == 18) .OR. (vi == 19) ) THEN 
     698                 IF( .not. ln_diaregmean_pea ) do_reg_mean = .FALSE.    
     699               ENDIF  
     700 
     701               tmp_name=TRIM( name_dat_mat(vi) ) 
     702               IF ( do_reg_mean ) THEN 
     703                   IF (iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_ave'))))    .OR. & 
     704                     & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_tot'))))    .OR. & 
     705                     & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_var'))))    .OR. & 
     706                     & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_cnt'))))    .OR. & 
     707                     & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_reg_id')))) .OR. & 
     708                     & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_mask_id')))) ) THEN 
     709 
     710                        CALL dia_wri_region_mean(kt, TRIM(tmp_name) , output_mulitpler_dat_mat(vi)*tmp_field_mat(:,:,vi)/real(tmp_field_cnt,wp)) 
     711                        WRITE(numout,*)  'JT dia_regmean SBC variable - region mean: ',TRIM( name_dat_mat(vi) ),';' 
     712                    ELSE 
     713                        WRITE(numout,*)  'JT dia_regmean SBC variable - no iom_use: ',TRIM( name_dat_mat(vi) ),';' 
     714                    ENDIF 
     715                ELSE 
     716                    WRITE(numout,*)  'JT dia_regmean SBC variable - no do_reg_mean: ',TRIM( name_dat_mat(vi) ),';',ln_diaregmean_karamld,ln_diaregmean_pea 
     717                ENDIF 
     718                tmp_name="" 
    651719            END DO 
     720             
     721            tmp_field_mat(:,:,:) = 0. 
     722 
    652723            DO vi=1,4 ! State loop 
    653                WRITE(numout,*)  'JT dia_regmean SBC variable : ',TRIM( name_AR5_mat(vi) ) 
    654             END DO 
    655             DO vi=1,7 ! State loop 
    656                WRITE(numout,*)  'JT dia_regmean SBC variable : ',TRIM( name_SBC_mat(vi) ) 
    657             END DO 
    658         ENDIF 
    659  
    660          
    661         tmp_field_cnt = tmp_field_cnt + 1 
    662  
    663         ! On the hour, calculate hourly means from the hourly total,and process the regional means.  
    664          
    665         IF ( MOD( kt, i_steps ) == 0 .and. kt .ne. nn_it000 ) THEN 
    666  
    667             
    668 !            DO vi=1,19 ! State loop 
    669  
    670 !               do_reg_mean = .TRUE. 
    671  
    672 !               IF (vi == 16) THEN 
    673 !                 IF( .not. ln_diaregmean_karamld ) do_reg_mean = .FALSE.    
    674 !               ENDIF  
    675  
    676 !               IF ((vi == 17) .OR. (vi == 18) .OR. (vi == 19) ) THEN 
    677 !                 IF( .not. ln_diaregmean_pea ) do_reg_mean = .FALSE.    
    678 !               ENDIF  
    679  
    680 !               tmp_name=TRIM( name_dat_mat(vi) ) 
    681 !               IF ( do_reg_mean ) THEN 
    682 !                   IF (iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_ave'))))    .OR. & 
    683 !                      & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_tot'))))    .OR. & 
    684 !                      & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_var'))))    .OR. & 
    685 !                      & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_cnt'))))    .OR. & 
    686 !                      & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_reg_id')))) .OR. & 
    687 !                      & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_mask_id')))) ) THEN 
    688  
    689 !                        CALL dia_wri_region_mean(kt, TRIM(tmp_name) , output_mulitpler_dat_mat(vi)*tmp_field_mat(:,:,vi)/real(tmp_field_cnt,wp)) 
    690 !                        WRITE(numout,*)  'JT dia_regmean SBC variable - region mean: ',TRIM( name_dat_mat(vi) ),';' 
    691 !                    ELSE 
    692 !                        WRITE(numout,*)  'JT dia_regmean SBC variable - no iom_use: ',TRIM( name_dat_mat(vi) ),';' 
    693 !                    ENDIF 
    694 !                ELSE 
    695 !                    WRITE(numout,*)  'JT dia_regmean SBC variable - no do_reg_mean: ',TRIM( name_dat_mat(vi) ),';',ln_diaregmean_karamld,ln_diaregmean_pea 
    696 !                ENDIF 
    697 !                tmp_name="" 
    698 !            END DO 
    699 !             
    700 !            tmp_field_mat(:,:,:) = 0. 
    701  
    702  
    703             tmp_name="sst" 
    704             IF (iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_ave'))))    .OR. & 
    705               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_tot'))))    .OR. & 
    706               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_var'))))    .OR. & 
    707               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_cnt'))))    .OR. & 
    708               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_reg_id')))) .OR. & 
    709               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_mask_id')))) ) THEN 
    710  
    711                 CALL dia_wri_region_mean(kt, TRIM(tmp_name) , tmp_field_mat(:,:,1)/real(tmp_field_cnt,wp)) 
    712             ENDIF 
    713             tmp_name="" 
    714  
    715             tmp_name="nbt" 
    716             IF (iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_ave'))))    .OR. & 
    717               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_tot'))))    .OR. & 
    718               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_var'))))    .OR. & 
    719               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_cnt'))))    .OR. & 
    720               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_reg_id')))) .OR. & 
    721               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_mask_id')))) ) THEN 
    722  
    723                 CALL dia_wri_region_mean(kt, TRIM(tmp_name) , tmp_field_mat(:,:,2)/real(tmp_field_cnt,wp)) 
    724             ENDIF 
    725             tmp_name="" 
    726  
    727             tmp_name="dft" 
    728             IF (iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_ave'))))    .OR. & 
    729               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_tot'))))    .OR. & 
    730               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_var'))))    .OR. & 
    731               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_cnt'))))    .OR. & 
    732               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_reg_id')))) .OR. & 
    733               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_mask_id')))) ) THEN 
    734  
    735                 CALL dia_wri_region_mean(kt, TRIM(tmp_name) , tmp_field_mat(:,:,3)/real(tmp_field_cnt,wp)) 
    736             ENDIF 
    737             tmp_name="" 
    738  
    739  
    740             tmp_name="zat" 
    741             IF (iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_ave'))))    .OR. & 
    742               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_tot'))))    .OR. & 
    743               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_var'))))    .OR. & 
    744               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_cnt'))))    .OR. & 
    745               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_reg_id')))) .OR. & 
    746               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_mask_id')))) ) THEN 
    747  
    748                 CALL dia_wri_region_mean(kt, TRIM(tmp_name) , tmp_field_mat(:,:,4)/real(tmp_field_cnt,wp)) 
    749             ENDIF 
    750             tmp_name="" 
    751  
    752  
    753             tmp_name="vat" 
    754             IF (iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_ave'))))    .OR. & 
    755               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_tot'))))    .OR. & 
    756               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_var'))))    .OR. & 
    757               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_cnt'))))    .OR. & 
    758               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_reg_id')))) .OR. & 
    759               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_mask_id')))) ) THEN 
    760  
    761                 CALL dia_wri_region_mean(kt, TRIM(tmp_name) , tmp_field_mat(:,:,5)/real(tmp_field_cnt,wp)) 
    762             ENDIF 
    763             tmp_name="" 
    764  
    765  
    766             tmp_name="heat" 
    767             IF (iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_ave'))))    .OR. & 
    768               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_tot'))))    .OR. & 
    769               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_var'))))    .OR. & 
    770               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_cnt'))))    .OR. & 
    771               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_reg_id')))) .OR. & 
    772               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_mask_id')))) ) THEN 
    773  
    774                 CALL dia_wri_region_mean(kt, TRIM(tmp_name) , tmp_field_mat(:,:,6)/real(tmp_field_cnt,wp)/1e12) 
    775             ENDIF 
    776             tmp_name="" 
    777  
    778             tmp_name="sss" 
    779             IF (iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_ave'))))    .OR. & 
    780               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_tot'))))    .OR. & 
    781               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_var'))))    .OR. & 
    782               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_cnt'))))    .OR. & 
    783               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_reg_id')))) .OR. & 
    784               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_mask_id')))) ) THEN 
    785  
    786                 CALL dia_wri_region_mean(kt, TRIM(tmp_name) , tmp_field_mat(:,:,7)/real(tmp_field_cnt,wp)) 
    787             ENDIF 
    788             tmp_name="" 
    789  
    790             tmp_name="nbs" 
    791             IF (iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_ave'))))    .OR. & 
    792               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_tot'))))    .OR. & 
    793               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_var'))))    .OR. & 
    794               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_cnt'))))    .OR. & 
    795               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_reg_id')))) .OR. & 
    796               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_mask_id')))) ) THEN 
    797  
    798                 CALL dia_wri_region_mean(kt, TRIM(tmp_name) , tmp_field_mat(:,:,8)/real(tmp_field_cnt,wp)) 
    799             ENDIF 
    800             tmp_name="" 
    801  
    802             tmp_name="dfs" 
    803             IF (iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_ave'))))    .OR. & 
    804               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_tot'))))    .OR. & 
    805               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_var'))))    .OR. & 
    806               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_cnt'))))    .OR. & 
    807               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_reg_id')))) .OR. & 
    808               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_mask_id')))) ) THEN 
    809  
    810                 CALL dia_wri_region_mean(kt, TRIM(tmp_name) , tmp_field_mat(:,:,9)/real(tmp_field_cnt,wp)) 
    811             ENDIF 
    812             tmp_name="" 
    813  
    814  
    815             tmp_name="zas" 
    816             IF (iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_ave'))))    .OR. & 
    817               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_tot'))))    .OR. & 
    818               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_var'))))    .OR. & 
    819               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_cnt'))))    .OR. & 
    820               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_reg_id')))) .OR. & 
    821               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_mask_id')))) ) THEN 
    822  
    823                 CALL dia_wri_region_mean(kt, TRIM(tmp_name) , tmp_field_mat(:,:,10)/real(tmp_field_cnt,wp)) 
    824             ENDIF 
    825             tmp_name="" 
    826  
    827  
    828             tmp_name="vas" 
    829             IF (iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_ave'))))    .OR. & 
    830               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_tot'))))    .OR. & 
    831               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_var'))))    .OR. & 
    832               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_cnt'))))    .OR. & 
    833               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_reg_id')))) .OR. & 
    834               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_mask_id')))) ) THEN 
    835  
    836                 CALL dia_wri_region_mean(kt, TRIM(tmp_name) , tmp_field_mat(:,:,11)/real(tmp_field_cnt,wp)) 
    837             ENDIF 
    838             tmp_name="" 
    839  
    840  
    841             tmp_name="salt" 
    842             IF (iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_ave'))))    .OR. & 
    843               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_tot'))))    .OR. & 
    844               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_var'))))    .OR. & 
    845               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_cnt'))))    .OR. & 
    846               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_reg_id')))) .OR. & 
    847               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_mask_id')))) ) THEN 
    848  
    849                 CALL dia_wri_region_mean(kt, TRIM(tmp_name) , tmp_field_mat(:,:,12)/real(tmp_field_cnt,wp)/1e12) 
    850             ENDIF 
    851             tmp_name="" 
    852  
    853             tmp_name="vol" 
    854             IF (iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_ave'))))    .OR. & 
    855               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_tot'))))    .OR. & 
    856               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_var'))))    .OR. & 
    857               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_cnt'))))    .OR. & 
    858               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_reg_id')))) .OR. & 
    859               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_mask_id')))) ) THEN 
    860  
    861                 CALL dia_wri_region_mean(kt, TRIM(tmp_name) , tmp_field_mat(:,:,13)/real(tmp_field_cnt,wp)) 
    862             ENDIF 
    863             tmp_name="" 
    864  
    865  
    866             tmp_name="mass" 
    867             IF (iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_ave'))))    .OR. & 
    868               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_tot'))))    .OR. & 
    869               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_var'))))    .OR. & 
    870               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_cnt'))))    .OR. & 
    871               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_reg_id')))) .OR. & 
    872               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_mask_id')))) ) THEN 
    873  
    874                 CALL dia_wri_region_mean(kt, TRIM(tmp_name) , tmp_field_mat(:,:,14)/real(tmp_field_cnt,wp)) 
    875             ENDIF 
    876             tmp_name="" 
    877  
    878  
    879             tmp_name="ssh" 
    880             IF (iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_ave'))))    .OR. & 
    881               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_tot'))))    .OR. & 
    882               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_var'))))    .OR. & 
    883               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_cnt'))))    .OR. & 
    884               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_reg_id')))) .OR. & 
    885               & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_mask_id')))) ) THEN 
    886  
    887                 CALL dia_wri_region_mean(kt, TRIM(tmp_name) , tmp_field_mat(:,:,15)/real(tmp_field_cnt,wp)) 
    888             ENDIF 
    889             tmp_name="" 
    890  
    891  
    892  
    893  
    894  
    895  
    896             !CALL dia_wri_region_mean(kt, "sst" , tmp_field_mat(:,:,1)/real(tmp_field_cnt,wp)) 
    897             !CALL dia_wri_region_mean(kt, "nbt" , tmp_field_mat(:,:,2)/real(tmp_field_cnt,wp)) 
    898             !CALL dia_wri_region_mean(kt, "dft" , tmp_field_mat(:,:,3)/real(tmp_field_cnt,wp)) 
    899  
    900             !CALL dia_wri_region_mean(kt, "zat" , tmp_field_mat(:,:,4)/real(tmp_field_cnt,wp)) 
    901             !CALL dia_wri_region_mean(kt, "vat" , tmp_field_mat(:,:,5)/real(tmp_field_cnt,wp)) 
    902             !CALL dia_wri_region_mean(kt, "heat" , tmp_field_mat(:,:,6)/real(tmp_field_cnt,wp)/1e12) 
    903  
    904             !CALL dia_wri_region_mean(kt, "sss" , tmp_field_mat(:,:,7)/real(tmp_field_cnt,wp)) 
    905             !CALL dia_wri_region_mean(kt, "nbs" , tmp_field_mat(:,:,8)/real(tmp_field_cnt,wp)) 
    906             !CALL dia_wri_region_mean(kt, "dfs" , tmp_field_mat(:,:,9)/real(tmp_field_cnt,wp)) 
    907  
    908             !CALL dia_wri_region_mean(kt, "zas" , tmp_field_mat(:,:,10)/real(tmp_field_cnt,wp)) 
    909             !CALL dia_wri_region_mean(kt, "vas" , tmp_field_mat(:,:,11)/real(tmp_field_cnt,wp)) 
    910             !CALL dia_wri_region_mean(kt, "salt" , tmp_field_mat(:,:,12)/real(tmp_field_cnt,wp)/1e12) 
    911  
    912             !CALL dia_wri_region_mean(kt, "vol" , tmp_field_mat(:,:,13)/real(tmp_field_cnt,wp)) 
    913             !CALL dia_wri_region_mean(kt, "mass" , tmp_field_mat(:,:,14)/real(tmp_field_cnt,wp)) 
    914  
    915             !CALL dia_wri_region_mean(kt, "ssh" , tmp_field_mat(:,:,15)/real(tmp_field_cnt,wp)) 
    916  
    917  
    918             IF( ln_diaregmean_karamld  ) THEN     
    919                 tmp_name="mldkara" 
     724 
     725                tmp_name=TRIM( name_HSCM_mat(vi) ) // trim('_inst') 
    920726                IF (iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_ave'))))    .OR. & 
    921727                  & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_tot'))))    .OR. & 
     
    925731                  & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_mask_id')))) ) THEN 
    926732 
    927                     CALL dia_wri_region_mean(kt, TRIM(tmp_name) , tmp_field_mat(:,:,16)/real(tmp_field_cnt,wp)) 
     733                    CALL dia_wri_region_mean(kt, TRIM(tmp_name) , output_mulitpler_HSVM_mat(vi)*tmp_field_HSVM_mat(:,:,vi)) 
    928734                ENDIF 
    929735                tmp_name="" 
    930        
    931                 !CALL dia_wri_region_mean(kt, "mldkara" , tmp_field_mat(:,:,16)/real(tmp_field_cnt,wp)) ! tm 
    932             ENDIF 
    933  
    934             IF( ln_diaregmean_pea  ) THEN           
    935  
    936                 tmp_name="pea" 
    937                 IF (iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_ave'))))    .OR. & 
    938                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_tot'))))    .OR. & 
    939                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_var'))))    .OR. & 
    940                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_cnt'))))    .OR. & 
    941                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_reg_id')))) .OR. & 
    942                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_mask_id')))) ) THEN 
    943  
    944                     CALL dia_wri_region_mean(kt, TRIM(tmp_name) , tmp_field_mat(:,:,17)/real(tmp_field_cnt,wp)) 
    945                 ENDIF 
    946                 tmp_name="" 
    947  
    948                 tmp_name="peat" 
    949                 IF (iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_ave'))))    .OR. & 
    950                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_tot'))))    .OR. & 
    951                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_var'))))    .OR. & 
    952                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_cnt'))))    .OR. & 
    953                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_reg_id')))) .OR. & 
    954                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_mask_id')))) ) THEN 
    955  
    956                     CALL dia_wri_region_mean(kt, TRIM(tmp_name) , tmp_field_mat(:,:,18)/real(tmp_field_cnt,wp)) 
    957                 ENDIF 
    958                 tmp_name="" 
    959  
    960  
    961                 tmp_name="peas" 
    962                 IF (iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_ave'))))    .OR. & 
    963                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_tot'))))    .OR. & 
    964                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_var'))))    .OR. & 
    965                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_cnt'))))    .OR. & 
    966                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_reg_id')))) .OR. & 
    967                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_mask_id')))) ) THEN 
    968  
    969                     CALL dia_wri_region_mean(kt, TRIM(tmp_name) , tmp_field_mat(:,:,19)/real(tmp_field_cnt,wp)) 
    970                 ENDIF 
    971                 tmp_name="" 
    972  
    973  
    974                 !CALL dia_wri_region_mean(kt, "pea"  , tmp_field_mat(:,:,17)/real(tmp_field_cnt,wp)) 
    975                 !CALL dia_wri_region_mean(kt, "peat" , tmp_field_mat(:,:,18)/real(tmp_field_cnt,wp)) 
    976                 !CALL dia_wri_region_mean(kt, "peas" , tmp_field_mat(:,:,19)/real(tmp_field_cnt,wp)) ! tmb 
    977             ENDIF 
    978  
    979             tmp_field_mat(:,:,:) = 0. 
    980  
     736            END DO 
     737 
     738            tmp_field_HSVM_mat(:,:,:) = 0. 
    981739            IF( ln_diaregmean_diaar5  ) THEN 
    982  
    983                 tmp_name="ssh_steric" 
    984                 IF (iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_ave'))))    .OR. & 
    985                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_tot'))))    .OR. & 
    986                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_var'))))    .OR. & 
    987                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_cnt'))))    .OR. & 
    988                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_reg_id')))) .OR. & 
    989                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_mask_id')))) ) THEN 
    990  
    991                     CALL dia_wri_region_mean(kt, TRIM(tmp_name) , tmp_field_AR5_mat(:,:,1)/real(tmp_field_cnt,wp)) 
    992                 ENDIF 
    993                 tmp_name="" 
    994  
    995                 tmp_name="ssh_thermosteric" 
    996                 IF (iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_ave'))))    .OR. & 
    997                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_tot'))))    .OR. & 
    998                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_var'))))    .OR. & 
    999                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_cnt'))))    .OR. & 
    1000                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_reg_id')))) .OR. & 
    1001                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_mask_id')))) ) THEN 
    1002  
    1003                     CALL dia_wri_region_mean(kt, TRIM(tmp_name) , tmp_field_AR5_mat(:,:,2)/real(tmp_field_cnt,wp)) 
    1004                 ENDIF 
    1005                 tmp_name="" 
    1006  
    1007                 tmp_name="ssh_halosteric" 
    1008                 IF (iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_ave'))))    .OR. & 
    1009                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_tot'))))    .OR. & 
    1010                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_var'))))    .OR. & 
    1011                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_cnt'))))    .OR. & 
    1012                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_reg_id')))) .OR. & 
    1013                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_mask_id')))) ) THEN 
    1014  
    1015                     CALL dia_wri_region_mean(kt, TRIM(tmp_name) , tmp_field_AR5_mat(:,:,3)/real(tmp_field_cnt,wp)) 
    1016                 ENDIF 
    1017                 tmp_name="" 
    1018  
    1019                 tmp_name="bot_pres" 
    1020                 IF (iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_ave'))))    .OR. & 
    1021                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_tot'))))    .OR. & 
    1022                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_var'))))    .OR. & 
    1023                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_cnt'))))    .OR. & 
    1024                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_reg_id')))) .OR. & 
    1025                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_mask_id')))) ) THEN 
    1026  
    1027                     CALL dia_wri_region_mean(kt, TRIM(tmp_name) , tmp_field_AR5_mat(:,:,4)/real(tmp_field_cnt,wp)) 
    1028                 ENDIF 
    1029                 tmp_name="" 
    1030  
    1031                 !CALL dia_wri_region_mean(kt, "ssh_steric" ,      tmp_field_AR5_mat(:,:,1)/real(tmp_field_cnt,wp)) 
    1032                 !CALL dia_wri_region_mean(kt, "ssh_thermosteric", tmp_field_AR5_mat(:,:,2)/real(tmp_field_cnt,wp)) 
    1033                 !CALL dia_wri_region_mean(kt, "ssh_halosteric" ,  tmp_field_AR5_mat(:,:,3)/real(tmp_field_cnt,wp)) 
    1034                 !CALL dia_wri_region_mean(kt, "bot_pres" ,        tmp_field_AR5_mat(:,:,4)/real(tmp_field_cnt,wp)) 
     740                DO vi=1,4 ! State loop 
     741 
     742                    tmp_name=TRIM( name_AR5_mat(vi) ) 
     743                    IF (iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_ave'))))    .OR. & 
     744                      & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_tot'))))    .OR. & 
     745                      & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_var'))))    .OR. & 
     746                      & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_cnt'))))    .OR. & 
     747                      & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_reg_id')))) .OR. & 
     748                      & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_mask_id')))) ) THEN 
     749 
     750                        CALL dia_wri_region_mean(kt, TRIM(tmp_name) , output_mulitpler_AR5_mat(vi)*tmp_field_AR5_mat(:,:,vi)/real(tmp_field_cnt,wp)) 
     751                    ENDIF 
     752                    tmp_name="" 
     753                END DO 
    1035754                tmp_field_AR5_mat(:,:,:) = 0. 
    1036755            ENDIF 
    1037756 
    1038757            IF( ln_diaregmean_diasbc  ) THEN 
    1039  
    1040  
    1041  
    1042                 tmp_name="qt" 
    1043                 IF (iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_ave'))))    .OR. & 
    1044                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_tot'))))    .OR. & 
    1045                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_var'))))    .OR. & 
    1046                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_cnt'))))    .OR. & 
    1047                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_reg_id')))) .OR. & 
    1048                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_mask_id')))) ) THEN 
    1049  
    1050                     CALL dia_wri_region_mean(kt, TRIM(tmp_name) , tmp_field_SBC_mat(:,:,1)/real(tmp_field_cnt,wp)) 
    1051                 ENDIF 
    1052                 tmp_name="" 
    1053  
    1054                 tmp_name="qsr" 
    1055                 IF (iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_ave'))))    .OR. & 
    1056                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_tot'))))    .OR. & 
    1057                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_var'))))    .OR. & 
    1058                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_cnt'))))    .OR. & 
    1059                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_reg_id')))) .OR. & 
    1060                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_mask_id')))) ) THEN 
    1061  
    1062                     CALL dia_wri_region_mean(kt, TRIM(tmp_name) , tmp_field_SBC_mat(:,:,2)/real(tmp_field_cnt,wp)) 
    1063                 ENDIF 
    1064                 tmp_name="" 
    1065  
    1066                 tmp_name="qns" 
    1067                 IF (iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_ave'))))    .OR. & 
    1068                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_tot'))))    .OR. & 
    1069                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_var'))))    .OR. & 
    1070                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_cnt'))))    .OR. & 
    1071                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_reg_id')))) .OR. & 
    1072                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_mask_id')))) ) THEN 
    1073  
    1074                     CALL dia_wri_region_mean(kt, TRIM(tmp_name) , tmp_field_SBC_mat(:,:,3)/real(tmp_field_cnt,wp)) 
    1075                 ENDIF 
    1076                 tmp_name="" 
    1077  
    1078                 tmp_name="emp" 
    1079                 IF (iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_ave'))))    .OR. & 
    1080                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_tot'))))    .OR. & 
    1081                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_var'))))    .OR. & 
    1082                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_cnt'))))    .OR. & 
    1083                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_reg_id')))) .OR. & 
    1084                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_mask_id')))) ) THEN 
    1085  
    1086                     CALL dia_wri_region_mean(kt, TRIM(tmp_name) , tmp_field_SBC_mat(:,:,4)/real(tmp_field_cnt,wp)) 
    1087                 ENDIF 
    1088                 tmp_name="" 
    1089  
    1090                 tmp_name="wspd" 
    1091                 IF (iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_ave'))))    .OR. & 
    1092                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_tot'))))    .OR. & 
    1093                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_var'))))    .OR. & 
    1094                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_cnt'))))    .OR. & 
    1095                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_reg_id')))) .OR. & 
    1096                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_mask_id')))) ) THEN 
    1097  
    1098                     CALL dia_wri_region_mean(kt, TRIM(tmp_name) , tmp_field_SBC_mat(:,:,5)/real(tmp_field_cnt,wp)) 
    1099                 ENDIF 
    1100                 tmp_name="" 
    1101  
    1102                 tmp_name="mslp" 
    1103                 IF (iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_ave'))))    .OR. & 
    1104                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_tot'))))    .OR. & 
    1105                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_var'))))    .OR. & 
    1106                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_cnt'))))    .OR. & 
    1107                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_reg_id')))) .OR. & 
    1108                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_mask_id')))) ) THEN 
    1109  
    1110                     CALL dia_wri_region_mean(kt, TRIM(tmp_name) , tmp_field_SBC_mat(:,:,6)/real(tmp_field_cnt,wp)) 
    1111                 ENDIF 
    1112                 tmp_name="" 
    1113  
    1114                 tmp_name="rnf" 
    1115                 IF (iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_ave'))))    .OR. & 
    1116                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_tot'))))    .OR. & 
    1117                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_var'))))    .OR. & 
    1118                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_cnt'))))    .OR. & 
    1119                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_reg_id')))) .OR. & 
    1120                   & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_mask_id')))) ) THEN 
    1121  
    1122                     CALL dia_wri_region_mean(kt, TRIM(tmp_name) , tmp_field_SBC_mat(:,:,7)/real(tmp_field_cnt,wp)) 
    1123                 ENDIF 
    1124                 tmp_name="" 
    1125  
    1126                 !CALL dia_wri_region_mean(kt, "qt"   , tmp_field_SBC_mat(:,:,1)/real(tmp_field_cnt,wp)) 
    1127                 !CALL dia_wri_region_mean(kt, "qsr"  , tmp_field_SBC_mat(:,:,2)/real(tmp_field_cnt,wp)) 
    1128                 !CALL dia_wri_region_mean(kt, "qns"  , tmp_field_SBC_mat(:,:,3)/real(tmp_field_cnt,wp)) 
    1129                 !CALL dia_wri_region_mean(kt, "emp"  , tmp_field_SBC_mat(:,:,4)/real(tmp_field_cnt,wp)) 
    1130                 !CALL dia_wri_region_mean(kt, "wspd" , tmp_field_SBC_mat(:,:,5)/real(tmp_field_cnt,wp)) 
    1131                 !CALL dia_wri_region_mean(kt, "mslp" , tmp_field_SBC_mat(:,:,6)/real(tmp_field_cnt,wp)) 
    1132                 !CALL dia_wri_region_mean(kt, "rnf"  , tmp_field_SBC_mat(:,:,7)/real(tmp_field_cnt,wp)) 
     758                DO vi=1,7 ! State loop 
     759 
     760                    tmp_name=TRIM( name_SBC_mat(vi) ) 
     761                    IF (iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_ave'))))    .OR. & 
     762                      & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_tot'))))    .OR. & 
     763                      & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_var'))))    .OR. & 
     764                      & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_cnt'))))    .OR. & 
     765                      & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_reg_id')))) .OR. & 
     766                      & iom_use(trim( trim(trim("reg_") // trim(tmp_name) // trim('_mask_id')))) ) THEN 
     767 
     768                        CALL dia_wri_region_mean(kt, TRIM(tmp_name) , output_mulitpler_SBC_mat(vi)*tmp_field_SBC_mat(:,:,vi)/real(tmp_field_cnt,wp)) 
     769                    ENDIF 
     770                    tmp_name="" 
     771                END DO 
    1133772                tmp_field_SBC_mat(:,:,:) = 0. 
    1134  
    1135773            ENDIF 
     774 
    1136775 
    1137776#if defined key_fabm 
     
    1218857                ENDIF 
    1219858 
    1220                 DEALLOCATE( region_mask, nreg_mat, tmp_field_mat) 
     859                DEALLOCATE( region_mask, nreg_mat, tmp_field_mat,tmp_field_HSVM_mat) 
    1221860                IF( ln_diaregmean_diaar5  ) DEALLOCATE( tmp_field_AR5_mat) 
    1222861                IF( ln_diaregmean_diasbc  ) DEALLOCATE( tmp_field_SBC_mat) 
     
    1258897      REAL(wp), ALLOCATABLE, DIMENSION(:) ::   zrmet_ave,zrmet_tot,zrmet_var,zrmet_cnt,zrmet_mask_id,zrmet_reg_id  ,zrmet_min,zrmet_max 
    1259898      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::   zrmet_out 
    1260       REAL(wp), ALLOCATABLE,   DIMENSION(:) ::   ave_mat,tot_mat,num_mat,var_mat,ssq_mat,cnt_mat,reg_id_mat,mask_id_mat ,min_mat,max_mat   !: region_mask 
     899      REAL(wp), ALLOCATABLE,   DIMENSION(:) ::   ave_mat,tot_mat,num_mat,var_mat,ssq_mat,cnt_mat,reg_id_mat,mask_id_mat    !: region_mask 
     900      !REAL(wp), ALLOCATABLE,   DIMENSION(:) ::   min_mat,max_mat   !: region_mask 
    1261901       
    1262902      REAL(wp)                         ::   zmdi, zrmet_val      ! set masked values 
     
    13651005          IF( ierr /= 0 )   CALL ctl_stop( 'dia_wri_region_mean: failed to allocate cnt_mat array' ) 
    13661006 
    1367           ALLOCATE( min_mat(nreg),  STAT= ierr ) 
    1368           IF( ierr /= 0 )   CALL ctl_stop( 'dia_wri_region_mean: failed to allocate min_mat array' ) 
    1369           ALLOCATE( max_mat(nreg),  STAT= ierr ) 
    1370           IF( ierr /= 0 )   CALL ctl_stop( 'dia_wri_region_mean: failed to allocate max_mat array' ) 
     1007          !ALLOCATE( min_mat(nreg),  STAT= ierr ) 
     1008          !IF( ierr /= 0 )   CALL ctl_stop( 'dia_wri_region_mean: failed to allocate min_mat array' ) 
     1009          !ALLOCATE( max_mat(nreg),  STAT= ierr ) 
     1010          !IF( ierr /= 0 )   CALL ctl_stop( 'dia_wri_region_mean: failed to allocate max_mat array' ) 
    13711011 
    13721012          ALLOCATE( reg_id_mat(nreg),  STAT= ierr ) 
     
    13841024          ssq_mat(:) = 0. 
    13851025 
    1386           min_mat(:) = zmdi 
    1387           max_mat(:) = -zmdi 
     1026          !min_mat(:) = zmdi 
     1027          !max_mat(:) = -zmdi 
    13881028          reg_id_mat(:) = 0. 
    13891029          mask_id_mat(:) = 0. 
     
    14031043                        cnt_mat(ind) = cnt_mat(ind) + 1. 
    14041044 
    1405                         min_mat(ind) = min(min_mat(ind),internal_infield(ji,jj)) 
    1406                         max_mat(ind) = max(max_mat(ind),internal_infield(ji,jj)) 
     1045                        !min_mat(ind) = min(min_mat(ind),internal_infield(ji,jj)) 
     1046                        !max_mat(ind) = max(max_mat(ind),internal_infield(ji,jj)) 
    14071047                    ENDIF 
    14081048              END DO 
     
    14111051          ! sum the totals, the counts, and the squares across the processors           
    14121052          CALL mpp_sum( 'diaregionmean',tot_mat,nreg ) 
    1413           IF(lwp .AND. verbose) WRITE(numout,*) 'dia_wri_region_mean : '//tmp_name//'; finished mpp_sum 1' 
    1414           CALL mpp_sum( 'diaregionmean',ssq_mat,nreg ) 
    1415           IF(lwp .AND. verbose) WRITE(numout,*) 'dia_wri_region_mean : '//tmp_name//'; finished mpp_sum 2' 
     1053          IF(lwp .AND. verbose) WRITE(numout,*) 'dia_wri_region_mean : '//tmp_name//'; finished mpp_sum tot' 
    14161054          CALL mpp_sum( 'diaregionmean',cnt_mat,nreg ) 
    1417           IF(lwp .AND. verbose) WRITE(numout,*) 'dia_wri_region_mean : '//tmp_name//'; finished mpp_sum 2' 
    1418  
    1419           CALL mpp_min( 'diaregionmean',min_mat,nreg ) 
    1420           IF(lwp .AND. verbose) WRITE(numout,*) 'dia_wri_region_mean : '//tmp_name//'; finished mpp_min' 
    1421           CALL mpp_max( 'diaregionmean',max_mat,nreg ) 
    1422           IF(lwp .AND. verbose) WRITE(numout,*) 'dia_wri_region_mean : '//tmp_name//'; finished mpp_max' 
    1423            
     1055          IF(lwp .AND. verbose) WRITE(numout,*) 'dia_wri_region_mean : '//tmp_name//'; finished mpp_sum cnt' 
     1056 
     1057 
     1058 
     1059          !tmp_name_iom =  trim(trim("reg_") // trim(tmp_name) // trim('_var')) 
     1060          !IF (iom_use(trim(tmp_name_iom)) .OR. ln_diaregmean_bin .OR. ln_diaregmean_ascii) THEN 
     1061              CALL mpp_sum( 'diaregionmean',ssq_mat,nreg ) 
     1062              IF(lwp .AND. verbose) WRITE(numout,*) 'dia_wri_region_mean : '//tmp_name//'; finished mpp_sum ssq' 
     1063          !ENDIF 
     1064           
     1065     
     1066 
     1067          !tmp_name_iom =  trim(trim("reg_") // trim(tmp_name) // trim('_min')) 
     1068          !IF (iom_use(trim(tmp_name_iom)) .OR. ln_diaregmean_bin .OR. ln_diaregmean_ascii) THEN 
     1069              !CALL mpp_min( 'diaregionmean',min_mat,nreg ) 
     1070              !IF(lwp .AND. verbose) WRITE(numout,*) 'dia_wri_region_mean : '//tmp_name//'; finished mpp_min' 
     1071          !ENDIF 
     1072           
     1073 
     1074          !tmp_name_iom =  trim(trim("reg_") // trim(tmp_name) // trim('_max')) 
     1075          !IF (iom_use(trim(tmp_name_iom)) .OR. ln_diaregmean_bin .OR. ln_diaregmean_ascii)  THEN 
     1076              !CALL mpp_max( 'diaregionmean',max_mat,nreg ) 
     1077              !IF(lwp .AND. verbose) WRITE(numout,*) 'dia_wri_region_mean : '//tmp_name//'; finished mpp_max' 
     1078          !ENDIF 
    14241079           
    14251080          !calculate the mean and variance from the total, sum of squares and the count.  
     
    14481103                  WRITE(numdct_reg_bin) ssq_mat 
    14491104                  WRITE(numdct_reg_bin) cnt_mat 
    1450                   WRITE(numdct_reg_bin) min_mat 
    1451                   WRITE(numdct_reg_bin) max_mat 
     1105                  !WRITE(numdct_reg_bin) min_mat 
     1106                  !WRITE(numdct_reg_bin) max_mat 
    14521107              ENDIF 
    14531108               
     
    14631118                  WRITE(numdct_reg_txt, FMT=trim(FormatString)) trim(tmp_name)//" "//"ssq_mat:", ssq_mat 
    14641119                  WRITE(numdct_reg_txt, FMT=trim(FormatString)) trim(tmp_name)//" "//"cnt_mat:", cnt_mat 
    1465                   WRITE(numdct_reg_txt, FMT=trim(FormatString)) trim(tmp_name)//" "//"min_mat:", min_mat 
    1466                   WRITE(numdct_reg_txt, FMT=trim(FormatString)) trim(tmp_name)//" "//"max_mat:", max_mat 
     1120                  !WRITE(numdct_reg_txt, FMT=trim(FormatString)) trim(tmp_name)//" "//"min_mat:", min_mat 
     1121                  !WRITE(numdct_reg_txt, FMT=trim(FormatString)) trim(tmp_name)//" "//"max_mat:", max_mat 
    14671122                  WRITE(numdct_reg_txt, FMT=trim(FormatString)) trim(tmp_name)//" "//"reg_mat:", reg_id_mat 
    14681123                  WRITE(numdct_reg_txt, FMT=trim(FormatString)) trim(tmp_name)//" "//"msk_mat:", mask_id_mat 
     
    14751130                  zrmet_var(    reg_ind_cnt) =     var_mat(jm) 
    14761131                  zrmet_cnt(    reg_ind_cnt) =     cnt_mat(jm) 
    1477                   zrmet_min(    reg_ind_cnt) =     min_mat(jm) 
    1478                   zrmet_max(    reg_ind_cnt) =     max_mat(jm) 
     1132                  !zrmet_min(    reg_ind_cnt) =     min_mat(jm) 
     1133                  !zrmet_max(    reg_ind_cnt) =     max_mat(jm) 
    14791134                  zrmet_reg_id( reg_ind_cnt) =  reg_id_mat(jm) 
    14801135                  zrmet_mask_id(reg_ind_cnt) = mask_id_mat(jm) 
     
    14861141         
    14871142          IF(lwp .AND. verbose) WRITE(numout,*) 'dia_regmean about to deallocated arrays for ',kt,maskno 
    1488           DEALLOCATE(ave_mat,tot_mat,num_mat,var_mat,ssq_mat,cnt_mat,min_mat,max_mat,reg_id_mat,mask_id_mat) 
     1143          DEALLOCATE(ave_mat,tot_mat,num_mat,var_mat,ssq_mat,cnt_mat,reg_id_mat,mask_id_mat) 
     1144          !DEALLOCATE(min_mat,max_mat) 
    14891145 
    14901146          IF(lwp .AND. verbose) WRITE(numout,*) 'dia_regmean deallocated arrays for ',kt,maskno 
    1491           IF(lwp)CALL FLUSH(numdct_reg_txt) 
     1147          IF(lwp .AND. ln_diaregmean_ascii ) CALL FLUSH(numdct_reg_txt) 
    14921148          IF(lwp .AND. verbose) WRITE(numout,*) 'dia_regmean flushed region mean text for ',kt,maskno 
    14931149      END DO 
  • NEMO/branches/UKMO/NEMO_4.0.4_CO9_shelf_climate/src/OCE/IOM/iom.F90

    r15343 r15357  
    137137      LOGICAL :: ln_diaregmean_diaar5  ! region mean calculation including AR5 SLR terms 
    138138      LOGICAL :: ln_diaregmean_diasbc  ! region mean calculation including Surface BC 
     139      INTEGER :: nn_diaregmean_nhourlymean ! region mean number of hours in mean (normally 1., <0 = instantanous (slower)) 
    139140     
    140141#if defined key_fabm 
     
    166167#if defined key_fabm 
    167168      NAMELIST/nam_diaregmean/ ln_diaregmean,nn_regions_output,ln_diaregmean_ascii,ln_diaregmean_bin,ln_diaregmean_nc,& 
    168         & ln_diaregmean_karamld, ln_diaregmean_pea,ln_diaregmean_diaar5,ln_diaregmean_diasbc,ln_diaregmean_bgc 
     169        & ln_diaregmean_karamld, ln_diaregmean_pea,ln_diaregmean_diaar5,ln_diaregmean_diasbc,ln_diaregmean_bgc,nn_diaregmean_nhourlymean 
    169170#else 
    170171      NAMELIST/nam_diaregmean/ ln_diaregmean,nn_regions_output,ln_diaregmean_ascii,ln_diaregmean_bin,ln_diaregmean_nc,& 
    171         & ln_diaregmean_karamld, ln_diaregmean_pea,ln_diaregmean_diaar5,ln_diaregmean_diasbc 
     172        & ln_diaregmean_karamld, ln_diaregmean_pea,ln_diaregmean_diaar5,ln_diaregmean_diasbc,nn_diaregmean_nhourlymean 
    172173#endif 
    173174       
Note: See TracChangeset for help on using the changeset viewer.