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 @ 4849

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

moved ooo_data.F90 to sao_data.F90 along with renaming its internal subroutines appropriately

File size: 7.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   !! Class 4 file settings
15   INTEGER :: &
16           & cl4_fcst_idx(MaxNumFiles), & !: forecast indices
17           & cl4_match_len, &             !: number of match types
18           & cl4_fcst_len                 !: number of forecast days
19   CHARACTER(len=lc) :: &
20           & cl4_vars(MaxNumFiles), &  !: class 4 variables
21           & cl4_sys, &                !: class 4 system
22           & cl4_cfg, &                !: class 4 configuration
23           & cl4_date, &               !: class 4 date
24           & cl4_vn,  &                !: class 4 version
25           & cl4_prefix, &             !: class 4 prefix
26           & cl4_contact, &            !: class 4 contact
27           & cl4_inst                  !: class 4 institute
28   REAL ::   cl4_modjuld               !: model Julian day
29   REAL :: &
30      & cl4_leadtime(MaxNumFiles)      !: Lead time data
31
32   !! Stand Alone Observation operator settings
33   CHARACTER(len=lc) :: &
34      & sao_files(MaxNumFiles)         !: model files
35   INTEGER            :: &
36      & jifile, &                      !: current file list index
37      & n_files, &                     !: number of files
38      & jimatch, &                     !: current match
39      & nn_sao_idx(MaxNumFiles), &     !: time_counter indices
40      & nn_sao_freq                    !: read frequency in time steps
41   CHARACTER(len=128) :: &
42      & alt_file                       !: altimeter file
43CONTAINS
44   SUBROUTINE sao_data_init( ld_cl4 )
45      !!----------------------------------------------------------------------
46      !!                    ***  SUBROUTINE sao_data_init ***
47      !!
48      !! ** Purpose : To read namelists and initialise offline_oper run.
49      !!
50      !!----------------------------------------------------------------------
51      USE in_out_manager
52      INTEGER            :: &
53         & jf                           !: file dummy loop index
54      LOGICAL :: lmask(MaxNumFiles)     !: Logical mask used for counting
55      LOGICAL, INTENT(IN) :: ld_cl4     !: Logical class 4 on/off
56      INTEGER :: ios
57
58      ! Standard offline obs_oper information
59      NAMELIST/namsao/sao_files, nn_sao_idx, nn_sao_freq
60
61      ! Class 4 file specifiers
62      NAMELIST/namcl4/cl4_vars, cl4_sys, cl4_cfg, cl4_date, cl4_vn, &
63         &            cl4_prefix, cl4_contact, cl4_inst, cl4_leadtime, &
64         &            cl4_fcst_idx, cl4_fcst_len, cl4_match_len
65
66      ! Standard offline obs_oper initialisation
67      jimatch = 0                   !: match-up iteration variable
68      jifile = 1                    !: input file iteration variable
69      n_files = 0                   !: number of files to cycle through
70      sao_files(:) = ''             !: list of files to read in
71      nn_sao_idx(:) = 0             !: list of indices inside each file
72      nn_sao_freq = -1              !: input frequency in time steps
73
74      ! Class 4 initialisation
75      cl4_leadtime(:) = 0           !: Lead time axis value for each file
76      cl4_fcst_len = 0              !: Length of the forecast dimension
77      cl4_match_len = 1             !: Number of match types
78      cl4_fcst_idx(:) = 0           !: output file forecast index
79      cl4_vars(:) = ''              !: output file variable names
80      cl4_sys = ''                  !: output file system
81      cl4_cfg = ''                  !: output file configuration
82      cl4_date = ''                 !: output file date string
83      cl4_vn = ''                   !: output file version
84      cl4_prefix = 'class4'         !: output file prefix
85      cl4_contact = ''              !: output file contact details
86      cl4_inst = ''                 !: output file institution
87
88      ! Standard offline obs_oper settings
89      REWIND( numnam_ref )              ! Namelist namctl in reference namelist : Control prints & Benchmark
90      READ  ( numnam_ref, namsao, IOSTAT = ios, ERR = 901 )
91901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsao in reference namelist', .TRUE. )
92
93      REWIND( numnam_cfg )              ! Namelist namctl in confguration namelist : Control prints & Benchmark
94      READ  ( numnam_cfg, namsao, IOSTAT = ios, ERR = 902 )
95902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsao in configuration namelist', .TRUE. )
96
97      ! Read class 4 output settings
98      IF (ld_cl4) THEN
99         REWIND( numnam_ref )              ! Namelist namctl in reference namelist : Control prints & Benchmark
100         READ  ( numnam_ref, namcl4, IOSTAT = ios, ERR = 903 )
101903      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namcl4 in reference namelist', .TRUE. )
102
103         REWIND( numnam_cfg )              ! Namelist namctl in confguration namelist : Control prints & Benchmark
104         READ  ( numnam_cfg, namcl4, IOSTAT = ios, ERR = 904 )
105904      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namcl4 in configuration namelist', .TRUE. )
106      ENDIF
107
108      ! count input files
109      lmask(:) = .FALSE.
110      WHERE (sao_files(:) /= '') lmask(:) = .TRUE.
111      n_files = COUNT(lmask)
112
113      !! Initialise sub obs window frequency
114      IF (nn_sao_freq == -1) THEN
115         !! Run length
116         nn_sao_freq = nitend - nit000 + 1
117      ENDIF
118
119      !! Print summary of settings
120      IF(lwp) THEN
121         WRITE(numout,*)
122         WRITE(numout,*) 'offline obs_oper : Initialization'
123         WRITE(numout,*) '~~~~~~~~~~~~~~~~~'
124         WRITE(numout,*) '   Namelist namsao : set stand alone obs_oper parameters' 
125         DO jf = 1, n_files
126            WRITE(numout,'(1X,2A)') '   Input forecast file name          forecastfile = ', &
127               TRIM(sao_files(jf))
128            WRITE(numout,*) '   Input forecast file index        forecastindex = ', &
129               nn_sao_idx(jf)
130            WRITE(numout,*) '   Output forecast leadtime index   leadtimeindex = ', &
131               cl4_fcst_idx(jf)
132            WRITE(numout,*) '   Output forecast leadtime value   leadtimevalue = ', &
133               cl4_leadtime(jf)
134            WRITE(numout,'(1X,2A)') '   Input class 4 variable       class 4 parameter = ', &
135               TRIM(cl4_vars(jf))
136         END DO
137         WRITE(numout, '(1X,2A)') '   Input class 4 system            class 4 system = ', &
138            TRIM(cl4_sys)
139         WRITE(numout, '(1X,2A)') '   Input class 4 config            class 4 config = ', &
140            TRIM(cl4_cfg)
141         WRITE(numout, '(1X,2A)') '   Input class 4 date                class 4 date = ', &
142            TRIM(cl4_date)
143         WRITE(numout, '(1X,2A)') '   Input class 4 version          class 4 version = ', &
144            TRIM(cl4_vn)
145         WRITE(numout, '(1X,2A)') '   Input class 4 prefix            class 4 prefix = ', &
146            TRIM(cl4_prefix)
147         WRITE(numout, '(1X,2A)') '   Input class 4 contact          class 4 contact = ', &
148            TRIM(cl4_contact)
149         WRITE(numout, '(1X,2A)') '   Input class 4 institute      class 4 institute = ', &
150            TRIM(cl4_inst)
151      END IF
152
153   END SUBROUTINE sao_data_init
154
155END MODULE sao_data
156
Note: See TracBrowser for help on using the repository browser.