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

Diff of /trunk/dyn3d/start_init_phys_m.f90

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

revision 342 by guez, Thu Jun 13 14:40:06 2019 UTC revision 343 by guez, Mon Oct 28 08:14:26 2019 UTC
# Line 1  Line 1 
1  MODULE start_init_phys_m  MODULE start_init_phys_m
2    
3    ! From startvar.F, version 1.4    ! From startvar.F, version 1.4 2006/01/27
   ! 2006/01/27 15:14:22 Fairhead  
4    
5    IMPLICIT NONE    IMPLICIT NONE
6    
# Line 9  CONTAINS Line 8  CONTAINS
8    
9    SUBROUTINE start_init_phys(tsol_2d, qsol_2d)    SUBROUTINE start_init_phys(tsol_2d, qsol_2d)
10    
11      use conf_dat2d_m, only: conf_dat2d      ! Libraries:
     use dimensions, only: iim, jjm  
     use dynetat0_m, only: rlonu, rlatv  
     use gr_int_dyn_m, only: gr_int_dyn  
     use inter_barxy_m, only: inter_barxy  
12      use netcdf, only: nf90_nowrite      use netcdf, only: nf90_nowrite
13      use netcdf95, only: nf95_open, nf95_close, nf95_get_var, nf95_inq_varid, &      use netcdf95, only: nf95_open, nf95_close, nf95_get_var, nf95_inq_varid, &
14           nf95_gw_var, find_coord           nf95_gw_var, find_coord
15      use nr_util, only: assert, pi      use nr_util, only: assert, pi
16    
17      REAL, intent(out):: tsol_2d(:, :), qsol_2d(:, :) ! (iim + 1, jjm + 1)      use conf_dat2d_m, only: conf_dat2d
18        use dimensions, only: iim, jjm
19        use dynetat0_m, only: rlonu, rlatv
20        use gr_int_dyn_m, only: gr_int_dyn
21        use inter_barxy_m, only: inter_barxy
22    
23      ! Variables local to the procedure:      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    
28        ! Local:
29      INTEGER iml_phys, jml_phys, ncid, varid      INTEGER iml_phys, jml_phys, ncid, varid
30      REAL, ALLOCATABLE:: lon_rad(:), lat_rad(:)      REAL, ALLOCATABLE:: lon_rad(:), lat_rad(:)
31      REAL, ALLOCATABLE:: lon_ini(:), lat_ini(:) ! longitude and latitude in rad      REAL, ALLOCATABLE:: lon_ini(:), lat_ini(:) ! longitude and latitude in rad

Legend:
Removed from v.342  
changed lines
  Added in v.343

  ViewVC Help
Powered by ViewVC 1.1.21