Ignore:
Timestamp:
Jul 26, 2012 9:14:24 AM (12 years ago)
Author:
raasch
Message:

old profil-parameters (cross_xtext, cross_normalized_x, etc. ) and respective code removed
(check_open, check_parameters, close_file, data_output_profiles, data_output_spectra, header, modules, parin)

reformatting (netcdf)

append feature removed from unit 14 (check_open)

File:
1 edited

Legend:

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

    r941 r964  
    44! Current revisions:
    55! -----------------
    6 !
     6! check of old profil-parameters removed
    77!
    88! Former revisions:
     
    25182518       END SELECT
    25192519
    2520 !
    2521 !--    Check to which of the predefined coordinate systems the profile belongs
    2522        DO  k = 1, crmax
    2523           IF ( INDEX( cross_profiles(k), ' '//TRIM( data_output_pr(i) )//' ' ) &
    2524                /=0 ) &
    2525           THEN
    2526              dopr_crossindex(i) = k
    2527              EXIT
    2528           ENDIF
    2529        ENDDO
    2530 !
    2531 !--    Generate the text for the labels of the PROFIL output file. "-characters
    2532 !--    must be substituted, otherwise PROFIL would interpret them as TeX
    2533 !--    control characters
    2534        dopr_label(i) = data_output_pr(i)
    2535        position = INDEX( dopr_label(i) , '"' )
    2536        DO WHILE ( position /= 0 )
    2537           dopr_label(i)(position:position) = ''''
    2538           position = INDEX( dopr_label(i) , '"' )
    2539        ENDDO
    2540 
    25412520    ENDDO
    2542 
    2543 !
    2544 !-- y-value range of the coordinate system (PROFIL).
    2545 !-- x-value range determined in plot_1d.
    2546     IF ( .NOT. ocean )  THEN
    2547        cross_uymin = 0.0
    2548        IF ( z_max_do1d == -1.0 )  THEN
    2549           cross_uymax = zu(nzt+1)
    2550        ELSEIF ( z_max_do1d < zu(nzb+1)  .OR.  z_max_do1d > zu(nzt+1) )  THEN
    2551           WRITE( message_string, * )  'z_max_do1d = ', z_max_do1d, ' must ', &
    2552                  'be >= ', zu(nzb+1), ' or <= ', zu(nzt+1)
    2553           CALL message( 'check_parameters', 'PA0099', 1, 2, 0, 6, 0 )
    2554        ELSE
    2555           cross_uymax = z_max_do1d
    2556        ENDIF
    2557     ENDIF
    2558 
    2559 !
    2560 !-- Check whether the chosen normalizing factor for the coordinate systems is
    2561 !-- permissible
    2562     DO  i = 1, crmax
    2563        SELECT CASE ( TRIM( cross_normalized_x(i) ) )  ! TRIM required on IBM
    2564 
    2565           CASE ( '', 'wpt0', 'ws2', 'tsw2', 'ws3', 'ws2tsw', 'wstsw2' )
    2566              j = 0
    2567 
    2568           CASE DEFAULT
    2569              message_string = 'unknown normalization method cross_normali' // &
    2570                               'zed_x = "' // TRIM( cross_normalized_x(i) ) // &
    2571                               '"'
    2572              CALL message( 'check_parameters', 'PA0100', 1, 2, 0, 6, 0 )
    2573 
    2574        END SELECT
    2575        SELECT CASE ( TRIM( cross_normalized_y(i) ) )  ! TRIM required on IBM
    2576 
    2577           CASE ( '', 'z_i' )
    2578              j = 0
    2579 
    2580           CASE DEFAULT
    2581              message_string = 'unknown normalization method cross_normali' // &
    2582                               'zed_y = "' // TRIM( cross_normalized_y(i) ) // &
    2583                               '"'
    2584              CALL message( 'check_parameters', 'PA0101', 1, 2, 0, 6, 0 )
    2585 
    2586        END SELECT
    2587     ENDDO
    2588 !
    2589 !-- Check normalized y-value range of the coordinate system (PROFIL)
    2590     IF ( z_max_do1d_normalized /= -1.0  .AND.  z_max_do1d_normalized <= 0.0 ) &
    2591     THEN
    2592        WRITE( message_string, * )  'z_max_do1d_normalized = ', &
    2593                                    z_max_do1d_normalized, ' must be >= 0.0'
    2594        CALL message( 'check_parameters', 'PA0101', 1, 2, 0, 6, 0 )
    2595     ENDIF
    25962521
    25972522
     
    28642789
    28652790!
    2866 !-- Upper plot limit (grid point value) for 1D profiles
    2867     IF ( z_max_do1d == -1.0 )  THEN
    2868 
    2869        nz_do1d = nzt+1
    2870 
    2871     ELSE
    2872        DO  k = nzb+1, nzt+1
    2873           nz_do1d = k
    2874           IF ( zw(k) > z_max_do1d )  EXIT
    2875        ENDDO
    2876     ENDIF
    2877 
    2878 !
    28792791!-- Upper plot limit for 2D vertical sections
    28802792    IF ( z_max_do2d == -1.0 )  z_max_do2d = zu(nzt)
     
    29582870             CASE ( 'iso2d' )
    29592871                iso2d_output  = .TRUE.
    2960              CASE ( 'profil' )
    2961                 profil_output = .TRUE.
    29622872             CASE ( 'avs' )
    29632873                avs_output    = .TRUE.
Note: See TracChangeset for help on using the changeset viewer.