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

Diff of /trunk/dyn3d/start_init_phys_m.f

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

revision 48 by guez, Tue Jul 19 12:54:20 2011 UTC revision 49 by guez, Wed Aug 24 11:43:14 2011 UTC
# Line 9  CONTAINS Line 9  CONTAINS
9    
10    SUBROUTINE start_init_phys(tsol_2d, qsol_2d)    SUBROUTINE start_init_phys(tsol_2d, qsol_2d)
11    
     USE flincom, only: flininfo, flinopen_nozoom, flinclo  
     use conf_dat2d_m, only: conf_dat2d  
     use inter_barxy_m, only: inter_barxy  
     use gr_int_dyn_m, only: gr_int_dyn  
12      use comgeom, only: rlonu, rlatv      use comgeom, only: rlonu, rlatv
13        use conf_dat2d_m, only: conf_dat2d
14      use dimens_m, only: iim, jjm      use dimens_m, only: iim, jjm
15      use nr_util, only: assert      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      use netcdf, only: nf90_nowrite
19      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, &
20             nf95_gw_var
21        use nr_util, only: assert, pi
22    
23      REAL, intent(out):: tsol_2d(:, :), qsol_2d(:, :) ! (iim + 1, jjm + 1)      REAL, intent(out):: tsol_2d(:, :), qsol_2d(:, :) ! (iim + 1, jjm + 1)
24    
25      ! Variables local to the procedure:      ! Variables local to the procedure:
26    
27      INTEGER fid_phys, iml_phys, jml_phys, ncid, varid      INTEGER iml_phys, jml_phys, ncid, varid
     REAL, ALLOCATABLE, DIMENSION(:, :):: lon_phys, lat_phys  
     REAL date, dt  
     REAL, ALLOCATABLE:: levphys_ini(:)  
   
     INTEGER itau(1)  
     INTEGER  llm_tmp, ttm_tmp  
   
28      REAL, ALLOCATABLE:: lon_rad(:), lat_rad(:)      REAL, ALLOCATABLE:: lon_rad(:), lat_rad(:)
29      REAL, ALLOCATABLE:: lon_ini(:), lat_ini(:)      REAL, pointer:: lon_ini(:), lat_ini(:) ! longitude and latitude in rad
30      REAL, ALLOCATABLE:: var_ana(:, :)      REAL, ALLOCATABLE:: var_ana(:, :)
31      real tmp_var(iim, jjm + 1)      real tmp_var(iim, jjm + 1)
32    
# Line 45  CONTAINS Line 39  CONTAINS
39      call assert((/size(tsol_2d, 2), size(qsol_2d, 2)/) == jjm + 1, &      call assert((/size(tsol_2d, 2), size(qsol_2d, 2)/) == jjm + 1, &
40           "start_init_phys 2")           "start_init_phys 2")
41    
42      CALL flininfo('ECPHY.nc', iml_phys, jml_phys, llm_tmp, ttm_tmp, fid_phys)      call nf95_open('ECPHY.nc', nf90_nowrite, ncid)
   
     ALLOCATE(lat_phys(iml_phys, jml_phys))  
     ALLOCATE(lon_phys(iml_phys, jml_phys))  
     ALLOCATE(levphys_ini(llm_tmp))  
   
     CALL flinopen_nozoom(iml_phys, jml_phys, llm_tmp, lon_phys, lat_phys, &  
          levphys_ini, ttm_tmp, itau, date, dt, fid_phys)  
     CALL flinclo(fid_phys)  
43    
44      DEALLOCATE(levphys_ini)      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      ! Allocate the space we will need to get the data out of this file
55      ALLOCATE(var_ana(iml_phys, jml_phys))      ALLOCATE(var_ana(iml_phys, jml_phys))
56    
     !   In case we have a file which is in degrees we do the transformation  
57      ALLOCATE(lon_rad(iml_phys))      ALLOCATE(lon_rad(iml_phys))
     ALLOCATE(lon_ini(iml_phys))  
   
     IF ( MAXVAL(lon_phys) > 2.0 * ASIN(1.0) ) THEN  
        lon_ini = lon_phys(:, 1) * 2.0 * ASIN(1.0) / 180.0  
     ELSE  
        lon_ini = lon_phys(:, 1)  
     ENDIF  
   
58      ALLOCATE(lat_rad(jml_phys))      ALLOCATE(lat_rad(jml_phys))
     ALLOCATE(lat_ini(jml_phys))  
   
     IF ( MAXVAL(lat_phys) > 2.0 * ASIN(1.0) ) THEN  
        lat_ini = lat_phys(1, :) * 2.0 * ASIN(1.0) / 180.0  
     ELSE  
        lat_ini = lat_phys(1, :)  
     ENDIF  
   
     call nf95_open('ECPHY.nc', nf90_nowrite, ncid)  
59    
60      ! We get the two standard variables      ! We get the two standard variables
61      ! 'ST': surface temperature      ! 'ST': surface temperature
# Line 99  CONTAINS Line 75  CONTAINS
75      qsol_2d = gr_int_dyn(tmp_var)      qsol_2d = gr_int_dyn(tmp_var)
76    
77      call nf95_close(ncid)      call nf95_close(ncid)
78        deallocate(lon_ini, lat_ini) ! pointers
79    
80    END SUBROUTINE start_init_phys    END SUBROUTINE start_init_phys
81    

Legend:
Removed from v.48  
changed lines
  Added in v.49

  ViewVC Help
Powered by ViewVC 1.1.21