Ignore:
Timestamp:
Mar 7, 2008 1:42:18 PM (16 years ago)
Author:
raasch
Message:

preliminary update for the turbulence recycling method

File:
1 edited

Legend:

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

    r147 r151  
    602602
    603603!
    604 !--    apply channel flow boundary condition
     604!--    Apply channel flow boundary condition
    605605       IF ( TRIM( bc_uv_t ) == 'dirichlet_0' )  THEN
    606606
     
    608608          v(nzt+1,:,:) = 0.0
    609609
    610 !--       for the Dirichlet condition to be correctly applied at the top, set
     610!--       For the Dirichlet condition to be correctly applied at the top, set
    611611!--       ug and vg to zero there
    612612          ug(nzt+1)    = 0.0
     
    755755
    756756!
     757!--    For the moment, perturbation pressure and vertical velocity are zero
     758       p = 0.0; w = 0.0
     759
     760!
     761!--    Initialize array sums (must be defined in first call of pres)
     762       sums = 0.0
     763
     764!
     765!--    Treating cloud physics, liquid water content and precipitation amount
     766!--    are zero at beginning of the simulation
     767       IF ( cloud_physics )  THEN
     768          ql = 0.0
     769          IF ( precipitation )  precipitation_amount = 0.0
     770       ENDIF
     771
     772!
     773!--    Impose vortex with vertical axis on the initial velocity profile
     774       IF ( INDEX( initializing_actions, 'initialize_vortex' ) /= 0 )  THEN
     775          CALL init_rankine
     776       ENDIF
     777
     778!
     779!--    Impose temperature anomaly (advection test only)
     780       IF ( INDEX( initializing_actions, 'initialize_ptanom' ) /= 0 )  THEN
     781          CALL init_pt_anomaly
     782       ENDIF
     783
     784!
     785!--    If required, change the surface temperature at the start of the 3D run
     786       IF ( pt_surface_initial_change /= 0.0 )  THEN
     787          pt(nzb,:,:) = pt(nzb,:,:) + pt_surface_initial_change
     788       ENDIF
     789
     790!
     791!--    If required, change the surface humidity/scalar at the start of the 3D
     792!--    run
     793       IF ( ( humidity .OR. passive_scalar ) .AND. &
     794            q_surface_initial_change /= 0.0 )  THEN
     795          q(nzb,:,:) = q(nzb,:,:) + q_surface_initial_change
     796       ENDIF
     797
     798!
     799!--    Initialize the random number generator (from numerical recipes)
     800       CALL random_function_ini
     801
     802!
     803!--    Impose random perturbation on the horizontal velocity field and then
     804!--    remove the divergences from the velocity field
     805       IF ( create_disturbances )  THEN
     806          CALL disturb_field( nzb_u_inner, tend, u )
     807          CALL disturb_field( nzb_v_inner, tend, v )
     808          n_sor = nsor_ini
     809          CALL pres
     810          n_sor = nsor
     811       ENDIF
     812
     813!
     814!--    Once again set the perturbation pressure explicitly to zero in order to
     815!--    assure that it does not generate any divergences in the first time step.
     816!--    At t=0 the velocity field is free of divergence (as constructed above).
     817!--    Divergences being created during a time step are not yet known and thus
     818!--    cannot be corrected during the time step yet.
     819       p = 0.0
     820
     821!
     822!--    Initialize old and new time levels.
     823       IF ( timestep_scheme(1:5) /= 'runge' )  THEN
     824          e_m = e; pt_m = pt; u_m = u; v_m = v; w_m = w; kh_m = kh; km_m = km
     825       ELSE
     826          te_m = 0.0; tpt_m = 0.0; tu_m = 0.0; tv_m = 0.0; tw_m = 0.0
     827       ENDIF
     828       e_p = e; pt_p = pt; u_p = u; v_p = v; w_p = w
     829
     830       IF ( humidity  .OR.  passive_scalar )  THEN
     831          IF ( ASSOCIATED( q_m ) )  q_m = q
     832          IF ( timestep_scheme(1:5) == 'runge' )  tq_m = 0.0
     833          q_p = q
     834          IF ( humidity  .AND.  ASSOCIATED( vpt_m ) )  vpt_m = vpt
     835       ENDIF
     836
     837       IF ( ocean )  THEN
     838          tsa_m = 0.0
     839          sa_p  = sa
     840       ENDIF
     841
     842
     843    ELSEIF ( TRIM( initializing_actions ) == 'read_restart_data'  .OR.    &
     844             TRIM( initializing_actions ) == 'read_data_for_recycling' )  &
     845    THEN
     846!
     847!--    When reading data for initializing the recycling method, first read
     848!--    some of the global variables from restart file
     849       IF ( TRIM( initializing_actions ) == 'read_data_for_recycling' )  THEN
     850
     851          WRITE (9,*) 'before read_parts_of_var_list'
     852          CALL local_flush( 9 )
     853          CALL read_parts_of_var_list
     854          WRITE (9,*) 'after read_parts_of_var_list'
     855          CALL local_flush( 9 )
     856          CALL close_file( 13 )
     857!
     858!--       Store temporally and horizontally averaged vertical profiles to be
     859!--       used as mean inflow profiles
     860          ALLOCATE( mean_inflow_profiles(nzb:nzt+1,5) )
     861
     862          mean_inflow_profiles(:,1) = hom_sum(:,1,0)    ! u
     863          mean_inflow_profiles(:,2) = hom_sum(:,2,0)    ! v
     864          mean_inflow_profiles(:,4) = hom_sum(:,4,0)    ! pt
     865          mean_inflow_profiles(:,5) = hom_sum(:,8,0)    ! e
     866
     867!
     868!--       Use these mean profiles for the inflow (provided that Dirichlet
     869!--       conditions are used)
     870          IF ( inflow_l )  THEN
     871             DO  j = nys-1, nyn+1
     872                DO  k = nzb, nzt+1
     873                   u(k,j,-1)  = mean_inflow_profiles(k,1)
     874                   v(k,j,-1)  = mean_inflow_profiles(k,2)
     875                   w(k,j,-1)  = 0.0
     876                   pt(k,j,-1) = mean_inflow_profiles(k,4)
     877                   e(k,j,-1)  = mean_inflow_profiles(k,5)
     878                ENDDO
     879             ENDDO
     880          ENDIF
     881
     882!
     883!--       Calculate the damping factors to be used at the inflow. For a
     884!--       turbulent inflow the turbulent fluctuations have to be limited
     885!--       vertically because otherwise the turbulent inflow layer will grow
     886!--       in time.
     887          IF ( inflow_damping_height == 9999999.9 )  THEN
     888!
     889!--          Default: use the inversion height calculated by the prerun
     890             inflow_damping_height = hom_sum(nzb+6,pr_palm,0)
     891
     892          ENDIF
     893
     894          IF ( inflow_damping_width == 9999999.9 )  THEN
     895!
     896!--          Default for the transition range: one tenth of the undamped layer
     897             inflow_damping_width = 0.1 * inflow_damping_height
     898
     899          ENDIF
     900
     901          ALLOCATE( inflow_damping_factor(nzb:nzt+1) )
     902
     903          DO  k = nzb, nzt+1
     904
     905             IF ( zu(k) <= inflow_damping_height )  THEN
     906                inflow_damping_factor(k) = 1.0
     907             ELSEIF ( zu(k) <= inflow_damping_height + inflow_damping_width ) &
     908             THEN
     909                inflow_damping_factor(k) = 1.0 -                               &
     910                                           ( zu(k) - inflow_damping_height ) / &
     911                                           inflow_damping_width
     912             ELSE
     913                inflow_damping_factor(k) = 0.0
     914             ENDIF
     915
     916          ENDDO
     917
     918       ENDIF
     919
     920
     921!
     922!--    Read binary data from restart file
     923          WRITE (9,*) 'before read_3d_binary'
     924          CALL local_flush( 9 )
     925       CALL read_3d_binary
     926          WRITE (9,*) 'after read_3d_binary'
     927          CALL local_flush( 9 )
     928
     929!
     930!--    Calculate initial temperature field and other constants used in case
     931!--    of a sloping surface
     932       IF ( sloping_surface )  CALL init_slope
     933
     934!
     935!--    Initialize new time levels (only done in order to set boundary values
     936!--    including ghost points)
     937       e_p = e; pt_p = pt; u_p = u; v_p = v; w_p = w
     938       IF ( humidity  .OR.  passive_scalar )  q_p = q
     939       IF ( ocean )  sa_p = sa
     940
     941    ELSE
     942!
     943!--    Actually this part of the programm should not be reached
     944       IF ( myid == 0 )  PRINT*,'+++ init_3d_model: unknown initializing ', &
     945                                                    'problem'
     946       CALL local_stop
     947    ENDIF
     948
     949
     950    IF (  TRIM( initializing_actions ) /= 'read_restart_data' )  THEN
     951!
     952!--    Initialize old timelevels needed for radiation boundary conditions
     953       IF ( outflow_l )  THEN
     954          u_m_l(:,:,:) = u(:,:,1:2)
     955          v_m_l(:,:,:) = v(:,:,0:1)
     956          w_m_l(:,:,:) = w(:,:,0:1)
     957       ENDIF
     958       IF ( outflow_r )  THEN
     959          u_m_r(:,:,:) = u(:,:,nx-1:nx)
     960          v_m_r(:,:,:) = v(:,:,nx-1:nx)
     961          w_m_r(:,:,:) = w(:,:,nx-1:nx)
     962       ENDIF
     963       IF ( outflow_s )  THEN
     964          u_m_s(:,:,:) = u(:,0:1,:)
     965          v_m_s(:,:,:) = v(:,1:2,:)
     966          w_m_s(:,:,:) = w(:,0:1,:)
     967       ENDIF
     968       IF ( outflow_n )  THEN
     969          u_m_n(:,:,:) = u(:,ny-1:ny,:)
     970          v_m_n(:,:,:) = v(:,ny-1:ny,:)
     971          w_m_n(:,:,:) = w(:,ny-1:ny,:)
     972       ENDIF
     973
     974!
    757975!--    Calculate the initial volume flow at the right and north boundary
    758976       IF ( conserve_volume_flow )  THEN
     
    8001018       ENDIF
    8011019
    802 !
    803 !--    For the moment, perturbation pressure and vertical velocity are zero
    804        p = 0.0; w = 0.0
    805 
    806 !
    807 !--    Initialize array sums (must be defined in first call of pres)
    808        sums = 0.0
    809 
    810 !
    811 !--    Treating cloud physics, liquid water content and precipitation amount
    812 !--    are zero at beginning of the simulation
    813        IF ( cloud_physics )  THEN
    814           ql = 0.0
    815           IF ( precipitation )  precipitation_amount = 0.0
    816        ENDIF
    817 
    818 !
    819 !--    Impose vortex with vertical axis on the initial velocity profile
    820        IF ( INDEX( initializing_actions, 'initialize_vortex' ) /= 0 )  THEN
    821           CALL init_rankine
    822        ENDIF
    823 
    824 !
    825 !--    Impose temperature anomaly (advection test only)
    826        IF ( INDEX( initializing_actions, 'initialize_ptanom' ) /= 0 )  THEN
    827           CALL init_pt_anomaly
    828        ENDIF
    829 
    830 !
    831 !--    If required, change the surface temperature at the start of the 3D run
    832        IF ( pt_surface_initial_change /= 0.0 )  THEN
    833           pt(nzb,:,:) = pt(nzb,:,:) + pt_surface_initial_change
    834        ENDIF
    835 
    836 !
    837 !--    If required, change the surface humidity/scalar at the start of the 3D
    838 !--    run
    839        IF ( ( humidity .OR. passive_scalar ) .AND. &
    840             q_surface_initial_change /= 0.0 )  THEN
    841           q(nzb,:,:) = q(nzb,:,:) + q_surface_initial_change
    842        ENDIF
    843 
    844 !
    845 !--    Initialize the random number generator (from numerical recipes)
    846        CALL random_function_ini
    847 
    848 !
    849 !--    Impose random perturbation on the horizontal velocity field and then
    850 !--    remove the divergences from the velocity field
    851        IF ( create_disturbances )  THEN
    852           CALL disturb_field( nzb_u_inner, tend, u )
    853           CALL disturb_field( nzb_v_inner, tend, v )
    854           n_sor = nsor_ini
    855           CALL pres
    856           n_sor = nsor
    857        ENDIF
    858 
    859 !
    860 !--    Once again set the perturbation pressure explicitly to zero in order to
    861 !--    assure that it does not generate any divergences in the first time step.
    862 !--    At t=0 the velocity field is free of divergence (as constructed above).
    863 !--    Divergences being created during a time step are not yet known and thus
    864 !--    cannot be corrected during the time step yet.
    865        p = 0.0
    866 
    867 !
    868 !--    Initialize old and new time levels.
    869        IF ( timestep_scheme(1:5) /= 'runge' )  THEN
    870           e_m = e; pt_m = pt; u_m = u; v_m = v; w_m = w; kh_m = kh; km_m = km
    871        ELSE
    872           te_m = 0.0; tpt_m = 0.0; tu_m = 0.0; tv_m = 0.0; tw_m = 0.0
    873        ENDIF
    874        e_p = e; pt_p = pt; u_p = u; v_p = v; w_p = w
    875 
    876        IF ( humidity  .OR.  passive_scalar )  THEN
    877           IF ( ASSOCIATED( q_m ) )  q_m = q
    878           IF ( timestep_scheme(1:5) == 'runge' )  tq_m = 0.0
    879           q_p = q
    880           IF ( humidity  .AND.  ASSOCIATED( vpt_m ) )  vpt_m = vpt
    881        ENDIF
    882 
    883        IF ( ocean )  THEN
    884           tsa_m = 0.0
    885           sa_p  = sa
    886        ENDIF
    887 
    888 !
    889 !--    Initialize old timelevels needed for radiation boundary conditions
    890        IF ( outflow_l )  THEN
    891           u_m_l(:,:,:) = u(:,:,1:2)
    892           v_m_l(:,:,:) = v(:,:,0:1)
    893           w_m_l(:,:,:) = w(:,:,0:1)
    894        ENDIF
    895        IF ( outflow_r )  THEN
    896           u_m_r(:,:,:) = u(:,:,nx-1:nx)
    897           v_m_r(:,:,:) = v(:,:,nx-1:nx)
    898           w_m_r(:,:,:) = w(:,:,nx-1:nx)
    899        ENDIF
    900        IF ( outflow_s )  THEN
    901           u_m_s(:,:,:) = u(:,0:1,:)
    902           v_m_s(:,:,:) = v(:,1:2,:)
    903           w_m_s(:,:,:) = w(:,0:1,:)
    904        ENDIF
    905        IF ( outflow_n )  THEN
    906           u_m_n(:,:,:) = u(:,ny-1:ny,:)
    907           v_m_n(:,:,:) = v(:,ny-1:ny,:)
    908           w_m_n(:,:,:) = w(:,ny-1:ny,:)
    909        ENDIF
    910 
    911     ELSEIF ( TRIM( initializing_actions ) == 'read_restart_data'  .OR.    &
    912              TRIM( initializing_actions ) == 'read_data_for_recycling' )  &
    913     THEN
    914 !
    915 !--    When reading data for initializing the recycling method, first read
    916 !--    some of the global variables from restart file
    917        IF ( TRIM( initializing_actions ) == 'read_data_for_recycling' )  THEN
    918           WRITE (9,*) 'before read_parts_of_var_list'
    919           CALL local_flush( 9 )
    920           CALL read_parts_of_var_list
    921           WRITE (9,*) 'after read_parts_of_var_list'
    922           CALL local_flush( 9 )
    923           CALL close_file( 13 )
    924        ENDIF
    925 
    926 !
    927 !--    Read binary data from restart file
    928           WRITE (9,*) 'before read_3d_binary'
    929           CALL local_flush( 9 )
    930        CALL read_3d_binary
    931           WRITE (9,*) 'after read_3d_binary'
    932           CALL local_flush( 9 )
    933 
    934 !
    935 !--    Calculate initial temperature field and other constants used in case
    936 !--    of a sloping surface
    937        IF ( sloping_surface )  CALL init_slope
    938 
    939 !
    940 !--    Initialize new time levels (only done in order to set boundary values
    941 !--    including ghost points)
    942        e_p = e; pt_p = pt; u_p = u; v_p = v; w_p = w
    943        IF ( humidity  .OR.  passive_scalar )  q_p = q
    944        IF ( ocean )  sa_p = sa
    945 
    946     ELSE
    947 !
    948 !--    Actually this part of the programm should not be reached
    949        IF ( myid == 0 )  PRINT*,'+++ init_3d_model: unknown initializing ', &
    950                                                     'problem'
    951        CALL local_stop
    9521020    ENDIF
    9531021
Note: See TracChangeset for help on using the changeset viewer.