Changeset da10dc8 in flexpart.git


Ignore:
Timestamp:
Oct 4, 2016, 10:09:55 AM (8 years ago)
Author:
Don Morton <Don.Morton@…>
Branches:
FPv9.3.1, FPv9.3.2, fp9.3.1-20161214-nc4, grib2nc4_repair
Children:
5cef1eb
Parents:
e4b7087 (diff), 9cdf8bd (diff)
Note: this is a merge changeset, the changes displayed below correspond to the merge itself.
Use the (diff) links above to see all the changes relative to each parent.
Message:

Merge branch 'fp9.3.1-fpdimcheck' into FPv9.3.1

Location:
flexpart_code
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • flexpart_code/fpmetbinary_mod.F90

    r496c607 r9cdf8bd  
    3131    USE com_mod
    3232    USE conv_mod
     33    USE par_mod, ONLY : nxmax, nymax, nzmax, nuvzmax, nwzmax
    3334
    3435    IMPLICIT NONE
     
    248249                                                  ! most com_mod variables.
    249250                                                  ! Should be 1 or 2
     251
     252        ! These are temporary variables, used in the LOAD option, for
     253        ! comparing against the current values in FLEXPART of nxmax, nymax, ...
     254        INTEGER :: temp_nxmax, temp_nymax, temp_nzmax, &
     255&                  temp_nuvzmax, temp_nwzmax
     256
    250257        CHARACTER(LEN=128) :: errmesg
    251258
    252259        if (op == 'DUMP') THEN
     260
     261            ! Write the compiled max dimensions from par_mod - these are
     262            ! not meant to be reassigned during a LOAD, but used as "header"
     263            ! information to provide the structure of arrays
     264            WRITE (iounit) nxmax, nymax, nzmax, nuvzmax, nwzmax
    253265
    254266            ! Scalar values
     
    390402        ELSE IF (op == 'LOAD') THEN
    391403
     404            ! Read the compiled max dimensions that were dumped from par_mod
     405            ! when creating the fp file, so that we can compare against
     406            ! current FLEXPART dimensions - they need to be the same, or else
     407            ! we abort.
     408            READ (iounit) temp_nxmax, temp_nymax, temp_nzmax, &
     409&                         temp_nuvzmax, temp_nwzmax
     410
     411
     412            IF ( (temp_nxmax == nxmax) .AND. (temp_nymax == nymax) .AND. &
     413&                   (temp_nzmax == nzmax) .AND. &
     414&                   (temp_nuvzmax == nuvzmax) .AND. &
     415&                   (temp_nwzmax == nwzmax) ) THEN
     416                CONTINUE
     417            ELSE
     418                PRINT *, 'Incompatible dimensions between fp file and current FLEXPART!'
     419                PRINT *, ''
     420                PRINT *, '                  FP file     Compiled FP'
     421                PRINT *, 'nxmax:     ', temp_nxmax, '    ', nxmax
     422                PRINT *, 'nymax:     ', temp_nymax, '    ', nymax
     423                PRINT *, 'nzmax:     ', temp_nzmax, '    ', nzmax
     424                PRINT *, 'nuvzmax:     ', temp_nuvzmax, '    ', nuvzmax
     425                PRINT *, 'nwzmax:     ', temp_nwzmax, '    ', nwzmax
     426                PRINT *, ''
     427                STOP
     428            END IF
     429
     430
    392431            ! Scalar values
    393432            READ(iounit) nx, ny, nxmin1, nymin1, nxfield
  • flexpart_code/class_vtable_mod.F90

    r496c607 r7e6dc50  
    188188        ! Allocate array for storing the vtable records, and store
    189189        ! num_entries
    190         print *, 'Ready to allocate the_vtable_data'
     190        !print *, 'Ready to allocate the_vtable_data'
    191191        allocate(the_vtable_data%the_entries(num_vrecs))
    192         print *, 'Allocated the_vtable_data'
     192        !print *, 'Allocated the_vtable_data'
    193193        the_vtable_data%num_entries = num_vrecs
    194194
  • flexpart_code/gridcheck.F90

    r496c607 r7e6dc50  
    155155    !!!!!!! Vtable choice
    156156    gribfile_name = path(3)(1:length(3))//trim(wfname(ifn))
    157     print *, 'gribfile_name: ', gribfile_name
     157    !print *, 'gribfile_name: ', gribfile_name
    158158
    159159    gribfile_type = vtable_detect_gribfile_type( gribfile_name )
    160160
    161     print *, 'gribfile_type: ', gribfile_type
     161    !print *, 'gribfile_type: ', gribfile_type
    162162
    163163    if (gribfile_type .eq. VTABLE_GRIBFILE_TYPE_ECMWF_GRIB1) then
     
    174174
    175175    ! Load the Vtable into 'my_vtable'
    176     print *, 'Loading Vtable: ', vtable_path
     176    !print *, 'Loading Vtable: ', vtable_path
    177177    call vtable_load_by_name(vtable_path, my_vtable)
    178     print *, 'Vtable Initialized: ', my_vtable%initialized
    179     print *, 'Vtable num_entries: ', my_vtable%num_entries
     178    !print *, 'Vtable Initialized: ', my_vtable%initialized
     179    !print *, 'Vtable num_entries: ', my_vtable%num_entries
    180180    !!!!!!!!!!!!!!!!!!!  VTABLE code
    181181    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
  • flexpart_code/readwind.F90

    r496c607 r7e6dc50  
    224224    !!!!!!! Vtable choice
    225225    gribfile_name = path(3)(1:length(3))//trim(wfname(indj))
    226     print *, 'gribfile_name: ', gribfile_name
     226    !print *, 'gribfile_name: ', gribfile_name
    227227
    228228    gribfile_type = vtable_detect_gribfile_type( gribfile_name )
    229229
    230     print *, 'gribfile_type: ', gribfile_type
     230    !print *, 'gribfile_type: ', gribfile_type
    231231
    232232    if (gribfile_type .eq. VTABLE_GRIBFILE_TYPE_ECMWF_GRIB1) then
     
    243243
    244244    ! Load the Vtable into 'my_vtable'
    245     print *, 'Loading Vtable: ', vtable_path
     245    !print *, 'Loading Vtable: ', vtable_path
    246246    call vtable_load_by_name(vtable_path, my_vtable)
    247     print *, 'Vtable Initialized: ', my_vtable%initialized
    248     print *, 'Vtable num_entries: ', my_vtable%num_entries
     247    !print *, 'Vtable Initialized: ', my_vtable%initialized
     248    !print *, 'Vtable num_entries: ', my_vtable%num_entries
    249249    !!!!!!!!!!!!!!!!!!!  VTABLE code
    250250    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG