Ignore:
Timestamp:
02/08/13 12:09:35 (11 years ago)
Author:
ymipsl
Message:

Some operations must be only done by the mpi master task.

YM

File:
1 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/trunk/src/metric.f90

    r21 r131  
    124124  CALL dist_cart(vertex_glo(3,1,1)%xyz,vertex_glo(4,1,1)%xyz,d3)  
    125125  CALL div_arc(vertex_glo(1,1,1)%xyz,vertex_glo(3,1,1)%xyz,0.5,p1) 
    126 !  CALL div_arc(vertex_glo(2,1,1)%xyz,vertex_glo(1,3,1)%xyz,1./3,p1) 
    127 !  CALL div_arc(vertex_glo(1,2,1)%xyz,vertex_glo(3,1,1)%xyz,1./3,p2) 
    128 !  CALL div_arc(vertex_glo(2,2,1)%xyz,vertex_glo(1,1,1)%xyz,1./3,p3) 
    129 !  PRINT *, "dist",d1 
    130 !  PRINT *, "dist",d2 
    131 !  PRINT *, "dist",d3 
    132 !  PRINT *,"dist",vertex_glo(2,1,1)%xyz 
    133 !  PRINT *,"dist",p1/sqrt(sum(p1**2)) 
     126 
    134127  CALL circumcenter(vertex_glo(1,1,1)%xyz,vertex_glo(2,1,1)%xyz,vertex_glo(1,2,1)%xyz,p1) 
    135128!  CALL Centroide(vertex_glo(1,2,1)%xyz,vertex_glo(2,1,1)%xyz,vertex_glo(1,1,1)%xyz,p1) 
     
    138131  CALL dist_cart(vertex_glo(2,1,1)%xyz,p1,d2)  
    139132  CALL dist_cart(vertex_glo(1,2,1)%xyz,p1,d3)  
    140 !  PRINT *, "dist",d1 
    141 !  PRINT *, "dist",d2 
    142 !  PRINT *, "dist",d3 
    143133 
    144134  END SUBROUTINE compute_face 
     
    337327          
    338328        ind=vertex_glo(i,j,nf)%ind 
    339         IF (ind==0) THEN 
    340           PRINT *,"ind=0",i,j,nf 
    341         ENDIF 
    342329        delta=MOD(vertex_glo(i,j,nf)%delta+neighbour+6,6) 
    343330        ind2=cell_glo(ind)%neighbour(delta) 
     
    758745    cell_glo(ind)%neighbour(3)=cell_glo(ind)%neighbour(2) 
    759746       
    760  
    761     ind=vertex_glo(1,jjm_glo,1)%ind 
    762     DO i=0,5 
    763       ind2=cell_glo(ind)%neighbour(i) 
    764       IF (ind2>0) PRINT *,"neighbour",i,cell_glo(ind2)%assign_face,cell_glo(ind2)%assign_i,cell_glo(ind2)%assign_j 
    765     ENDDO 
    766      
    767747     
    768748 !! assignation des delta  
Note: See TracChangeset for help on using the changeset viewer.