/[lmdze]/trunk/libf/phylmd/Orography/start_init_orog_m.f90
ViewVC logotype

Diff of /trunk/libf/phylmd/Orography/start_init_orog_m.f90

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

trunk/libf/dyn3d/start_init_orog_m.f90 revision 3 by guez, Wed Feb 27 13:16:39 2008 UTC trunk/libf/phylmd/Orography/start_init_orog_m.f90 revision 42 by guez, Thu Mar 24 11:52:41 2011 UTC
# Line 5  MODULE start_init_orog_m Line 5  MODULE start_init_orog_m
5    
6    IMPLICIT NONE    IMPLICIT NONE
7    
8    REAL, ALLOCATABLE, SAVE:: masque(:, :) ! fraction of land (iim + 1, jjm + 1)    REAL, ALLOCATABLE, SAVE:: mask(:, :) ! fraction of land (iim + 1, jjm + 1)
9    REAL, ALLOCATABLE, SAVE:: phis(:, :) ! surface geopotential, in m2 s-2    REAL, ALLOCATABLE, SAVE:: phis(:, :) ! surface geopotential, in m2 s-2
10    
11  CONTAINS  CONTAINS
# Line 13  CONTAINS Line 13  CONTAINS
13    SUBROUTINE start_init_orog(relief, zstd_2d, zsig_2d, zgam_2d, zthe_2d, &    SUBROUTINE start_init_orog(relief, zstd_2d, zsig_2d, zgam_2d, zthe_2d, &
14         zpic_2d, zval_2d)         zpic_2d, zval_2d)
15    
     USE ioipsl, only: flininfo, flinopen_nozoom, flinget, flinclo  
16      use conf_dat2d_m, only: conf_dat2d      use conf_dat2d_m, only: conf_dat2d
17      use comgeom, only: rlatu, rlonv      use comgeom, only: rlatu, rlonv
18      use dimens_m, only: iim, jjm      use dimens_m, only: iim, jjm
19      use indicesol, only: epsfra      USE flincom, only: flininfo, flinopen_nozoom, flinclo
20      use comconst, only: pi      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
23        use nr_util, only: pi
24    
25      REAL, intent(out):: relief(:, :) ! orographie moyenne      REAL, intent(out):: relief(:, :) ! (iim + 1, jjm + 1) orographie moyenne
26    
27      REAL, intent(out):: zstd_2d(:, :)      REAL, intent(out):: zstd_2d(:, :) ! (iim + 1, jjm + 1)
28      ! (deviation standard de l'orographie sous-maille)      ! (deviation standard de l'orographie sous-maille)
29    
30      REAL, intent(out):: zsig_2d(:, :)      REAL, intent(out):: zsig_2d(:, :) ! (iim + 1, jjm + 1)
31      ! (pente de l'orographie sous-maille)      ! (pente de l'orographie sous-maille)
32            
33      REAL, intent(out):: zgam_2d(:, :)      REAL, intent(out):: zgam_2d(:, :) ! (iim + 1, jjm + 1)
34      ! (anisotropie de l'orographie sous maille)      ! (anisotropie de l'orographie sous maille)
35    
36      REAL, intent(out):: zthe_2d(:, :)      REAL, intent(out):: zthe_2d(:, :) ! (iim + 1, jjm + 1)
37      ! (orientation de l'axe oriente dans la direction de plus grande      ! (orientation de l'axe oriente dans la direction de plus grande
38      ! pente de l'orographie sous maille)      ! pente de l'orographie sous maille)
39    
40      REAL, intent(out):: zpic_2d(:, :) ! hauteur pics de la SSO      REAL, intent(out):: zpic_2d(:, :) ! (iim + 1, jjm + 1)
41      REAL, intent(out):: zval_2d(:, :) ! hauteur vallees de la SSO      ! hauteur pics de la SSO
42    
43        REAL, intent(out):: zval_2d(:, :) ! (iim + 1, jjm + 1)
44        ! hauteur vallees de la SSO
45    
46      ! Local:      ! Local:
47    
48      INTEGER, SAVE:: iml_rel      INTEGER iml_rel
49      INTEGER, SAVE:: jml_rel      INTEGER jml_rel
50      REAL lev(1), date, dt      REAL lev(1), date, dt
51      INTEGER itau(1), fid      INTEGER itau(1), fid
52      INTEGER  llm_tmp, ttm_tmp      INTEGER  llm_tmp, ttm_tmp
# Line 51  CONTAINS Line 55  CONTAINS
55      REAL, ALLOCATABLE:: lon_ini(:), lat_ini(:)      REAL, ALLOCATABLE:: lon_ini(:), lat_ini(:)
56      REAL, ALLOCATABLE:: lon_rel(:, :), lat_rel(:, :)      REAL, ALLOCATABLE:: lon_rel(:, :), lat_rel(:, :)
57    
     CHARACTER(len=120) orogfname  
   
