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 7567 for branches/UKMO/CO6_shelfclimate/NEMOGCM/NEMO/OPA_SRC/IOM – NEMO

Ignore:
Timestamp:
2017-01-16T20:11:00+01:00 (8 years ago)
Author:
hadjt
Message:

CO6 version adapted for shelf seas climate projections, including added diagnostics

Location:
branches/UKMO/CO6_shelfclimate/NEMOGCM/NEMO/OPA_SRC/IOM
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/CO6_shelfclimate/NEMOGCM/NEMO/OPA_SRC/IOM/in_out_manager.F90

    r7566 r7567  
    3030   CHARACTER(lc) ::   cn_ocerst_outdir !: restart output directory 
    3131   LOGICAL       ::   ln_rstart        !: start from (F) rest or (T) a restart file 
     32   LOGICAL       ::   ln_rstdate       !: datestamping of restarts  
    3233   LOGICAL       ::   ln_rst_list      !: output restarts at list of times (T) or by frequency (F) 
    3334   INTEGER       ::   nn_no            !: job number 
     
    4142   INTEGER       ::   nn_write         !: model standard output frequency 
    4243   INTEGER       ::   nn_stock         !: restart file frequency 
    43    INTEGER, DIMENSION(10) :: nn_stocklist  !: restart dump times 
     44   INTEGER, DIMENSION(100) :: nn_stocklist  !: restart dump times 
    4445   LOGICAL       ::   ln_dimgnnn       !: type of dimgout. (F): 1 file for all proc 
    4546                                                       !:                  (T): 1 file per proc 
     
    4748   LOGICAL       ::   ln_cfmeta        !: output additional data to netCDF files required for compliance with the CF metadata standard 
    4849   LOGICAL       ::   ln_clobber       !: clobber (overwrite) an existing file 
     50   !JT 
     51   LOGICAL       ::   ln_NOOS          !: NOOS transects  diagnostics 
     52   !JT 
    4953   INTEGER       ::   nn_chunksz       !: chunksize (bytes) for NetCDF file (works only with iom_nf90 routines) 
    5054#if defined key_netcdf4 
     
    8387   INTEGER       ::   nwrite                      !: model standard output frequency 
    8488   INTEGER       ::   nstock                      !: restart file frequency 
    85    INTEGER, DIMENSION(10) :: nstocklist           !: restart dump times 
     89   INTEGER, DIMENSION(100) :: nstocklist           !: restart dump times 
    8690 
    8791   !!---------------------------------------------------------------------- 
     
    131135   INTEGER ::   numdct_in       =   -1      !: logical unit for transports computing 
    132136   INTEGER ::   numdct_vol      =   -1      !: logical unit for voulume transports output 
    133    INTEGER ::   numdct_heat     =   -1      !: logical unit for heat    transports output 
    134    INTEGER ::   numdct_salt     =   -1      !: logical unit for salt    transports output 
     137   !JT INTEGER ::   numdct_heat     =   -1      !: logical unit for heat    transports output 
     138   !JT INTEGER ::   numdct_salt     =   -1      !: logical unit for salt    transports output 
     139   !JT 
     140   INTEGER ::   numdct_temp =   -1      !: logical unit for heat    transports output 
     141   INTEGER ::   numdct_sal  =   -1      !: logical unit for salt    transports output 
     142 
     143   INTEGER ::   numdct_NOOS     =   -1      !: logical unit for NOOS    transports output 
     144   INTEGER ::   numdct_NOOS_h   =   -1      !: logical unit for NOOS hourly transports output 
     145   !JT 
    135146   INTEGER ::   numfl           =   -1      !: logical unit for floats ascii output 
    136147   INTEGER ::   numflo          =   -1      !: logical unit for floats ascii output 
  • branches/UKMO/CO6_shelfclimate/NEMOGCM/NEMO/OPA_SRC/IOM/iom.F90

    r7566 r7567  
    4444   USE ioipsl, ONLY :  ju2ymds    ! for calendar 
    4545   USE crs             ! Grid coarsening 
    46  
     46     
    4747   IMPLICIT NONE 
    4848   PUBLIC   !   must be public to be able to access iom_def through iom 
     
    5555   PUBLIC iom_init, iom_swap, iom_open, iom_close, iom_setkt, iom_varid, iom_get, iom_gettime, iom_rstput, iom_put 
    5656   PUBLIC iom_getatt, iom_use, iom_context_finalize 
    57  
     57    
     58    
     59   !JT REGION MEANS 
     60   !INTEGER , PUBLIC ::   n_regions_output = 100 
     61    
     62   INTEGER , PUBLIC ::   n_regions_output 
     63   !JT REGION MEANS 
     64    
    5865   PRIVATE iom_rp0d, iom_rp1d, iom_rp2d, iom_rp3d 
    5966   PRIVATE iom_g0d, iom_g1d, iom_g2d, iom_g3d, iom_get_123d 
     
    106113      REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: z_bnds 
    107114      !!---------------------------------------------------------------------- 
     115       
     116       
     117       
     118      !JT REGION MEANS 
     119      !! read namelist to see if the region mask code is called, if so read the region mask, and count the regions.  
     120       
     121       
     122      REAL(wp),  ALLOCATABLE,   DIMENSION(:,:) ::   tmpregion !: temporary region_mask 
     123      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 
     124      INTEGER               ::   zndims   ! number of dimensions in an array (i.e. 3, ) 
     125      INTEGER :: inum, nmasks,ierr,maskno,idmaskvar,tmpint 
     126      REAL(wp), ALLOCATABLE,   DIMENSION(:,:,:)  ::   tmp_region_mask_real   ! tempory region_mask of reals 
     127       
     128      LOGICAL ::   ln_diaregmean  ! region mean calculation 
     129    
     130     
     131      INTEGER ::   ios                  ! Local integer output status for namelist read 
     132      LOGICAL :: ln_diaregmean_ascii  ! region mean calculation ascii output 
     133      LOGICAL :: ln_diaregmean_bin  ! region mean calculation binary output 
     134      LOGICAL :: ln_diaregmean_nc  ! region mean calculation netcdf output 
     135     
     136       
     137       
     138      NAMELIST/nam_diaregmean/ ln_diaregmean,ln_diaregmean_ascii,ln_diaregmean_bin,ln_diaregmean_nc 
     139       
     140      ! read in Namelist.  
     141      !!---------------------------------------------------------------------- 
     142      ! 
     143      REWIND ( numnam_ref )              ! Read Namelist nam_diatmb in referdiatmbence namelist : TMB diagnostics 
     144      READ   ( numnam_ref, nam_diaregmean, IOSTAT=ios, ERR= 901 ) 
     145901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_diaregmean in reference namelist', lwp ) 
     146 
     147      REWIND( numnam_cfg )              ! Namelist nam_diatmb in configuration namelist  TMB diagnostics 
     148      READ  ( numnam_cfg, nam_diaregmean, IOSTAT = ios, ERR = 902 ) 
     149902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_diaregmean in configuration namelist', lwp ) 
     150      IF(lwm) WRITE ( numond, nam_diaregmean ) 
     151 
     152      IF (ln_diaregmean) THEN 
     153       
     154        ! Open region mask for region means, and retrieve the size of the mask (number of levels)           
     155          CALL iom_open ( 'region_mask.nc', inum ) 
     156          idmaskvar = iom_varid( inum, 'mask', kdimsz=zdimsz, kndims=zndims, ldstop = .FALSE.)           
     157          nmasks = zdimsz(3) 
     158           
     159          ! read in the region mask (which contains floating point numbers) into a temporary array of reals. 
     160          ALLOCATE( tmp_region_mask_real(jpi,jpj,nmasks),  STAT= ierr ) 
     161          IF( ierr /= 0 )   CALL ctl_stop( 'dia_regmean_init: failed to allocate tmp_region_mask_real array' ) 
     162           
     163          ! Use jpdom_unknown to read in a n layer mask. 
     164          tmp_region_mask_real(:,:,:) = 0 
     165          CALL iom_get( inum, jpdom_unknown, 'mask', tmp_region_mask_real(1:nlci,1:nlcj,1:nmasks),   & 
     166              &          kstart = (/ mig(1),mjg(1),1 /), kcount = (/ nlci,nlcj,nmasks /) ) 
     167           
     168          CALL iom_close( inum ) 
     169          !Convert the region mask of reals into one of integers.  
     170           
     171           
     172          n_regions_output = 0 
     173          DO maskno = 1,nmasks 
     174              tmpint = maxval(int(tmp_region_mask_real(:,:,maskno))) 
     175              CALL mpp_max( tmpint ) 
     176              n_regions_output = n_regions_output + (tmpint + 1) 
     177          END DO 
     178       
     179           
     180         
     181        WRITE(numout,*)  'IOM: n_regions_output: ',n_regions_output 
     182         
     183      ELSE 
     184        n_regions_output = 1 
     185      ENDIF 
     186       
     187       
     188       
     189      !JT REGION MEANS 
     190       
     191       
     192       
     193       
    108194#if ! defined key_xios2 
    109195      ALLOCATE( z_bnds(jpk,2) ) 
     
    227313      CALL iom_set_axis_attr( "iax_20C", (/ REAL(20,wp) /) ) 
    228314      CALL iom_set_axis_attr( "iax_28C", (/ REAL(28,wp) /) ) 
     315       
     316       
     317       
     318      ! JT Region means.  
     319      CALL iom_set_axis_attr( "region", (/ (REAL(ji,wp), ji=1,n_regions_output) /) ) 
     320 
     321      !CALL iom_set_axis_attr( "region", (/ (REAL(ji,wp), ji=1,100) /) ) 
     322 
    229323       
    230324      ! automatic definitions of some of the xml attributs 
     
    12461340      REAL(wp), DIMENSION(:)  , OPTIONAL, INTENT(in) ::   paxis 
    12471341      REAL(wp), DIMENSION(:,:), OPTIONAL, INTENT(in) ::   bounds 
     1342       
     1343      !INTEGER :: iind_JT 
     1344       
     1345       
     1346      !write(numout,*) 'IOM/iom.F90:iom_set_axis_attr: ',cdid 
     1347       
    12481348      IF ( PRESENT(paxis) ) THEN 
     1349       
     1350        !write(numout,*) 'IOM/iom.F90:iom_set_axis_attr paxis size for: ',cdid,SIZE(paxis) 
     1351        !write(numout,*) 'IOM/iom.F90:iom_set_axis_attr paxis values for: ',cdid,paxis 
     1352        !do iind_JT = 1,SIZE(paxis)         
     1353        !  write(numout,*) 'IOM/iom.F90:iom_set_axis_attr paxis individual values for: ',cdid,iind_JT,paxis(iind_JT) 
     1354        !end do 
     1355         
    12491356#if ! defined key_xios2 
    12501357         IF ( xios_is_valid_axis     (cdid) )   CALL xios_set_axis_attr     ( cdid, size=SIZE(paxis), value=paxis ) 
  • branches/UKMO/CO6_shelfclimate/NEMOGCM/NEMO/OPA_SRC/IOM/restart.F90

    r7566 r7567  
    2121   USE in_out_manager  ! I/O manager 
    2222   USE iom             ! I/O module 
     23   USE ioipsl, ONLY : ju2ymds    ! for calendar 
    2324   USE eosbn2          ! equation of state            (eos bn2 routine) 
    2425   USE trdmxl_oce      ! ocean active mixed layer tracers trends variables 
     
    5455      !!---------------------------------------------------------------------- 
    5556      INTEGER, INTENT(in) ::   kt     ! ocean time-step 
     57      INTEGER             ::   iyear, imonth, iday 
     58      REAL (wp)           ::   zsec 
     59      REAL (wp)           ::   zfjulday 
    5660      !! 
    5761      CHARACTER(LEN=20)   ::   clkt     ! ocean time-step deine as a character 
    5862      CHARACTER(LEN=50)   ::   clname   ! ocean output restart file name 
    59       CHARACTER(lc)       ::   clpath   ! full path to ocean output restart file 
     63      CHARACTER(LEN=150)  ::   clpath   ! full path to ocean output restart file 
    6064      !!---------------------------------------------------------------------- 
    6165      ! 
     
    8185      IF( kt == nitrst - 1 .OR. nstock == 1 .OR. ( kt == nitend .AND. .NOT. lrst_oce ) ) THEN 
    8286         IF( nitrst <= nitend .AND. nitrst > 0 ) THEN  
    83             ! beware of the format used to write kt (default is i8.8, that should be large enough...) 
    84             IF( nitrst > 999999999 ) THEN   ;   WRITE(clkt, *       ) nitrst 
    85             ELSE                            ;   WRITE(clkt, '(i8.8)') nitrst 
     87            IF ( ln_rstdate ) THEN 
     88               zfjulday = fjulday + rdttra(1) / rday 
     89               IF( ABS(zfjulday - REAL(NINT(zfjulday),wp)) < 0.1 / rday )   zfjulday = REAL(NINT(zfjulday),wp)   ! avoid truncation error 
     90               CALL ju2ymds( zfjulday, iyear, imonth, iday, zsec )            
     91               WRITE(clkt, '(i4.4,2i2.2)') iyear, imonth, iday             
     92               IF ( ln_rst_list .AND. ( kt .NE. nitend) ) THEN 
     93                 ! JT IF ( nstock_list_in_use_JT .AND. ( kt .NE. nitend - 1) ) THEN 
     94                 WRITE(clkt, '(i4.4,2i2.2,a1,i10.10)') iyear, imonth, iday,'_',kt !JT 
     95               ENDIF 
     96            ELSE 
     97               ! beware of the format used to write kt (default is i8.8, that should be large enough...) 
     98               IF( nitrst > 999999999 ) THEN   ;   WRITE(clkt, *       ) nitrst 
     99               ELSE                            ;   WRITE(clkt, '(i8.8)') nitrst 
     100               ENDIF 
    86101            ENDIF 
    87102            ! create the file 
Note: See TracChangeset for help on using the changeset viewer.