/[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 48 - (hide annotations)
Tue Jul 19 12:54:20 2011 UTC (12 years, 10 months ago) by guez
Original Path: trunk/libf/dyn3d/start_init_phys_m.f90
File size: 3212 byte(s)
Replaced calls to "flinget" 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 guez 3 use conf_dat2d_m, only: conf_dat2d
14     use inter_barxy_m, only: inter_barxy
15     use gr_int_dyn_m, only: gr_int_dyn
16     use comgeom, only: rlonu, rlatv
17     use dimens_m, only: iim, jjm
18 guez 43 use nr_util, only: assert
19 guez 48 use netcdf, only: nf90_nowrite
20     use netcdf95, only: nf95_open, nf95_close, nf95_get_var, nf95_inq_varid
21 guez 3
22 guez 43 REAL, intent(out):: tsol_2d(:, :), qsol_2d(:, :) ! (iim + 1, jjm + 1)
23 guez 3
24 guez 42 ! Variables local to the procedure:
25 guez 3
26 guez 48 INTEGER fid_phys, iml_phys, jml_phys, ncid, varid
27 guez 3 REAL, ALLOCATABLE, DIMENSION(:, :):: lon_phys, lat_phys
28 guez 43 REAL date, dt
29     REAL, ALLOCATABLE:: levphys_ini(:)
30    
31 guez 48 INTEGER itau(1)
32     INTEGER llm_tmp, ttm_tmp
33 guez 3
34     REAL, ALLOCATABLE:: lon_rad(:), lat_rad(:)
35     REAL, ALLOCATABLE:: lon_ini(:), lat_ini(:)
36     REAL, ALLOCATABLE:: var_ana(:, :)
37     real tmp_var(iim, jjm + 1)
38    
39     !-----------------------------------
40    
41     print *, "Call sequence information: start_init_phys"
42 guez 43
43     call assert((/size(tsol_2d, 1), size(qsol_2d, 1)/) == iim + 1, &
44     "start_init_phys 1")
45     call assert((/size(tsol_2d, 2), size(qsol_2d, 2)/) == jjm + 1, &
46     "start_init_phys 2")
47    
48 guez 36 CALL flininfo('ECPHY.nc', iml_phys, jml_phys, llm_tmp, ttm_tmp, fid_phys)
49 guez 3
50     ALLOCATE(lat_phys(iml_phys, jml_phys))
51     ALLOCATE(lon_phys(iml_phys, jml_phys))
52     ALLOCATE(levphys_ini(llm_tmp))
53    
54 guez 42 CALL flinopen_nozoom(iml_phys, jml_phys, llm_tmp, lon_phys, lat_phys, &
55     levphys_ini, ttm_tmp, itau, date, dt, fid_phys)
56 guez 48 CALL flinclo(fid_phys)
57 guez 3
58     DEALLOCATE(levphys_ini)
59    
60     ! Allocate the space we will need to get the data out of this file
61     ALLOCATE(var_ana(iml_phys, jml_phys))
62    
63     ! In case we have a file which is in degrees we do the transformation
64     ALLOCATE(lon_rad(iml_phys))
65     ALLOCATE(lon_ini(iml_phys))
66    
67 guez 43 IF ( MAXVAL(lon_phys) > 2.0 * ASIN(1.0) ) THEN
68     lon_ini = lon_phys(:, 1) * 2.0 * ASIN(1.0) / 180.0
69 guez 3 ELSE
70 guez 43 lon_ini = lon_phys(:, 1)
71 guez 3 ENDIF
72    
73     ALLOCATE(lat_rad(jml_phys))
74     ALLOCATE(lat_ini(jml_phys))
75    
76 guez 43 IF ( MAXVAL(lat_phys) > 2.0 * ASIN(1.0) ) THEN
77     lat_ini = lat_phys(1, :) * 2.0 * ASIN(1.0) / 180.0
78 guez 3 ELSE
79 guez 43 lat_ini = lat_phys(1, :)
80 guez 3 ENDIF
81    
82 guez 48 call nf95_open('ECPHY.nc', nf90_nowrite, ncid)
83    
84 guez 42 ! We get the two standard variables
85     ! 'ST': surface temperature
86 guez 48 call nf95_inq_varid(ncid, 'ST', varid)
87     call nf95_get_var(ncid, varid, var_ana)
88 guez 3 CALL conf_dat2d(lon_ini, lat_ini, lon_rad, lat_rad, var_ana)
89     CALL inter_barxy(lon_rad, lat_rad(:jml_phys -1), var_ana, rlonu(:iim), &
90     rlatv, tmp_var)
91 guez 43 tsol_2d = gr_int_dyn(tmp_var)
92 guez 3
93     ! Soil moisture
94 guez 48 call nf95_inq_varid(ncid, 'CDSW', varid)
95     call nf95_get_var(ncid, varid, var_ana)
96 guez 3 CALL conf_dat2d(lon_ini, lat_ini, lon_rad, lat_rad, var_ana)
97     CALL inter_barxy(lon_rad, lat_rad(:jml_phys -1), var_ana, rlonu(:iim), &
98     rlatv, tmp_var)
99 guez 43 qsol_2d = gr_int_dyn(tmp_var)
100 guez 3
101 guez 48 call nf95_close(ncid)
102 guez 3
103     END SUBROUTINE start_init_phys
104    
105     END MODULE start_init_phys_m

  ViewVC Help
Powered by ViewVC 1.1.21