/[lmdze]/trunk/Sources/phylmd/Orography/start_init_orog.f
ViewVC logotype

Diff of /trunk/Sources/phylmd/Orography/start_init_orog.f

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

trunk/libf/phylmd/Orography/start_init_orog_m.f90 revision 39 by guez, Tue Jan 25 15:11:05 2011 UTC trunk/Sources/phylmd/Orography/start_init_orog_m.f revision 227 by guez, Thu Nov 2 15:47:03 2017 UTC
# Line 3  MODULE start_init_orog_m Line 3  MODULE start_init_orog_m
3    ! From startvar.F, version 1.4    ! From startvar.F, version 1.4
4    ! 2006/01/27 15:14:22 Fairhead    ! 2006/01/27 15:14:22 Fairhead
5    
6      use dimens_m, only: iim, jjm
7    
8    IMPLICIT NONE    IMPLICIT NONE
9    
10    REAL, ALLOCATABLE, SAVE:: mask(:, :) ! fraction of land (iim + 1, jjm + 1)    REAL, SAVE:: mask(iim + 1, jjm + 1) ! interpolated fraction of land
11    REAL, ALLOCATABLE, SAVE:: phis(:, :) ! surface geopotential, in m2 s-2  
12      private iim, jjm
13    
14  CONTAINS  CONTAINS
15    
16    SUBROUTINE start_init_orog(relief, zstd_2d, zsig_2d, zgam_2d, zthe_2d, &    SUBROUTINE start_init_orog(phis, zmea_2d, zstd_2d, zsig_2d, zgam_2d, &
17         zpic_2d, zval_2d)         zthe_2d, zpic_2d, zval_2d)
18    
19      use conf_dat2d_m, only: conf_dat2d      use conf_dat2d_m, only: conf_dat2d
20      use comgeom, only: rlatu, rlonv      use dynetat0_m, only: rlatu, rlonv
     use dimens_m, only: iim, jjm  
     USE flincom, only: flininfo, flinopen_nozoom, flinclo  
     use flinget_m, only: flinget  
21      use grid_noro_m, only: grid_noro      use grid_noro_m, only: grid_noro
22      use indicesol, only: epsfra      use indicesol, only: epsfra
23      use nr_util, only: pi      use netcdf, only: nf90_nowrite
24        use netcdf95, only: nf95_open, nf95_gw_var, nf95_inq_varid, nf95_close
25        use nr_util, only: pi, assert
26    
27        REAL, intent(out):: phis(:, :) ! (iim + 1, jjm + 1)
28        ! surface geopotential, in m2 s-2
29    
30      REAL, intent(out):: relief(:, :) ! orographie moyenne      REAL, intent(out):: zmea_2d(:, :) ! (iim + 1, jjm + 1) orographie moyenne
31    
32      REAL, intent(out):: zstd_2d(:, :)      REAL, intent(out):: zstd_2d(:, :) ! (iim + 1, jjm + 1)
33      ! (deviation standard de l'orographie sous-maille)      ! (deviation standard de l'orographie sous-maille)
34    
35      REAL, intent(out):: zsig_2d(:, :)      REAL, intent(out):: zsig_2d(:, :) ! (iim + 1, jjm + 1)
36      ! (pente de l'orographie sous-maille)      ! (pente de l'orographie sous-maille)
37            
38      REAL, intent(out):: zgam_2d(:, :)      REAL, intent(out):: zgam_2d(:, :) ! (iim + 1, jjm + 1)
39      ! (anisotropie de l'orographie sous maille)      ! (anisotropie de l'orographie sous maille)
40    
41      REAL, intent(out):: zthe_2d(:, :)      REAL, intent(out):: zthe_2d(:, :) ! (iim + 1, jjm + 1)
42      ! (orientation de l'axe oriente dans la direction de plus grande      ! (orientation de l'axe oriente dans la direction de plus grande
43      ! pente de l'orographie sous maille)      ! pente de l'orographie sous maille)
44    
45      REAL, intent(out):: zpic_2d(:, :) ! hauteur pics de la SSO      REAL, intent(out):: zpic_2d(:, :) ! (iim + 1, jjm + 1)
46      REAL, intent(out):: zval_2d(:, :) ! hauteur vallees de la SSO      ! hauteur pics de la SSO
47    
48        REAL, intent(out):: zval_2d(:, :) ! (iim + 1, jjm + 1)
49        ! hauteur vallees de la SSO
50    
51      ! Local:      ! Local:
52    
53      INTEGER, SAVE:: iml_rel      INTEGER iml_rel
54      INTEGER, SAVE:: jml_rel      INTEGER jml_rel
55      REAL lev(1), date, dt      INTEGER ncid, varid
56      INTEGER itau(1), fid      REAL, ALLOCATABLE:: relief(:, :) ! in m
     INTEGER  llm_tmp, ttm_tmp  
     REAL, ALLOCATABLE:: relief_hi(:, :)  
57      REAL, ALLOCATABLE:: lon_rad(:), lat_rad(:)      REAL, ALLOCATABLE:: lon_rad(:), lat_rad(:)
58      REAL, ALLOCATABLE:: lon_ini(:), lat_ini(:)      REAL, ALLOCATABLE:: lon_ini(:), lat_ini(:)
     REAL, ALLOCATABLE:: lon_rel(:, :), lat_rel(:, :)  
