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

Annotation of /trunk/dyn3d/start_init_phys_m.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 344 - (hide annotations)
Tue Nov 12 15:18:14 2019 UTC (4 years, 7 months ago) by guez
File size: 2551 byte(s)
Replace pi / 180 by `deg_to_rad`

In procedure etat0, rename variable tsoil to ftsoil, which is the
corresponding name in the gcm program.

In `laplacien_gam`, replace call to scopy by array assignment.

Replace pi / 180 by `deg_to_rad` in `start_init_phys`.

Encapsulate diagcld1 and orolift in modules.

Avoid duplicated computation in `interfsurf_hq`.

Promote internal function fz of procedure soil to function of module
`soil_m`.  Use `new_unit` in procedure soil.

1 guez 3 MODULE start_init_phys_m
2    
3 guez 343 ! From startvar.F, version 1.4 2006/01/27
4 guez 3
5     IMPLICIT NONE
6    
7     CONTAINS
8    
9 guez 43 SUBROUTINE start_init_phys(tsol_2d, qsol_2d)
10 guez 3
11 guez 343 ! Libraries:
12     use netcdf, only: nf90_nowrite
13     use netcdf95, only: nf95_open, nf95_close, nf95_get_var, nf95_inq_varid, &
14     nf95_gw_var, find_coord
15 guez 344 use nr_util, only: assert, deg_to_rad
16 guez 343
17 guez 3 use conf_dat2d_m, only: conf_dat2d
18 guez 265 use dimensions, only: iim, jjm
19 guez 139 use dynetat0_m, only: rlonu, rlatv
20 guez 49 use gr_int_dyn_m, only: gr_int_dyn
21 guez 3 use inter_barxy_m, only: inter_barxy
22    
23 guez 343 REAL, intent(out):: tsol_2d(:, :)
24     ! both soil temperature and surface temperature, in K
25    
26     REAL, intent(out):: qsol_2d(:, :) ! (iim + 1, jjm + 1)
27 guez 3
28 guez 343 ! Local:
29 guez 49 INTEGER iml_phys, jml_phys, ncid, varid
30 guez 3 REAL, ALLOCATABLE:: lon_rad(:), lat_rad(:)
31 guez 225 REAL, ALLOCATABLE:: lon_ini(:), lat_ini(:) ! longitude and latitude in rad
32 guez 3 REAL, ALLOCATABLE:: var_ana(:, :)
33     real tmp_var(iim, jjm + 1)
34    
35     !-----------------------------------
36    
37     print *, "Call sequence information: start_init_phys"
38 guez 43
39     call assert((/size(tsol_2d, 1), size(qsol_2d, 1)/) == iim + 1, &
40     "start_init_phys 1")
41     call assert((/size(tsol_2d, 2), size(qsol_2d, 2)/) == jjm + 1, &
42     "start_init_phys 2")
43    
44 guez 49 call nf95_open('ECPHY.nc', nf90_nowrite, ncid)
45 guez 3
46 guez 64 call find_coord(ncid, varid=varid, std_name="longitude")
47 guez 49 call nf95_gw_var(ncid, varid, lon_ini)
48 guez 344 lon_ini = lon_ini * deg_to_rad
49 guez 49 iml_phys = size(lon_ini)
50 guez 3
51 guez 64 call find_coord(ncid, varid=varid, std_name="latitude")
52 guez 49 call nf95_gw_var(ncid, varid, lat_ini)
53 guez 344 lat_ini = lat_ini * deg_to_rad
54 guez 49 jml_phys = size(lat_ini)
55 guez 3
56     ! Allocate the space we will need to get the data out of this file
57     ALLOCATE(var_ana(iml_phys, jml_phys))
58    
59     ALLOCATE(lon_rad(iml_phys))
60     ALLOCATE(lat_rad(jml_phys))
61    
62 guez 99 ! Surface temperature:
63 guez 48 call nf95_inq_varid(ncid, 'ST', varid)
64     call nf95_get_var(ncid, varid, var_ana)
65 guez 3 CALL conf_dat2d(lon_ini, lat_ini, lon_rad, lat_rad, var_ana)
66     CALL inter_barxy(lon_rad, lat_rad(:jml_phys -1), var_ana, rlonu(:iim), &
67     rlatv, tmp_var)
68 guez 43 tsol_2d = gr_int_dyn(tmp_var)
69 guez 3
70 guez 99 ! Soil moisture:
71 guez 48 call nf95_inq_varid(ncid, 'CDSW', varid)
72     call nf95_get_var(ncid, varid, var_ana)
73 guez 3 CALL conf_dat2d(lon_ini, lat_ini, lon_rad, lat_rad, var_ana)
74     CALL inter_barxy(lon_rad, lat_rad(:jml_phys -1), var_ana, rlonu(:iim), &
75     rlatv, tmp_var)
76 guez 43 qsol_2d = gr_int_dyn(tmp_var)
77 guez 3
78 guez 48 call nf95_close(ncid)
79 guez 3
80     END SUBROUTINE start_init_phys
81    
82     END MODULE start_init_phys_m

  ViewVC Help
Powered by ViewVC 1.1.21