1 | ! $Id$ |
---|
2 | module press_coefoz_m |
---|
3 | |
---|
4 | implicit none |
---|
5 | |
---|
6 | real, allocatable, save:: plev(:) |
---|
7 | ! (pressure level of Mobidic input data, converted to Pa, in strictly |
---|
8 | ! ascending order) |
---|
9 | |
---|
10 | real, allocatable, save:: press_in_edg(:) |
---|
11 | ! (edges of pressure intervals for Mobidic input data, in Pa, in strictly |
---|
12 | ! ascending order) |
---|
13 | |
---|
14 | contains |
---|
15 | |
---|
16 | subroutine press_coefoz |
---|
17 | |
---|
18 | ! This procedure is called once per "gcm" run. |
---|
19 | ! A single thread of the root process reads the pressure levels |
---|
20 | ! from "coefoz_LMDZ.nc" and broadcasts them to the other processes. |
---|
21 | |
---|
22 | ! We assume that, in "coefoz_LMDZ.nc", the pressure levels are in hPa |
---|
23 | ! and in strictly ascending order. |
---|
24 | |
---|
25 | use netcdf95, only: nf95_open, nf95_close, nf95_gw_var, nf95_inq_varid |
---|
26 | use netcdf, only: nf90_nowrite |
---|
27 | |
---|
28 | use mod_phys_lmdz_mpi_data, only: is_mpi_root |
---|
29 | use mod_phys_lmdz_mpi_transfert, only: bcast_mpi ! broadcast |
---|
30 | |
---|
31 | ! Variables local to the procedure: |
---|
32 | integer ncid, varid ! for NetCDF |
---|
33 | integer n_plev ! number of pressure levels in the input data |
---|
34 | integer k |
---|
35 | |
---|
36 | !--------------------------------------- |
---|
37 | |
---|
38 | !$omp single |
---|
39 | print *, "Call sequence information: press_coefoz" |
---|
40 | |
---|
41 | if (is_mpi_root) then |
---|
42 | call nf95_open("coefoz_LMDZ.nc", nf90_nowrite, ncid) |
---|
43 | |
---|
44 | call nf95_inq_varid(ncid, "plev", varid) |
---|
45 | call nf95_gw_var(ncid, varid, plev) |
---|
46 | ! Convert from hPa to Pa because "paprs" and "pplay" are in Pa: |
---|
47 | plev = plev * 100. |
---|
48 | n_plev = size(plev) |
---|
49 | |
---|
50 | call nf95_close(ncid) |
---|
51 | end if |
---|
52 | |
---|
53 | call bcast_mpi(n_plev) |
---|
54 | if (.not. is_mpi_root) allocate(plev(n_plev)) |
---|
55 | call bcast_mpi(plev) |
---|
56 | |
---|
57 | ! Compute edges of pressure intervals: |
---|
58 | allocate(press_in_edg(n_plev + 1)) |
---|
59 | if (is_mpi_root) then |
---|
60 | press_in_edg(1) = 0. |
---|
61 | ! We choose edges halfway in logarithm: |
---|
62 | DO k = 2,n_plev |
---|
63 | press_in_edg(k) = SQRT(plev(k - 1) * plev(k)) |
---|
64 | ENDDO |
---|
65 | press_in_edg(n_plev + 1) = huge(0.) |
---|
66 | ! (infinity, but any value guaranteed to be greater than the |
---|
67 | ! surface pressure would do) |
---|
68 | end if |
---|
69 | call bcast_mpi(press_in_edg) |
---|
70 | !$omp end single |
---|
71 | |
---|
72 | end subroutine press_coefoz |
---|
73 | |
---|
74 | end module press_coefoz_m |
---|