Changes between Initial Version and Version 1 of FpCtbtoWo4FpFormat


Ignore:
Timestamp:
Nov 5, 2015, 12:19:11 PM (8 years ago)
Author:
dearn
Comment:

--

Legend:

Unmodified
Added
Removed
Modified
  • FpCtbtoWo4FpFormat

    v1 v1  
     1= Documentation on fp format and FLEXPART workflow regarding meteorological input data =
     2
     3For diagrams of routines and dependencies, see: [http://borealscicomp.com/CTBTO_FLEXPART/flexdoxygen/20151015/]
     4
     5In order to facilitate the conversion of processed met data into a form that can be stored in a file, and then read by another process, we have defined an “fp format.”   Like anything in life, there are tradeoffs between ease of use and performance.  One option, which some of the community has favoured, has been to store it in NetCDF format.  This would allow for relatively easy access to specific data, and the data would be “self describing.”  This may still be an option in the future, but we opted for a straight binary dump/load of variables, which Fortran can do very efficiently.  With this approach, a full array may be efficiently dumped/loaded to/from a file with simple WRITE/READ statements.  For example (this program was used to initially test the concept)
     6
     7
     8{{{
     9PROGRAM t2
     10
     11INTEGER, PARAMETER :: N = 2
     12REAL, DIMENSION(N,N) :: A, B
     13
     14!! Create simple array
     15A = 3.14
     16B = 2.0*A
     17
     18WRITE(6,*) 'ORIGINAL A:', A
     19WRITE(6,*) 'ORIGINAL B:', B
     20WRITE(6,*)
     21
     22!!! Dump the data to .fp file
     23OPEN(3, file='temp.fp', form="unformatted", access="sequential")
     24WRITE(3) A, B
     25CLOSE(3)
     26
     27! Change the original A, so we're sure that it's loaded correctly
     28A = -9999.99
     29B = -9999.99
     30
     31WRITE(6,*) 'MODIFIED A:', A
     32WRITE(6,*) 'MODIFIED B:', B
     33WRITE(6,*)
     34
     35!!! Load the data from .fp file
     36OPEN(4, file='temp.fp', form="unformatted", access="sequential")
     37READ(4) A, B
     38CLOSE(4)
     39
     40WRITE(6,*) 'NEWLY LOADED A:', A
     41WRITE(6,*) 'NEWLY LOADED B:', B
     42
     43END PROGRAM t2
     44}}}
     45
     46
     47The met fields are all stored in complex arrays defined in ''com_mod.f90'' - for example
     48
     49
     50{{{
     51  real :: uu(0:nxmax-1,0:nymax-1,nzmax,2)
     52  real :: vv(0:nxmax-1,0:nymax-1,nzmax,2)
     53  real :: uupol(0:nxmax-1,0:nymax-1,nzmax,2)
     54  real :: vvpol(0:nxmax-1,0:nymax-1,nzmax,2)
     55}}}
     56
     57
     58
     59By understanding which arrays were important, we could build dump and load routines by insuring that the WRITE and READ statements were in the same order.  There was difficulty in figuring out which arrays and variables were important.  We could have chosen just to dump all of ''com_mod'' (it's what we did initially), but wanted to be more efficient. What we dump is more than sufficient.  There are some variables that we’re not sure of, particularly when we think about how they might not be necessary now, but might be in the future, and in such cases, if we were in doubt, we chose to keep them in the fp file. 
     60
     61Most of the arrays have one of their dimensions valued at 2, and this is used because FLEXPART always needs to store data from two met files so that it can efficiently interpolate.  For a number of reasons - efficiency being one of them - we wanted to make sure that we only dumped one of the sets into a file, and when we loaded, we wanted to make sure we loaded it into the correct index of the arrays.  FLEXPART gets tricky with these index pointers to minimise swapping of fields when a new one is read in, but we were finally able to understand how this works, and build a system that dumps and loads correctly. 
     62
     63The fp format is best illustrated by showing the code for the ''fpmetbinary_dump()'' routine.  ''cm_index'' in the following array slices is the index being dumped (1 or 2) from the ''com_mod.f90'' arrays.
     64
     65
     66{{{
     67            ! Scalar values
     68            WRITE(iounit) nx, ny, nxmin1, nymin1, nxfield
     69            WRITE(iounit) nuvz, nwz, nz, nmixz, nlev_ec
     70            WRITE(iounit) dx, dy, xlon0, ylat0, dxconst, dyconst
     71
     72            ! Fixed fields, static in time
     73            WRITE(iounit) oro, excessoro, lsm, xlanduse, height
     74
     75            ! 3d fields
     76            WRITE(iounit) uu(:,:,:,cm_index)
     77            WRITE(iounit) vv(:,:,:,cm_index)
     78            WRITE(iounit) uupol(:,:,:,cm_index)
     79            WRITE(iounit) vvpol(:,:,:,cm_index)
     80            WRITE(iounit) ww(:,:,:,cm_index)
     81            WRITE(iounit) tt(:,:,:,cm_index)
     82            WRITE(iounit) qv(:,:,:,cm_index)
     83            WRITE(iounit) pv(:,:,:,cm_index)
     84            WRITE(iounit) rho(:,:,:,cm_index)
     85            WRITE(iounit) drhodz(:,:,:,cm_index)
     86            WRITE(iounit) tth(:,:,:,cm_index)
     87            WRITE(iounit) qvh(:,:,:,cm_index)
     88            WRITE(iounit) pplev(:,:,:,cm_index)
     89            WRITE(iounit) clouds(:,:,:,cm_index)
     90            WRITE(iounit) cloudsh(:,:,cm_index)
     91
     92            ! 2d fields
     93            WRITE(iounit) ps(:,:,:,cm_index)
     94            WRITE(iounit) sd(:,:,:,cm_index)
     95            WRITE(iounit) msl(:,:,:,cm_index)
     96            WRITE(iounit) tcc(:,:,:,cm_index)
     97            WRITE(iounit) u10(:,:,:,cm_index)
     98            WRITE(iounit) v10(:,:,:,cm_index)
     99            WRITE(iounit) tt2(:,:,:,cm_index)
     100            WRITE(iounit) td2(:,:,:,cm_index)
     101            WRITE(iounit) lsprec(:,:,:,cm_index)
     102            WRITE(iounit) convprec(:,:,:,cm_index)
     103            WRITE(iounit) sshf(:,:,:,cm_index)
     104            WRITE(iounit) ssr(:,:,:,cm_index)
     105            WRITE(iounit) surfstr(:,:,:,cm_index)
     106            WRITE(iounit) ustar(:,:,:,cm_index)
     107            WRITE(iounit) wstar(:,:,:,cm_index)
     108            WRITE(iounit) hmix(:,:,:,cm_index)
     109            WRITE(iounit) tropopause(:,:,:,cm_index)
     110            WRITE(iounit) oli(:,:,:,cm_index)
     111            WRITE(iounit) diffk(:,:,:,cm_index)
     112            WRITE(iounit) vdep(:,:,:,cm_index)
     113
     114            ! 1d fields
     115            WRITE(iounit) z0(:)
     116            WRITE(iounit) akm(:)
     117            WRITE(iounit) bkm(:)
     118            WRITE(iounit) akz(:)
     119            WRITE(iounit) bkz(:)
     120            WRITE(iounit) aknew(:)
     121            WRITE(iounit) bknew(:)
     122
     123            ! Nested, scalar values (for each nest)
     124            WRITE(iounit) nxn(:)
     125            WRITE(iounit) nyn(:)
     126            WRITE(iounit) dxn(:)
     127            WRITE(iounit) dyn(:)
     128            WRITE(iounit) xlon0n(:)
     129            WRITE(iounit) ylat0n(:)
     130
     131            ! Nested fields, static over time
     132            WRITE(iounit) oron, excessoron, lsmn, xlandusen
     133
     134            ! 3d nested fields
     135            WRITE(iounit) uun(:,:,:,cm_index,:)
     136            WRITE(iounit) vvn(:,:,:,cm_index,:)
     137            WRITE(iounit) wwn(:,:,:,cm_index,:)
     138            WRITE(iounit) ttn(:,:,:,cm_index,:)
     139            WRITE(iounit) qvn(:,:,:,cm_index,:)
     140            WRITE(iounit) pvn(:,:,:,cm_index,:)
     141            WRITE(iounit) cloudsn(:,:,:,cm_index,:)
     142            WRITE(iounit) cloudsnh(:,:,cm_index,:)
     143            WRITE(iounit) rhon(:,:,:,cm_index,:)
     144            WRITE(iounit) drhodzn(:,:,:,cm_index,:)
     145            WRITE(iounit) tthn(:,:,:,cm_index,:)
     146            WRITE(iounit) qvhn(:,:,:,cm_index,:)
     147
     148            ! 2d nested fields
     149            WRITE(iounit) psn(:,:,:,cm_index,:)
     150            WRITE(iounit) sdn(:,:,:,cm_index,:)
     151            WRITE(iounit) msln(:,:,:,cm_index,:)
     152            WRITE(iounit) tccn(:,:,:,cm_index,:)
     153            WRITE(iounit) u10n(:,:,:,cm_index,:)
     154            WRITE(iounit) v10n(:,:,:,cm_index,:)
     155            WRITE(iounit) tt2n(:,:,:,cm_index,:)
     156            WRITE(iounit) td2n(:,:,:,cm_index,:)
     157            WRITE(iounit) lsprecn(:,:,:,cm_index,:)
     158            WRITE(iounit) convprecn(:,:,:,cm_index,:)
     159            WRITE(iounit) sshfn(:,:,:,cm_index,:)
     160            WRITE(iounit) ssrn(:,:,:,cm_index,:)
     161            WRITE(iounit) surfstrn(:,:,:,cm_index,:)
     162            WRITE(iounit) ustarn(:,:,:,cm_index,:)
     163            WRITE(iounit) wstarn(:,:,:,cm_index,:)
     164            WRITE(iounit) hmixn(:,:,:,cm_index,:)
     165            WRITE(iounit) tropopausen(:,:,:,cm_index,:)
     166            WRITE(iounit) olin(:,:,:,cm_index,:)
     167            WRITE(iounit) diffkn(:,:,:,cm_index,:)
     168            WRITE(iounit) vdepn(:,:,:,cm_index,:)
     169
     170            ! Auxiliary variables for nests
     171            WRITE(iounit) xresoln(:)
     172            WRITE(iounit) yresoln(:)
     173            WRITE(iounit) xln(:)
     174            WRITE(iounit) yln(:)
     175            WRITE(iounit) xrn(:)
     176            WRITE(iounit) yrn(:)
     177
     178            ! Variables for polar stereographic projection
     179            WRITE(iounit) xglobal, sglobal, nglobal
     180            WRITE(iounit) switchnorthg, switchsouthg
     181            WRITE(iounit) southpolemap(:)
     182            WRITE(iounit) northpolemap(:)
     183
     184            ! Variables declared in conv_mod (convection)
     185            WRITE(iounit) pconv(:)
     186            WRITE(iounit) phconv(:)
     187            WRITE(iounit) dpr(:)
     188            WRITE(iounit) pconv_hpa(:)
     189            WRITE(iounit) phconv_hpa(:)
     190            WRITE(iounit) ft(:)
     191            WRITE(iounit) fq(:)
     192            WRITE(iounit) fmass(:,:)
     193            WRITE(iounit) sub(:)
     194            WRITE(iounit) fmassfrac(:,:)
     195            WRITE(iounit) cbaseflux(:,:)
     196            WRITE(iounit) cbasefluxn(:,:,:)
     197            WRITE(iounit) tconv(:)
     198            WRITE(iounit) qconv(:)
     199            WRITE(iounit) qsconv(:)
     200            WRITE(iounit) psconv, tt2conv, td2conv
     201            WRITE(iounit) nconvlev, nconvtop
     202
     203}}}
     204
     205
     206The implementation of the above was somewhat straightforward, but it took some time to understand how to make sure we dumped and loaded the correct cm_index.  Once this was figured out, it seemed like our tests were all working well - we could generate fp data from a forward run, then start another run that read the .fp data, and come up with identical results. 
     207
     208
     209== A difference between forward and backward met fields ==
     210
     211
     212However, in one of our tests we generated fp data for a forward run and tried to use it in both forward and backward runs and the backward run gave us errors relative to our control output data.  With a lot of experimentation and investigation it was finally found that FLEXPART itself doesn’t use exactly identical fields in forward and backward runs.  Specifically, in a forward run the ''gridcheck()'' routine will use the earliest met file and set up the vertical coordinate system which will remain constant for the rest of the simulation.  In a backward run, ''gridcheck()'' will use the latest met file to set up the vertical coordinate system.   What this means is that if we want “traditional” FLEXPART behaviour, we need to generate a set of fp files where every file has the same vertical coordinate system, and this will be different between backward and forward runs.
     213
     214
     215
     216Recognising that this is an issue that will need to be discussed over time, our team has constructed a solution that will allow for a variety of fp files to be generated with ''grib2flexpart''.  The fp files can be generated so that they contain the exactly the same data that a traditional FLEXPART run would contain.  This means, for example, that in the case of CTBTO, 15 days of fp files would be generated, and they would all use the vertical coordinate system defined by the latest met file, as FLEXPART currently does.  This, of course, means all fifteen days have to be processed every day, but only once - all 90 runs could use these preprocessed files, and results would be identical to those from traditional FLEXPART.  Alternatively, fp files may also be generated one at a time, or in a specified sequence, where each fp file contains the vertical coordinate system as defined by the met file that produced it.  This means that during a simulation the vertical coordinate system will vary with time.  It’s not clear to us yet whether this might be a good or a bad thing, so we have chosen to make ''gribflexpart'' capable of multiple output configurations, which may be modified in the future if desired.
     217
     218
     219A potentially confusing downside of our raw dump/load procedure is that the arrays that are filled with an ''fpmetbinary_load()'' must be dimensioned (as defined in ''par_mod.F90'')  exactly as the arrays that were used in the ''fpmetbinary_dump()''.    Since GRIB2FLEXPART and FLEXPART are compiled in the same distribution, with the same ''par_mod.F90'', as long as the two binaries are used with each other, there will be no problem.  However, we all know how people love to copy binaries to different places, and it’s entirely feasible that someone ends up using a GRIB2FLEXPART from one configuration and a FLEXPART from another configuration, and this simply will not work - even if the dimensions are only slightly different.
     220
     221We could have partially alleviated this by making sure that we dump dimensions to the fp files and loaded arrays based on these, but, again, the overhead of filling arrays in this manner would probably be excessive.  However, it might be useful in the future to go ahead and add these dimensions to the fp format just as an error checking tool.  A process that wants to load the fp data into its variables could at least check that its own dimensions match those of the fp file and offer a warning if not.  Some of the dimensions are already dumped, just to be safe, but not all of them.
     222
     223
     224Preliminary performance testing suggests that the dumping and loading of fp files is quick.  For a 0.5 degree global ECMWF the actual processing of the GRIB met data (getting it into the arrays) will take (on a specific machine) about 160 seconds, but the actual dumping to fp file will take about 3 seconds.  Loading the file as input into FLEXPART will take about 10-16 seconds on our test platform.   
     225
     226
     227If we chose to use NetCDF as the fp format in the future, we could do so simply by modifying the new ''fpmetbinary_mod.F90'', but our suspicion is that anything other than a raw binary dump/load will require significant overhead.  Testing this, however, would be an interesting activity.