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 7200 for branches/2016/dev_r6409_SIMPLIF_2_usrdef/NEMOGCM/NEMO/SAO_SRC/sao_data.F90 – NEMO

Ignore:
Timestamp:
2016-11-06T17:31:33+01:00 (7 years ago)
Author:
gm
Message:

#1692 - branch SIMPLIF_2_usrdef: add depth_e3 module + management of ORCA family + domain_cfg filename (in&out) given in namelist

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2016/dev_r6409_SIMPLIF_2_usrdef/NEMOGCM/NEMO/SAO_SRC/sao_data.F90

    r5063 r7200  
    11MODULE sao_data 
    2    !! ================================================================= 
    3    !!                    *** MODULE sao_data *** 
    4    !! ================================================================= 
     2   !!====================================================================== 
     3   !!                       ***  MODULE sao_data  *** 
     4   !!====================================================================== 
     5   !! History :  3.6  ! 2015-12  (A. Ryan)  Original code 
     6   !!---------------------------------------------------------------------- 
    57   USE par_kind, ONLY: lc 
    68   USE lib_mpp         ! distributed memory computing 
     9   USE in_out_manager 
    710 
    811   IMPLICIT NONE 
    9  
    10    !! Public data 
    1112 
    1213   INTEGER, PARAMETER :: MaxNumFiles = 1000 
    1314 
    1415   !! Stand Alone Observation operator settings 
    15    CHARACTER(len=lc) :: & 
    16       & sao_files(MaxNumFiles)         !: model files 
    17    INTEGER            :: & 
    18       & n_files, &                     !: number of files 
    19       & nn_sao_idx(MaxNumFiles), &     !: time_counter indices 
    20       & nn_sao_freq                    !: read frequency in time steps 
     16   CHARACTER(len=lc) ::   sao_files(MaxNumFiles)   !: model files 
     17   INTEGER           ::   n_files                  !: number of files 
     18   INTEGER           :: nn_sao_idx(MaxNumFiles)    !: time_counter indices 
     19   INTEGER           :: nn_sao_freq                !: read frequency in time steps 
     20    
     21   !!---------------------------------------------------------------------- 
     22   !! NEMO/OPA 3.7 , NEMO Consortium (2015) 
     23   !! $Id: trazdf_imp.F90 6140 2015-12-21 11:35:23Z timgraham $ 
     24   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     25   !!---------------------------------------------------------------------- 
    2126CONTAINS 
     27 
    2228   SUBROUTINE sao_data_init() 
    2329      !!---------------------------------------------------------------------- 
     
    2733      !! 
    2834      !!---------------------------------------------------------------------- 
    29       USE in_out_manager 
    30       INTEGER            :: & 
    31          & jf                           !: file dummy loop index 
    32       LOGICAL :: lmask(MaxNumFiles)     !: Logical mask used for counting 
    33       INTEGER :: ios 
    34  
    35       ! Standard offline obs_oper information 
     35      INTEGER ::   jf                   ! file dummy loop index 
     36      LOGICAL ::   lmask(MaxNumFiles)   ! Logical mask used for counting 
     37      INTEGER ::   ios 
     38      !! 
    3639      NAMELIST/namsao/sao_files, nn_sao_idx, nn_sao_freq 
     40      !!---------------------------------------------------------------------- 
    3741 
    3842      ! Standard offline obs_oper initialisation 
    39       n_files = 0                   !: number of files to cycle through 
    40       sao_files(:) = ''             !: list of files to read in 
    41       nn_sao_idx(:) = 0             !: list of indices inside each file 
    42       nn_sao_freq = -1              !: input frequency in time steps 
     43      n_files = 0                   ! number of files to cycle through 
     44      sao_files(:) = ''             ! list of files to read in 
     45      nn_sao_idx(:) = 0             ! list of indices inside each file 
     46      nn_sao_freq = -1              ! input frequency in time steps 
    4347 
    4448      ! Standard offline obs_oper settings 
     
    4650      READ  ( numnam_ref, namsao, IOSTAT = ios, ERR = 901 ) 
    4751901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsao in reference namelist', .TRUE. ) 
    48  
     52      ! 
    4953      REWIND( numnam_cfg )              ! Namelist namctl in confguration namelist : Control prints & Benchmark 
    5054      READ  ( numnam_cfg, namsao, IOSTAT = ios, ERR = 902 ) 
    5155902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsao in configuration namelist', .TRUE. ) 
    52  
    53  
    54       ! count input files 
    55       lmask(:) = .FALSE. 
     56      
     57      lmask(:) = .FALSE.               ! count input files 
    5658      WHERE (sao_files(:) /= '') lmask(:) = .TRUE. 
    5759      n_files = COUNT(lmask) 
    58  
    59       !! Initialise sub obs window frequency 
    60       IF (nn_sao_freq == -1) THEN 
    61          !! Run length 
    62          nn_sao_freq = nitend - nit000 + 1 
     60      ! 
     61      IF(nn_sao_freq == -1) THEN      ! Initialise sub obs window frequency 
     62         nn_sao_freq = nitend - nit000 + 1      ! Run length 
    6363      ENDIF 
    64  
    65       !! Print summary of settings 
    66       IF(lwp) THEN 
     64      ! 
     65      IF(lwp) THEN                     ! Print summary of settings 
    6766         WRITE(numout,*) 
    6867         WRITE(numout,*) 'offline obs_oper : Initialization' 
     
    7069         WRITE(numout,*) '   Namelist namsao : set stand alone obs_oper parameters' 
    7170         DO jf = 1, n_files 
    72             WRITE(numout,'(1X,2A)') '   Input forecast file name          forecastfile = ', & 
    73                TRIM(sao_files(jf)) 
    74             WRITE(numout,*) '   Input forecast file index        forecastindex = ', & 
    75                nn_sao_idx(jf) 
     71            WRITE(numout,'(1X,2A)') '   Input forecast file name          forecastfile = ', TRIM(sao_files(jf)) 
     72            WRITE(numout,*) '   Input forecast file index        forecastindex = ', nn_sao_idx(jf) 
    7673         END DO 
    7774      END IF 
    78  
     75      ! 
    7976   END SUBROUTINE sao_data_init 
    8077 
     78   !!====================================================================== 
    8179END MODULE sao_data 
    8280 
Note: See TracChangeset for help on using the changeset viewer.