Ignore:
Timestamp:
Aug 29, 2019 11:02:06 AM (5 years ago)
Author:
gronemeier
Message:

Consider rotation of model domain for claculation of Coriolis force:

  • check_parameters: Overwrite rotation_angle from namelist by value from static driver;
  • coriolis: Consider rotation of model domain;
  • header: Write information about rotation angle;
  • modules: Added rotation_angle;
  • netcdf_interface_mod: replaced rotation angle from input-netCDF file by namelist parameter 'rotation_angle';
  • ocean_mod: Consider rotation of model domain for calculating the Stokes drift;
  • parin: added rotation_angle to initialization_parameters;
File:
1 edited

Legend:

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

    r4182 r4196  
    2525! -----------------
    2626! $Id$
     27! Consider rotation of model domain for calculating the Stokes drift
     28!
     29! 4182 2019-08-22 15:20:23Z scharf
    2730! Corrected "Former revisions" section
    2831!
     
    21262129               v_stokes_zw, w, tend
    21272130
     2131    USE basic_constants_and_equations_mod,                                     &
     2132        ONLY:  pi
     2133
    21282134    USE control_parameters,                                                    &
    2129         ONLY:  f, fs, message_string
     2135        ONLY:  f, fs, message_string, rotation_angle
    21302136
    21312137    USE grid_variables,                                                        &
     
    21372143    IMPLICIT NONE
    21382144
    2139     INTEGER(iwp) ::  component  !< component of momentum equation
    2140     INTEGER(iwp) ::  i          !< loop index along x
    2141     INTEGER(iwp) ::  j          !< loop index along y
    2142     INTEGER(iwp) ::  k          !< loop index along z
    2143 
     2145    INTEGER(iwp) ::  component      !< component of momentum equation
     2146    INTEGER(iwp) ::  i              !< loop index along x
     2147    INTEGER(iwp) ::  j              !< loop index along y
     2148    INTEGER(iwp) ::  k              !< loop index along z
     2149
     2150    REAL(wp)     ::  cos_rot_angle  !< cosine of model rotation angle
     2151    REAL(wp)     ::  sin_rot_angle  !< sine of model rotation angle
    21442152
    21452153!
     
    21822190!--    w-component
    21832191       CASE ( 3 )
     2192
     2193!
     2194!--       Precalculate cosine and sine of rotation angle
     2195          cos_rot_angle = COS( rotation_angle * pi / 180.0_wp )
     2196          sin_rot_angle = SIN( rotation_angle * pi / 180.0_wp )
     2197
    21842198          DO  i = nxl, nxr
    21852199             DO  j = nys, nyn
     
    21972211                                                   + v(k+1,j+1,i) - v(k,j+1,i) &
    21982212                                                   ) * ddzu(k)  )              &
    2199                                            + fs * u_stokes_zw(k)
     2213                                           + fs * (                            &
     2214                                               sin_rot_angle * v_stokes_zw(k)  &
     2215                                             + cos_rot_angle * u_stokes_zw(k)  &
     2216                                                  )
    22002217                ENDDO
    22012218             ENDDO
     
    22262243               v_stokes_zw, w, tend
    22272244
     2245    USE basic_constants_and_equations_mod,                                     &
     2246        ONLY:  pi
     2247
    22282248    USE control_parameters,                                                    &
    2229         ONLY:  f, fs, message_string
     2249        ONLY:  f, fs, message_string, rotation_angle
    22302250
    22312251    USE grid_variables,                                                        &
     
    22372257    IMPLICIT NONE
    22382258
    2239     INTEGER(iwp) ::  component  !< component of momentum equation
    2240     INTEGER(iwp) ::  i          !< loop index along x
    2241     INTEGER(iwp) ::  j          !< loop index along y
    2242     INTEGER(iwp) ::  k          !< loop incex along z
    2243 
     2259    INTEGER(iwp) ::  component      !< component of momentum equation
     2260    INTEGER(iwp) ::  i              !< loop index along x
     2261    INTEGER(iwp) ::  j              !< loop index along y
     2262    INTEGER(iwp) ::  k              !< loop incex along z
     2263
     2264    REAL(wp)     ::  cos_rot_angle  !< cosine of model rotation angle
     2265    REAL(wp)     ::  sin_rot_angle  !< sine of model rotation angle
    22442266
    22452267!
     
    22732295!--    w-component
    22742296       CASE ( 3 )
     2297
     2298!
     2299!--       Precalculate cosine and sine of rotation angle
     2300          cos_rot_angle = COS( rotation_angle * pi / 180.0_wp )
     2301          sin_rot_angle = SIN( rotation_angle * pi / 180.0_wp )
     2302
    22752303          DO  k = nzb+1, nzt
    22762304             tend(k,j,i) = tend(k,j,i) + u_stokes_zw(k) * (              &
     
    22862314                                                   + v(k+1,j+1,i) - v(k,j+1,i) &
    22872315                                                   ) * ddzu(k)  )              &
    2288                                        + fs * u_stokes_zw(k)
     2316                                       + fs * ( sin_rot_angle * v_stokes_zw(k) &
     2317                                              + cos_rot_angle * u_stokes_zw(k) &
     2318                                              )
    22892319          ENDDO
    22902320
Note: See TracChangeset for help on using the changeset viewer.