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

Changeset 15333


Ignore:
Timestamp:
2021-10-05T18:12:13+02:00 (3 years ago)
Author:
hadjt
Message:

Adding Regional Means, but without XIOS or MLD.

Search on
!JT MLD
!JT IOM

in IOM/iom.F90 and DIA/diaregmean.F90

to see the code commented out.

Location:
NEMO/branches/UKMO/NEMO_4.0.4_CO9_shelf_climate/src/OCE
Files:
1 added
5 edited

Legend:

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

    r15328 r15333  
    3636   !JT 
    3737   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   tn0          ! initial temperature 
     38   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sshthster_mat         ! ssh_thermosteric height 
     39   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sshhlster_mat         ! ssh_halosteric height 
     40   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sshsteric_mat         ! ssh_steric height 
     41   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   zbotpres_mat          ! bottom pressure 
     42 
    3843   !JT 
    3944 
     
    6469      CALL mpp_sum ( 'diaar5', dia_ar5_alloc ) 
    6570      IF( dia_ar5_alloc /= 0 )   CALL ctl_stop( 'STOP', 'dia_ar5_alloc: failed to allocate Temp arrays' ) 
     71 
     72      ALLOCATE( sshthster_mat(jpi,jpj),sshhlster_mat(jpi,jpj),sshsteric_mat(jpi,jpj), & 
     73          & zbotpres_mat(jpi,jpj),STAT=dia_ar5_alloc ) 
     74      CALL mpp_sum ( 'diaar5', dia_ar5_alloc ) 
     75      IF( dia_ar5_alloc /= 0 )   CALL ctl_stop( 'STOP', 'dia_ar5_alloc: failed to allocate Temp arrays' ) 
     76 
    6677      !JT 
    6778      ! 
  • NEMO/branches/UKMO/NEMO_4.0.4_CO9_shelf_climate/src/OCE/DIA/diawri.F90

    r15329 r15333  
    4848   USE dia25h         ! 25h Mean output 
    4949   !JT 
     50   USE diaregmean      ! regionalmean 
    5051   USE diapea         ! pea 
    5152   !JT 
     
    425426         CALL dia_pea( kt ) 
    426427      ENDIF 
     428    
     429      IF (ln_diaregmean) THEN 
     430         !write(*,*) kt,narea,'diawri before dia_regmean' 
     431         CALL dia_regmean( kt ) 
     432         !write(*,*) kt,narea,'diawri after dia_regmean' 
     433      ENDIF 
     434 
    427435      !JT 
    428436 
  • NEMO/branches/UKMO/NEMO_4.0.4_CO9_shelf_climate/src/OCE/IOM/in_out_manager.F90

    r14078 r15333  
    155155   INTEGER ::   numfl           =   -1      !: logical unit for floats ascii output 
    156156   INTEGER ::   numflo          =   -1      !: logical unit for floats ascii output 
     157   !JT  
     158   INTEGER ::   numdct_reg_bin     =   -1      !: logical unit for NOOS    transports output 
     159   INTEGER ::   numdct_reg_txt   =   -1      !: logical unit for NOOS hourly transports output 
     160   !JT 
    157161 
    158162   !!---------------------------------------------------------------------- 
  • NEMO/branches/UKMO/NEMO_4.0.4_CO9_shelf_climate/src/OCE/IOM/iom.F90

    r14078 r15333  
    5858   PUBLIC iom_init, iom_swap, iom_open, iom_close, iom_setkt, iom_varid, iom_get, iom_get_var 
    5959   PUBLIC iom_chkatt, iom_getatt, iom_putatt, iom_getszuld, iom_rstput, iom_delay_rst, iom_put 
     60 
     61   !JT 
     62   INTEGER , PUBLIC ::   n_regions_output 
     63   !JT 
     64 
    6065   PUBLIC iom_use, iom_context_finalize, iom_miss_val 
    6166 
     
    116121      INTEGER ::   nldi_save, nlei_save    !:      and close boundaries in output files 
    117122      INTEGER ::   nldj_save, nlej_save    !: 
     123 
     124 
     125 
     126 
     127    !JT 
     128 
     129      REAL(wp),  ALLOCATABLE,   DIMENSION(:,:) ::   tmpregion !: temporary region_mask 
     130      INTEGER, DIMENSION(3) ::   zdimsz   ! number of elements in each of the 3 dimensions (i.e., lon, lat, no of masks, 297,  375,  4) for an array 
     131      INTEGER               ::   zndims   ! number of dimensions in an array (i.e. 3, ) 
     132      INTEGER :: inum, nmasks,ierr,maskno,idmaskvar,tmpint 
     133      REAL(wp), ALLOCATABLE,   DIMENSION(:,:,:)  ::   tmp_region_mask_real   ! tempory region_mask of reals 
     134       
     135      LOGICAL ::   ln_diaregmean  ! region mean calculation 
     136    
     137     
     138      INTEGER :: ios                  ! Local integer output status for namelist read 
     139      LOGICAL :: ln_diaregmean_ascii  ! region mean calculation ascii output 
     140      LOGICAL :: ln_diaregmean_bin  ! region mean calculation binary output 
     141      LOGICAL :: ln_diaregmean_nc  ! region mean calculation netcdf output 
     142      LOGICAL :: ln_diaregmean_karamld  ! region mean calculation including kara mld terms 
     143      LOGICAL :: ln_diaregmean_pea  ! region mean calculation including pea terms 
     144      LOGICAL :: ln_diaregmean_diaar5  ! region mean calculation including AR5 SLR terms 
     145      LOGICAL :: ln_diaregmean_diasbc  ! region mean calculation including Surface BC 
     146     
     147#if defined key_fabm 
     148      LOGICAL :: ln_diaregmean_bgc  ! region mean calculation including BGC 
     149#endif 
     150 
     151 
     152    !JT 
     153 
    118154      !!---------------------------------------------------------------------- 
    119155      ! 
     
    132168      ! 
    133169      ALLOCATE( zt_bnds(2,jpk), zw_bnds(2,jpk) ) 
    134       ! 
     170 
     171 
     172    !JT 
     173      ! Read the number region mask to work out how many regions are needed. 
     174       
     175#if defined key_fabm 
     176      NAMELIST/nam_diaregmean/ ln_diaregmean,ln_diaregmean_ascii,ln_diaregmean_bin,ln_diaregmean_nc,& 
     177        & ln_diaregmean_karamld, ln_diaregmean_pea,ln_diaregmean_diaar5,ln_diaregmean_diasbc,ln_diaregmean_bgc 
     178#else 
     179      NAMELIST/nam_diaregmean/ ln_diaregmean,ln_diaregmean_ascii,ln_diaregmean_bin,ln_diaregmean_nc,& 
     180        & ln_diaregmean_karamld, ln_diaregmean_pea,ln_diaregmean_diaar5,ln_diaregmean_diasbc 
     181#endif 
     182       
     183      ! read in Namelist.  
     184      !!---------------------------------------------------------------------- 
     185      ! 
     186      REWIND ( numnam_ref )              ! Read Namelist nam_diatmb in referdiatmbence namelist : TMB diagnostics 
     187      READ   ( numnam_ref, nam_diaregmean, IOSTAT=ios, ERR= 901 ) 
     188901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_diaregmean in reference namelist' ) 
     189 
     190      REWIND( numnam_cfg )              ! Namelist nam_diatmb in configuration namelist  TMB diagnostics 
     191      READ  ( numnam_cfg, nam_diaregmean, IOSTAT = ios, ERR = 902 ) 
     192902   IF( ios > 0 ) CALL ctl_nam ( ios , 'nam_diaregmean in configuration namelist' ) 
     193      IF(lwm) WRITE ( numond, nam_diaregmean ) 
     194 
     195      IF (ln_diaregmean) THEN 
     196       
     197        ! Open region mask for region means, and retrieve the size of the mask (number of levels)           
     198          CALL iom_open ( 'region_mask.nc', inum ) 
     199          idmaskvar = iom_varid( inum, 'mask', kdimsz=zdimsz, kndims=zndims, ldstop = .FALSE.)           
     200          nmasks = zdimsz(3) 
     201           
     202          ! read in the region mask (which contains floating point numbers) into a temporary array of reals. 
     203          ALLOCATE( tmp_region_mask_real(jpi,jpj,nmasks),  STAT= ierr ) 
     204          IF( ierr /= 0 )   CALL ctl_stop( 'dia_regmean_init: failed to allocate tmp_region_mask_real array' ) 
     205           
     206          ! Use jpdom_unknown to read in a n layer mask. 
     207          tmp_region_mask_real(:,:,:) = 0 
     208          CALL iom_get( inum, jpdom_unknown, 'mask', tmp_region_mask_real(1:nlci,1:nlcj,1:nmasks),   & 
     209              &          kstart = (/ mig(1),mjg(1),1 /), kcount = (/ nlci,nlcj,nmasks /) ) 
     210           
     211          CALL iom_close( inum ) 
     212          !Convert the region mask of reals into one of integers.  
     213           
     214           
     215          n_regions_output = 0 
     216          DO maskno = 1,nmasks 
     217              tmpint = maxval(int(tmp_region_mask_real(:,:,maskno))) 
     218              CALL mpp_max( 'iom',tmpint ) 
     219              n_regions_output = n_regions_output + (tmpint + 1) 
     220          END DO 
     221       
     222           
     223         
     224      ELSE 
     225        n_regions_output = 1 
     226      ENDIF 
     227       
     228       
     229 
     230 
     231 
     232    !JT 
     233 
     234 
     235 
     236 
     237 
     238 
     239     
     240 
     241 
     242 
     243 
     244 
    135245      clname = cdname 
    136246      IF( TRIM(Agrif_CFixed()) /= '0' )   clname = TRIM(Agrif_CFixed())//"_"//TRIM(cdname) 
     
    205315          CALL iom_set_axis_attr( "depthw",  paxis = gdepw_1d ) 
    206316 
     317 
     318       
     319 
     320       
     321 
    207322          ! Add vertical grid bounds 
    208323          zt_bnds(2,:        ) = gdept_1d(:) 
     
    231346          CALL iom_set_axis_attr( "basin"  , (/ (REAL(ji,wp), ji=1,5) /) ) 
    232347      ENDIF 
     348 
     349 
     350      !JT 
     351      !JT CALL iom_set_axis_attr( "region", (/ (REAL(ji,wp), ji=1,n_regions_output) /) ) 
     352      !JT CALL iom_set_axis_attr( "noos", (/ (REAL(ji,wp), ji=1,3) /) ) 
     353      !JT 
    233354      ! 
    234355      ! automatic definitions of some of the xml attributs 
  • NEMO/branches/UKMO/NEMO_4.0.4_CO9_shelf_climate/src/OCE/nemogcm.F90

    r15329 r15333  
    7474   USE dia25h         ! 25h mean output 
    7575   !JT 
     76   USE diaregmean      ! Top,middle,bottom output 
    7677   USE diapea         ! pea 
    7778   !JT 
     
    499500     IF( ln_diaobs    )    CALL dia_obs( nit000-1 )   ! Observation operator for restart 
    500501                           !JT 
     502                           CALL dia_regmean_init  ! Initialise Regiona mean 
    501503                           CALL dia_pea_init  ! Initialise PEA  
    502504                           !JT 
Note: See TracChangeset for help on using the changeset viewer.