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_3d_model.f90

    r90 r94  
    77! Actual revisions:
    88! -----------------
    9 !
     9! Initialization of salinity
    1010!
    1111! Former revisions:
     
    187187    ENDIF
    188188
     189    IF ( ocean )  THEN
     190       ALLOCATE( saswst_1(nys-1:nyn+1,nxl-1:nxr+1) )
     191       ALLOCATE( r(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1),    &
     192                 sa_1(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1), &
     193                 sa_2(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1), &
     194                 sa_3(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
     195    ENDIF
     196
    189197!
    190198!-- 3D-array for storing the dissipation, needed for calculating the sgs
     
    285293          qsws   => qsws_1
    286294          qswst  => qswst_1
    287           q      => q_1;     q_p  => q_2;     tq_m => q_3;    q_m => q_3
     295          q      => q_1;     q_p  => q_2;     tq_m  => q_3;    q_m => q_3
    288296          IF ( humidity )        vpt  => vpt_1
    289297          IF ( cloud_physics )   ql   => ql_1
     
    292300             ql_c => ql_2
    293301          ENDIF
     302       ENDIF
     303
     304       IF ( ocean )  THEN
     305          saswst => saswst_1
     306          sa     => sa_1;    sa_p => sa_2;    tsa_m => sa_3
    294307       ENDIF
    295308
     
    457470          ENDIF
    458471
     472          IF ( ocean )  THEN
     473             DO  i = nxl-1, nxr+1
     474                DO  j = nys-1, nyn+1
     475                   sa(:,j,i) = sa_init
     476                ENDDO
     477             ENDDO
     478          ENDIF
    459479         
    460480          IF ( constant_diffusion )  THEN
     
    566586!
    567587!--    Initialize fluxes at top surface
    568 !--    Currently, only the heatflux can be prescribed. The latent flux is
    569 !--    zero in this case!
     588!--    Currently, only the heatflux and salinity flux can be prescribed.
     589!--    The latent flux is zero in this case!
    570590       IF ( use_top_fluxes )  THEN
    571591
     
    579599                qswst = 0.0
    580600                IF ( ASSOCIATED( qswst_m ) )  qswst_m = qswst
     601             ENDIF
     602
     603             IF ( ocean )  THEN
     604                saswst = top_salinityflux
    581605             ENDIF
    582606         ENDIF
     
    744768       ENDIF
    745769
     770       IF ( ocean )  THEN
     771          tsa_m = 0.0
     772          sa_p  = sa
     773       ENDIF
     774
    746775!
    747776!--    Initialize old timelevels needed for radiation boundary conditions
     
    783812       e_p = e; pt_p = pt; u_p = u; v_p = v; w_p = w
    784813       IF ( humidity  .OR.  passive_scalar )  q_p = q
     814       IF ( ocean )  sa_p = sa
    785815
    786816    ELSE
Note: See TracChangeset for help on using the changeset viewer.