Ignore:
Timestamp:
Oct 29, 2013 1:21:31 PM (10 years ago)
Author:
heinze
Message:

Undoing commit 1239

File:
1 edited

Legend:

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

    r1239 r1240  
    2020! Current revisions:
    2121! -----------------
    22 ! profiles of ug and vg added
    23 ! checks for nudging and large scale forcing from external file
     22!
    2423!
    2524! Former revisions:
     
    312311    USE statistics
    313312    USE subsidence_mod
    314     USE statistics
    315313    USE transpose_indices
    316314
     
    16081606    ENDIF
    16091607
    1610     IF (myid == 0 )THEN
    1611       PRINT*, "vorher surface_heatflux: ", surface_heatflux
    1612     END IF
    1613 
    1614     IF ( surface_heatflux == 9999999.9  .AND.  .NOT. large_scale_forcing )  THEN
    1615         constant_heatflux     = .FALSE.
    1616     ELSE
    1617         constant_heatflux     = .TRUE.
    1618         IF ( TRIM( initializing_actions ) /= 'read_restart_data' ) THEN
    1619            surface_heatflux      = shf_surf(1)
    1620         ENDIF
    1621     ENDIF
    1622 
    1623     IF (myid == 0 )THEN
    1624       PRINT*, "nachher surface_heatflux: ", surface_heatflux
    1625     END IF
    1626 
     1608    IF ( surface_heatflux == 9999999.9 )  constant_heatflux     = .FALSE.
    16271609    IF ( top_heatflux     == 9999999.9 )  constant_top_heatflux = .FALSE.
    16281610
     
    17441726       ENDIF
    17451727
    1746        IF ( surface_waterflux == 9999999.9  .AND.  &
    1747                              .NOT. large_scale_forcing )  THEN
    1748            constant_waterflux     = .FALSE.
    1749        ELSE
    1750            constant_waterflux     = .TRUE.
    1751            IF ( TRIM( initializing_actions ) /= 'read_restart_data' ) THEN
    1752               surface_waterflux      = qsws_surf(1)
    1753            ENDIF
    1754        ENDIF
     1728       IF ( surface_waterflux == 9999999.9 )  constant_waterflux = .FALSE.
    17551729
    17561730!
     
    26922666             ENDIF
    26932667
    2694           CASE ( 'ug' )
    2695              dopr_index(i) = 78
    2696              dopr_unit(i)  = 'm/s'
    2697              hom(:,2,78,:) = SPREAD( zu, 2, statistic_regions+1 )
    2698 
    2699           CASE ( 'vg' )
    2700              dopr_index(i) = 79
    2701              dopr_unit(i)  = 'm/s'
    2702              hom(:,2,79,:) = SPREAD( zu, 2, statistic_regions+1 )
    2703 
    27042668          CASE DEFAULT
    27052669
     
    36333597
    36343598!
    3635 !-- Check nudging and large scale forcing from external file
    3636     IF ( nudging .AND. ( .NOT. large_scale_forcing ) )  THEN
    3637        message_string = 'Nudging requires large_scale_forcing = .T.. &'// &
    3638                         'Surface fluxes and geostrophic wind should be &'// &
    3639                         'prescribed in file LSF_DATA'
    3640        CALL message( 'check_parameters', 'PA0374', 1, 2, 0, 6, 0 )
    3641     ENDIF
    3642 
    3643     IF ( large_scale_forcing .AND. ( bc_lr /= 'cyclic'  .OR. &
    3644                                     bc_ns /= 'cyclic' ) )  THEN
    3645        message_string = 'Non-cyclic lateral boundaries do not allow for &' // &
    3646                         'the usage of large scale forcing from external file.'
    3647        CALL message( 'check_parameters', 'PA0375', 1, 2, 0, 6, 0 )
    3648      ENDIF
    3649 
    3650     IF ( large_scale_forcing .AND. ( .NOT. humidity ) )  THEN
    3651        message_string = 'The usage of large scale forcing from external &'//&
    3652                         'file LSF_DATA requires humidity = .T..'
    3653        CALL message( 'check_parameters', 'PA0376', 1, 2, 0, 6, 0 )
    3654      ENDIF
    3655 
    3656     IF ( large_scale_forcing .AND. topography /= 'flat' )  THEN
    3657        message_string = 'The usage of large scale forcing from external &'//&
    3658                         'file LSF_DATA is not implemented for non-flat topography'
    3659        CALL message( 'check_parameters', 'PA0377', 1, 2, 0, 6, 0 )
    3660     ENDIF
    3661 
    3662     IF ( large_scale_forcing .AND.  ocean  )  THEN
    3663        message_string = 'The usage of large scale forcing from external &'//&
    3664                         'file LSF_DATA is not implemented for ocean runs'
    3665        CALL message( 'check_parameters', 'PA0378', 1, 2, 0, 6, 0 )
    3666     ENDIF
    3667 !
    36683599!-- Check &userpar parameters
    36693600    CALL user_check_parameters
Note: See TracChangeset for help on using the changeset viewer.