source: trunk/MESOSCALE/LMD_MM_MARS/SRC/PREP_MARS/Generic/create_readmeteo.F90

Last change on this file was 2070, checked in by mlefevre, 7 years ago

Add necessary files to create start state for generic mesoscale model

File size: 6.2 KB
Line 
1program create_readmeteo
2
3implicit none
4include "netcdf.inc"
5
6!------------------------------------------------------------------------!
7! create_readmeteo generates the file 'readmeteo.def'                    !
8! ... must be run prior to readmeteo                                     !
9! ... the user will be asked a few questions                             !
10!                                                                        !
11! A. Spiga - 01/08/2007                                                  !
12!------------------------------------------------------------------------!
13
14INTEGER, PARAMETER :: MONTHS_PER_YEAR = 100
15INTEGER, PARAMETER :: mday = 24
16INTEGER :: start_day,init,i,month,day
17INTEGER :: ierr,nid,nvarid
18INTEGER :: n,start,my,interval_subs,subs
19INTEGER :: start_hour,interval,hour,inc_hour
20INTEGER :: no_please
21INTEGER :: timedim,timelen
22INTEGER :: inc
23REAL, DIMENSION(100) :: param
24REAL, DIMENSION(:), ALLOCATABLE :: time
25
26
27!
28! Init
29!
30interval = 0
31
32!mday(:)=24
33!
34! Open input NETCDF file
35!
36write(*,*) "Scanning netcdf file ..."
37ierr=NF_OPEN ("input_diagfi.nc",NF_NOWRITE,nid)
38!ierr=NF90_OPEN("input_diagfi.nc",NF_NOWRITE,nid)
39IF (ierr.NE.NF_NOERR) THEN
40      write(*,*)'**** Please create a symbolic link called input_diagfi.nc'
41      CALL ABORT
42ENDIF
43
44ierr=NF_INQ_DIMID(nid,"time_counter",timedim)
45IF (ierr .NE. NF_NOERR) THEN
46    ierr=NF_INQ_DIMID(nid,"time",timedim)
47    IF (ierr .NE. NF_NOERR) THEN
48        ierr = NF_INQ_DIMID (nid, "Loctime",timedim)
49        IF (ierr .NE. NF_NOERR) THEN
50          ierr = NF_INQ_DIMID (nid, "Time",timedim)
51        ENDIF
52    ENDIF
53ENDIF
54ierr=NF_INQ_DIMLEN(nid,timedim,timelen)
55
56!
57! Get starting time
58!
59ALLOCATE(time(timelen))
60ierr = NF_INQ_VARID (nid, "time_counter",nvarid)
61IF (ierr .NE. NF_NOERR) THEN
62        ierr = NF_INQ_VARID (nid, "time",nvarid)
63        IF (ierr .NE. NF_NOERR) THEN
64           ierr = NF_INQ_VARID (nid, "Loctime",nvarid)
65          IF (ierr .NE. NF_NOERR) THEN
66             ierr = NF_INQ_VARID (nid, "Time",nvarid)
67             IF (ierr .NE. NF_NOERR) THEN
68                PRINT *, "Error: Readmeteo <Time> not found"
69                stop
70             ENDIF
71          ENDIF
72        ENDIF
73ENDIF
74#ifdef NC_DOUBLE
75ierr = NF_GET_VAR_DOUBLE(nid, nvarid, time)
76#else
77ierr = NF_GET_VAR_REAL(nid, nvarid, time)
78#endif
79
80ierr = NF_INQ_VARID (nid,"controle",nvarid)
81IF (ierr .NE. NF_NOERR) THEN
82        PRINT *, "Error: Readmeteo <ps> not found"
83        !stop
84ENDIF
85#ifdef NC_DOUBLE
86ierr = NF_GET_VAR_DOUBLE(nid, nvarid, param)
87#else
88ierr = NF_GET_VAR_REAL(nid, nvarid, param)
89#endif
90
91write(*,*) "Done."
92
93
94!
95! fill the include if no info can be found in the diagfi
96!
97include "fix_no_info.inc"
98
99
100! beware, param(4) is the day reference of start and startfi
101! ...have to add time(1) to get the real starting date in diagfi
102!start_day=floor(param(4)+time(1))             
103!start_hour=nint((param(4)-floor(param(4))+time(1))*13) ! starting hour
104!start_hour=MOD(start_hour,24)   
105!IF (interval .eq. 0) interval=nint(time(1)*24)  ! interval between each time subscript
106
107start_day=1
108start_hour=0
109!interval=864 ! in hours, 864 HH = 1 MM = 1/100 Vd
110!interval=3456
111interval=12
112PRINT *,'*****************'
113PRINT *,'GCM data file starts at sol ',start_day,'and hour',start_hour
114PRINT *,'GCM data interval is ',interval,'hours'
115
116month=1
117day=1
118!interval=864
119!
120! User defined parameters
121!
122write(*,*) "This will erase readmeteo.def file"
123write(*,*) "  NB: Default mode is to generate "
124write(*,*) "      a WPS-compatible file for each timestep "
125write(*,*) "      included in the diagfi "
126write(*,*) "Total number of generated files: ",timelen
127write(*,*) "Continue ? 0 if no, 1 if yes, 99 for settings"
128read(*,*) no_please
129if (no_please == 0) stop
130if (no_please == 1) then
131        my=1000
132        n=timelen
133        start=0
134        interval_subs=1
135else
136        write(*,*) "-- GCM data file information --"
137        write(*,*) "Starting Martian year ? ex: 24,25,26..."
138        read(*,*) my
139        my=1000+my
140        write(*,*) "-- WRF data file information --"
141        write(*,*) "How many files do you want to create ? at least 2, max is",timelen
142        read(*,*) n
143        IF (n == timelen) THEN
144                start=1
145                interval_subs=1
146        ELSE
147                write(*,*) "Time subscript you want to begin with (first is 1) ? max is",timelen-n+1
148                read(*,*) start
149                write(*,*) "Time subscript interval you want to get ? no more than",(timelen-start+1)/n
150                read(*,*) interval_subs
151        END IF
152endif
153
154
155
156!
157! Info
158!
159PRINT *,'-------'
160PRINT *,'run readmeteo with the command line:'
161PRINT *,'readmeteo.exe < readmeteo.def'
162
163
164!
165! Generate readmeteo.def
166!
167OPEN(6,file='readmeteo.def',status='replace',form='formatted')
168! files
169IF (n < 10) THEN
170        write(6,fmt='(I1)') n
171ELSE IF (n < 100) THEN
172        write(6,fmt='(I2)') n
173ELSE IF (n < 1000) THEN
174        write(6,fmt='(I3)') n
175ELSE
176        write(6,fmt='(I4)') n       
177END IF
178! subscript in GCM data file
179DO i=1,n
180        subs=start+(i-1)*interval_subs
181        IF (subs < 10) THEN
182                write(6,fmt='(I1)') subs
183        ELSE IF (subs < 100) THEN
184                write(6,fmt='(I2)') subs
185        ELSE IF (subs < 1000) THEN
186                write(6,fmt='(I3)') subs
187        ELSE
188                write(6,fmt='(I4)') subs   
189        END IF       
190END DO
191! WRF time reference
192hour=start_hour+(start-1)*interval
193inc_hour=interval*interval_subs
194IF (hour >= 24) day=day+INT(hour/24)
195hour=MOD(hour,24)
196IF (day > 30) THEN
197      day=day-30
198      month=month+1
199END IF
200IF (month > 12) THEN
201      my=my+1
202      month=1
203END IF
204DO i=1,n
205        write(6,fmt='(I4)') my
206        IF (month < 10) THEN
207                write(6,fmt='(I1,I1)') 0,month
208        ELSE
209                write(6,fmt='(I2)') month
210        END IF
211        IF (day < 10) THEN
212                write(6,fmt='(I1,I1)') 0,day
213        ELSE
214                write(6,fmt='(I2)') day
215        END IF
216        IF (hour < 10) THEN
217                write(6,fmt='(I1,I1)') 0,hour
218        ELSE
219                write(6,fmt='(I2)') hour
220        END IF
221        write(6,fmt='(A1)') 'y'
222IF (hour+inc_hour >= 24) day=day+INT((hour+inc_hour)/24)
223hour=MOD(hour+inc_hour,24)
224IF (day > 30) THEN
225        day=day-30
226        month=month+1
227END IF       
228IF (month > 12) THEN
229        my=my+1
230        month=1
231END IF       
232END DO
233close(6)
234
235END
Note: See TracBrowser for help on using the repository browser.