58      !-----------------------------------      !-----------------------------------
59    
60      print *, "Call sequence information: start_init_orog"      print *, "Call sequence information: start_init_orog"
# Line 64  CONTAINS Line 66  CONTAINS
66           size(zgam_2d, 2), size(zthe_2d, 2), size(zpic_2d, 2), &           size(zgam_2d, 2), size(zthe_2d, 2), size(zpic_2d, 2), &
67           size(zval_2d, 2)/) /= jjm + 1)) stop "start_init_orog size 2"           size(zval_2d, 2)/) /= jjm + 1)) stop "start_init_orog size 2"
68    
     orogfname = 'Relief.nc'  
69      print *, 'Reading the high resolution orography'      print *, 'Reading the high resolution orography'
70        CALL flininfo('Relief.nc', iml_rel, jml_rel, llm_tmp, ttm_tmp, fid)
     CALL flininfo(orogfname, iml_rel, jml_rel, llm_tmp, ttm_tmp, fid)  
71    
72      ALLOCATE(lat_rel(iml_rel, jml_rel))      ALLOCATE(lat_rel(iml_rel, jml_rel))
73      ALLOCATE(lon_rel(iml_rel, jml_rel))      ALLOCATE(lon_rel(iml_rel, jml_rel))
74      ALLOCATE(relief_hi(iml_rel, jml_rel))      ALLOCATE(relief_hi(iml_rel, jml_rel))
75    
76      CALL flinopen_nozoom(orogfname, iml_rel, jml_rel, llm_tmp, &      CALL flinopen_nozoom(iml_rel, jml_rel, llm_tmp, &
77           lon_rel, lat_rel, lev, ttm_tmp, itau, date, dt, fid)           lon_rel, lat_rel, lev, ttm_tmp, itau, date, dt, fid)
78      ! 'RELIEF': high resolution orography      ! 'RELIEF': high resolution orography
79      CALL flinget(fid, 'RELIEF', iml_rel, jml_rel, llm_tmp, ttm_tmp, 1, 1, &      CALL flinget(fid, 'RELIEF', iml_rel, jml_rel, llm_tmp, ttm_tmp, 1, 1, &
# Line 107  CONTAINS Line 107  CONTAINS
107    
108      ! Allocate the data we need to put in the interpolated fields:      ! Allocate the data we need to put in the interpolated fields:
109      ALLOCATE(phis(iim + 1, jjm + 1))      ALLOCATE(phis(iim + 1, jjm + 1))
110      ALLOCATE(masque(iim + 1, jjm + 1))      ALLOCATE(mask(iim + 1, jjm + 1))
111    
112      CALL grid_noro(lon_rad, lat_rad, relief_hi, rlonv, rlatu, phis, relief, &      CALL grid_noro(lon_rad, lat_rad, relief_hi, rlonv, rlatu, phis, relief, &
113           zstd_2d, zsig_2d, zgam_2d, zthe_2d, zpic_2d, zval_2d, masque)           zstd_2d, zsig_2d, zgam_2d, zthe_2d, zpic_2d, zval_2d, mask)
114    
115      phis(iim + 1, :) = phis(1, :)      phis(iim + 1, :) = phis(1, :)
116      phis(:, :) = phis(:, :) * 9.81      phis(:, :) = phis(:, :) * 9.81
117    
118      masque(2:, 1) = masque(1, 1) ! north pole      mask(2:, 1) = mask(1, 1) ! north pole
119      masque(2:, jjm + 1) = masque(1, jjm + 1) ! south pole      mask(2:, jjm + 1) = mask(1, jjm + 1) ! south pole
120      masque(iim + 1, 2:jjm) = masque(1, 2:jjm) ! Greenwich      mask(iim + 1, 2:jjm) = mask(1, 2:jjm) ! Greenwich
121      WHERE (masque < EPSFRA)      WHERE (mask < EPSFRA)
122         masque = 0.         mask = 0.
123      elsewhere (1. - masque < EPSFRA)      elsewhere (1. - mask < EPSFRA)
124         masque = 1.         mask = 1.
125      endwhere      endwhere
126    
127    END SUBROUTINE start_init_orog    END SUBROUTINE start_init_orog

Legend:
Removed from v.3  
changed lines
  Added in v.42

  ViewVC Help
Powered by ViewVC 1.1.21