Ignore:
Timestamp:
Jun 1, 2007 3:25:22 PM (17 years ago)
Author:
raasch
Message:

preliminary uncomplete changes for ocean version

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/init_grid.f90

    r77 r94  
    44! Actual revisions:
    55! -----------------
    6 !
     6! Grid definition for ocean version
    77!
    88! Former revisions:
     
    7070       CALL local_stop
    7171    ENDIF
    72 !
    73 !-- Since the w-level lies on the surface, the first u-level (staggered!) lies
    74 !-- below the surface (used for "mirror" boundary condition).
    75 !-- The first u-level above the surface corresponds to the top of the
    76 !-- Prandtl-layer.
    77     zu(0) = - dz * 0.5
    78     zu(1) =   dz * 0.5
    79 
    80     dz_stretch_level_index = nzt+1
    81     dz_stretched = dz
    82     DO  k = 2, nzt+1
    83        IF ( dz_stretch_level <= zu(k-1)  .AND.  dz_stretched < dz_max )  THEN
    84           dz_stretched = dz_stretched * dz_stretch_factor
    85           dz_stretched = MIN( dz_stretched, dz_max )
    86           IF ( dz_stretch_level_index == nzt+1 )  dz_stretch_level_index = k-1
    87        ENDIF
    88        zu(k) = zu(k-1) + dz_stretched
    89     ENDDO
    90 
    91 !
    92 !-- Compute the u-levels. They are always staggered half-way between the
    93 !-- corresponding w-levels. The top w-level is extrapolated linearly.
    94     zw(0) = 0.0
    95     DO  k = 1, nzt
    96        zw(k) = ( zu(k) + zu(k+1) ) * 0.5
    97     ENDDO
    98     zw(nzt+1) = zw(nzt) + 2.0 * ( zu(nzt+1) - zw(nzt) )
     72
     73!
     74!-- Define the vertical grid levels
     75    IF ( .NOT. ocean )  THEN
     76!
     77!--    Grid for atmosphere with surface at z=0 (k=0, w-grid).
     78!--    Since the w-level lies on the surface, the first u-level (staggered!)
     79!--    lies below the surface (used for "mirror" boundary condition).
     80!--    The first u-level above the surface corresponds to the top of the
     81!--    Prandtl-layer.
     82       zu(0) = - dz * 0.5
     83       zu(1) =   dz * 0.5
     84
     85       dz_stretch_level_index = nzt+1
     86       dz_stretched = dz
     87       DO  k = 2, nzt+1
     88          IF ( dz_stretch_level <= zu(k-1)  .AND.  dz_stretched < dz_max )  THEN
     89             dz_stretched = dz_stretched * dz_stretch_factor
     90             dz_stretched = MIN( dz_stretched, dz_max )
     91             IF ( dz_stretch_level_index == nzt+1 ) dz_stretch_level_index = k-1
     92          ENDIF
     93          zu(k) = zu(k-1) + dz_stretched
     94       ENDDO
     95
     96!
     97!--    Compute the w-levels. They are always staggered half-way between the
     98!--    corresponding u-levels. The top w-level is extrapolated linearly.
     99       zw(0) = 0.0
     100       DO  k = 1, nzt
     101          zw(k) = ( zu(k) + zu(k+1) ) * 0.5
     102       ENDDO
     103       zw(nzt+1) = zw(nzt) + 2.0 * ( zu(nzt+1) - zw(nzt) )
     104
     105    ELSE
     106!
     107!--    Grid for ocean with solid surface at z=0 (k=0, w-grid). The free water
     108!--    surface is at k=nzt (w-grid).
     109!--    Since the w-level lies always on the surface, the first/last u-level
     110!--    (staggered!) lies below the bottom surface / above the free surface.
     111!--    It is used for "mirror" boundary condition.
     112!--    The first u-level above the bottom surface corresponds to the top of the
     113!--    Prandtl-layer.
     114       zu(nzt+1) =   dz * 0.5
     115       zu(nzt)   = - dz * 0.5
     116
     117       dz_stretch_level_index = 0
     118       dz_stretched = dz
     119       DO  k = nzt-1, 0, -1
     120          IF ( dz_stretch_level <= ABS( zu(k+1) )  .AND.  &
     121               dz_stretched < dz_max )  THEN
     122             dz_stretched = dz_stretched * dz_stretch_factor
     123             dz_stretched = MIN( dz_stretched, dz_max )
     124             IF ( dz_stretch_level_index == 0 ) dz_stretch_level_index = k+1
     125          ENDIF
     126          zu(k) = zu(k+1) - dz_stretched
     127       ENDDO
     128
     129!
     130!--    Compute the w-levels. They are always staggered half-way between the
     131!--    corresponding u-levels.
     132!--    The top w-level (nzt+1) is not used but set for consistency, since
     133!--    w and all scalar variables are defined up tp nzt+1.
     134       zw(nzt+1) = dz
     135       zw(nzt)   = 0.0
     136       DO  k = 0, nzt
     137          zw(k) = ( zu(k) + zu(k+1) ) * 0.5
     138       ENDDO
     139
     140    ENDIF
    99141
    100142!
Note: See TracChangeset for help on using the changeset viewer.