/[lmdze]/trunk/libf/dyn3d/grid_change.f90
ViewVC logotype

Annotation of /trunk/libf/dyn3d/grid_change.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 15 - (hide annotations)
Fri Aug 1 15:24:12 2008 UTC (15 years, 10 months ago) by guez
File size: 3087 byte(s)
-- Minor modification of input/output:

Added variable "Sigma_O3_Royer" to "histday.nc". "ecrit_day" is not
modified in "physiq". Removed variables "pyu1", "pyv1", "ftsol1",
"ftsol2", "ftsol3", "ftsol4", "psrf1", "psrf2", "psrf3", "psrf4"
"mfu", "mfd", "en_u", "en_d", "de_d", "de_u", "coefh" from
"histrac.nc".

Variable "raz_date" of module "conf_gcm_m" has logical type instead of
integer type.

-- Should not change any result at run time:

Modified calls to "IOIPSL_Lionel" procedures because the interfaces of
these procedures have been simplified.

Changed name of variable in module "start_init_orog_m": "masque" to
"mask".

Created a module containing procedure "phyredem".

Removed arguments "punjours", "pdayref" and "ptimestep" of procedure
"iniphysiq".

Renamed procedure "gr_phy_write" to "gr_phy_write_2d". Created
procedure "gr_phy_write_3d".

Removed procedures "ini_undefstd", "moy_undefSTD", "calcul_STDlev",
"calcul_divers".

1 guez 3 module grid_change
2    
3     use dimens_m, only: iim, jjm
4    
5     IMPLICIT NONE
6    
7     logical, save:: dyn_phy(iim + 1, jjm + 1)
8     ! (mask for distinct points in the scalar grid and the "u" grid,
9     ! first index is for longitude, second index is for latitude)
10    
11     private iim, jjm
12    
13     contains
14    
15     subroutine init_dyn_phy
16    
17     ! Construct the mask:
18     dyn_phy = .true.
19     dyn_phy(2:, 1) = .false.
20     dyn_phy(2:, jjm + 1) = .false.
21     dyn_phy(iim + 1, 2:jjm) = .false.
22     ! Note that "count(dyn_phy)" equals "klon"
23    
24     end subroutine init_dyn_phy
25    
26     !********************************************
27    
28     function gr_fi_dyn(pfi)
29    
30     ! From gr_fi_dyn.F, version 1.1.1.1 2004/05/19 12:53:05
31     ! Passage d'un champ de la grille physique à la grille dynamique
32    
33     use dimphy, only: klon
34    
35     REAL, intent(in):: pfi(:)
36     real gr_fi_dyn(iim + 1, jjm + 1)
37    
38     ! Variable local to the procedure:
39     real field(iim + 1, jjm + 1)
40    
41     !-----------------------------------------------------------------------
42    
43     if (size(pfi) /= klon) stop "gr_fi_dyn"
44    
45     ! Traitement des pôles :
46     field(2:, 1) = pfi(1)
47     field(2:, jjm + 1) = pfi(klon)
48     ! (We leave undefined elements in "field")
49    
50     gr_fi_dyn = unpack(pfi, dyn_phy, field)
51     ! Undefined elements at last longitude in "gr_fi_dyn" come from
52     ! undefined elements in "field".
53     ! Overwrite them now, knowing that last longitude equals first longitude:
54     gr_fi_dyn(iim + 1, 2:jjm) = gr_fi_dyn(1, 2:jjm)
55    
56     END function gr_fi_dyn
57    
58     !********************************************
59    
60 guez 15 function gr_phy_write_2d(pfi)
61 guez 3
62     ! From phylmd/physiq.F, version 1.22 2006/02/20 09:38:28
63     ! Transforme une variable de la grille physique à la grille d'écriture.
64     ! The grid for output files does not duplicate the first longitude
65     ! in the last longitude.
66    
67     use dimphy, only: klon
68    
69     REAL, intent(in):: pfi(:)
70 guez 15 real gr_phy_write_2d(iim, jjm + 1)
71 guez 3
72     ! Variable local to the procedure:
73     real field(iim, jjm + 1)
74    
75     !-----------------------------------------------------------------------
76    
77 guez 15 if (size(pfi) /= klon) stop "gr_phy_write_2d"
78 guez 3
79     ! Traitement des pôles :
80     field(2:, 1) = pfi(1)
81     field(2:, jjm + 1) = pfi(klon)
82    
83 guez 15 gr_phy_write_2d = unpack(pfi, dyn_phy(:iim, :), field)
84 guez 3
85 guez 15 END function gr_phy_write_2d
86 guez 3
87 guez 15 !***************************************************
88    
89     function gr_phy_write_3d(pfi)
90    
91     ! Transforme une variable dépendant de la position verticale de la
92     ! grille physique à la grille d'écriture.
93     ! The grid for output files does not duplicate the first longitude
94     ! in the last longitude.
95    
96     use dimphy, only: klon
97     use dimens_m, only: llm
98     use numer_rec, only: assert
99    
100     REAL, intent(in):: pfi(:, :)
101     real gr_phy_write_3d(iim, jjm + 1, llm)
102    
103     ! Variable local to the procedure:
104     integer l
105    
106     !-----------------------------------------------------------------------
107    
108     call assert(shape(pfi) == (/klon, llm/), "gr_phy_write_3d")
109    
110     do l = 1, llm
111     gr_phy_write_3d(:, :, l) = gr_phy_write_2d(pfi(:, l))
112     end do
113    
114     END function gr_phy_write_3d
115    
116 guez 3 end module grid_change

  ViewVC Help
Powered by ViewVC 1.1.21