CTBTO FLEXPART WO4 (2015-10-15)
 All Classes Files Functions Variables
fpmetbinary_mod_fullload.F90
Go to the documentation of this file.
1 MODULE 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  ! Note that these routines need more robustness. For example, what *
17  ! what happens if the filename can't be read or written. Or, what *
18  ! happens if a read or write fails in any way. Right now, it's crash *
19  ! city. *
20  ! *
21  !*****************************************************************************
22 
23  USE com_mod
24 
25  IMPLICIT NONE
26 
27  ! Users may want to change these IO Unit values if they conflict with other parts
28  ! of code
29  INTEGER, PARAMETER :: iounit_dump = 33, iounit_load = 34
30  PRIVATE iounit_dump, iounit_load, fpio
31 
32 
33 CONTAINS
34 
35  !*****************************************************************************
36  ! *
37  ! Subroutines fpdump() and fpload() provide the public interface to *
38  ! this module functionality. I created the PRIVATE fpio() because I *
39  ! wanted all interactions with variables to be in one place. The read *
40  ! and write operations need to be done in exactly the same sequence, so *
41  ! I felt like keeping them in the same routine would at least allow for *
42  ! coders to more easily compare the two sequences than if they were *
43  ! separate. *
44  ! *
45  !*****************************************************************************
46 
47 
48  SUBROUTINE fpdump(filename)
49  CHARACTER(LEN=*), INTENT(IN) :: filename
50 
51  OPEN(iounit_dump, file=filename, action='WRITE', status='REPLACE', form="unformatted", access="stream")
52  CALL fpio(iounit_dump, 'DUMP')
53  CLOSE(iounit_dump)
54  END SUBROUTINE fpdump
55 
56  SUBROUTINE fpload(filename)
57  CHARACTER(LEN=*), INTENT(IN) :: filename
58 
59  OPEN(iounit_load, file=filename, action='READ', status='OLD', form="unformatted", access="stream")
60  CALL fpio(iounit_load, 'LOAD')
61  CLOSE(iounit_load)
62  END SUBROUTINE fpload
63 
64 
65 
66 
67 
68  SUBROUTINE fpio(iounit, op)
69  IMPLICIT NONE
70  INTEGER, INTENT(IN) :: iounit
71  CHARACTER(LEN=4), INTENT(IN) :: op
72 
73  if (op == 'DUMP') THEN
74 #ifndef QUICKDUMP
75  WRITE(iounit) path, length
76  WRITE(iounit) ibdate, ibtime, iedate, ietime, bdate, edate
77  WRITE(iounit) ldirect, ideltas, loutstep, loutaver, loutsample, method, lsynctime, outstep
78  WRITE(iounit) ctl, fine, ifine, iout, ipin, iflux, mdomainfill
79  WRITE(iounit) mquasilag,nested_output,ind_source,ind_receptor
80  WRITE(iounit) ind_rel,ind_samp,ioutputforeachrelease,linit_cond, turbswitch
81  WRITE(iounit) mintime,itsplit, lsubgrid,lconvection,lagespectra
82  WRITE(iounit) nageclass, lage, gdomainfill
83  WRITE(iounit) compoint, numpoint, specnum
84  WRITE(iounit) decay, weta, wetb, reldiff, henry, f0
85  WRITE(iounit) density, dquer, dsigma, vsetaver, cunningham, weightmolar
86  WRITE(iounit) vset, schmi, fract, ri, rac, rcl ,rgs, rlu, rm, dryvel, kao, ohreact
87  WRITE(iounit) spec_ass, area_hour, point_hour, area_dow, point_dow
88  WRITE(iounit) nspec, maxpointspec_act, species
89  WRITE(iounit) nx_we, ny_sn, numcolumn, numcolumn_we, numcolumn_sn
90  WRITE(iounit) zcolumn_we, zcolumn_sn, xmassperparticle, acc_mass_we, acc_mass_sn
91  WRITE(iounit) numbwf, wftime, lwindinterv, wfname, wfspec
92  WRITE(iounit) memtime, memind
93  WRITE(iounit) nx,ny,nxmin1,nymin1,nxfield,nuvz,nwz,nz,nmixz,nlev_ec
94  WRITE(iounit) dx,dy,xlon0,ylat0,dxconst,dyconst,height
95  WRITE(iounit) akm, bkm, akz, bkz, aknew, bknew
96  WRITE(iounit) oro, excessoro, lsm, xlanduse
97  WRITE(iounit) uu, vv, uupol, vvpol, ww, tt, qv, pv, rho, drhodz, tth, qvh, pplev, clouds, cloudsh
98  WRITE(iounit) ps, sd, msl, tcc, u10, v10, tt2, td2, lsprec, convprec
99  WRITE(iounit) sshf, ssr, surfstr, ustar, wstar, hmix, tropopause, oli, diffk
100  WRITE(iounit) vdep, numbnests, wfnamen, wfspecn, nxn, nyn, dxn, dyn, xlon0n, ylat0n
101  WRITE(iounit) oron, excessoron, lsmn, xlandusen
102  WRITE(iounit) uun, vvn, wwn, ttn, qvn, pvn, cloudsn, cloudsnh, rhon, drhodzn, tthn, qvhn
103  WRITE(iounit) psn, sdn, msln, tccn, u10n, v10n, tt2n, td2n
104  WRITE(iounit) lsprecn, convprecn, sshfn, ssrn, surfstrn, ustarn, wstarn
105  WRITE(iounit) hmixn, tropopausen, olin, diffkn, vdepn
106  WRITE(iounit) xresoln, yresoln, xln, yln, xrn, yrn
107  WRITE(iounit) xglobal, sglobal, nglobal, switchnorthg, switchsouthg
108  WRITE(iounit) southpolemap, northpolemap
109  WRITE(iounit) landinvent, z0
110  WRITE(iounit) numxgrid, numygrid, numzgrid, dxout, dyout, outlon0, outlat0, xoutshiftn, youtshiftn
111  WRITE(iounit) dep, drydep, drydepspec, wetdep, ohrea, assspec
112  WRITE(iounit) xreceptor, yreceptor, receptorarea, creceptor, receptorname, numreceptor
113  WRITE(iounit) numpart, itra1, npoint, nclass, idt, itramem, itrasplit, numparticlecount
114  WRITE(iounit) xtra1, ytra1, ztra1, xmass1, rannumb
115 #endif
116 
117  ! This IO was actually done above, but it's put in here to help serve to test this
118  ! routine. After all the writes and reads, it comes to this one, and a program that wants
119  ! to test all this can use this to insure that the values of uu, vv, ww read from the binary file
120  ! are the same as those that were written in
121  WRITE(iounit) uu, vv, ww
122 
123 
124  ELSE ! We assume op is 'LOAD'
125 #ifndef QUICKDUMP
126  READ(iounit) path, length
127  READ(iounit) ibdate, ibtime, iedate, ietime, bdate, edate
128  READ(iounit) ldirect, ideltas, loutstep, loutaver, loutsample, method, lsynctime, outstep
129  READ(iounit) ctl, fine, ifine, iout, ipin, iflux, mdomainfill
130  READ(iounit) mquasilag,nested_output,ind_source,ind_receptor
131  READ(iounit) ind_rel,ind_samp,ioutputforeachrelease,linit_cond, turbswitch
132  READ(iounit) mintime,itsplit, lsubgrid,lconvection,lagespectra
133  READ(iounit) nageclass, lage, gdomainfill
134  READ(iounit) compoint, numpoint, specnum
135  READ(iounit) decay, weta, wetb, reldiff, henry, f0
136  READ(iounit) density, dquer, dsigma, vsetaver, cunningham, weightmolar
137  READ(iounit) vset, schmi, fract, ri, rac, rcl ,rgs, rlu, rm, dryvel, kao, ohreact
138  READ(iounit) spec_ass, area_hour, point_hour, area_dow, point_dow
139  READ(iounit) nspec, maxpointspec_act, species
140  READ(iounit) nx_we, ny_sn, numcolumn, numcolumn_we, numcolumn_sn
141  READ(iounit) zcolumn_we, zcolumn_sn, xmassperparticle, acc_mass_we, acc_mass_sn
142  READ(iounit) numbwf, wftime, lwindinterv, wfname, wfspec
143  READ(iounit) memtime, memind
144  READ(iounit) nx,ny,nxmin1,nymin1,nxfield,nuvz,nwz,nz,nmixz,nlev_ec
145  READ(iounit) dx,dy,xlon0,ylat0,dxconst,dyconst,height
146  READ(iounit) akm, bkm, akz, bkz, aknew, bknew
147  READ(iounit) oro, excessoro, lsm, xlanduse
148  READ(iounit) uu, vv, uupol, vvpol, ww, tt, qv, pv, rho, drhodz, tth, qvh, pplev, clouds, cloudsh
149  READ(iounit) ps, sd, msl, tcc, u10, v10, tt2, td2, lsprec, convprec
150  READ(iounit) sshf, ssr, surfstr, ustar, wstar, hmix, tropopause, oli, diffk
151  READ(iounit) vdep, numbnests, wfnamen, wfspecn, nxn, nyn, dxn, dyn, xlon0n, ylat0n
152  READ(iounit) oron, excessoron, lsmn, xlandusen
153  READ(iounit) uun, vvn, wwn, ttn, qvn, pvn, cloudsn, cloudsnh, rhon, drhodzn, tthn, qvhn
154  READ(iounit) psn, sdn, msln, tccn, u10n, v10n, tt2n, td2n
155  READ(iounit) lsprecn, convprecn, sshfn, ssrn, surfstrn, ustarn, wstarn
156  READ(iounit) hmixn, tropopausen, olin, diffkn, vdepn
157  READ(iounit) xresoln, yresoln, xln, yln, xrn, yrn
158  READ(iounit) xglobal, sglobal, nglobal, switchnorthg, switchsouthg
159  READ(iounit) southpolemap, northpolemap
160  READ(iounit) landinvent, z0
161  READ(iounit) numxgrid, numygrid, numzgrid, dxout, dyout, outlon0, outlat0, xoutshiftn, youtshiftn
162  READ(iounit) dep, drydep, drydepspec, wetdep, ohrea, assspec
163  READ(iounit) xreceptor, yreceptor, receptorarea, creceptor, receptorname, numreceptor
164  READ(iounit) numpart, itra1, npoint, nclass, idt, itramem, itrasplit, numparticlecount
165  READ(iounit) xtra1, ytra1, ztra1, xmass1, rannumb
166 #endif
167 
168  ! This IO was actually done above, but it's put in here to help serve to test this
169  ! routine. After all the writes and reads, it comes to this one, and a program that wants
170  ! to test all this can use this to insure that the values of uu, vv, ww read from the binary file
171  ! are the same as those that were written in
172  READ(iounit) uu, vv, ww
173  ENDIF
174  END SUBROUTINE fpio
175 
176 
177 END MODULE fpmetbinary_mod
subroutine, private fpio(iounit, op, cm_index)
subroutine fpdump(filename)
subroutine fpload(filename)