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

    r77 r82  
    117117!       WRITE (9,*) '--- advec_particles: #1'
    118118!       WRITE (9,*) '    #of p=',number_of_particles,' #of t=',number_of_tails
    119 !       CALL FLUSH_( 9 )
     119!       CALL local_flush( 9 )
    120120!    ENDIF
    121121!
     
    165165
    166166!    WRITE ( 9, * ) '*** advec_particles: ##0.3'
    167 !    CALL FLUSH_( 9 )
     167!    CALL local_flush( 9 )
    168168!    nd = 0
    169169!    DO  n = 1, number_of_particles
     
    172172!    IF ( nd /= deleted_particles ) THEN
    173173!       WRITE (9,*) '*** nd=',nd,' deleted_particles=',deleted_particles
    174 !       CALL FLUSH_( 9 )
     174!       CALL local_flush( 9 )
    175175!       CALL MPI_ABORT( comm2d, 9999, ierr )
    176176!    ENDIF
     
    18721872
    18731873!    WRITE ( 9, * ) '*** advec_particles: ##0.4'
    1874 !    CALL FLUSH_( 9 )
     1874!    CALL local_flush( 9 )
    18751875!    nd = 0
    18761876!    DO  n = 1, number_of_particles
     
    18791879!    IF ( nd /= deleted_particles ) THEN
    18801880!       WRITE (9,*) '*** nd=',nd,' deleted_particles=',deleted_particles
    1881 !       CALL FLUSH_( 9 )
     1881!       CALL local_flush( 9 )
    18821882!       CALL MPI_ABORT( comm2d, 9999, ierr )
    18831883!    ENDIF
     
    19041904             ELSE
    19051905!    WRITE ( 9, * ) '*** advec_particles: before allocate_prt_memory dt_prel'
    1906 !    CALL FLUSH_( 9 )
     1906!    CALL local_flush( 9 )
    19071907                CALL allocate_prt_memory( number_of_initial_particles )
    19081908!    WRITE ( 9, * ) '*** advec_particles: after allocate_prt_memory dt_prel'
    1909 !    CALL FLUSH_( 9 )
     1909!    CALL local_flush( 9 )
    19101910             ENDIF
    19111911          ENDIF
     
    19281928                ELSE
    19291929!    WRITE ( 9, * ) '*** advec_particles: before allocate_tail_memory dt_prel'
    1930 !    CALL FLUSH_( 9 )
     1930!    CALL local_flush( 9 )
    19311931                   CALL allocate_tail_memory( number_of_initial_tails )
    19321932!    WRITE ( 9, * ) '*** advec_particles: after allocate_tail_memory dt_prel'
    1933 !    CALL FLUSH_( 9 )
     1933!    CALL local_flush( 9 )
    19341934                ENDIF
    19351935             ENDIF
     
    20082008             ENDIF
    20092009!    WRITE ( 9, * ) '*** advec_particles: after setting the beginning of new tails'
    2010 !    CALL FLUSH_( 9 )
     2010!    CALL local_flush( 9 )
    20112011
    20122012             number_of_particles = number_of_particles + &
     
    20172017
    20182018!    WRITE ( 9, * ) '*** advec_particles: ##0.5'
    2019 !    CALL FLUSH_( 9 )
     2019!    CALL local_flush( 9 )
    20202020!    nd = 0
    20212021!    DO  n = 1, number_of_particles
     
    20242024!    IF ( nd /= deleted_particles ) THEN
    20252025!       WRITE (9,*) '*** nd=',nd,' deleted_particles=',deleted_particles
    2026 !       CALL FLUSH_( 9 )
     2026!       CALL local_flush( 9 )
    20272027!       CALL MPI_ABORT( comm2d, 9999, ierr )
    20282028!    ENDIF
     
    20312031!       WRITE (9,*) '--- advec_particles: #2'
    20322032!       WRITE (9,*) '    #of p=',number_of_particles,' #of t=',number_of_tails
    2033 !       CALL FLUSH_( 9 )
     2033!       CALL local_flush( 9 )
    20342034!    ENDIF
    20352035!    DO  n = 1, number_of_particles
     
    20382038!          WRITE (9,*) '+++ n=',n,' (of ',number_of_particles,')'
    20392039!          WRITE (9,*) '    id=',particles(n)%tail_id,' of (',number_of_tails,')'
    2040 !          CALL FLUSH_( 9 )
     2040!          CALL local_flush( 9 )
    20412041!          CALL MPI_ABORT( comm2d, 9999, ierr )
    20422042!       ENDIF
     
    21032103
    21042104!    WRITE ( 9, * ) '*** advec_particles: ##1'
    2105 !    CALL FLUSH_( 9 )
     2105!    CALL local_flush( 9 )
    21062106!    nd = 0
    21072107!    DO  n = 1, number_of_particles
     
    21112111!          WRITE (9,*) '+++ n=',n,' (of ',number_of_particles,')'
    21122112!          WRITE (9,*) '    id=',particles(n)%tail_id,' of (',number_of_tails,')'
    2113 !          CALL FLUSH_( 9 )
     2113!          CALL local_flush( 9 )
    21142114!          CALL MPI_ABORT( comm2d, 9999, ierr )
    21152115!       ENDIF
     
    21172117!    IF ( nd /= deleted_particles ) THEN
    21182118!       WRITE (9,*) '*** nd=',nd,' deleted_particles=',deleted_particles
    2119 !       CALL FLUSH_( 9 )
     2119!       CALL local_flush( 9 )
    21202120!       CALL MPI_ABORT( comm2d, 9999, ierr )
    21212121!    ENDIF
     
    22742274
    22752275!    WRITE ( 9, * ) '*** advec_particles: ##2'
    2276 !    CALL FLUSH_( 9 )
     2276!    CALL local_flush( 9 )
    22772277!    nd = 0
    22782278!    DO  n = 1, number_of_particles
     
    22822282!          WRITE (9,*) '+++ n=',n,' (of ',number_of_particles,')'
    22832283!          WRITE (9,*) '    id=',particles(n)%tail_id,' of (',number_of_tails,')'
    2284 !          CALL FLUSH_( 9 )
     2284!          CALL local_flush( 9 )
    22852285!          CALL MPI_ABORT( comm2d, 9999, ierr )
    22862286!       ENDIF
     
    22882288!    IF ( nd /= deleted_particles ) THEN
    22892289!       WRITE (9,*) '*** nd=',nd,' deleted_particles=',deleted_particles
    2290 !       CALL FLUSH_( 9 )
     2290!       CALL local_flush( 9 )
    22912291!       CALL MPI_ABORT( comm2d, 9999, ierr )
    22922292!    ENDIF
     
    23132313             ELSE
    23142314!    WRITE ( 9, * ) '*** advec_particles: before allocate_prt_memory trrp'
    2315 !    CALL FLUSH_( 9 )
     2315!    CALL local_flush( 9 )
    23162316                CALL allocate_prt_memory( trrp_count_recv )
    23172317!    WRITE ( 9, * ) '*** advec_particles: after allocate_prt_memory trrp'
    2318 !    CALL FLUSH_( 9 )
     2318!    CALL local_flush( 9 )
    23192319             ENDIF
    23202320          ENDIF
     
    23412341                ELSE
    23422342!    WRITE ( 9, * ) '*** advec_particles: before allocate_tail_memory trrpt'
    2343 !    CALL FLUSH_( 9 )
     2343!    CALL local_flush( 9 )
    23442344                   CALL allocate_tail_memory( trrpt_count_recv )
    23452345!    WRITE ( 9, * ) '*** advec_particles: after allocate_tail_memory trrpt'
    2346 !    CALL FLUSH_( 9 )
     2346!    CALL local_flush( 9 )
    23472347                ENDIF
    23482348             ENDIF
     
    23702370!          WRITE (9,*) '--- advec_particles: #3'
    23712371!          WRITE (9,*) '    #of p=',number_of_particles,' #of t=',number_of_tails
    2372 !          CALL FLUSH_( 9 )
     2372!          CALL local_flush( 9 )
    23732373!       ENDIF
    23742374
     
    23902390             ELSE
    23912391!    WRITE ( 9, * ) '*** advec_particles: before allocate_prt_memory trlp'
    2392 !    CALL FLUSH_( 9 )
     2392!    CALL local_flush( 9 )
    23932393                CALL allocate_prt_memory( trlp_count_recv )
    23942394!    WRITE ( 9, * ) '*** advec_particles: after allocate_prt_memory trlp'
    2395 !    CALL FLUSH_( 9 )
     2395!    CALL local_flush( 9 )
    23962396             ENDIF
    23972397          ENDIF
     
    24182418                ELSE
    24192419!    WRITE ( 9, * ) '*** advec_particles: before allocate_tail_memory trlpt'
    2420 !    CALL FLUSH_( 9 )
     2420!    CALL local_flush( 9 )
    24212421                   CALL allocate_tail_memory( trlpt_count_recv )
    24222422!    WRITE ( 9, * ) '*** advec_particles: after allocate_tail_memory trlpt'
    2423 !    CALL FLUSH_( 9 )
     2423!    CALL local_flush( 9 )
    24242424                ENDIF
    24252425             ENDIF
     
    24472447!          WRITE (9,*) '--- advec_particles: #4'
    24482448!          WRITE (9,*) '    #of p=',number_of_particles,' #of t=',number_of_tails
    2449 !          CALL FLUSH_( 9 )
     2449!          CALL local_flush( 9 )
    24502450!       ENDIF
    24512451
     
    24602460
    24612461!    WRITE ( 9, * ) '*** advec_particles: ##3'
    2462 !    CALL FLUSH_( 9 )
     2462!    CALL local_flush( 9 )
    24632463!    nd = 0
    24642464!    DO  n = 1, number_of_particles
     
    24682468!          WRITE (9,*) '+++ n=',n,' (of ',number_of_particles,')'
    24692469!          WRITE (9,*) '    id=',particles(n)%tail_id,' of (',number_of_tails,')'
    2470 !          CALL FLUSH_( 9 )
     2470!          CALL local_flush( 9 )
    24712471!          CALL MPI_ABORT( comm2d, 9999, ierr )
    24722472!       ENDIF
     
    24742474!    IF ( nd /= deleted_particles ) THEN
    24752475!       WRITE (9,*) '*** nd=',nd,' deleted_particles=',deleted_particles
    2476 !       CALL FLUSH_( 9 )
     2476!       CALL local_flush( 9 )
    24772477!       CALL MPI_ABORT( comm2d, 9999, ierr )
    24782478!    ENDIF
     
    25382538
    25392539!    WRITE ( 9, * ) '*** advec_particles: ##4'
    2540 !    CALL FLUSH_( 9 )
     2540!    CALL local_flush( 9 )
    25412541!    nd = 0
    25422542!    DO  n = 1, number_of_particles
     
    25462546!          WRITE (9,*) '+++ n=',n,' (of ',number_of_particles,')'
    25472547!          WRITE (9,*) '    id=',particles(n)%tail_id,' of (',number_of_tails,')'
    2548 !          CALL FLUSH_( 9 )
     2548!          CALL local_flush( 9 )
    25492549!          CALL MPI_ABORT( comm2d, 9999, ierr )
    25502550!       ENDIF
     
    25522552!    IF ( nd /= deleted_particles ) THEN
    25532553!       WRITE (9,*) '*** nd=',nd,' deleted_particles=',deleted_particles
    2554 !       CALL FLUSH_( 9 )
     2554!       CALL local_flush( 9 )
    25552555!       CALL MPI_ABORT( comm2d, 9999, ierr )
    25562556!    ENDIF
     
    27152715
    27162716!    WRITE ( 9, * ) '*** advec_particles: ##5'
    2717 !    CALL FLUSH_( 9 )
     2717!    CALL local_flush( 9 )
    27182718!    nd = 0
    27192719!    DO  n = 1, number_of_particles
     
    27232723!          WRITE (9,*) '+++ n=',n,' (of ',number_of_particles,')'
    27242724!          WRITE (9,*) '    id=',particles(n)%tail_id,' of (',number_of_tails,')'
    2725 !          CALL FLUSH_( 9 )
     2725!          CALL local_flush( 9 )
    27262726!          CALL MPI_ABORT( comm2d, 9999, ierr )
    27272727!       ENDIF
     
    27292729!    IF ( nd /= deleted_particles ) THEN
    27302730!       WRITE (9,*) '*** nd=',nd,' deleted_particles=',deleted_particles
    2731 !       CALL FLUSH_( 9 )
     2731!       CALL local_flush( 9 )
    27322732!       CALL MPI_ABORT( comm2d, 9999, ierr )
    27332733!    ENDIF
     
    27542754             ELSE
    27552755!    WRITE ( 9, * ) '*** advec_particles: before allocate_prt_memory trnp'
    2756 !    CALL FLUSH_( 9 )
     2756!    CALL local_flush( 9 )
    27572757                CALL allocate_prt_memory( trnp_count_recv )
    27582758!    WRITE ( 9, * ) '*** advec_particles: after allocate_prt_memory trnp'
    2759 !    CALL FLUSH_( 9 )
     2759!    CALL local_flush( 9 )
    27602760             ENDIF
    27612761          ENDIF
     
    27822782                ELSE
    27832783!    WRITE ( 9, * ) '*** advec_particles: before allocate_tail_memory trnpt'
    2784 !    CALL FLUSH_( 9 )
     2784!    CALL local_flush( 9 )
    27852785                   CALL allocate_tail_memory( trnpt_count_recv )
    27862786!    WRITE ( 9, * ) '*** advec_particles: after allocate_tail_memory trnpt'
    2787 !    CALL FLUSH_( 9 )
     2787!    CALL local_flush( 9 )
    27882788                ENDIF
    27892789             ENDIF
     
    28112811!          WRITE (9,*) '--- advec_particles: #5'
    28122812!          WRITE (9,*) '    #of p=',number_of_particles,' #of t=',number_of_tails
    2813 !          CALL FLUSH_( 9 )
     2813!          CALL local_flush( 9 )
    28142814!       ENDIF
    28152815
     
    28312831             ELSE
    28322832!    WRITE ( 9, * ) '*** advec_particles: before allocate_prt_memory trsp'
    2833 !    CALL FLUSH_( 9 )
     2833!    CALL local_flush( 9 )
    28342834                CALL allocate_prt_memory( trsp_count_recv )
    28352835!    WRITE ( 9, * ) '*** advec_particles: after allocate_prt_memory trsp'
    2836 !    CALL FLUSH_( 9 )
     2836!    CALL local_flush( 9 )
    28372837             ENDIF
    28382838          ENDIF
     
    28592859                ELSE
    28602860!    WRITE ( 9, * ) '*** advec_particles: before allocate_tail_memory trspt'
    2861 !    CALL FLUSH_( 9 )
     2861!    CALL local_flush( 9 )
    28622862                   CALL allocate_tail_memory( trspt_count_recv )
    28632863!    WRITE ( 9, * ) '*** advec_particles: after allocate_tail_memory trspt'
    2864 !    CALL FLUSH_( 9 )
     2864!    CALL local_flush( 9 )
    28652865                ENDIF
    28662866             ENDIF
     
    28882888!          WRITE (9,*) '--- advec_particles: #6'
    28892889!          WRITE (9,*) '    #of p=',number_of_particles,' #of t=',number_of_tails
    2890 !          CALL FLUSH_( 9 )
     2890!          CALL local_flush( 9 )
    28912891!       ENDIF
    28922892
     
    29012901
    29022902!    WRITE ( 9, * ) '*** advec_particles: ##6'
    2903 !    CALL FLUSH_( 9 )
     2903!    CALL local_flush( 9 )
    29042904!    nd = 0
    29052905!    DO  n = 1, number_of_particles
     
    29092909!          WRITE (9,*) '+++ n=',n,' (of ',number_of_particles,')'
    29102910!          WRITE (9,*) '    id=',particles(n)%tail_id,' of (',number_of_tails,')'
    2911 !          CALL FLUSH_( 9 )
     2911!          CALL local_flush( 9 )
    29122912!          CALL MPI_ABORT( comm2d, 9999, ierr )
    29132913!       ENDIF
     
    29152915!    IF ( nd /= deleted_particles ) THEN
    29162916!       WRITE (9,*) '*** nd=',nd,' deleted_particles=',deleted_particles
    2917 !       CALL FLUSH_( 9 )
     2917!       CALL local_flush( 9 )
    29182918!       CALL MPI_ABORT( comm2d, 9999, ierr )
    29192919!    ENDIF
     
    31333133
    31343134!    WRITE ( 9, * ) '*** advec_particles: ##7'
    3135 !    CALL FLUSH_( 9 )
     3135!    CALL local_flush( 9 )
    31363136!    nd = 0
    31373137!    DO  n = 1, number_of_particles
     
    31413141!          WRITE (9,*) '+++ n=',n,' (of ',number_of_particles,')'
    31423142!          WRITE (9,*) '    id=',particles(n)%tail_id,' of (',number_of_tails,')'
    3143 !          CALL FLUSH_( 9 )
     3143!          CALL local_flush( 9 )
    31443144!          CALL MPI_ABORT( comm2d, 9999, ierr )
    31453145!       ENDIF
     
    31473147!    IF ( nd /= deleted_particles ) THEN
    31483148!       WRITE (9,*) '*** nd=',nd,' deleted_particles=',deleted_particles
    3149 !       CALL FLUSH_( 9 )
     3149!       CALL local_flush( 9 )
    31503150!       CALL MPI_ABORT( comm2d, 9999, ierr )
    31513151!    ENDIF
     
    31673167!       IF ( nd /= deleted_particles ) THEN
    31683168!          WRITE (9,*) '*** advec_part nd=',nd,' deleted_particles=',deleted_particles
    3169 !          CALL FLUSH_( 9 )
     3169!          CALL local_flush( 9 )
    31703170!          CALL MPI_ABORT( comm2d, 9999, ierr )
    31713171!       ENDIF
     
    31893189!                WRITE (9,*) '+++ n=',n,' (of ',number_of_tails,' #oftails)'
    31903190!                WRITE (9,*) '    id=',new_tail_id(n)
    3191 !                CALL FLUSH_( 9 )
     3191!                CALL local_flush( 9 )
    31923192                ENDIF
    31933193             ENDDO
     
    31963196!       IF ( nd /= deleted_tails  .AND.  use_particle_tails ) THEN
    31973197!          WRITE (9,*) '*** advec_part nd=',nd,' deleted_tails=',deleted_tails
    3198 !          CALL FLUSH_( 9 )
     3198!          CALL local_flush( 9 )
    31993199!          CALL MPI_ABORT( comm2d, 9999, ierr )
    32003200!       ENDIF
     
    32113211!        WRITE (9,*) '    new_tail_id=', new_tail_id(particles(n)%tail_id), &
    32123212!                         ' of (',number_of_tails,')'
    3213 !        CALL FLUSH_( 9 )
     3213!        CALL local_flush( 9 )
    32143214!     ENDIF
    32153215                particles(n)%tail_id = new_tail_id(particles(n)%tail_id)
     
    32193219!     IF ( nn /= number_of_tails  .AND.  use_particle_tails ) THEN
    32203220!        WRITE (9,*) '*** advec_part #of_tails=',number_of_tails,' nn=',nn
    3221 !        CALL FLUSH_( 9 )
     3221!        CALL local_flush( 9 )
    32223222!        DO  n = 1, number_of_particles
    32233223!           WRITE (9,*) 'prt# ',n,' tail_id=',particles(n)%tail_id, &
     
    32333233!       WRITE (9,*) '--- advec_particles: #7'
    32343234!       WRITE (9,*) '    #of p=',number_of_particles,' #of t=',number_of_tails
    3235 !       CALL FLUSH_( 9 )
     3235!       CALL local_flush( 9 )
    32363236!    ENDIF
    32373237!    WRITE ( 9, * ) '*** advec_particles: ##8'
    3238 !    CALL FLUSH_( 9 )
     3238!    CALL local_flush( 9 )
    32393239!    DO  n = 1, number_of_particles
    32403240!       IF ( particles(n)%tail_id<0 .OR. particles(n)%tail_id>number_of_tails ) &
     
    32423242!          WRITE (9,*) '+++ n=',n,' (of ',number_of_particles,')'
    32433243!          WRITE (9,*) '    id=',particles(n)%tail_id,' of (',number_of_tails,')'
    3244 !          CALL FLUSH_( 9 )
     3244!          CALL local_flush( 9 )
    32453245!          CALL MPI_ABORT( comm2d, 9999, ierr )
    32463246!       ENDIF
     
    32523252
    32533253!    WRITE ( 9, * ) '*** advec_particles: ##9'
    3254 !    CALL FLUSH_( 9 )
     3254!    CALL local_flush( 9 )
    32553255!    DO  n = 1, number_of_particles
    32563256!       IF ( particles(n)%tail_id<0 .OR. particles(n)%tail_id>number_of_tails ) &
     
    32583258!          WRITE (9,*) '+++ n=',n,' (of ',number_of_particles,')'
    32593259!          WRITE (9,*) '    id=',particles(n)%tail_id,' of (',number_of_tails,')'
    3260 !          CALL FLUSH_( 9 )
     3260!          CALL local_flush( 9 )
    32613261!          CALL MPI_ABORT( comm2d, 9999, ierr )
    32623262!       ENDIF
     
    33413341    CALL user_particle_attributes
    33423342!    WRITE ( 9, * ) '*** advec_particles: ##10'
    3343 !    CALL FLUSH_( 9 )
     3343!    CALL local_flush( 9 )
    33443344!    DO  n = 1, number_of_particles
    33453345!       IF ( particles(n)%tail_id<0 .OR. particles(n)%tail_id>number_of_tails ) &
     
    33473347!          WRITE (9,*) '+++ n=',n,' (of ',number_of_particles,')'
    33483348!          WRITE (9,*) '    id=',particles(n)%tail_id,' of (',number_of_tails,')'
    3349 !          CALL FLUSH_( 9 )
     3349!          CALL local_flush( 9 )
    33503350!          CALL MPI_ABORT( comm2d, 9999, ierr )
    33513351!       ENDIF
     
    33663366!--          next tailpoint
    33673367!             WRITE ( 9, * ) '*** advec_particles: ##10.1  nn=',nn
    3368 !             CALL FLUSH_( 9 )
     3368!             CALL local_flush( 9 )
    33693369             IF ( minimum_tailpoint_distance /= 0.0 )  THEN
    33703370                distance = ( particle_tail_coordinates(1,1,nn) -      &
     
    33763376             ENDIF
    33773377!             WRITE ( 9, * ) '*** advec_particles: ##10.2'
    3378 !             CALL FLUSH_( 9 )
     3378!             CALL local_flush( 9 )
    33793379!
    33803380!--          First, increase the index of all existings tailpoints by one
     
    33953395             ENDIF
    33963396!             WRITE ( 9, * ) '*** advec_particles: ##10.3'
    3397 !             CALL FLUSH_( 9 )
     3397!             CALL local_flush( 9 )
    33983398!
    33993399!--          In any case, store the new point at the beginning of the tail
     
    34033403             particle_tail_coordinates(1,4,nn) = particles(n)%color
    34043404!             WRITE ( 9, * ) '*** advec_particles: ##10.4'
    3405 !             CALL FLUSH_( 9 )
     3405!             CALL local_flush( 9 )
    34063406!
    34073407!--          Increase the age of the tailpoints
     
    34183418             ENDIF
    34193419!             WRITE ( 9, * ) '*** advec_particles: ##10.5'
    3420 !             CALL FLUSH_( 9 )
     3420!             CALL local_flush( 9 )
    34213421
    34223422          ENDIF
     
    34263426    ENDIF
    34273427!    WRITE ( 9, * ) '*** advec_particles: ##11'
    3428 !    CALL FLUSH_( 9 )
     3428!    CALL local_flush( 9 )
    34293429
    34303430!
     
    35333533    ENDIF
    35343534    WRITE (9,*) '*** Request: ',new_maximum_number,' new_maximum_number(tails)'
    3535 !    CALL FLUSH_( 9 )
     3535!    CALL local_flush( 9 )
    35363536
    35373537    tmp_tail(:,:,1:number_of_tails)  = &
Note: See TracChangeset for help on using the changeset viewer.