--- trunk/libf/phylmd/Orography/start_init_orog_m.f90 2010/04/06 17:52:58 32 +++ trunk/libf/phylmd/Orography/start_init_orog_m.f90 2011/03/24 11:52:41 42 @@ -13,37 +13,40 @@ SUBROUTINE start_init_orog(relief, zstd_2d, zsig_2d, zgam_2d, zthe_2d, & zpic_2d, zval_2d) - USE flincom, only: flininfo, flinopen_nozoom, flinclo - use flinget_m, only: flinget use conf_dat2d_m, only: conf_dat2d use comgeom, only: rlatu, rlonv use dimens_m, only: iim, jjm - use indicesol, only: epsfra - use comconst, only: pi + USE flincom, only: flininfo, flinopen_nozoom, flinclo + use flinget_m, only: flinget use grid_noro_m, only: grid_noro + use indicesol, only: epsfra + use nr_util, only: pi - REAL, intent(out):: relief(:, :) ! orographie moyenne + REAL, intent(out):: relief(:, :) ! (iim + 1, jjm + 1) orographie moyenne - REAL, intent(out):: zstd_2d(:, :) + REAL, intent(out):: zstd_2d(:, :) ! (iim + 1, jjm + 1) ! (deviation standard de l'orographie sous-maille) - REAL, intent(out):: zsig_2d(:, :) + REAL, intent(out):: zsig_2d(:, :) ! (iim + 1, jjm + 1) ! (pente de l'orographie sous-maille) - REAL, intent(out):: zgam_2d(:, :) + REAL, intent(out):: zgam_2d(:, :) ! (iim + 1, jjm + 1) ! (anisotropie de l'orographie sous maille) - REAL, intent(out):: zthe_2d(:, :) + REAL, intent(out):: zthe_2d(:, :) ! (iim + 1, jjm + 1) ! (orientation de l'axe oriente dans la direction de plus grande ! pente de l'orographie sous maille) - REAL, intent(out):: zpic_2d(:, :) ! hauteur pics de la SSO - REAL, intent(out):: zval_2d(:, :) ! hauteur vallees de la SSO + REAL, intent(out):: zpic_2d(:, :) ! (iim + 1, jjm + 1) + ! hauteur pics de la SSO + + REAL, intent(out):: zval_2d(:, :) ! (iim + 1, jjm + 1) + ! hauteur vallees de la SSO ! Local: - INTEGER, SAVE:: iml_rel - INTEGER, SAVE:: jml_rel + INTEGER iml_rel + INTEGER jml_rel REAL lev(1), date, dt INTEGER itau(1), fid INTEGER llm_tmp, ttm_tmp @@ -52,8 +55,6 @@ REAL, ALLOCATABLE:: lon_ini(:), lat_ini(:) REAL, ALLOCATABLE:: lon_rel(:, :), lat_rel(:, :) - CHARACTER(len=120) orogfname - !----------------------------------- print *, "Call sequence information: start_init_orog" @@ -65,10 +66,8 @@ size(zgam_2d, 2), size(zthe_2d, 2), size(zpic_2d, 2), & size(zval_2d, 2)/) /= jjm + 1)) stop "start_init_orog size 2" - orogfname = 'Relief.nc' print *, 'Reading the high resolution orography' - - CALL flininfo(orogfname, iml_rel, jml_rel, llm_tmp, ttm_tmp, fid) + CALL flininfo('Relief.nc', iml_rel, jml_rel, llm_tmp, ttm_tmp, fid) ALLOCATE(lat_rel(iml_rel, jml_rel)) ALLOCATE(lon_rel(iml_rel, jml_rel))