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.
sao_data.F90 in branches/2014/dev_r4650_UKMO14.12_STAND_ALONE_OBSOPER/NEMOGCM/NEMO/SAO_SRC – NEMO

source: branches/2014/dev_r4650_UKMO14.12_STAND_ALONE_OBSOPER/NEMOGCM/NEMO/SAO_SRC/sao_data.F90 @ 5600

Last change on this file since 5600 was 5063, checked in by andrewryan, 9 years ago

gross simplification of stand alone observation operator

File size: 3.1 KB
Line 
1MODULE sao_data
2   !! =================================================================
3   !!                    *** MODULE sao_data ***
4   !! =================================================================
5   USE par_kind, ONLY: lc
6   USE lib_mpp         ! distributed memory computing
7
8   IMPLICIT NONE
9
10   !! Public data
11
12   INTEGER, PARAMETER :: MaxNumFiles = 1000
13
14   !! 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
21CONTAINS
22   SUBROUTINE sao_data_init()
23      !!----------------------------------------------------------------------
24      !!                    ***  SUBROUTINE sao_data_init ***
25      !!
26      !! ** Purpose : To read namelists and initialise offline_oper run.
27      !!
28      !!----------------------------------------------------------------------
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
36      NAMELIST/namsao/sao_files, nn_sao_idx, nn_sao_freq
37
38      ! 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
44      ! Standard offline obs_oper settings
45      REWIND( numnam_ref )              ! Namelist namctl in reference namelist : Control prints & Benchmark
46      READ  ( numnam_ref, namsao, IOSTAT = ios, ERR = 901 )
47901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsao in reference namelist', .TRUE. )
48
49      REWIND( numnam_cfg )              ! Namelist namctl in confguration namelist : Control prints & Benchmark
50      READ  ( numnam_cfg, namsao, IOSTAT = ios, ERR = 902 )
51902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsao in configuration namelist', .TRUE. )
52
53
54      ! count input files
55      lmask(:) = .FALSE.
56      WHERE (sao_files(:) /= '') lmask(:) = .TRUE.
57      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
63      ENDIF
64
65      !! Print summary of settings
66      IF(lwp) THEN
67         WRITE(numout,*)
68         WRITE(numout,*) 'offline obs_oper : Initialization'
69         WRITE(numout,*) '~~~~~~~~~~~~~~~~~'
70         WRITE(numout,*) '   Namelist namsao : set stand alone obs_oper parameters'
71         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)
76         END DO
77      END IF
78
79   END SUBROUTINE sao_data_init
80
81END MODULE sao_data
82
Note: See TracBrowser for help on using the repository browser.