Ignore:
Timestamp:
Apr 5, 2016 7:44:00 PM (8 years ago)
Author:
raasch
Message:

preprocessor directives using machine dependent flags (lc, ibm, etc.) mostly removed from the code

File:
1 edited

Legend:

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

    r1789 r1808  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! test output removed
    2222!
    2323! Former revisions:
     
    288288         
    289289       IF ( j > 0 )  overlap_count(files_to_be_opened) = j
    290 
    291 !
    292 !--    Test output, to be removed later
    293        IF ( j > 0 )  THEN
    294           WRITE (9,*) '*** reading from file: ', i, j, ' times'
    295           WRITE (9,*) '    nxl = ', nxl, ' nxr = ', nxr, ' nys = ', &
    296                                     nys, ' nyn = ', nyn
    297           WRITE (9,*) ' '
    298           DO  k = 1, j
    299              WRITE (9,*) 'k = ', k
    300              WRITE (9,'(6(A,I4))') 'nxlfa = ', nxlfa(files_to_be_opened,k),&
    301                      ' nxrfa = ', nxrfa(files_to_be_opened,k), &
    302                      ' offset_xa = ', offset_xa(files_to_be_opened,k), &
    303                      ' nysfa = ', nysfa(files_to_be_opened,k), &
    304                      ' nynfa = ', nynfa(files_to_be_opened,k), &
    305                      ' offset_ya = ', offset_ya(files_to_be_opened,k)
    306           ENDDO
    307           CALL local_flush( 9 )
    308        ENDIF
    309 
    310290         
    311291    ENDDO
     
    314294!-- Save the id-string of the current process, since myid_char may now be used
    315295!-- to open files created by PEs with other id.
    316           myid_char_save = myid_char
    317 
    318 !
    319 !-- Test output (remove later)
    320          
    321     DO i = 1, numprocs_previous_run
    322        WRITE (9,*) 'i=',i-1, ' ibs= ',hor_index_bounds_previous_run(1:4,i-1)
    323     ENDDO
    324     CALL local_flush( 9 )
     296    myid_char_save = myid_char
    325297
    326298    IF ( files_to_be_opened /= 1  .OR.  numprocs /= numprocs_previous_run ) &
     
    340312!--    Set the filename (underscore followed by four digit processor id)
    341313       WRITE (myid_char,'(''_'',I6.6)')  j
    342        WRITE (9,*) 'myid=',myid,' opening file "',myid_char,'"'
    343        CALL local_flush( 9 )
    344314
    345315!
     
    348318!--    first.
    349319       CALL check_open( 13 )
    350        WRITE (9,*) 'before skipping'
    351        CALL local_flush( 9 )
    352320       IF ( j == 0 )  CALL skip_var_list
    353        WRITE (9,*) 'skipping done'
    354        CALL local_flush( 9 )
    355321
    356322!
     
    468434             nync = nynfa(i,k) + offset_ya(i,k)
    469435
    470 
    471              WRITE (9,*) 'var = ', field_chr
    472              CALL local_flush( 9 )
    473436
    474437             SELECT CASE ( TRIM( field_chr ) )
Note: See TracChangeset for help on using the changeset viewer.