Ignore:
Timestamp:
Aug 24, 2007 3:10:38 PM (17 years ago)
Author:
letzel
Message:
  • Improved coupler: evaporation - salinity-flux coupling for humidity = .T.,

avoid MPI hangs when coupled runs terminate, add DOC/app/chapter_3.8;

  • Optional calculation of km and kh from initial TKE e_init;
  • Default initialization of km,kh = 0.00001 for ocean = .T.;
  • Allow data_output_pr= q, wq, w"q", w*q* for humidity = .T.;
  • Bugfix: Rayleigh damping for ocean fixed.
File:
1 edited

Legend:

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

    r106 r108  
    99! Flux initialization in case of coupled runs, +momentum fluxes at top boundary,
    1010! +arrays for phase speed c_u, c_v, c_w, indices for u|v|w_m_l|r changed
     11! +qswst_remote in case of atmosphere model with humidity coupled to ocean
     12! Rayleigh damping for ocean
     13! optionally calculate km and kh from initial TKE e_init
    1114!
    1215! Former revisions:
     
    204207       rho => rho_1  ! routine calc_mean_profile requires density to be a
    205208                     ! pointer
     209       IF ( humidity_remote )  THEN
     210          ALLOCATE( qswst_remote(nys-1:nyn+1,nxl-1:nxr+1) )
     211          qswst_remote = 0.0
     212       ENDIF
    206213    ENDIF
    207214
     
    507514             km   = km_constant
    508515             kh   = km / prandtl_number
     516             e    = 0.0
     517          ELSEIF ( e_init > 0.0 )  THEN
     518             DO  k = nzb+1, nzt
     519                km(k,:,:) = 0.1 * l_grid(k) * SQRT( e_init )
     520             ENDDO
     521             km(nzb,:,:)   = km(nzb+1,:,:)
     522             km(nzt+1,:,:) = km(nzt,:,:)
     523             kh   = km / prandtl_number
     524             e    = e_init
    509525          ELSE
    510              kh   = 0.01   ! there must exist an initial diffusion, because
    511              km   = 0.01   ! otherwise no TKE would be produced by the
    512                            ! production terms, as long as not yet
    513                            ! e = (u*/cm)**2 at k=nzb+1
    514           ENDIF
    515           e     = 0.0
     526             IF ( .NOT. ocean )  THEN
     527                kh   = 0.01   ! there must exist an initial diffusion, because
     528                km   = 0.01   ! otherwise no TKE would be produced by the
     529                              ! production terms, as long as not yet
     530                              ! e = (u*/cm)**2 at k=nzb+1
     531             ELSE
     532                kh   = 0.00001
     533                km   = 0.00001
     534             ENDIF
     535             e    = 0.0
     536          ENDIF
    516537          rif   = 0.0
    517538          ts    = 0.0
     
    892913    rdf = 0.0
    893914    IF ( rayleigh_damping_factor /= 0.0 )  THEN
    894        DO  k = nzb+1, nzt
    895           IF ( zu(k) >= rayleigh_damping_height )  THEN
    896              rdf(k) = rayleigh_damping_factor * &
     915       IF ( .NOT. ocean )  THEN
     916          DO  k = nzb+1, nzt
     917             IF ( zu(k) >= rayleigh_damping_height )  THEN
     918                rdf(k) = rayleigh_damping_factor * &
    897919                      ( SIN( pi * 0.5 * ( zu(k) - rayleigh_damping_height )    &
    898920                                      / ( zu(nzt) - rayleigh_damping_height ) )&
    899921                      )**2
    900           ENDIF
    901        ENDDO
     922             ENDIF
     923          ENDDO
     924       ELSE
     925          DO  k = nzt, nzb+1, -1
     926             IF ( zu(k) <= rayleigh_damping_height )  THEN
     927                rdf(k) = rayleigh_damping_factor * &
     928                      ( SIN( pi * 0.5 * ( rayleigh_damping_height - zu(k) )    &
     929                                      / ( rayleigh_damping_height - zu(nzb+1)))&
     930                      )**2
     931             ENDIF
     932          ENDDO
     933       ENDIF
    902934    ENDIF
    903935
Note: See TracChangeset for help on using the changeset viewer.