source: LMDZ6/branches/Amaury_dev/libf/phylmd/regr_pr_o3_m.F90 @ 5158

Last change on this file since 5158 was 5158, checked in by abarral, 7 weeks ago

Add missing klon on strataer_emiss_mod.F90
Correct various missing explicit declarations
Replace tabs by spaces (tabs are not part of the fortran charset)
Continue cleaning modules
Removed unused arguments and variables

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
File size: 3.8 KB
Line 
1! $Id$
2module regr_pr_o3_m
3
4  IMPLICIT NONE
5
6CONTAINS
7
8  SUBROUTINE regr_pr_o3(p3d, o3_mob_regr)
9
10    ! "regr_pr_o3" stands for "regrid pressure ozone".
11    ! This procedure reads Mobidic ozone mole fraction from
12    ! "coefoz_LMDZ.nc" at the initial day of the run and regrids it in
13    ! pressure.
14    ! Ozone mole fraction from "coefoz_LMDZ.nc" at the initial day is
15    ! a 2D latitude -- pressure variable.
16    ! The target horizontal LMDZ grid is the "scalar" grid: "rlonv", "rlatu".
17    ! The target vertical LMDZ grid is the grid of layer boundaries.
18    ! We assume that the input variable is already on the LMDZ "rlatu"
19    ! latitude grid.
20    ! The input variable does not depend on longitude, but the
21    ! pressure at LMDZ layers does.
22    ! Therefore, the values on the LMDZ grid do depend on longitude.
23    ! Regridding is by averaging, assuming a step function.
24    ! We assume that, in the input file, the pressure levels are in
25    ! hPa and strictly increasing.
26
27    USE netcdf95, ONLY: nf95_open, nf95_close, nf95_inq_varid, nf95_get_var
28    USE netcdf, ONLY:  nf90_nowrite
29    USE lmdz_assert, ONLY: assert
30    USE lmdz_regr_conserv, ONLY: regr_conserv
31    USE press_coefoz_m, ONLY: press_in_edg
32    USE time_phylmdz_mod, ONLY: day_ref
33    USE lmdz_grid_phy, ONLY: nbp_lon, nbp_lat, nbp_lev
34
35    REAL, INTENT(IN):: p3d(:, :, :) ! pressure at layer interfaces, in Pa
36    ! ("p3d(i, j, l)" is at longitude "rlonv(i)", latitude "rlatu(j)",
37    ! for interface "l")
38
39    REAL, INTENT(OUT):: o3_mob_regr(:, :, :) ! (iim + 1, jjm + 1, llm)
40    ! (ozone mole fraction from Mobidic adapted to the LMDZ grid)
41    ! ("o3_mob_regr(i, j, l)" is at longitude "rlonv(i)", latitude
42    ! "rlatu(j)" and pressure level "pls(i, j, l)")
43
44    ! Variables local to the procedure:
45
46    INTEGER ncid, varid, ncerr ! for NetCDF
47    INTEGER i, j
48
49    REAL r_mob(nbp_lat, size(press_in_edg) - 1)
50    ! (ozone mole fraction from Mobidic at day "day_ref")
51    ! (r_mob(j, k) is at latitude "rlatu(j)", in pressure interval
52    ! "[press_in_edg(k), press_in_edg(k+1)]".)
53
54    !------------------------------------------------------------
55
56    print *, "Call sequence information: regr_pr_o3"
57    CALL assert(shape(o3_mob_regr) == (/nbp_lon + 1, nbp_lat, nbp_lev/), &
58         "regr_pr_o3 o3_mob_regr")
59    CALL assert(shape(p3d) == (/nbp_lon + 1, nbp_lat, nbp_lev + 1/), "regr_pr_o3 p3d")
60
61    CALL nf95_open("coefoz_LMDZ.nc", nf90_nowrite, ncid)
62
63    CALL nf95_inq_varid(ncid, "r_Mob", varid)
64    ! Get data at the right day from the input file:
65    CALL nf95_get_var(ncid, varid, r_mob, start=(/1, 1, day_ref/))
66    ! Latitudes are in ascending order in the input file while
67    ! "rlatu" is in descending order so we need to invert order:
68    r_mob = r_mob(nbp_lat:1:-1, :)
69
70    CALL nf95_close(ncid)
71
72    ! Regrid in pressure by averaging a step function of pressure:
73
74    ! Poles:
75    DO j = 1, nbp_lat, nbp_lat-1
76       CALL regr_conserv(1, r_mob(j, :), press_in_edg, &
77            p3d(1, j, nbp_lev + 1:1:-1), o3_mob_regr(1, j, nbp_lev:1:-1))
78       ! (invert order of indices because "p3d" is in descending order)
79    END DO
80
81    ! Other latitudes:
82    DO j = 2, nbp_lat-1
83       DO i = 1, nbp_lon
84          CALL regr_conserv(1, r_mob(j, :), press_in_edg, &
85               p3d(i, j, nbp_lev + 1:1:-1), o3_mob_regr(i, j, nbp_lev:1:-1))
86          ! (invert order of indices because "p3d" is in descending order)
87       END DO
88    END DO
89
90    ! Duplicate pole values on all longitudes:
91    o3_mob_regr(2:, 1, :) = spread(o3_mob_regr(1, 1, :), dim=1, ncopies=nbp_lon)
92    o3_mob_regr(2:, nbp_lat, :) &
93         = spread(o3_mob_regr(1, nbp_lat, :), dim=1, ncopies=nbp_lon)
94
95    ! Duplicate first longitude to last longitude:
96    o3_mob_regr(nbp_lon + 1, 2:nbp_lat-1, :) = o3_mob_regr(1, 2:nbp_lat-1, :)
97
98  END SUBROUTINE  regr_pr_o3
99
100END MODULE regr_pr_o3_m
Note: See TracBrowser for help on using the repository browser.