Ignore:
Timestamp:
Apr 16, 2007 3:40:52 PM (17 years ago)
Author:
raasch
Message:

vorlaeufige Standalone-Version fuer Linux-Cluster

File:
1 edited

Legend:

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

    r77 r82  
    3232! Actual revisions:
    3333! -----------------
     34! Preprocessor strings for different linux clusters changed to "lc",
     35! routine local_flush is used for buffer flushing
    3436! TEST: write statements
    3537!
     
    8486
    8587    WRITE ( 9, * ) '*** myid=', myid, ' Anfang data_output_dvrp'
    86 #if defined( __ibm )
    87     CALL FLUSH_( 9 )
    88 #elif defined( __lcmuk )  ||  defined( __lctit )  ||  defined( __nec )
    89     CALL FLUSH( 9 )
    90 #endif
     88    CALL local_flush( 9 )
    9189    CALL cpu_log( log_point(27), 'data_output_dvrp', 'start' )
    9290
     
    104102          lock_steering_update = .TRUE.
    105103    WRITE ( 9, * ) '*** myid=', myid, ' data_output_dvrp: vor steering_update'
    106 #if defined( __ibm )
    107     CALL FLUSH_( 9 )
    108 #elif defined( __lcmuk )  ||  defined( __lctit )  ||  defined( __nec )
    109     CALL FLUSH( 9 )
    110 #endif
     104    CALL local_flush( 9 )
    111105          CALL DVRP_STEERING_UPDATE( m-1, data_output_dvrp )
    112106    WRITE ( 9, * ) '*** myid=', myid, ' data_output_dvrp: nach steering_update'
    113 #if defined( __ibm )
    114     CALL FLUSH_( 9 )
    115 #elif defined( __lcmuk )  ||  defined( __lctit )  ||  defined( __nec )
    116     CALL FLUSH( 9 )
    117 #endif
     107    CALL local_flush( 9 )
    118108          lock_steering_update = .FALSE.
    119109       ENDIF
     
    150140
    151141    WRITE ( 9, * ) '*** myid=', myid, ' data_output_dvrp: anfang particles'
    152 #if defined( __ibm )
    153     CALL FLUSH_( 9 )
    154 #elif defined( __lcmuk )  ||  defined( __lctit )  ||  defined( __nec )
    155     CALL FLUSH( 9 )
    156 #endif
     142    CALL local_flush( 9 )
    157143!
    158144!--       DVRP-Calls for plotting particles:
     
    183169             WRITE (9,*) '--- before ALLOCATE  simtime=',simulated_time,' #of_tails=', number_of_tails, &
    184170                           ' max#of_tp=', maximum_number_of_tailpoints
    185 #if defined( __ibm )
    186     CALL FLUSH_( 9 )
    187 #elif defined( __lcmuk )  ||  defined( __lctit )  ||  defined( __nec )
    188     CALL FLUSH( 9 )
    189 #endif
     171    CALL local_flush( 9 )
    190172             ALLOCATE( psize(number_of_tails), p_t(number_of_tails),      &
    191173                       p_c(number_of_tails*maximum_number_of_tailpoints), &
     
    194176                       p_z(number_of_tails*maximum_number_of_tailpoints) )
    195177             WRITE (9,*) '--- after ALLOCATE'
    196 #if defined( __ibm )
    197     CALL FLUSH_( 9 )
    198 #elif defined( __lcmuk )  ||  defined( __lctit )  ||  defined( __nec )
    199     CALL FLUSH( 9 )
    200 #endif
     178    CALL local_flush( 9 )
    201179             psize = 0.0;  p_t = 0;  p_c = 0.0;  p_x = 0.0;  p_y = 0.0
    202180             p_z   = 0.0;
     
    209187                   IF ( simulated_time > 1338.0 )  THEN
    210188                      WRITE (9,*) '--- particle ',n,' tail_id=',nn,' #of_tp=',particles(n)%tailpoints
    211 #if defined( __ibm )
    212     CALL FLUSH_( 9 )
    213 #elif defined( __lcmuk )  ||  defined( __lctit )  ||  defined( __nec )
    214     CALL FLUSH( 9 )
    215 #endif
     189    CALL local_flush( 9 )
    216190                   ENDIF
    217191                   DO  j = 1, particles(n)%tailpoints
     
    227201                         WRITE (9,*) '--- tp= ',i,' x=',p_x(i),' y=',p_y(i), &
    228202                                                 ' z=',p_z(i),' c=',p_c(i)
    229 #if defined( __ibm )
    230     CALL FLUSH_( 9 )
    231 #elif defined( __lcmuk )  ||  defined( __lctit )  ||  defined( __nec )
    232     CALL FLUSH( 9 )
    233 #endif
     203    CALL local_flush( 9 )
    234204                      ENDIF
    235205                   ENDDO
     
    238208                   IF ( simulated_time > 1338.0 )  THEN
    239209                      WRITE (9,*) '--- t= ',k,' psize=',psize(k),' p_t=',p_t(k)
    240 #if defined( __ibm )
    241     CALL FLUSH_( 9 )
    242 #elif defined( __lcmuk )  ||  defined( __lctit )  ||  defined( __nec )
    243     CALL FLUSH( 9 )
    244 #endif
     210    CALL local_flush( 9 )
    245211                   ENDIF
    246212                ENDIF               
    247213             ENDDO
    248214             WRITE (9,*) '--- after locally storing the particle attributes'
    249 #if defined( __ibm )
    250     CALL FLUSH_( 9 )
    251 #elif defined( __lcmuk )  ||  defined( __lctit )  ||  defined( __nec )
    252     CALL FLUSH( 9 )
    253 #endif
     215    CALL local_flush( 9 )
    254216          ENDIF
    255217
     
    275237             ELSE
    276238                WRITE (9,*) '--- before DVRP_PARTICLES'
    277 #if defined( __ibm )
    278     CALL FLUSH_( 9 )
    279 #elif defined( __lcmuk )  ||  defined( __lctit )  ||  defined( __nec )
    280     CALL FLUSH( 9 )
    281 #endif
     239    CALL local_flush( 9 )
    282240                CALL DVRP_PARTICLES( m-1, number_of_tails, p_x, p_y, p_z, 15, &
    283241                                     psize, p_c, p_t )
     
    292250                WRITE (9,*) 'p_t =', p_t
    293251
    294 #if defined( __ibm )
    295     CALL FLUSH_( 9 )
    296 #elif defined( __lcmuk )  ||  defined( __lctit )  ||  defined( __nec )
    297     CALL FLUSH( 9 )
    298 #endif
     252    CALL local_flush( 9 )
    299253             ENDIF
    300254          ENDIF
     
    302256          CALL DVRP_VISUALIZE( m-1, 3, dvrp_filecount )
    303257    WRITE ( 9, * ) '*** myid=', myid, ' data_output_dvrp: ende particles'
    304 #if defined( __ibm )
    305     CALL FLUSH_( 9 )
    306 #elif defined( __lcmuk )  ||  defined( __lctit )  ||  defined( __nec )
    307     CALL FLUSH( 9 )
    308 #endif
     258    CALL local_flush( 9 )
    309259
    310260          DEALLOCATE( psize, p_c, p_t, p_x, p_y, p_z )
     
    456406
    457407    WRITE ( 9, * ) '*** myid=', myid, ' data_output_dvrp: anfang isosurface'
    458 #if defined( __ibm )
    459     CALL FLUSH_( 9 )
    460 #elif defined( __lcmuk )  ||  defined( __lctit )  ||  defined( __nec )
    461     CALL FLUSH( 9 )
    462 #endif
     408    CALL local_flush( 9 )
    463409!
    464410!--          DVRP-Calls for plotting isosurfaces:
     
    481427             CALL DVRP_VISUALIZE( m-1, 1, dvrp_filecount )
    482428    WRITE ( 9, * ) '*** myid=', myid, ' data_output_dvrp: ende isosurface'
    483 #if defined( __ibm )
    484     CALL FLUSH_( 9 )
    485 #elif defined( __lcmuk )  ||  defined( __lctit )  ||  defined( __nec )
    486     CALL FLUSH( 9 )
    487 #endif
     429    CALL local_flush( 9 )
    488430
    489431             CALL cpu_log( log_point_s(26), 'dvrp_isosurface', 'stop' )
     
    492434
    493435    WRITE ( 9, * ) '*** myid=', myid, ' data_output_dvrp: anfang slicer'
    494 #if defined( __ibm )
    495     CALL FLUSH_( 9 )
    496 #elif defined( __lcmuk )  ||  defined( __lctit )  ||  defined( __nec )
    497     CALL FLUSH( 9 )
    498 #endif
     436    CALL local_flush( 9 )
    499437!
    500438!--          DVRP-Calls for plotting slicers:
     
    526464
    527465    WRITE ( 9, * ) '*** myid=', myid, ' data_output_dvrp: ende slicer'
    528 #if defined( __ibm )
    529     CALL FLUSH_( 9 )
    530 #elif defined( __lcmuk )  ||  defined( __lctit )  ||  defined( __nec )
    531     CALL FLUSH( 9 )
    532 #endif
     466    CALL local_flush( 9 )
    533467          ENDIF
    534468
     
    545479    CALL cpu_log( log_point(27), 'data_output_dvrp', 'stop' )
    546480    WRITE ( 9, * ) '*** myid=', myid, ' Ende data_output_dvrp'
    547 #if defined( __ibm )
    548     CALL FLUSH_( 9 )
    549 #elif defined( __lcmuk )  ||  defined( __lctit )  ||  defined( __nec )
    550     CALL FLUSH( 9 )
    551 #endif
     481    CALL local_flush( 9 )
    552482
    553483#endif
Note: See TracChangeset for help on using the changeset viewer.