Ignore:
Timestamp:
Jul 27, 2007 9:09:17 AM (17 years ago)
Author:
raasch
Message:

preliminary version for coupled runs

File:
1 edited

Legend:

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

    r98 r102  
    77! Actual revisions:
    88! -----------------
    9 !
     9! Flux initialization in case of coupled runs, +momentum fluxes at top boundary
    1010!
    1111! Former revisions:
     
    102102              ts(nys-1:nyn+1,nxl-1:nxr+1), tswst_1(nys-1:nyn+1,nxl-1:nxr+1),  &
    103103              us(nys-1:nyn+1,nxl-1:nxr+1), usws_1(nys-1:nyn+1,nxl-1:nxr+1),   &
    104               vsws_1(nys-1:nyn+1,nxl-1:nxr+1), z0(nys-1:nyn+1,nxl-1:nxr+1) )
     104              uswst_1(nys-1:nyn+1,nxl-1:nxr+1),                               &
     105              vsws_1(nys-1:nyn+1,nxl-1:nxr+1),                                &
     106              vswst_1(nys-1:nyn+1,nxl-1:nxr+1), z0(nys-1:nyn+1,nxl-1:nxr+1) )
    105107
    106108    IF ( timestep_scheme(1:5) /= 'runge' )  THEN
     
    111113                 tswst_2(nys-1:nyn+1,nxl-1:nxr+1), &
    112114                 usws_2(nys-1:nyn+1,nxl-1:nxr+1),  &
     115                 uswst_2(nys-1:nyn+1,nxl-1:nxr+1), &
     116                 vswst_2(nys-1:nyn+1,nxl-1:nxr+1), &
    113117                 vsws_2(nys-1:nyn+1,nxl-1:nxr+1) )
    114118    ENDIF
     
    260264       tswst_m => tswst_1;  tswst => tswst_2
    261265       usws_m  => usws_1;   usws  => usws_2
     266       uswst_m => uswst_1;  uswst => uswst_2
    262267       vsws_m  => vsws_1;   vsws  => vsws_2
     268       vswst_m => vswst_1;  vswst => vswst_2
    263269       e_m  => e_1;   e  => e_2;   e_p  => e_3;   te_m  => e_3
    264270       kh_m => kh_1;  kh => kh_2
     
    287293       tswst => tswst_1
    288294       usws  => usws_1
     295       uswst => uswst_1
    289296       vsws  => vsws_1
     297       vswst => vswst_1
    290298       e     => e_1;   e_p  => e_2;   te_m  => e_3;   e_m  => e_3
    291299       kh    => kh_1
     
    381389             vsws = 0.0
    382390          ENDIF
     391          uswst = top_momentumflux_u
     392          vswst = top_momentumflux_v
    383393
    384394!
     
    494504                           ! e = (u*/cm)**2 at k=nzb+1
    495505          ENDIF
    496           e    = 0.0
    497           rif  = 0.0
    498           ts   = 0.0
    499           us   = 0.0
    500           usws = 0.0
    501           vsws = 0.0
     506          e     = 0.0
     507          rif   = 0.0
     508          ts    = 0.0
     509          us    = 0.0
     510          usws  = 0.0
     511          uswst = top_momentumflux_u
     512          vsws  = 0.0
     513          vswst = top_momentumflux_v
    502514          IF ( humidity  .OR.  passive_scalar ) qs = 0.0
    503515
     
    617629                saswst = top_salinityflux
    618630             ENDIF
    619          ENDIF
     631          ENDIF
     632
     633!
     634!--       Initialization in case of a coupled model run
     635          IF ( coupling_mode == 'ocean_to_atmosphere' )  THEN
     636             tswst = 0.0
     637             IF ( ASSOCIATED( tswst_m ) )  tswst_m = tswst
     638          ENDIF
    620639
    621640       ENDIF
Note: See TracChangeset for help on using the changeset viewer.