source: flexpart.git/flexpart_code/fpmetbinary_mod.F90 @ 496c607

FPv9.3.1FPv9.3.1b_testingFPv9.3.2fp9.3.1-20161214-nc4grib2nc4_repair
Last change on this file since 496c607 was 496c607, checked in by Don Morton <Don.Morton@…>, 8 years ago

Initial commit of FPv9.3.1

Currently, this is a clone of snapshot FPv9.3.0

  • Property mode set to 100644
File size: 23.5 KB
Line 
1MODULE fpmetbinary_mod
2
3  !*****************************************************************************
4  !                                                                            *
5  !     Contains data and routines for dumping and loading processed met       *
6  !     fields.                                                                *
7  !     Authors Don Morton (Don.Morton@borealscicomp.com)                      *
8  !             Delia Arnold (deliona.arnold@gmail.com)                        *
9  !                                                                            *
10  !     15 Sep 2015                                                            *
11  !                                                                            *
12  !     Currently, the only data being dumped and loaded has data structures   *
13  !     defined in com_mod.f90.  In the future, perhaps it will be necessary   *
14  !     to use data structures from other parts of the FLEXPART code system.   *
15  !                                                                            *
16  !                                                                            *
17  !     Most of the data structures from com_mod.f90 that are dumped and       *
18  !     loaded have a final dimension of size two, so that they may hold data  *
19  !     from two met files.  When we dump the contents into a .fp file, we     *
20  !     need to specify which of the two to dump.  Likewise, when we load      *
21  !     from a .fp file, we need to specify which of the two possible indices  *
22  !     to load into.                                                          *
23  !                                                                            *
24  !     Note that these routines need more robustness.  For example, what      *
25  !     what happens if the filename can't be read or written.  Or, what       *
26  !     happens if a read or write fails in any way.  Right now, it's crash    *
27  !     city.                                                                  *
28  !                                                                            *
29  !*****************************************************************************
30
31    USE com_mod
32    USE conv_mod
33
34    IMPLICIT NONE
35
36    ! Users may want to change these IO Unit values if they conflict with other parts
37    ! of code
38    INTEGER, PARAMETER :: IOUNIT_DUMP = 33, IOUNIT_LOAD = 34, &
39                          IOUNIT_TEXTOUT = 35
40    PRIVATE IOUNIT_DUMP, IOUNIT_LOAD, IOUNIT_TEXTOUT, fpio
41
42
43CONTAINS
44
45  !*****************************************************************************
46  !                                                                            *
47  !    Subroutines fpmetbinary_dump() and fpmetbinary_load() provide the       *
48  !    public interface to                                                     *
49  !    this module functionality.  I created the PRIVATE fpio() because I      *
50  !    wanted all interactions with variables to be in one place.  The read    *
51  !    and write operations need to be done in exactly the same sequence, so   *
52  !    I felt like keeping them in the same routine would at least allow for   *
53  !    coders to more easily compare the two sequences than if they were       *
54  !    separate.                                                               *
55  !                                                                            *
56  !    As mentioned above, the dumps and loads will, for most variables,       *
57  !    need to refer to one of two index values for the last dimension of      *
58  !    the array.                                                              *
59  !                                                                            *
60  !*****************************************************************************
61
62
63    SUBROUTINE fpmetbinary_dump(filename, cm_index)
64        CHARACTER(LEN=*), INTENT(IN) :: filename  ! Full path for file
65        INTEGER, INTENT(IN) :: cm_index           ! Index of last dimension in
66                                                  ! most com_mod variables.
67                                                  ! Should be 1 or 2
68
69        INTEGER millisecs_start, millisecs_stop, count_rate, count_max
70
71        CALL SYSTEM_CLOCK(millisecs_start, count_rate, count_max)
72        OPEN(IOUNIT_DUMP, file=filename, action='WRITE', status='REPLACE', form="unformatted", access="stream")
73        CALL fpio(IOUNIT_DUMP, 'DUMP', cm_index)
74        CLOSE(IOUNIT_DUMP)
75        CALL SYSTEM_CLOCK(millisecs_stop, count_rate, count_max)
76
77        !PRINT *, 'Dump walltime secs: ', (millisecs_stop-millisecs_start)/1000.0
78    END SUBROUTINE fpmetbinary_dump
79
80    SUBROUTINE fpmetbinary_load(filename, cm_index)
81        CHARACTER(LEN=*), INTENT(IN) :: filename  ! Full path for file
82        INTEGER, INTENT(IN) :: cm_index           ! Index of last dimension in
83                                                  ! most com_mod variables.
84                                                  ! Should be 1 or 2
85
86        INTEGER millisecs_start, millisecs_stop, count_rate, count_max
87
88        CALL SYSTEM_CLOCK(millisecs_start, count_rate, count_max)
89        OPEN(IOUNIT_LOAD, file=filename, action='READ', status='OLD', form="unformatted", access="stream")
90        CALL fpio(IOUNIT_LOAD, 'LOAD', cm_index)
91        CLOSE(IOUNIT_LOAD)
92        CALL SYSTEM_CLOCK(millisecs_stop, count_rate, count_max)
93        !PRINT *, 'Load walltime secs: ', (millisecs_stop-millisecs_start)/1000.0
94    END SUBROUTINE fpmetbinary_load
95
96    SUBROUTINE fpmetbinary_zero(cm_index)
97        INTEGER, INTENT(IN) :: cm_index           ! Index of last dimension in
98                                                  ! most com_mod variables.
99                                                  ! Should be 1 or 2
100
101
102        ! Zeroes out, in local datastructures, the values dumped/loaded
103        ! This was written primarily as a testing mechanism.
104        ! The lines here correspond to READ and WRITE in the dump/load routines
105
106        ! Scalar values
107        nx=0.0; ny=0.0; nxmin1=0.0; nymin1=0.0; nxfield=0.0
108        nuvz=0.0; nwz=0.0; nz=0.0; nmixz=0.0; nlev_ec=0.0
109        dx=0.0; dy=0.0; xlon0=0.0; ylat0=0.0; dxconst=0.0; dyconst=0.0
110
111        ! Fixed fields, static in time
112        oro=0.0; excessoro=0.0; lsm=0.0; xlanduse=0.0; height=0.0
113
114        ! 3d fields
115        uu(:,:,:,cm_index) = 0.0
116        vv(:,:,:,cm_index) = 0.0
117        uupol(:,:,:,cm_index) = 0.0
118        vvpol(:,:,:,cm_index) = 0.0
119        ww(:,:,:,cm_index) = 0.0
120        tt(:,:,:,cm_index) = 0.0
121        qv(:,:,:,cm_index) = 0.0
122        pv(:,:,:,cm_index) = 0.0
123        rho(:,:,:,cm_index) = 0.0
124        drhodz(:,:,:,cm_index) = 0.0
125        tth(:,:,:,cm_index) = 0.0
126        qvh(:,:,:,cm_index) = 0.0
127        pplev(:,:,:,cm_index) = 0.0
128        clouds(:,:,:,cm_index) = 0.0
129        cloudsh(:,:,cm_index) = 0.0
130
131        ! 2d fields
132        ps(:,:,:,cm_index) = 0.0
133        sd(:,:,:,cm_index) = 0.0
134        msl(:,:,:,cm_index) = 0.0
135        tcc(:,:,:,cm_index) = 0.0
136        u10(:,:,:,cm_index) = 0.0
137        v10(:,:,:,cm_index) = 0.0
138        tt2(:,:,:,cm_index) = 0.0
139        td2(:,:,:,cm_index) = 0.0
140        lsprec(:,:,:,cm_index) = 0.0
141        convprec(:,:,:,cm_index) = 0.0
142        sshf(:,:,:,cm_index) = 0.0
143        ssr(:,:,:,cm_index) = 0.0
144        surfstr(:,:,:,cm_index) = 0.0
145        ustar(:,:,:,cm_index) = 0.0
146        wstar(:,:,:,cm_index) = 0.0
147        hmix(:,:,:,cm_index) = 0.0
148        tropopause(:,:,:,cm_index) = 0.0
149        oli(:,:,:,cm_index) = 0.0
150        diffk(:,:,:,cm_index) = 0.0
151        vdep(:,:,:,cm_index) = 0.0
152
153        ! 1d fields
154        z0(:) = 0.0
155        akm(:) = 0.0
156        bkm(:) = 0.0
157        akz(:) = 0.0
158        bkz(:) = 0.0
159        aknew(:) = 0.0
160        bknew(:) = 0.0
161
162        ! Nested, scalar values (for each nest)
163        nxn(:) = 0.0
164        nyn(:) = 0.0
165        dxn(:) = 0.0
166        dyn(:) = 0.0
167        xlon0n(:) = 0.0
168        ylat0n(:) = 0.0
169
170        ! Nested fields, static in time
171        oron=0.0; excessoron=0.0; lsmn=0.0; xlandusen=0.0
172
173        ! 3d nested fields
174        uun(:,:,:,cm_index,:) = 0.0
175        wwn(:,:,:,cm_index,:) = 0.0
176        ttn(:,:,:,cm_index,:) = 0.0
177        qvn(:,:,:,cm_index,:) = 0.0
178        pvn(:,:,:,cm_index,:) = 0.0
179        cloudsn(:,:,:,cm_index,:) = 0.0
180        cloudsnh(:,:,cm_index,:) = 0.0
181        rhon(:,:,:,cm_index,:) = 0.0
182        drhodzn(:,:,:,cm_index,:) = 0.0
183        tthn(:,:,:,cm_index,:) = 0.0
184        qvhn(:,:,:,cm_index,:) = 0.0
185
186        ! 2d nested fields
187        psn(:,:,:,cm_index,:) = 0.0
188        sdn(:,:,:,cm_index,:) = 0.0
189        msln(:,:,:,cm_index,:) = 0.0
190        tccn(:,:,:,cm_index,:) = 0.0
191        u10n(:,:,:,cm_index,:) = 0.0
192        v10n(:,:,:,cm_index,:) = 0.0
193        tt2n(:,:,:,cm_index,:) = 0.0
194        td2n(:,:,:,cm_index,:) = 0.0
195        lsprecn(:,:,:,cm_index,:) = 0.0
196        convprecn(:,:,:,cm_index,:) = 0.0
197        sshfn(:,:,:,cm_index,:) = 0.0
198        ssrn(:,:,:,cm_index,:) = 0.0
199        surfstrn(:,:,:,cm_index,:) = 0.0
200        ustarn(:,:,:,cm_index,:) = 0.0
201        wstarn(:,:,:,cm_index,:) = 0.0
202        hmixn(:,:,:,cm_index,:) = 0.0
203        tropopausen(:,:,:,cm_index,:) = 0.0
204        olin(:,:,:,cm_index,:) = 0.0
205        diffkn(:,:,:,cm_index,:) = 0.0
206        vdepn(:,:,:,cm_index,:) = 0.0
207
208        ! Auxiliary variables for nests
209        xresoln(:) = 0.0
210        yresoln(:) = 0.0
211        xln(:) = 0.0
212        yln(:) = 0.0
213        xrn(:) = 0.0
214        yrn(:) = 0.0
215
216        ! Variables for polar stereographic projection
217        xglobal=.FALSE.; sglobal=.FALSE.; nglobal=.FALSE.
218        switchnorthg=0.0; switchsouthg=0.0
219        southpolemap(:) = 0.0
220        northpolemap(:) = 0.0
221
222        ! Variables declared in conv_mod (convection)
223        pconv(:) = 0.0
224        phconv(:) = 0.0
225        dpr(:) = 0.0
226        pconv_hpa(:) = 0.0
227        phconv_hpa(:) = 0.0
228        ft(:) = 0.0
229        fq(:) = 0.0
230        fmass(:,:) = 0.0
231        sub(:) = 0.0
232        fmassfrac(:,:) = 0.0
233        cbaseflux(:,:) = 0.0
234        cbasefluxn(:,:,:) = 0.0
235        tconv(:) = 0.0
236        qconv(:) = 0.0
237        qsconv(:) = 0.0
238        psconv=0.0; tt2conv=0.0; td2conv=0.0
239        nconvlev=0.0; nconvtop=0.0
240
241    END SUBROUTINE fpmetbinary_zero
242
243    SUBROUTINE fpio(iounit, op, cm_index)
244        IMPLICIT NONE
245        INTEGER, INTENT(IN) :: iounit
246        CHARACTER(LEN=4), INTENT(IN) :: op        ! Operation - DUMP or LOAD
247        INTEGER, INTENT(IN) :: cm_index           ! Index of last dimension in
248                                                  ! most com_mod variables.
249                                                  ! Should be 1 or 2
250        CHARACTER(LEN=128) :: errmesg
251
252        if (op == 'DUMP') THEN
253
254            ! Scalar values
255            WRITE(iounit) nx, ny, nxmin1, nymin1, nxfield
256            WRITE(iounit) nuvz, nwz, nz, nmixz, nlev_ec
257            WRITE(iounit) dx, dy, xlon0, ylat0, dxconst, dyconst
258
259            ! Fixed fields, static in time
260            WRITE(iounit) oro, excessoro, lsm, xlanduse, height
261
262            ! 3d fields
263            WRITE(iounit) uu(:,:,:,cm_index)
264            WRITE(iounit) vv(:,:,:,cm_index)
265            WRITE(iounit) uupol(:,:,:,cm_index)
266            WRITE(iounit) vvpol(:,:,:,cm_index)
267            WRITE(iounit) ww(:,:,:,cm_index)
268            WRITE(iounit) tt(:,:,:,cm_index)
269            WRITE(iounit) qv(:,:,:,cm_index)
270            WRITE(iounit) pv(:,:,:,cm_index)
271            WRITE(iounit) rho(:,:,:,cm_index)
272            WRITE(iounit) drhodz(:,:,:,cm_index)
273            WRITE(iounit) tth(:,:,:,cm_index)
274            WRITE(iounit) qvh(:,:,:,cm_index)
275            WRITE(iounit) pplev(:,:,:,cm_index)
276            WRITE(iounit) clouds(:,:,:,cm_index)
277            WRITE(iounit) cloudsh(:,:,cm_index)
278
279            ! 2d fields
280            WRITE(iounit) ps(:,:,:,cm_index)
281            WRITE(iounit) sd(:,:,:,cm_index)
282            WRITE(iounit) msl(:,:,:,cm_index)
283            WRITE(iounit) tcc(:,:,:,cm_index)
284            WRITE(iounit) u10(:,:,:,cm_index)
285            WRITE(iounit) v10(:,:,:,cm_index)
286            WRITE(iounit) tt2(:,:,:,cm_index)
287            WRITE(iounit) td2(:,:,:,cm_index)
288            WRITE(iounit) lsprec(:,:,:,cm_index)
289            WRITE(iounit) convprec(:,:,:,cm_index)
290            WRITE(iounit) sshf(:,:,:,cm_index)
291            WRITE(iounit) ssr(:,:,:,cm_index)
292            WRITE(iounit) surfstr(:,:,:,cm_index)
293            WRITE(iounit) ustar(:,:,:,cm_index)
294            WRITE(iounit) wstar(:,:,:,cm_index)
295            WRITE(iounit) hmix(:,:,:,cm_index)
296            WRITE(iounit) tropopause(:,:,:,cm_index)
297            WRITE(iounit) oli(:,:,:,cm_index)
298            WRITE(iounit) diffk(:,:,:,cm_index)
299            WRITE(iounit) vdep(:,:,:,cm_index)
300
301            ! 1d fields
302            WRITE(iounit) z0(:)
303            WRITE(iounit) akm(:)
304            WRITE(iounit) bkm(:)
305            WRITE(iounit) akz(:)
306            WRITE(iounit) bkz(:)
307            WRITE(iounit) aknew(:)
308            WRITE(iounit) bknew(:)
309
310            ! Nested, scalar values (for each nest)
311            WRITE(iounit) nxn(:)
312            WRITE(iounit) nyn(:)
313            WRITE(iounit) dxn(:)
314            WRITE(iounit) dyn(:)
315            WRITE(iounit) xlon0n(:)
316            WRITE(iounit) ylat0n(:)
317
318            ! Nested fields, static over time
319            WRITE(iounit) oron, excessoron, lsmn, xlandusen
320
321            ! 3d nested fields
322            WRITE(iounit) uun(:,:,:,cm_index,:)
323            WRITE(iounit) vvn(:,:,:,cm_index,:)
324            WRITE(iounit) wwn(:,:,:,cm_index,:)
325            WRITE(iounit) ttn(:,:,:,cm_index,:)
326            WRITE(iounit) qvn(:,:,:,cm_index,:)
327            WRITE(iounit) pvn(:,:,:,cm_index,:)
328            WRITE(iounit) cloudsn(:,:,:,cm_index,:)
329            WRITE(iounit) cloudsnh(:,:,cm_index,:)
330            WRITE(iounit) rhon(:,:,:,cm_index,:)
331            WRITE(iounit) drhodzn(:,:,:,cm_index,:)
332            WRITE(iounit) tthn(:,:,:,cm_index,:)
333            WRITE(iounit) qvhn(:,:,:,cm_index,:)
334
335            ! 2d nested fields
336            WRITE(iounit) psn(:,:,:,cm_index,:)
337            WRITE(iounit) sdn(:,:,:,cm_index,:)
338            WRITE(iounit) msln(:,:,:,cm_index,:)
339            WRITE(iounit) tccn(:,:,:,cm_index,:)
340            WRITE(iounit) u10n(:,:,:,cm_index,:)
341            WRITE(iounit) v10n(:,:,:,cm_index,:)
342            WRITE(iounit) tt2n(:,:,:,cm_index,:)
343            WRITE(iounit) td2n(:,:,:,cm_index,:)
344            WRITE(iounit) lsprecn(:,:,:,cm_index,:)
345            WRITE(iounit) convprecn(:,:,:,cm_index,:)
346            WRITE(iounit) sshfn(:,:,:,cm_index,:)
347            WRITE(iounit) ssrn(:,:,:,cm_index,:)
348            WRITE(iounit) surfstrn(:,:,:,cm_index,:)
349            WRITE(iounit) ustarn(:,:,:,cm_index,:)
350            WRITE(iounit) wstarn(:,:,:,cm_index,:)
351            WRITE(iounit) hmixn(:,:,:,cm_index,:)
352            WRITE(iounit) tropopausen(:,:,:,cm_index,:)
353            WRITE(iounit) olin(:,:,:,cm_index,:)
354            WRITE(iounit) diffkn(:,:,:,cm_index,:)
355            WRITE(iounit) vdepn(:,:,:,cm_index,:)
356
357            ! Auxiliary variables for nests
358            WRITE(iounit) xresoln(:)
359            WRITE(iounit) yresoln(:)
360            WRITE(iounit) xln(:)
361            WRITE(iounit) yln(:)
362            WRITE(iounit) xrn(:)
363            WRITE(iounit) yrn(:)
364
365            ! Variables for polar stereographic projection
366            WRITE(iounit) xglobal, sglobal, nglobal
367            WRITE(iounit) switchnorthg, switchsouthg
368            WRITE(iounit) southpolemap(:)
369            WRITE(iounit) northpolemap(:)
370
371            ! Variables declared in conv_mod (convection)
372            WRITE(iounit) pconv(:)
373            WRITE(iounit) phconv(:)
374            WRITE(iounit) dpr(:)
375            WRITE(iounit) pconv_hpa(:)
376            WRITE(iounit) phconv_hpa(:)
377            WRITE(iounit) ft(:)
378            WRITE(iounit) fq(:)
379            WRITE(iounit) fmass(:,:)
380            WRITE(iounit) sub(:)
381            WRITE(iounit) fmassfrac(:,:)
382            WRITE(iounit) cbaseflux(:,:)
383            WRITE(iounit) cbasefluxn(:,:,:)
384            WRITE(iounit) tconv(:)
385            WRITE(iounit) qconv(:)
386            WRITE(iounit) qsconv(:)
387            WRITE(iounit) psconv, tt2conv, td2conv
388            WRITE(iounit) nconvlev, nconvtop
389
390        ELSE IF (op == 'LOAD') THEN
391
392            ! Scalar values
393            READ(iounit) nx, ny, nxmin1, nymin1, nxfield
394            READ(iounit) nuvz, nwz, nz, nmixz, nlev_ec
395            READ(iounit) dx, dy, xlon0, ylat0, dxconst, dyconst
396
397            ! Fixed fields, static in time
398            READ(iounit) oro, excessoro, lsm, xlanduse, height
399
400            ! 3d fields
401            READ(iounit) uu(:,:,:,cm_index)
402            READ(iounit) vv(:,:,:,cm_index)
403            READ(iounit) uupol(:,:,:,cm_index)
404            READ(iounit) vvpol(:,:,:,cm_index)
405            READ(iounit) ww(:,:,:,cm_index)
406            READ(iounit) tt(:,:,:,cm_index)
407            READ(iounit) qv(:,:,:,cm_index)
408            READ(iounit) pv(:,:,:,cm_index)
409            READ(iounit) rho(:,:,:,cm_index)
410            READ(iounit) drhodz(:,:,:,cm_index)
411            READ(iounit) tth(:,:,:,cm_index)
412            READ(iounit) qvh(:,:,:,cm_index)
413            READ(iounit) pplev(:,:,:,cm_index)
414            READ(iounit) clouds(:,:,:,cm_index)
415            READ(iounit) cloudsh(:,:,cm_index)
416
417            ! 2d fields
418            READ(iounit) ps(:,:,:,cm_index)
419            READ(iounit) sd(:,:,:,cm_index)
420            READ(iounit) msl(:,:,:,cm_index)
421            READ(iounit) tcc(:,:,:,cm_index)
422            READ(iounit) u10(:,:,:,cm_index)
423            READ(iounit) v10(:,:,:,cm_index)
424            READ(iounit) tt2(:,:,:,cm_index)
425            READ(iounit) td2(:,:,:,cm_index)
426            READ(iounit) lsprec(:,:,:,cm_index)
427            READ(iounit) convprec(:,:,:,cm_index)
428            READ(iounit) sshf(:,:,:,cm_index)
429            READ(iounit) ssr(:,:,:,cm_index)
430            READ(iounit) surfstr(:,:,:,cm_index)
431            READ(iounit) ustar(:,:,:,cm_index)
432            READ(iounit) wstar(:,:,:,cm_index)
433            READ(iounit) hmix(:,:,:,cm_index)
434            READ(iounit) tropopause(:,:,:,cm_index)
435            READ(iounit) oli(:,:,:,cm_index)
436            READ(iounit) diffk(:,:,:,cm_index)
437            READ(iounit) vdep(:,:,:,cm_index)
438
439            ! 1d fields
440            READ(iounit) z0(:)
441            READ(iounit) akm(:)
442            READ(iounit) bkm(:)
443            READ(iounit) akz(:)
444            READ(iounit) bkz(:)
445            READ(iounit) aknew(:)
446            READ(iounit) bknew(:)
447
448
449            ! Nested, scalar values (for each nest)
450            READ(iounit) nxn(:)
451            READ(iounit) nyn(:)
452            READ(iounit) dxn(:)
453            READ(iounit) dyn(:)
454            READ(iounit) xlon0n(:)
455            READ(iounit) ylat0n(:)
456
457
458            ! Nested fields, static over time
459            READ(iounit) oron, excessoron, lsmn, xlandusen
460
461            ! 3d nested fields
462            READ(iounit) uun(:,:,:,cm_index,:)
463            READ(iounit) vvn(:,:,:,cm_index,:)
464            READ(iounit) wwn(:,:,:,cm_index,:)
465            READ(iounit) ttn(:,:,:,cm_index,:)
466            READ(iounit) qvn(:,:,:,cm_index,:)
467            READ(iounit) pvn(:,:,:,cm_index,:)
468            READ(iounit) cloudsn(:,:,:,cm_index,:)
469            READ(iounit) cloudsnh(:,:,cm_index,:)
470            READ(iounit) rhon(:,:,:,cm_index,:)
471            READ(iounit) drhodzn(:,:,:,cm_index,:)
472            READ(iounit) tthn(:,:,:,cm_index,:)
473            READ(iounit) qvhn(:,:,:,cm_index,:)
474
475            ! 2d nested fields
476            READ(iounit) psn(:,:,:,cm_index,:)
477            READ(iounit) sdn(:,:,:,cm_index,:)
478            READ(iounit) msln(:,:,:,cm_index,:)
479            READ(iounit) tccn(:,:,:,cm_index,:)
480            READ(iounit) u10n(:,:,:,cm_index,:)
481            READ(iounit) v10n(:,:,:,cm_index,:)
482            READ(iounit) tt2n(:,:,:,cm_index,:)
483            READ(iounit) td2n(:,:,:,cm_index,:)
484            READ(iounit) lsprecn(:,:,:,cm_index,:)
485            READ(iounit) convprecn(:,:,:,cm_index,:)
486            READ(iounit) sshfn(:,:,:,cm_index,:)
487            READ(iounit) ssrn(:,:,:,cm_index,:)
488            READ(iounit) surfstrn(:,:,:,cm_index,:)
489            READ(iounit) ustarn(:,:,:,cm_index,:)
490            READ(iounit) wstarn(:,:,:,cm_index,:)
491            READ(iounit) hmixn(:,:,:,cm_index,:)
492            READ(iounit) tropopausen(:,:,:,cm_index,:)
493            READ(iounit) olin(:,:,:,cm_index,:)
494            READ(iounit) diffkn(:,:,:,cm_index,:)
495            READ(iounit) vdepn(:,:,:,cm_index,:)
496
497            ! Auxiliary variables for nests
498            READ(iounit) xresoln(:)
499            READ(iounit) yresoln(:)
500            READ(iounit) xln(:)
501            READ(iounit) yln(:)
502            READ(iounit) xrn(:)
503            READ(iounit) yrn(:)
504
505            ! Variables for polar stereographic projection
506            READ(iounit) xglobal, sglobal, nglobal
507            READ(iounit) switchnorthg, switchsouthg
508            READ(iounit) southpolemap(:)
509            READ(iounit) northpolemap(:)
510
511            ! Variables declared in conv_mod (convection)
512            READ(iounit) pconv(:)
513            READ(iounit) phconv(:)
514            READ(iounit) dpr(:)
515            READ(iounit) pconv_hpa(:)
516            READ(iounit) phconv_hpa(:)
517            READ(iounit) ft(:)
518            READ(iounit) fq(:)
519            READ(iounit) fmass(:,:)
520            READ(iounit) sub(:)
521            READ(iounit) fmassfrac(:,:)
522            READ(iounit) cbaseflux(:,:)
523            READ(iounit) cbasefluxn(:,:,:)
524            READ(iounit) tconv(:)
525            READ(iounit) qconv(:)
526            READ(iounit) qsconv(:)
527            READ(iounit) psconv, tt2conv, td2conv
528            READ(iounit) nconvlev, nconvtop
529
530        ELSE
531            STOP 'fpio(): Illegal operation'
532           
533        ENDIF
534    END SUBROUTINE fpio
535
536    SUBROUTINE fpmetbinary_filetext(filename, cm_index)
537
538        ! This is a utility subroutine meant to be used for testing purposes.
539        ! It facilitates the text output of variables read in from the
540        ! specified .fp file.  This routine will easily cause the program
541        ! to crash due memory allocation issues, particularly when you are
542        ! trying to text print 3d arrays in a single formatted statetment.
543       
544        CHARACTER(LEN=*), INTENT(IN) :: filename
545        INTEGER, INTENT(IN) :: cm_index           ! Index of last dimension in
546                                                  ! most com_mod variables.
547                                                  ! Should be 1 or 2
548
549        !OPEN(IOUNIT_TEXTOUT, file=filename, action='WRITE', status='REPLACE', &
550        !    form="formatted", access="stream")
551        OPEN(IOUNIT_TEXTOUT, file=filename, action='WRITE', &
552             form="formatted", access="APPEND")
553
554        WRITE(IOUNIT_TEXTOUT, *) 'oro: ', oro
555        WRITE(IOUNIT_TEXTOUT, *) 'excessoro: ', excessoro
556        WRITE(IOUNIT_TEXTOUT, *) 'lsm: ', lsm
557        WRITE(IOUNIT_TEXTOUT, *) 'xlanduse: ', xlanduse
558        WRITE(IOUNIT_TEXTOUT, *) 'height: ', height
559
560        WRITE(IOUNIT_TEXTOUT, *) 'uu: ', uu(:,:,:,cm_index)
561        WRITE(IOUNIT_TEXTOUT, *) 'vv: ', vv(:,:,:,cm_index)
562        WRITE(IOUNIT_TEXTOUT, *) 'uupol: ', uupol(:,:,:,cm_index)
563        WRITE(IOUNIT_TEXTOUT, *) 'vvpol: ', vvpol(:,:,:,cm_index)
564        WRITE(IOUNIT_TEXTOUT, *) 'ww: ', ww(:,:,:,cm_index)
565        WRITE(IOUNIT_TEXTOUT, *) 'tt: ', tt(:,:,:,cm_index)
566        WRITE(IOUNIT_TEXTOUT, *) 'qv: ', qv(:,:,:,cm_index)
567        WRITE(IOUNIT_TEXTOUT, *) 'pv: ', pv(:,:,:,cm_index)
568        WRITE(IOUNIT_TEXTOUT, *) 'rho: ', rho(:,:,:,cm_index)
569        WRITE(IOUNIT_TEXTOUT, *) 'drhodz: ', drhodz(:,:,:,cm_index)
570        WRITE(IOUNIT_TEXTOUT, *) 'tth: ', tth(:,:,:,cm_index)
571        WRITE(IOUNIT_TEXTOUT, *) 'qvh: ', qvh(:,:,:,cm_index)
572        WRITE(IOUNIT_TEXTOUT, *) 'pplev: ', pplev(:,:,:,cm_index)
573        WRITE(IOUNIT_TEXTOUT, *) 'clouds: ', clouds(:,:,:,cm_index)
574        WRITE(IOUNIT_TEXTOUT, *) 'cloudsh: ', cloudsh(:,:,cm_index)
575
576
577
578
579        CLOSE(IOUNIT_TEXTOUT)
580    END SUBROUTINE fpmetbinary_filetext
581
582
583END MODULE fpmetbinary_mod
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG