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/netcdf.f90

    r960 r964  
    77! Current revisions:
    88! ------------------
    9 !
     9! rev 951 and 959 reformatted
    1010!
    1111! Former revisions:
     
    1414!
    1515! 959 2012-07-24 13:13:41Z hoffmann
    16 ! Bugfix in cross_profiles. It is not possible to arrange more than 100
     16! Bugfix in cross_profiles. It is not allowed to arrange more than 100
    1717! profiles with cross_profiles.
    1818!
     
    130130    INTEGER ::  av, cross_profiles_count, cross_profiles_maxi, delim, &
    131131                delim_old, file_id, i, id_last, id_x, id_y, id_z, j,  &
    132                 k, ns, ns_old, nz_old
     132                k, kk, ns, ns_old, nz_old
    133133
    134134    INTEGER, DIMENSION(1) ::  id_dim_time_old, id_dim_x_yz_old,  &
     
    31473147
    31483148!
    3149 !--       Write columns and rows of cross_profiles to netcdf header.
     3149!--       Write number of columns and rows of coordinate systems to be plotted
     3150!--       on one page to the netcdf header.
    31503151!--       This information can be used by palmplot.
    3151 
    31523152          nc_stat = NF90_PUT_ATT( id_set_pr, NF90_GLOBAL,                     &
    31533153                                  'no_rows',                                  &
     
    31613161
    31623162
    3163           cross_profiles_adj  = ADJUSTL( cross_profiles )
     3163          cross_profiles_adj  = ADJUSTL( cross_profiles )
    31643164          cross_profiles_numb = 999999
    31653165
    3166           k = 1
    3167 
    3168 !
    3169 !--       Each profile defined in cross_profiles is written to a array
    3170 !--       (cross_profiles_char). The number of its cross is assigned in a
    3171 !--       second array (cross_profiles_numb).
    3172 
    3173           DO  i = 1, crmax
    3174             IF ( TRIM( cross_profiles_adj(i) ) == ' ' )  EXIT
    3175             delim_old = 0
    3176             DO   j = 1, crmax
    3177               delim = INDEX( cross_profiles_adj(i)(delim_old+1:), ' ' )
    3178               IF (delim .EQ. 1)  EXIT
    3179               cross_profiles_char( MIN( crmax, k ) ) = cross_profiles_adj(i)  &
    3180                                        (delim_old+1:delim_old+delim-1)
    3181               cross_profiles_numb( MIN( crmax, k ) ) = i
    3182               k = k+1
    3183               cross_profiles_maxi  = i
    3184               delim_old = delim_old + delim
    3185             ENDDO
    3186           ENDDO
     3166!
     3167!--       Each profile defined in cross_profiles is written to an array
     3168!--       (cross_profiles_char). The number of the respective coordinate
     3169!--       system is assigned in a second array (cross_profiles_numb).
     3170          k = 1
     3171
     3172          DO  i = 1, crmax
     3173
     3174             IF ( TRIM( cross_profiles_adj(i) ) == ' ' )  EXIT
     3175             delim_old = 0
     3176
     3177             DO   j = 1, crmax
     3178                delim = INDEX( cross_profiles_adj(i)(delim_old+1:), ' ' )
     3179                IF ( delim == 1 )  EXIT
     3180                kk = MIN( crmax, k )
     3181                cross_profiles_char(kk) = cross_profiles_adj(i)(delim_old+1: &
     3182                                                              delim_old+delim-1)
     3183                cross_profiles_numb(kk) = i
     3184                k = k + 1
     3185                cross_profiles_maxi  = i
     3186                delim_old = delim_old + delim
     3187             ENDDO
     3188
     3189          ENDDO
    31873190
    31883191          cross_profiles_count = MIN( crmax, k-1 )
    3189          
    31903192!
    31913193!--       Check if all profiles defined in cross_profiles are defined in
    31923194!--       data_output_pr. If not, they will be skipped.
    3193 
     3195          cross_profiles_log = .FALSE.
     3196          message_string = ''
     3197
     3198          DO  i = 1, cross_profiles_count
     3199             DO  j = 1, dopr_n
     3200
     3201                IF ( TRIM(cross_profiles_char(i)) == TRIM(data_output_pr(j)) ) &
     3202                THEN
     3203                   EXIT
     3204                ENDIF
     3205
     3206                IF ( j == dopr_n )  THEN
     3207                   cross_profiles_numb(i) = 999999
     3208                   cross_profiles_log = .TRUE.
     3209                   message_string = TRIM( message_string ) // ', ' // &
     3210                                    TRIM( cross_profiles_char(i) )
     3211                ENDIF
     3212
     3213             ENDDO
     3214          ENDDO
     3215
     3216          IF ( cross_profiles_log )  THEN
     3217             message_string = TRIM( message_string ) // ' is/are not' // &
     3218                              ' defined in data_output_pr.'
     3219             CALL message( 'define_netcdf_header', 'PA0352', 0, 0, 0, 6, 0 )
     3220          ENDIF
     3221
     3222!
     3223!--       Check if all profiles defined in data_output_pr are defined in
     3224!--       cross_profiles. If not, they will be added to cross_profiles.
    31943225          cross_profiles_log = .FALSE.
    31953226          message_string = ' '
    31963227
    3197           DO  i = 1, cross_profiles_count
    3198             DO  j = 1, dopr_n
    3199               IF ( TRIM(cross_profiles_char(i) ) == TRIM(data_output_pr(j)) ) &
    3200                  EXIT
    3201               IF ( j == dopr_n)  THEN
    3202                 cross_profiles_numb(i) = 999999
    3203                 cross_profiles_log = .TRUE.
    3204                 message_string = TRIM(message_string) // ', ' //              &
    3205                                  TRIM(cross_profiles_char(i))
    3206               ENDIF
    3207             ENDDO
    3208           ENDDO
    3209 
    3210           IF (cross_profiles_log)  THEN
    3211             message_string = TRIM(message_string(2:)) // ' is/are not' //     &
    3212                              ' defined in data_output_pr.'
    3213             CALL message( 'define_netcdf_header', 'PA0352', 0, 0, 0, 6, 0 )
    3214           ENDIF
    3215 
    3216 !
    3217 !--       Check if all profiles defined in data_output_pr are defined in
    3218 !--       cross_profiles. If not, they will be added to cross_profiles.
    3219 
    3220           cross_profiles_log = .FALSE.
    3221           message_string = ' '
    3222 
    3223           DO  i = 1, dopr_n
    3224             DO  j = 1, cross_profiles_count
    3225               IF ( TRIM( cross_profiles_char(j) ) == TRIM( data_output_pr(i)) )&
    3226                  EXIT
    3227               IF ( j == cross_profiles_count )  THEN
    3228                 cross_profiles_count = cross_profiles_count + 1
    3229                 cross_profiles_maxi  = cross_profiles_maxi  + 1
    3230                 cross_profiles_char( MIN( crmax, cross_profiles_count ) ) =    &
     3228          DO  i = 1, dopr_n
     3229             DO  j = 1, cross_profiles_count
     3230
     3231                IF ( TRIM(cross_profiles_char(j)) == TRIM(data_output_pr(i))) &
     3232                THEN
     3233                   EXIT
     3234                ENDIF
     3235
     3236                IF ( j == cross_profiles_count )  THEN
     3237                   cross_profiles_count = cross_profiles_count + 1
     3238                   cross_profiles_maxi  = cross_profiles_maxi  + 1
     3239                   cross_profiles_char(MIN( crmax, cross_profiles_count )) =  &
    32313240                                                      TRIM( data_output_pr(i) )
    3232                 cross_profiles_numb( MIN( crmax, cross_profiles_count ) ) =    &
     3241                   cross_profiles_numb(MIN( crmax, cross_profiles_count )) =  &
    32333242                                                      cross_profiles_maxi
    3234                 cross_profiles_log = .TRUE.
    3235                 message_string = TRIM( message_string ) // ', '&
    3236                                          // TRIM( data_output_pr(i) )
    3237               ENDIF
    3238             ENDDO
    3239           ENDDO
    3240 
    3241           IF ( cross_profiles_log )  THEN
    3242             message_string = TRIM(message_string(2:)) //               &
    3243                              ' has/have been added to cross_profiles.'
    3244             CALL message( 'define_netcdf_header', 'PA0353', 0, 0, 0, 6, 0 )
    3245           ENDIF
    3246 
    3247           IF ( cross_profiles_count .ge. crmax )  THEN
    3248             message_string = 'It is not possible to arrange more than '&
    3249                              // '100 profiles with cross_profiles.'
    3250             CALL message( 'define_netcdf_header', 'PA0354', 0, 0, 0, 6, 0 )
    3251           ENDIF
     3243                   cross_profiles_log   = .TRUE.
     3244                   message_string = TRIM( message_string ) // ', ' // &
     3245                                    TRIM( data_output_pr(i) )
     3246                ENDIF
     3247
     3248             ENDDO
     3249          ENDDO
     3250
     3251          IF ( cross_profiles_log )  THEN
     3252             message_string = TRIM(message_string(2:)) // ' has/have been' //  &
     3253                              ' added to cross_profiles.'
     3254             CALL message( 'define_netcdf_header', 'PA0353', 0, 0, 0, 6, 0 )
     3255          ENDIF
     3256
     3257          IF ( cross_profiles_count >= crmax )  THEN
     3258             message_string = 'It is not allowed to arrange more than '&
     3259                              // '100 profiles with cross_profiles.'
     3260             CALL message( 'define_netcdf_header', 'PA0354', 0, 0, 0, 6, 0 )
     3261          ENDIF
    32523262
    32533263!
     
    32553265!--       used by palmplot. Each profile is separated by ",", each cross is
    32563266!--       separated by ";".
    3257 
    3258           char_cross_profiles = ';'
    3259           id_last = 1
    3260 
    3261           DO  i = 1, cross_profiles_count
    3262             IF ( cross_profiles_numb(i) /= 999999 )  THEN
    3263               IF ( TRIM( char_cross_profiles ) == ';' )  THEN
    3264                char_cross_profiles = TRIM( char_cross_profiles ) // &
    3265                                      TRIM( cross_profiles_char(i) )
    3266               ELSEIF ( id_last == cross_profiles_numb(i) )  THEN
    3267                 char_cross_profiles = TRIM( char_cross_profiles ) // &
    3268                                       ',' // TRIM( cross_profiles_char(i) )
    3269               ELSE
    3270                 char_cross_profiles = TRIM( char_cross_profiles ) // &
    3271                                       ';' // TRIM( cross_profiles_char(i) )
    3272               ENDIF
    3273               id_last = cross_profiles_numb(i)
    3274             ENDIF
    3275           ENDDO
    3276          
     3267          char_cross_profiles = ';'
     3268          id_last = 1
     3269
     3270          DO  i = 1, cross_profiles_count
     3271
     3272             IF ( cross_profiles_numb(i) /= 999999 )  THEN
     3273                IF ( TRIM( char_cross_profiles ) == ';' )  THEN
     3274                   char_cross_profiles = TRIM( char_cross_profiles ) // &
     3275                                         TRIM( cross_profiles_char(i) )
     3276                ELSEIF ( id_last == cross_profiles_numb(i) )  THEN
     3277                   char_cross_profiles = TRIM( char_cross_profiles ) // &
     3278                                         ',' // TRIM( cross_profiles_char(i) )
     3279                ELSE
     3280                   char_cross_profiles = TRIM( char_cross_profiles ) // &
     3281                                         ';' // TRIM( cross_profiles_char(i) )
     3282                ENDIF
     3283                id_last = cross_profiles_numb(i)
     3284             ENDIF
     3285
     3286          ENDDO
     3287
    32773288          char_cross_profiles = TRIM( char_cross_profiles ) // ';'
    32783289
    3279           nc_stat = NF90_PUT_ATT( id_set_pr, NF90_GLOBAL, 'cross_profiles',   &
     3290          nc_stat = NF90_PUT_ATT( id_set_pr, NF90_GLOBAL, 'cross_profiles',   &
    32803291                                  TRIM( char_cross_profiles ) )
    3281           CALL handle_netcdf_error( 'netcdf', 521 )
     3292          CALL handle_netcdf_error( 'netcdf', 521 )
    32823293
    32833294!
Note: See TracChangeset for help on using the changeset viewer.