[1263] | 1 | ! $Id$ |
---|
| 2 | module regr_pr_av_m |
---|
| 3 | |
---|
| 4 | ! Author: Lionel GUEZ |
---|
| 5 | |
---|
| 6 | implicit none |
---|
| 7 | |
---|
| 8 | contains |
---|
| 9 | |
---|
| 10 | subroutine regr_pr_av(ncid, name, julien, press_in_edg, paprs, v3) |
---|
| 11 | |
---|
| 12 | ! "regr_pr_av" stands for "regrid pressure averaging". |
---|
| 13 | ! In this procedure: |
---|
| 14 | ! -- the root process reads 2D latitude-pressure fields from a |
---|
| 15 | ! NetCDF file, at a given day. |
---|
| 16 | ! -- the fields are packed to the LMDZ horizontal "physics" |
---|
| 17 | ! grid and scattered to all threads of all processes; |
---|
| 18 | ! -- in all the threads of all the processes, the fields are regridded in |
---|
| 19 | ! pressure to the LMDZ vertical grid. |
---|
| 20 | ! We assume that, in the input file, the fields have 3 dimensions: |
---|
| 21 | ! latitude, pressure, julian day. |
---|
| 22 | ! We assume that the input fields are already on the "rlatu" |
---|
[1403] | 23 | ! latitudes, except that latitudes are in ascending order in the input |
---|
[1263] | 24 | ! file. |
---|
[1403] | 25 | ! We assume that all the inputs fields have the same coordinates. |
---|
[1263] | 26 | |
---|
| 27 | ! The target vertical LMDZ grid is the grid of layer boundaries. |
---|
[2440] | 28 | ! Regridding in pressure is conservative, second order. |
---|
[1263] | 29 | |
---|
| 30 | ! All the fields are regridded as a single multi-dimensional array |
---|
| 31 | ! so it saves CPU time to call this procedure once for several NetCDF |
---|
| 32 | ! variables rather than several times, each time for a single |
---|
| 33 | ! NetCDF variable. |
---|
| 34 | |
---|
| 35 | use dimphy, only: klon |
---|
| 36 | use netcdf95, only: nf95_inq_varid, handle_err |
---|
| 37 | use netcdf, only: nf90_get_var |
---|
| 38 | use assert_m, only: assert |
---|
| 39 | use assert_eq_m, only: assert_eq |
---|
[2440] | 40 | use regr1_conserv_m, only: regr1_conserv |
---|
| 41 | use slopes_m, only: slopes |
---|
[1263] | 42 | use mod_phys_lmdz_mpi_data, only: is_mpi_root |
---|
[2346] | 43 | use mod_grid_phy_lmdz, only: nbp_lon, nbp_lat, nbp_lev |
---|
[1263] | 44 | use mod_phys_lmdz_transfert_para, only: scatter2d |
---|
| 45 | ! (pack to the LMDZ horizontal "physics" grid and scatter) |
---|
| 46 | |
---|
| 47 | integer, intent(in):: ncid ! NetCDF ID of the file |
---|
| 48 | character(len=*), intent(in):: name(:) ! of the NetCDF variables |
---|
| 49 | integer, intent(in):: julien ! jour julien, 1 <= julien <= 360 |
---|
| 50 | |
---|
| 51 | real, intent(in):: press_in_edg(:) |
---|
| 52 | ! edges of pressure intervals for input data, in Pa, in strictly |
---|
| 53 | ! ascending order |
---|
| 54 | |
---|
| 55 | real, intent(in):: paprs(:, :) ! (klon, llm + 1) |
---|
| 56 | ! (pression pour chaque inter-couche, en Pa) |
---|
| 57 | |
---|
| 58 | real, intent(out):: v3(:, :, :) ! (klon, llm, size(name)) |
---|
| 59 | ! regridded fields on the partial "physics" grid |
---|
| 60 | ! "v3(i, k, l)" is at longitude "xlon(i)", latitude |
---|
| 61 | ! "xlat(i)", in pressure interval "[paprs(i, k+1), paprs(i, k)]", |
---|
| 62 | ! for NetCDF variable "name(l)". |
---|
| 63 | |
---|
| 64 | ! Variables local to the procedure: |
---|
| 65 | |
---|
| 66 | integer varid, ncerr ! for NetCDF |
---|
| 67 | |
---|
[2346] | 68 | real v1(nbp_lon, nbp_lat, size(press_in_edg) - 1, size(name)) |
---|
[1263] | 69 | ! input fields at day "julien", on the global "dynamics" horizontal grid |
---|
| 70 | ! First dimension is for longitude. |
---|
| 71 | ! The values are the same for all longitudes. |
---|
| 72 | ! "v1(:, j, k, l)" is at latitude "rlatu(j)", for |
---|
| 73 | ! pressure interval "[press_in_edg(k), press_in_edg(k+1)]" and |
---|
| 74 | ! NetCDF variable "name(l)". |
---|
| 75 | |
---|
| 76 | real v2(klon, size(press_in_edg) - 1, size(name)) |
---|
| 77 | ! fields scattered to the partial "physics" horizontal grid |
---|
| 78 | ! "v2(i, k, l)" is at longitude "xlon(i)", latitude "xlat(i)", |
---|
| 79 | ! for pressure interval "[press_in_edg(k), press_in_edg(k+1)]" and |
---|
| 80 | ! NetCDF variable "name(l)". |
---|
| 81 | |
---|
| 82 | integer i, n_var |
---|
| 83 | |
---|
| 84 | !-------------------------------------------- |
---|
| 85 | |
---|
[2440] | 86 | call assert(size(v3, 1) == klon, size(v3, 2) == nbp_lev, & |
---|
| 87 | "regr_pr_av v3 klon") |
---|
[1263] | 88 | n_var = assert_eq(size(name), size(v3, 3), "regr_pr_av v3 n_var") |
---|
[2346] | 89 | call assert(shape(paprs) == (/klon, nbp_lev+1/), "regr_pr_av paprs") |
---|
[1263] | 90 | |
---|
| 91 | !$omp master |
---|
| 92 | if (is_mpi_root) then |
---|
| 93 | do i = 1, n_var |
---|
[1403] | 94 | call nf95_inq_varid(ncid, trim(name(i)), varid) |
---|
[1263] | 95 | |
---|
| 96 | ! Get data at the right day from the input file: |
---|
| 97 | ncerr = nf90_get_var(ncid, varid, v1(1, :, :, i), & |
---|
| 98 | start=(/1, 1, julien/)) |
---|
[1403] | 99 | call handle_err("regr_pr_av nf90_get_var " // trim(name(i)), ncerr, & |
---|
| 100 | ncid) |
---|
[1263] | 101 | end do |
---|
| 102 | |
---|
| 103 | ! Latitudes are in ascending order in the input file while |
---|
| 104 | ! "rlatu" is in descending order so we need to invert order: |
---|
[2346] | 105 | v1(1, :, :, :) = v1(1, nbp_lat:1:-1, :, :) |
---|
[1263] | 106 | |
---|
| 107 | ! Duplicate on all longitudes: |
---|
[2346] | 108 | v1(2:, :, :, :) = spread(v1(1, :, :, :), dim=1, ncopies=nbp_lon-1) |
---|
[1263] | 109 | end if |
---|
| 110 | !$omp end master |
---|
| 111 | |
---|
| 112 | call scatter2d(v1, v2) |
---|
| 113 | |
---|
| 114 | ! Regrid in pressure at each horizontal position: |
---|
| 115 | do i = 1, klon |
---|
[2440] | 116 | call regr1_conserv(v2(i, :, :), press_in_edg, & |
---|
| 117 | paprs(i, nbp_lev + 1:1:-1), v3(i, nbp_lev:1:-1, :), & |
---|
| 118 | slopes(v2(i, :, :), press_in_edg)) |
---|
[1263] | 119 | ! (invert order of indices because "paprs" is in descending order) |
---|
| 120 | end do |
---|
| 121 | |
---|
| 122 | end subroutine regr_pr_av |
---|
| 123 | |
---|
| 124 | end module regr_pr_av_m |
---|