1 ! Program to modify levels in the intermediate format. Two input
2 ! files come in on the command line: input file and output file.
3 ! An additional namelist file is used to select which pressure levels
6 ! NRCM helper, WPS toy code
13 USE misc_definitions_module
17 ! Intermediate input and output from same source.
19 CHARACTER ( LEN =132 ) :: flnm, flnm2
21 INTEGER :: istatus, iop
24 TYPE (met_data) :: fg_data
26 ! The namelist has a pressure array that we want.
28 LOGICAL :: keep_this_one
29 INTEGER :: l , max_pres_keep
30 INTEGER , PARAMETER :: num_pres_lev = 1000
31 REAL, DIMENSION(num_pres_lev) :: press_pa = -1.
32 NAMELIST /mod_levs/ press_pa
34 INTEGER , EXTERNAL :: lenner
36 ! Open up the file with the pressure levels to process.
39 FILE = 'namelist.wps' , &
41 FORM = 'FORMATTED' , &
45 print *, 'Problem with namelist.input file, I can''t open it'
49 ! Input the pressure levels requested.
51 READ ( 10 , mod_levs )
55 ! How many pressure levels were asked for?
57 DO l = 1 , num_pres_lev
58 IF ( press_pa(l) .EQ. -1. ) THEN
64 ! Get the two files: input and output.
66 CALL getarg ( 1 , flnm )
68 IF ( flnm(1:1) .EQ. ' ' ) THEN
69 print *,'USAGE: mod_levs.exe FILE:2006-07-31_00 new_FILE:2006-07-31_00'
73 CALL getarg ( 2 , flnm2 )
76 IF ( flnm2(1:1) .EQ. ' ' ) THEN
77 flnm2(5:l+4) = flnm(1:l)
81 CALL set_debug_level(WARN)
83 CALL read_met_init(TRIM(flnm), .true., '0000-00-00_00', istatus)
85 IF ( istatus == 0 ) THEN
87 CALL write_met_init(TRIM(flnm2), .true., '0000-00-00_00', istatus)
89 IF ( istatus == 0 ) THEN
91 CALL read_next_met_field(fg_data, istatus)
93 DO WHILE (istatus == 0)
96 keep_this_one = .FALSE.
97 DO l = 1 , max_pres_keep
98 IF ( fg_data%xlvl .EQ. press_pa(l) ) THEN
99 keep_this_one = .TRUE.
104 IF (keep_this_one) THEN
105 CALL write_next_met_field(fg_data, istatus)
107 CALL mprintf(.true.,STDOUT,'Deleting level %f Pa',f1=fg_data%xlvl)
110 CALL mprintf(.true.,STDOUT,'Processed %s at level %f for time %s', &
111 s1=fg_data%field, f1=fg_data%xlvl, s2=fg_data%hdate)
112 IF (ASSOCIATED(fg_data%slab)) DEALLOCATE(fg_data%slab)
114 CALL read_next_met_field(fg_data, istatus)
117 CALL write_met_close()
121 print *, 'File = ',TRIM(flnm2)
122 print *, 'Problem with output file, I can''t open it'
127 CALL read_met_close()
131 print *, 'File = ',TRIM(flnm)
132 print *, 'Problem with input file, I can''t open it'
137 print *,'SUCCESSFUL COMPLETION OF PROGRAM MOD_LEVS'
140 END PROGRAM mod_levs_prog
142 INTEGER FUNCTION lenner ( string )
143 CHARACTER ( LEN = 132 ) :: string
146 IF ( ( ( string(l:l) .GE. 'A' ) .AND. ( string(l:l) .LE. 'Z' ) ) .OR. &
147 ( ( string(l:l) .GE. 'a' ) .AND. ( string(l:l) .LE. 'z' ) ) .OR. &
148 ( ( string(l:l) .GE. '0' ) .AND. ( string(l:l) .LE. '9' ) ) ) THEN