/[lmdze]/trunk/libf/dyn3d/start_init_orog_m.f90
ViewVC logotype

Diff of /trunk/libf/dyn3d/start_init_orog_m.f90

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

revision 14 by guez, Wed Feb 27 13:16:39 2008 UTC revision 15 by guez, Fri Aug 1 15:24:12 2008 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 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.14  
changed lines
  Added in v.15

  ViewVC Help
Powered by ViewVC 1.1.21