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

Contents of /trunk/libf/dyn3d/start_init_phys_m.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 49 - (show annotations)
Wed Aug 24 11:43:14 2011 UTC (12 years, 9 months ago) by guez
File size: 2604 byte(s)
LMDZE now uses library Jumble.

Removed all calls to "flinget". Replaced calls to "flinget",
"flininfo", "flinopen_nozoom" by calls to NetCDF95 and Jumble.

Split file "cv_driver.f" into "cv_driver.f90", "cv_flag.f90" and
"cv_thermo.f90".

Bug fix: "QANCIEN" was read twice in "phyeytat0".

In "physiq", initialization of "d_t", "d_u", "d_v" was useless.

1 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 SUBROUTINE start_init_phys(tsol_2d, qsol_2d)
11
12 use comgeom, only: rlonu, rlatv
13 use conf_dat2d_m, only: conf_dat2d
14 use dimens_m, only: iim, jjm
15 use gr_int_dyn_m, only: gr_int_dyn
16 use inter_barxy_m, only: inter_barxy
17 use jumble, only: find_longitude, find_latitude
18 use netcdf, only: nf90_nowrite
19 use netcdf95, only: nf95_open, nf95_close, nf95_get_var, nf95_inq_varid, &
20 nf95_gw_var
21 use nr_util, only: assert, pi
22
23 REAL, intent(out):: tsol_2d(:, :), qsol_2d(:, :) ! (iim + 1, jjm + 1)
24
25 ! Variables local to the procedure:
26
27 INTEGER iml_phys, jml_phys, ncid, varid
28 REAL, ALLOCATABLE:: lon_rad(:), lat_rad(:)
29 REAL, pointer:: lon_ini(:), lat_ini(:) ! longitude and latitude in rad
30 REAL, ALLOCATABLE:: var_ana(:, :)
31 real tmp_var(iim, jjm + 1)
32
33 !-----------------------------------
34
35 print *, "Call sequence information: start_init_phys"
36
37 call assert((/size(tsol_2d, 1), size(qsol_2d, 1)/) == iim + 1, &
38 "start_init_phys 1")
39 call assert((/size(tsol_2d, 2), size(qsol_2d, 2)/) == jjm + 1, &
40 "start_init_phys 2")
41
42 call nf95_open('ECPHY.nc', nf90_nowrite, ncid)
43
44 call find_longitude(ncid, varid=varid)
45 call nf95_gw_var(ncid, varid, lon_ini)
46 lon_ini = lon_ini * pi / 180. ! convert to rad
47 iml_phys = size(lon_ini)
48
49 call find_latitude(ncid, varid=varid)
50 call nf95_gw_var(ncid, varid, lat_ini)
51 lat_ini = lat_ini * pi / 180. ! convert to rad
52 jml_phys = size(lat_ini)
53
54 ! Allocate the space we will need to get the data out of this file
55 ALLOCATE(var_ana(iml_phys, jml_phys))
56
57 ALLOCATE(lon_rad(iml_phys))
58 ALLOCATE(lat_rad(jml_phys))
59
60 ! We get the two standard variables
61 ! 'ST': surface temperature
62 call nf95_inq_varid(ncid, 'ST', varid)
63 call nf95_get_var(ncid, varid, var_ana)
64 CALL conf_dat2d(lon_ini, lat_ini, lon_rad, lat_rad, var_ana)
65 CALL inter_barxy(lon_rad, lat_rad(:jml_phys -1), var_ana, rlonu(:iim), &
66 rlatv, tmp_var)
67 tsol_2d = gr_int_dyn(tmp_var)
68
69 ! Soil moisture
70 call nf95_inq_varid(ncid, 'CDSW', varid)
71 call nf95_get_var(ncid, varid, var_ana)
72 CALL conf_dat2d(lon_ini, lat_ini, lon_rad, lat_rad, var_ana)
73 CALL inter_barxy(lon_rad, lat_rad(:jml_phys -1), var_ana, rlonu(:iim), &
74 rlatv, tmp_var)
75 qsol_2d = gr_int_dyn(tmp_var)
76
77 call nf95_close(ncid)
78 deallocate(lon_ini, lat_ini) ! pointers
79
80 END SUBROUTINE start_init_phys
81
82 END MODULE start_init_phys_m

  ViewVC Help
Powered by ViewVC 1.1.21