Ignore:
Timestamp:
Mar 7, 2007 8:38:00 AM (17 years ago)
Author:
raasch
Message:

preliminary version, several changes to be explained later

File:
1 edited

Legend:

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

    r48 r51  
    88! -----------------
    99! New initializing action "by_user" calls user_init_3d_model,
    10 ! ts_value is allocated
     10! ts_value is allocated, +module netcdf_control,
     11! initial velocities at nzb+1 are regarded for volume
     12! flow control in case they have been set zero before (to avoid small timesteps)
    1113!
    1214! Former revisions:
     
    4446    USE interfaces
    4547    USE model_1d
     48    USE netcdf_control
    4649    USE particle_attributes
    4750    USE pegrid
     
    183186
    184187!
     188!-- 4D-array for storing the Rif-values at vertical walls
     189    IF ( topography /= 'flat' )  THEN
     190       ALLOCATE( rif_wall(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1,1:4) )
     191       rif_wall = 0.0
     192    ENDIF
     193
     194!
     195!-- Velocities at nzb+1 needed for volume flow control
     196    IF ( conserve_volume_flow )  THEN
     197       ALLOCATE( u_nzb_p1_for_vfc(nys:nyn), v_nzb_p1_for_vfc(nxl:nxr) )
     198       u_nzb_p1_for_vfc = 0.0
     199       v_nzb_p1_for_vfc = 0.0
     200    ENDIF
     201
     202!
    185203!-- Initial assignment of the pointers
    186204    IF ( timestep_scheme(1:5) /= 'runge' )  THEN
     
    382400          ENDDO
    383401!
    384 !--       Set initial horizontal velocities at the lowest grid levels to zero
    385 !--       in order to avoid too small time steps caused by the diffusion
     402!--       Set initial horizontal velocities at the lowest computational grid levels
     403!--       to zero in order to avoid too small time steps caused by the diffusion
    386404!--       limit in the initial phase of a run (at k=1, dz/2 occurs in the
    387 !--       limiting formula!)
     405!--       limiting formula!). The original values are stored to be later used for
     406!--       volume flow control.
    388407          DO  i = nxl-1, nxr+1
    389408             DO  j = nys-1, nyn+1
     
    392411             ENDDO
    393412          ENDDO
     413          IF ( conserve_volume_flow )  THEN
     414             IF ( nxr == nx )  THEN
     415                DO  j = nys, nyn
     416                   k = nzb_u_inner(j,nx) + 1
     417                   u_nzb_p1_for_vfc(j) = u_init(k) * dzu(k)
     418                ENDDO
     419             ENDIF
     420             IF ( nyn == ny )  THEN
     421                DO  i = nxl, nxr
     422                   k = nzb_v_inner(ny,i) + 1
     423                   v_nzb_p1_for_vfc(i) = v_init(k) * dzu(k)
     424                ENDDO
     425             ENDIF
     426          ENDIF
    394427
    395428          IF ( moisture  .OR.  passive_scalar )  THEN
     
    568601                   volume_flow_area_l(1)    = volume_flow_area_l(1) + dzu(k)
    569602                ENDDO
     603!
     604!--             Correction if velocity at nzb+1 has been set zero further above
     605                volume_flow_initial_l(1) = volume_flow_initial_l(1) + &
     606                                           u_nzb_p1_for_vfc(j)
    570607             ENDDO
    571608          ENDIF
     
    578615                   volume_flow_area_l(2)    = volume_flow_area_l(2) + dzu(k)
    579616                ENDDO
     617!
     618!--             Correction if velocity at nzb+1 has been set zero further above
     619                volume_flow_initial_l(2) = volume_flow_initial_l(2) + &
     620                                           v_nzb_p1_for_vfc(i)
    580621             ENDDO
    581622          ENDIF
     
    704745!
    705746!-- If required, initialize dvrp-software
    706 !    WRITE ( 9, * ) '*** myid=', myid, ' vor init_dvrp'
    707 !    CALL FLUSH_( 9 )
    708747    IF ( dt_dvrp /= 9999999.9 )  CALL init_dvrp
    709 !    WRITE ( 9, * ) '*** myid=', myid, ' nach init_dvrp'
    710 !    CALL FLUSH_( 9 )
    711748
    712749!
     
    719756!
    720757!-- If required, initialize particles
    721 !    WRITE ( 9, * ) '*** myid=', myid, ' vor init_particles'
    722 !    CALL FLUSH_( 9 )
    723758    CALL init_particles
    724 !    WRITE ( 9, * ) '*** myid=', myid, ' nach init_particles'
    725 !    CALL FLUSH_( 9 )
    726759
    727760!
     
    825858
    826859!
    827 !-- User-defined initializing actions
     860!-- User-defined initializing actions. Check afterwards, if maximum number
     861!-- of allowed timeseries is not exceeded
    828862    CALL user_init
     863
     864    IF ( dots_num > dots_max )  THEN
     865       IF ( myid == 0 )  THEN
     866          PRINT*, '+++ user_init: number of time series quantities exceeds', &
     867                  ' its maximum of dots_max = ', dots_max
     868          PRINT*, '    Please increase dots_max in modules.f90.'
     869       ENDIF
     870       CALL local_stop
     871    ENDIF
    829872
    830873!
Note: See TracChangeset for help on using the changeset viewer.