59    
60      !-----------------------------------      !-----------------------------------
61    
62      print *, "Call sequence information: start_init_orog"      print *, "Call sequence information: start_init_orog"
63    
64      if (any((/size(relief, 1), size(zstd_2d, 1), size(zsig_2d, 1), &      call assert((/size(phis, 1), size(zmea_2d, 1), size(zstd_2d, 1), &
65           size(zgam_2d, 1), size(zthe_2d, 1), size(zpic_2d, 1), &           size(zsig_2d, 1), size(zgam_2d, 1), size(zthe_2d, 1), &
66           size(zval_2d, 1)/) /= iim + 1)) stop "start_init_orog size 1"           size(zpic_2d, 1), size(zval_2d, 1)/) == iim + 1, "start_init_orog iim")
67      if (any((/size(relief, 2), size(zstd_2d, 2), size(zsig_2d, 2), &      call assert((/size(phis, 2), size(zmea_2d, 2), size(zstd_2d, 2), &
68           size(zgam_2d, 2), size(zthe_2d, 2), size(zpic_2d, 2), &           size(zsig_2d, 2), size(zgam_2d, 2), size(zthe_2d, 2), &
69           size(zval_2d, 2)/) /= jjm + 1)) stop "start_init_orog size 2"           size(zpic_2d, 2), size(zval_2d, 2)/) == jjm + 1, "start_init_orog jjm")
70    
71      print *, 'Reading the high resolution orography'      print *, 'Reading the high resolution orography...'
72      CALL flininfo('Relief.nc', iml_rel, jml_rel, llm_tmp, ttm_tmp, fid)  
73        call nf95_open('Relief.nc', nf90_nowrite, ncid)
74      ALLOCATE(lat_rel(iml_rel, jml_rel))  
75      ALLOCATE(lon_rel(iml_rel, jml_rel))      call nf95_inq_varid(ncid, "longitude", varid)
76      ALLOCATE(relief_hi(iml_rel, jml_rel))      call nf95_gw_var(ncid, varid, lon_ini)
77        lon_ini = lon_ini * pi / 180. ! convert to rad
78      CALL flinopen_nozoom(iml_rel, jml_rel, llm_tmp, &      iml_rel = size(lon_ini)
79           lon_rel, lat_rel, lev, ttm_tmp, itau, date, dt, fid)  
80      ! 'RELIEF': high resolution orography      call nf95_inq_varid(ncid, "latitude", varid)
81      CALL flinget(fid, 'RELIEF', iml_rel, jml_rel, llm_tmp, ttm_tmp, 1, 1, &      call nf95_gw_var(ncid, varid, lat_ini)
82           relief_hi)      lat_ini = lat_ini * pi / 180. ! convert to rad
83      CALL flinclo(fid)      jml_rel = size(lat_ini)
   
     ! In case we have a file which is in degrees we do the transformation:  
84    
85      ALLOCATE(lon_rad(iml_rel))      call nf95_inq_varid(ncid, "RELIEF", varid)
86      ALLOCATE(lon_ini(iml_rel))      call nf95_gw_var(ncid, varid, relief)
87    
88      IF (MAXVAL(lon_rel(:, :)) > pi) THEN      call nf95_close(ncid)
        lon_ini(:) = lon_rel(:, 1) * pi / 180.  
     ELSE  
        lon_ini(:) = lon_rel(:, 1)  
     ENDIF  
89    
90        ALLOCATE(lon_rad(iml_rel))
91      ALLOCATE(lat_rad(jml_rel))      ALLOCATE(lat_rad(jml_rel))
     ALLOCATE(lat_ini(jml_rel))  
   
     IF (MAXVAL(lat_rel(:, :)) > pi) THEN  
        lat_ini(:) = lat_rel(1, :) * pi / 180.  
     ELSE  
        lat_ini(:) = lat_rel(1, :)  
     ENDIF  
92    
93      CALL conf_dat2d(lon_ini, lat_ini, lon_rad, lat_rad, relief_hi , &      CALL conf_dat2d(lon_ini, lat_ini, lon_rad, lat_rad, relief , &
94           interbar=.FALSE.)           interbar=.FALSE.)
95    
96      print *, 'Compute all the parameters needed for the gravity wave drag code'      print *, 'Compute all the parameters needed for the gravity wave drag code'
97    
98      ! Allocate the data we need to put in the interpolated fields:      CALL grid_noro(lon_rad, lat_rad, relief, rlonv, rlatu, phis, zmea_2d, &
     ALLOCATE(phis(iim + 1, jjm + 1))  
     ALLOCATE(mask(iim + 1, jjm + 1))  
   
     CALL grid_noro(lon_rad, lat_rad, relief_hi, rlonv, rlatu, phis, relief, &  
99           zstd_2d, zsig_2d, zgam_2d, zthe_2d, zpic_2d, zval_2d, mask)           zstd_2d, zsig_2d, zgam_2d, zthe_2d, zpic_2d, zval_2d, mask)
   
     phis(iim + 1, :) = phis(1, :)  
100      phis(:, :) = phis(:, :) * 9.81      phis(:, :) = phis(:, :) * 9.81
101    
102      mask(2:, 1) = mask(1, 1) ! north pole      mask(2:, 1) = mask(1, 1) ! north pole

Legend:
Removed from v.39  
changed lines
  Added in v.227

  ViewVC Help
Powered by ViewVC 1.1.21