/[lmdze]/trunk/dyn3d/start_init_phys_m.f
ViewVC logotype

Annotation of /trunk/dyn3d/start_init_phys_m.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 43 - (hide annotations)
Fri Apr 8 12:43:31 2011 UTC (13 years, 1 month ago) by guez
Original Path: trunk/libf/dyn3d/start_init_phys_m.f90
File size: 3069 byte(s)
"start_init_phys" is now called directly by "etat0" instead of through
"start_init_dyn". "qsol_2d" is no longer a variable of module
"start_init_phys_m", it is an argument of
"start_init_phys". "start_init_dyn" now receives "tsol_2d" from
"etat0".

Split file "vlspltqs.f" into "vlspltqs.f90", "vlxqs.f90" and
""vlyqs.f90".

In "start_init_orog", replaced calls to "flin*" by calls to NetCDF95.

1 guez 3 MODULE start_init_phys_m
2    
3     ! From startvar.F, version 1.4
4     ! 2006/01/27 15:14:22 Fairhead
5    
6     IMPLICIT NONE
7    
8     CONTAINS
9    
10 guez 43 SUBROUTINE start_init_phys(tsol_2d, qsol_2d)
11 guez 3
12 guez 32 USE flincom, only: flininfo, flinopen_nozoom, flinclo
13     use flinget_m, only: flinget
14 guez 3 use conf_dat2d_m, only: conf_dat2d
15     use inter_barxy_m, only: inter_barxy
16     use gr_int_dyn_m, only: gr_int_dyn
17     use comgeom, only: rlonu, rlatv
18     use dimens_m, only: iim, jjm
19 guez 43 use nr_util, only: assert
20 guez 3
21 guez 43 REAL, intent(out):: tsol_2d(:, :), qsol_2d(:, :) ! (iim + 1, jjm + 1)
22 guez 3
23 guez 42 ! Variables local to the procedure:
24 guez 3
25     INTEGER fid_phys, iml_phys, jml_phys
26     REAL, ALLOCATABLE, DIMENSION(:, :):: lon_phys, lat_phys
27 guez 43 REAL date, dt
28     REAL, ALLOCATABLE:: levphys_ini(:)
29    
30 guez 3 INTEGER:: itau(1)
31     INTEGER:: llm_tmp, ttm_tmp
32    
33     REAL, ALLOCATABLE:: lon_rad(:), lat_rad(:)
34     REAL, ALLOCATABLE:: lon_ini(:), lat_ini(:)
35     REAL, ALLOCATABLE:: var_ana(:, :)
36     real tmp_var(iim, jjm + 1)
37    
38     !-----------------------------------
39    
40     print *, "Call sequence information: start_init_phys"
41 guez 43
42     call assert((/size(tsol_2d, 1), size(qsol_2d, 1)/) == iim + 1, &
43     "start_init_phys 1")
44     call assert((/size(tsol_2d, 2), size(qsol_2d, 2)/) == jjm + 1, &
45     "start_init_phys 2")
46    
47 guez 36 CALL flininfo('ECPHY.nc', iml_phys, jml_phys, llm_tmp, ttm_tmp, fid_phys)
48 guez 3
49     ALLOCATE(lat_phys(iml_phys, jml_phys))
50     ALLOCATE(lon_phys(iml_phys, jml_phys))
51     ALLOCATE(levphys_ini(llm_tmp))
52    
53 guez 42 CALL flinopen_nozoom(iml_phys, jml_phys, llm_tmp, lon_phys, lat_phys, &
54     levphys_ini, ttm_tmp, itau, date, dt, fid_phys)
55 guez 3
56     DEALLOCATE(levphys_ini)
57    
58     ! Allocate the space we will need to get the data out of this file
59     ALLOCATE(var_ana(iml_phys, jml_phys))
60    
61     ! In case we have a file which is in degrees we do the transformation
62     ALLOCATE(lon_rad(iml_phys))
63     ALLOCATE(lon_ini(iml_phys))
64    
65 guez 43 IF ( MAXVAL(lon_phys) > 2.0 * ASIN(1.0) ) THEN
66     lon_ini = lon_phys(:, 1) * 2.0 * ASIN(1.0) / 180.0
67 guez 3 ELSE
68 guez 43 lon_ini = lon_phys(:, 1)
69 guez 3 ENDIF
70    
71     ALLOCATE(lat_rad(jml_phys))
72     ALLOCATE(lat_ini(jml_phys))
73    
74 guez 43 IF ( MAXVAL(lat_phys) > 2.0 * ASIN(1.0) ) THEN
75     lat_ini = lat_phys(1, :) * 2.0 * ASIN(1.0) / 180.0
76 guez 3 ELSE
77 guez 43 lat_ini = lat_phys(1, :)
78 guez 3 ENDIF
79    
80 guez 42 ! We get the two standard variables
81     ! 'ST': surface temperature
82 guez 3 CALL flinget(fid_phys, 'ST', iml_phys, jml_phys, &
83     llm_tmp, ttm_tmp, 1, 1, var_ana)
84     CALL conf_dat2d(lon_ini, lat_ini, lon_rad, lat_rad, var_ana)
85     CALL inter_barxy(lon_rad, lat_rad(:jml_phys -1), var_ana, rlonu(:iim), &
86     rlatv, tmp_var)
87    
88 guez 43 tsol_2d = gr_int_dyn(tmp_var)
89 guez 3
90     ! Soil moisture
91     CALL flinget(fid_phys, 'CDSW', iml_phys, jml_phys, &
92     llm_tmp, ttm_tmp, 1, 1, var_ana)
93     CALL conf_dat2d(lon_ini, lat_ini, lon_rad, lat_rad, var_ana)
94     CALL inter_barxy(lon_rad, lat_rad(:jml_phys -1), var_ana, rlonu(:iim), &
95     rlatv, tmp_var)
96 guez 43 qsol_2d = gr_int_dyn(tmp_var)
97 guez 3
98     CALL flinclo(fid_phys)
99    
100     END SUBROUTINE start_init_phys
101    
102     END MODULE start_init_phys_m

  ViewVC Help
Powered by ViewVC 1.1.21