/[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 52 - (show annotations)
Fri Sep 23 12:28:01 2011 UTC (12 years, 7 months ago) by guez
File size: 2583 byte(s)
Split "conflx.f" into single-procedure files in directory "Conflx".

Split "cv_routines.f" into single-procedure files in directory
"CV_routines". Made module "cvparam" from included file
"cvparam.h". No included file other than "netcdf.inc" left in LMDZE.

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

  ViewVC Help
Powered by ViewVC 1.1.21