Ignore:
Timestamp:
May 28, 2009 12:13:56 PM (15 years ago)
Author:
letzel
Message:
  • initializing_actions='read_data_for_recycling' renamed to 'cyclic_fill', now independent of turbulent_inflow (check_parameters, header, init_3d_model)
File:
1 edited

Legend:

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

    r292 r328  
    77! Current revisions:
    88! -----------------
     9! initializing_actions='read_data_for_recycling' renamed to 'cyclic_fill', now
     10! independent of turbulent_inflow
    911! Output of messages replaced by message handling routine.
    1012! Set the starting level and the vertical smoothing factor used for
     
    397399!-- Initialize model variables
    398400    IF ( TRIM( initializing_actions ) /= 'read_restart_data'  .AND.  &
    399          TRIM( initializing_actions ) /= 'read_data_for_recycling' )  THEN
     401         TRIM( initializing_actions ) /= 'cyclic_fill' )  THEN
    400402!
    401403!--    First model run of a possible job queue.
     
    925927
    926928    ELSEIF ( TRIM( initializing_actions ) == 'read_restart_data'  .OR.    &
    927              TRIM( initializing_actions ) == 'read_data_for_recycling' )  &
     929             TRIM( initializing_actions ) == 'cyclic_fill' )  &
    928930    THEN
    929931!
    930 !--    When reading data for initializing the recycling method, first read
     932!--    When reading data for cyclic fill of 3D prerun data, first read
    931933!--    some of the global variables from restart file
    932        IF ( TRIM( initializing_actions ) == 'read_data_for_recycling' )  THEN
     934       IF ( TRIM( initializing_actions ) == 'cyclic_fill' )  THEN
    933935
    934936          WRITE (9,*) 'before read_parts_of_var_list'
     
    938940          CALL local_flush( 9 )
    939941          CALL close_file( 13 )
    940 !
    941 !--       Store temporally and horizontally averaged vertical profiles to be
    942 !--       used as mean inflow profiles
    943           ALLOCATE( mean_inflow_profiles(nzb:nzt+1,5) )
    944 
    945           mean_inflow_profiles(:,1) = hom_sum(:,1,0)    ! u
    946           mean_inflow_profiles(:,2) = hom_sum(:,2,0)    ! v
    947           mean_inflow_profiles(:,4) = hom_sum(:,4,0)    ! pt
    948           mean_inflow_profiles(:,5) = hom_sum(:,8,0)    ! e
    949 
    950 !
    951 !--       Use these mean profiles for the inflow (provided that Dirichlet
    952 !--       conditions are used)
    953           IF ( inflow_l )  THEN
    954              DO  j = nys-1, nyn+1
    955                 DO  k = nzb, nzt+1
    956                    u(k,j,-1)  = mean_inflow_profiles(k,1)
    957                    v(k,j,-1)  = mean_inflow_profiles(k,2)
    958                    w(k,j,-1)  = 0.0
    959                    pt(k,j,-1) = mean_inflow_profiles(k,4)
    960                    e(k,j,-1)  = mean_inflow_profiles(k,5)
    961                 ENDDO
    962              ENDDO
    963           ENDIF
    964 
    965 !
    966 !--       Calculate the damping factors to be used at the inflow. For a
    967 !--       turbulent inflow the turbulent fluctuations have to be limited
    968 !--       vertically because otherwise the turbulent inflow layer will grow
    969 !--       in time.
    970           IF ( inflow_damping_height == 9999999.9 )  THEN
    971 !
    972 !--          Default: use the inversion height calculated by the prerun; if
    973 !--          this is zero, inflow_damping_height must be explicitly specified.
    974              IF ( hom_sum(nzb+6,pr_palm,0) /= 0.0 )  THEN
    975                 inflow_damping_height = hom_sum(nzb+6,pr_palm,0)
    976              ELSE
    977                 WRITE( message_string, * ) 'inflow_damping_height must be ', &
    978                      'explicitly specified because&the inversion height ', &
    979                      'calculated by the prerun is zero.'
    980                 CALL message( 'init_3d_model', 'PA0318', 1, 2, 0, 6, 0 )
    981              ENDIF
    982 
    983           ENDIF
    984 
    985           IF ( inflow_damping_width == 9999999.9 )  THEN
    986 !
    987 !--          Default for the transition range: one tenth of the undamped layer
    988              inflow_damping_width = 0.1 * inflow_damping_height
    989 
    990           ENDIF
    991 
    992           ALLOCATE( inflow_damping_factor(nzb:nzt+1) )
    993 
    994           DO  k = nzb, nzt+1
    995 
    996              IF ( zu(k) <= inflow_damping_height )  THEN
    997                 inflow_damping_factor(k) = 1.0
    998              ELSEIF ( zu(k) <= inflow_damping_height + inflow_damping_width ) &
    999              THEN
    1000                 inflow_damping_factor(k) = 1.0 -                               &
     942
     943!
     944!--       Initialization of the turbulence recycling method
     945          IF ( turbulent_inflow )  THEN
     946!
     947!--          Store temporally and horizontally averaged vertical profiles to be
     948!--          used as mean inflow profiles
     949             ALLOCATE( mean_inflow_profiles(nzb:nzt+1,5) )
     950
     951             mean_inflow_profiles(:,1) = hom_sum(:,1,0)    ! u
     952             mean_inflow_profiles(:,2) = hom_sum(:,2,0)    ! v
     953             mean_inflow_profiles(:,4) = hom_sum(:,4,0)    ! pt
     954             mean_inflow_profiles(:,5) = hom_sum(:,8,0)    ! e
     955
     956!
     957!--          Use these mean profiles for the inflow (provided that Dirichlet
     958!--          conditions are used)
     959             IF ( inflow_l )  THEN
     960                DO  j = nys-1, nyn+1
     961                   DO  k = nzb, nzt+1
     962                      u(k,j,-1)  = mean_inflow_profiles(k,1)
     963                      v(k,j,-1)  = mean_inflow_profiles(k,2)
     964                      w(k,j,-1)  = 0.0
     965                      pt(k,j,-1) = mean_inflow_profiles(k,4)
     966                      e(k,j,-1)  = mean_inflow_profiles(k,5)
     967                   ENDDO
     968                ENDDO
     969             ENDIF
     970
     971!
     972!--          Calculate the damping factors to be used at the inflow. For a
     973!--          turbulent inflow the turbulent fluctuations have to be limited
     974!--          vertically because otherwise the turbulent inflow layer will grow
     975!--          in time.
     976             IF ( inflow_damping_height == 9999999.9 )  THEN
     977!
     978!--             Default: use the inversion height calculated by the prerun; if
     979!--             this is zero, inflow_damping_height must be explicitly
     980!--             specified.
     981                IF ( hom_sum(nzb+6,pr_palm,0) /= 0.0 )  THEN
     982                   inflow_damping_height = hom_sum(nzb+6,pr_palm,0)
     983                ELSE
     984                   WRITE( message_string, * ) 'inflow_damping_height must be ',&
     985                        'explicitly specified because&the inversion height ', &
     986                        'calculated by the prerun is zero.'
     987                   CALL message( 'init_3d_model', 'PA0318', 1, 2, 0, 6, 0 )
     988                ENDIF
     989
     990             ENDIF
     991
     992             IF ( inflow_damping_width == 9999999.9 )  THEN
     993!
     994!--             Default for the transition range: one tenth of the undamped
     995!--             layer
     996                inflow_damping_width = 0.1 * inflow_damping_height
     997
     998             ENDIF
     999
     1000             ALLOCATE( inflow_damping_factor(nzb:nzt+1) )
     1001
     1002             DO  k = nzb, nzt+1
     1003
     1004                IF ( zu(k) <= inflow_damping_height )  THEN
     1005                   inflow_damping_factor(k) = 1.0
     1006                ELSEIF ( zu(k) <= inflow_damping_height +  &
     1007                                  inflow_damping_width )  THEN
     1008                   inflow_damping_factor(k) = 1.0 -                            &
    10011009                                           ( zu(k) - inflow_damping_height ) / &
    10021010                                           inflow_damping_width
    1003              ELSE
    1004                 inflow_damping_factor(k) = 0.0
    1005              ENDIF
    1006 
    1007           ENDDO
     1011                ELSE
     1012                   inflow_damping_factor(k) = 0.0
     1013                ENDIF
     1014
     1015             ENDDO
     1016          ENDIF
    10081017
    10091018       ENDIF
     
    10201029!--    Calculate the initial volume flow at the right and north boundary
    10211030       IF ( conserve_volume_flow  .AND.  &
    1022             TRIM( initializing_actions ) == 'read_data_for_recycling' )  THEN
     1031            TRIM( initializing_actions ) == 'cyclic_fill' )  THEN
    10231032
    10241033          volume_flow_initial_l = 0.0
     
    10341043!
    10351044!--             Correction if velocity at nzb+1 has been set zero further above
     1045!--             Note: at present, u_nzb_p1_for_vfc is zero (maybe revise later)
    10361046                volume_flow_initial_l(1) = volume_flow_initial_l(1) + &
    10371047                                           u_nzb_p1_for_vfc(j)
     
    10481058!
    10491059!--             Correction if velocity at nzb+1 has been set zero further above
     1060!--             Note: at present, v_nzb_p1_for_vfc is zero (maybe revise later)
    10501061                volume_flow_initial_l(2) = volume_flow_initial_l(2) + &
    10511062                                           v_nzb_p1_for_vfc(i)
Note: See TracChangeset for help on using the changeset viewer.