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

Annotation of /trunk/libf/dyn3d/start_init_orog_m.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: 4044 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 start_init_orog_m
2    
3     ! From startvar.F, version 1.4
4     ! 2006/01/27 15:14:22 Fairhead
5    
6     IMPLICIT NONE
7    
8 guez 15 REAL, ALLOCATABLE, SAVE:: mask(:, :) ! fraction of land (iim + 1, jjm + 1)
9 guez 3 REAL, ALLOCATABLE, SAVE:: phis(:, :) ! surface geopotential, in m2 s-2
10    
11     CONTAINS
12    
13     SUBROUTINE start_init_orog(relief, zstd_2d, zsig_2d, zgam_2d, zthe_2d, &
14     zpic_2d, zval_2d)
15    
16     USE ioipsl, only: flininfo, flinopen_nozoom, flinget, flinclo
17     use conf_dat2d_m, only: conf_dat2d
18     use comgeom, only: rlatu, rlonv
19     use dimens_m, only: iim, jjm
20     use indicesol, only: epsfra
21     use comconst, only: pi
22     use grid_noro_m, only: grid_noro
23    
24     REAL, intent(out):: relief(:, :) ! orographie moyenne
25    
26     REAL, intent(out):: zstd_2d(:, :)
27     ! (deviation standard de l'orographie sous-maille)
28    
29     REAL, intent(out):: zsig_2d(:, :)
30     ! (pente de l'orographie sous-maille)
31    
32     REAL, intent(out):: zgam_2d(:, :)
33     ! (anisotropie de l'orographie sous maille)
34    
35     REAL, intent(out):: zthe_2d(:, :)
36     ! (orientation de l'axe oriente dans la direction de plus grande
37     ! pente de l'orographie sous maille)
38    
39     REAL, intent(out):: zpic_2d(:, :) ! hauteur pics de la SSO
40     REAL, intent(out):: zval_2d(:, :) ! hauteur vallees de la SSO
41    
42     ! Local:
43    
44     INTEGER, SAVE:: iml_rel
45     INTEGER, SAVE:: jml_rel
46     REAL lev(1), date, dt
47     INTEGER itau(1), fid
48     INTEGER llm_tmp, ttm_tmp
49     REAL, ALLOCATABLE:: relief_hi(:, :)
50     REAL, ALLOCATABLE:: lon_rad(:), lat_rad(:)
51     REAL, ALLOCATABLE:: lon_ini(:), lat_ini(:)
52     REAL, ALLOCATABLE:: lon_rel(:, :), lat_rel(:, :)
53    
54     CHARACTER(len=120) orogfname
55    
56     !-----------------------------------
57    
58     print *, "Call sequence information: start_init_orog"
59    
60     if (any((/size(relief, 1), size(zstd_2d, 1), size(zsig_2d, 1), &
61     size(zgam_2d, 1), size(zthe_2d, 1), size(zpic_2d, 1), &
62     size(zval_2d, 1)/) /= iim + 1)) stop "start_init_orog size 1"
63     if (any((/size(relief, 2), size(zstd_2d, 2), size(zsig_2d, 2), &
64     size(zgam_2d, 2), size(zthe_2d, 2), size(zpic_2d, 2), &
65     size(zval_2d, 2)/) /= jjm + 1)) stop "start_init_orog size 2"
66    
67     orogfname = 'Relief.nc'
68     print *, 'Reading the high resolution orography'
69    
70     CALL flininfo(orogfname, iml_rel, jml_rel, llm_tmp, ttm_tmp, fid)
71    
72     ALLOCATE(lat_rel(iml_rel, jml_rel))
73     ALLOCATE(lon_rel(iml_rel, jml_rel))
74     ALLOCATE(relief_hi(iml_rel, jml_rel))
75    
76     CALL flinopen_nozoom(orogfname, iml_rel, jml_rel, llm_tmp, &
77     lon_rel, lat_rel, lev, ttm_tmp, itau, date, dt, fid)
78     ! 'RELIEF': high resolution orography
79     CALL flinget(fid, 'RELIEF', iml_rel, jml_rel, llm_tmp, ttm_tmp, 1, 1, &
80     relief_hi)
81     CALL flinclo(fid)
82    
83     ! In case we have a file which is in degrees we do the transformation:
84    
85     ALLOCATE(lon_rad(iml_rel))
86     ALLOCATE(lon_ini(iml_rel))
87    
88     IF (MAXVAL(lon_rel(:, :)) > pi) THEN
89     lon_ini(:) = lon_rel(:, 1) * pi / 180.
90     ELSE
91     lon_ini(:) = lon_rel(:, 1)
92     ENDIF
93    
94     ALLOCATE(lat_rad(jml_rel))
95     ALLOCATE(lat_ini(jml_rel))
96    
97     IF (MAXVAL(lat_rel(:, :)) > pi) THEN
98     lat_ini(:) = lat_rel(1, :) * pi / 180.
99     ELSE
100     lat_ini(:) = lat_rel(1, :)
101     ENDIF
102    
103     CALL conf_dat2d(lon_ini, lat_ini, lon_rad, lat_rad, relief_hi , &
104     interbar=.FALSE.)
105    
106     print *, 'Compute all the parameters needed for the gravity wave drag code'
107    
108     ! Allocate the data we need to put in the interpolated fields:
109     ALLOCATE(phis(iim + 1, jjm + 1))
110 guez 15 ALLOCATE(mask(iim + 1, jjm + 1))
111 guez 3
112     CALL grid_noro(lon_rad, lat_rad, relief_hi, rlonv, rlatu, phis, relief, &
113 guez 15 zstd_2d, zsig_2d, zgam_2d, zthe_2d, zpic_2d, zval_2d, mask)
114 guez 3
115     phis(iim + 1, :) = phis(1, :)
116     phis(:, :) = phis(:, :) * 9.81
117    
118 guez 15 mask(2:, 1) = mask(1, 1) ! north pole
119     mask(2:, jjm + 1) = mask(1, jjm + 1) ! south pole
120     mask(iim + 1, 2:jjm) = mask(1, 2:jjm) ! Greenwich
121     WHERE (mask < EPSFRA)
122     mask = 0.
123     elsewhere (1. - mask < EPSFRA)
124     mask = 1.
125 guez 3 endwhere
126    
127     END SUBROUTINE start_init_orog
128    
129     END MODULE start_init_orog_m

  ViewVC Help
Powered by ViewVC 1.1.21