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.
off_data.F90 in branches/2013/dev_r3987_UKMO4_OBS/NEMOGCM/NEMO/OOO_SRC – NEMO

source: branches/2013/dev_r3987_UKMO4_OBS/NEMOGCM/NEMO/OOO_SRC/off_data.F90 @ 4094

Last change on this file since 4094 was 4048, checked in by djlea, 11 years ago

Cleaning and debugging of the observation operator. Turn off the night time averaging of SST data by default, but add a namelist option to switch it on.

File size: 5.9 KB
Line 
1MODULE off_data
2   USE par_kind, ONLY: lc
3   IMPLICIT NONE
4   INTEGER, PARAMETER :: MaxNumFiles = 1000
5
6   !! Class 4 file settings
7   INTEGER :: &
8           & cl4_fcst_idx(MaxNumFiles), & !: forecast indices
9           & cl4_match_len, &             !: number of match types
10           & cl4_fcst_len                 !: number of forecast days
11   CHARACTER(len=lc) :: &
12           & cl4_vars(MaxNumFiles), &  !: class 4 variables
13           & cl4_sys, &                !: class 4 system
14           & cl4_cfg, &                !: class 4 configuration
15           & cl4_date, &               !: class 4 date
16           & cl4_vn,  &                !: class 4 version
17           & cl4_prefix, &             !: class 4 prefix
18           & cl4_contact, &            !: class 4 contact
19           & cl4_inst                  !: class 4 institute
20   REAL ::   cl4_modjuld               !: model Julian day
21   REAL :: &
22      & cl4_leadtime(MaxNumFiles)      !: Lead time data
23
24   !! Offline obs_oper settings
25   CHARACTER(len=lc) :: &
26      & off_files(MaxNumFiles)         !: model files
27   INTEGER            :: &
28      & jifile, &                      !: current file list index
29      & n_files, &                     !: number of files
30      & jimatch, &                     !: current match
31      & nn_off_idx(MaxNumFiles), &     !: time_counter indices
32      & nn_off_freq                    !: read frequency in time steps
33   CHARACTER(len=128) :: &
34      & alt_file                       !: altimeter file
35CONTAINS
36   SUBROUTINE off_data_init( ld_cl4 )
37      !!----------------------------------------------------------------------
38      !!                    ***  SUBROUTINE off_data_init ***
39      !!
40      !! ** Purpose : To read namelists and initialise offline_oper run.
41      !!
42      !!----------------------------------------------------------------------
43      USE in_out_manager
44      IMPLICIT NONE
45      INTEGER            :: &
46         & jf                           !: file dummy loop index
47      LOGICAL :: lmask(MaxNumFiles)     !: Logical mask used for counting
48      LOGICAL, INTENT(IN) :: ld_cl4     !: Logical class 4 on/off
49
50      ! Standard offline obs_oper information
51      NAMELIST/namoff/off_files, nn_off_idx, nn_off_freq
52
53      ! Class 4 file specifiers
54      NAMELIST/namcl4/cl4_vars, cl4_sys, cl4_cfg, cl4_date, cl4_vn, &
55         &            cl4_prefix, cl4_contact, cl4_inst, cl4_leadtime, &
56         &            cl4_fcst_idx, cl4_fcst_len, cl4_match_len
57
58      ! Standard offline obs_oper initialisation
59      jimatch = 0                   !: match-up iteration variable
60      jifile = 1                    !: input file iteration variable
61      n_files = 0                   !: number of files to cycle through
62      off_files(:) = ''             !: list of files to read in
63      nn_off_idx(:) = 0             !: list of indices inside each file
64      nn_off_freq = -1              !: input frequency in time steps
65
66      ! Class 4 initialisation
67      cl4_leadtime(:) = 0           !: Lead time axis value for each file
68      cl4_fcst_len = 0              !: Length of the forecast dimension
69      cl4_match_len = 1             !: Number of match types
70      cl4_fcst_idx(:) = 0           !: output file forecast index
71      cl4_vars(:) = ''              !: output file variable names
72      cl4_sys = ''                  !: output file system
73      cl4_cfg = ''                  !: output file configuration
74      cl4_date = ''                 !: output file date string
75      cl4_vn = ''                   !: output file version
76      cl4_prefix = 'class4'         !: output file prefix
77      cl4_contact = ''              !: output file contact details
78      cl4_inst = ''                 !: output file institution
79
80      ! Standard offline obs_oper settings
81      READ(numnam, namoff)
82
83      ! Read class 4 output settings
84      IF (ld_cl4) THEN
85         READ(numnam, namcl4)
86      ENDIF
87
88      ! count input files
89      lmask(:) = .FALSE.
90      WHERE (off_files(:) /= '') lmask(:) = .TRUE.
91      n_files = COUNT(lmask)
92
93      !! Initialise sub obs window frequency
94      IF (nn_off_freq == -1) THEN
95         !! Run length
96         nn_off_freq = nitend - nit000 + 1
97      ENDIF
98
99      !! Print summary of settings
100      IF(lwp) THEN
101         WRITE(numout,*)
102         WRITE(numout,*) 'offline obs_oper : Initialization'
103         WRITE(numout,*) '~~~~~~~~~~~~~~~~~'
104         WRITE(numout,*) '   Namelist namoff : set offline obs_oper parameters' 
105         DO jf = 1, n_files
106            WRITE(numout,'(1X,2A)') '   Input forecast file name          forecastfile = ', &
107               TRIM(off_files(jf))
108            WRITE(numout,*) '   Input forecast file index        forecastindex = ', &
109               nn_off_idx(jf)
110            WRITE(numout,*) '   Output forecast leadtime index   leadtimeindex = ', &
111               cl4_fcst_idx(jf)
112            WRITE(numout,*) '   Output forecast leadtime value   leadtimevalue = ', &
113               cl4_leadtime(jf)
114            WRITE(numout,'(1X,2A)') '   Input class 4 variable       class 4 parameter = ', &
115               TRIM(cl4_vars(jf))
116         END DO
117         WRITE(numout, '(1X,2A)') '   Input class 4 system            class 4 system = ', &
118            TRIM(cl4_sys)
119         WRITE(numout, '(1X,2A)') '   Input class 4 config            class 4 config = ', &
120            TRIM(cl4_cfg)
121         WRITE(numout, '(1X,2A)') '   Input class 4 date                class 4 date = ', &
122            TRIM(cl4_date)
123         WRITE(numout, '(1X,2A)') '   Input class 4 version          class 4 version = ', &
124            TRIM(cl4_vn)
125         WRITE(numout, '(1X,2A)') '   Input class 4 prefix            class 4 prefix = ', &
126            TRIM(cl4_prefix)
127         WRITE(numout, '(1X,2A)') '   Input class 4 contact          class 4 contact = ', &
128            TRIM(cl4_contact)
129         WRITE(numout, '(1X,2A)') '   Input class 4 institute      class 4 institute = ', &
130            TRIM(cl4_inst)
131      END IF
132
133   END SUBROUTINE off_data_init
134
135END MODULE off_data
136
Note: See TracBrowser for help on using the repository browser.