/[lmdze]/trunk/Sources/phylmd/Orography/start_init_orog.f
ViewVC logotype

Annotation of /trunk/Sources/phylmd/Orography/start_init_orog.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 39 - (hide annotations)
Tue Jan 25 15:11:05 2011 UTC (13 years, 4 months ago) by guez
Original Path: trunk/libf/phylmd/Orography/start_init_orog_m.f90
File size: 3996 byte(s)
"pi" comes from "nr_util". Removed subroutine "initialize" in module
"comconst".

Copied the content of "fxy_sin.h" into "fxysinus", instead of getting
it from an "include" line. Removed file "fxy_sin.h".

"ps" has rank 2 in "gcm" and "dynetat0".

Assumed-shape for argument "q" of "integrd".

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

  ViewVC Help
Powered by ViewVC 1.1.21