Ignore:
Timestamp:
06/13/19 16:45:41 (5 years ago)
Author:
adurocher
Message:

trunk : Fixed GCC warnings

Fixed iso c bindings
fixed warnings with -Wall -Wno-aliasing -Wno-unused -Wno-unused-dummy-argument -Wno-maybe-uninitialized -Wno-tabs warnings
Removed all unused variables (-Wunused-variable)
vector%dot_product is now dot_product_3d to avoid compilation warning "dot_product shadows intrinsic" with GCC

File:
1 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/trunk/src/parallel/transfert_mpi.f90

    r711 r899  
    100100  IMPLICIT NONE 
    101101  INTEGER :: ind,i,j 
    102   LOGICAL ::ok 
    103102 
    104103    CALL register_id('MPI', id_mpi) 
     
    484483 
    485484    INTEGER :: rank,i,j,pos 
    486     INTEGER :: size_,ind_glo,ind_loc, ind_src 
     485    INTEGER :: size_,ind_glo,ind_loc 
    487486    INTEGER :: isend, irecv, ireq, nreq, nsend, nrecv 
    488487    INTEGER, ALLOCATABLE :: mpi_req(:) 
     
    932931    CHARACTER(LEN=*), INTENT(IN),OPTIONAL :: name 
    933932 
    934     TYPE(ARRAY),POINTER :: recv,send  
    935933    TYPE(t_request),POINTER :: req 
    936934    INTEGER :: irecv,isend 
    937     INTEGER :: ireq,nreq, nreq_send 
     935    INTEGER :: ireq,nreq 
    938936    INTEGER :: ind 
    939937    INTEGER :: dim3,dim4 
    940     INTEGER :: i,j 
    941938    INTEGER,SAVE :: message_number=0 
    942939!    TYPE(t_reorder),POINTER :: reorder(:) 
     
    10611058    TYPE(t_message) :: message 
    10621059 
    1063     TYPE(t_request),POINTER :: req 
    1064     INTEGER :: irecv,isend 
    1065     INTEGER :: ireq,nreq 
    1066     INTEGER :: ind 
     1060    INTEGER :: ireq 
    10671061 
    10681062!$OMP BARRIER 
     
    11451139    TYPE(ARRAY),POINTER :: recv,send  
    11461140    TYPE(t_request),POINTER :: req 
    1147     INTEGER, ALLOCATABLE :: mpi_req(:) 
    1148     INTEGER, ALLOCATABLE :: status(:,:) 
    11491141    INTEGER :: irecv,isend 
    1150     INTEGER :: ireq,nreq 
    1151     INTEGER :: ind,i,n,l,m 
     1142    INTEGER :: ireq 
     1143    INTEGER :: ind,n 
    11521144    INTEGER :: dim3,dim4,d3,d4 
    11531145    INTEGER,POINTER :: src_value(:) 
    1154     INTEGER,POINTER :: sign(:) 
    11551146    INTEGER :: offset,msize,rank 
    11561147    INTEGER :: lbegin, lend 
     
    15541545    INTEGER,POINTER :: value(:)  
    15551546    INTEGER,POINTER :: sgn(:)  
    1556     TYPE(ARRAY),POINTER :: recv,send  
     1547    TYPE(ARRAY),POINTER :: recv  
    15571548    TYPE(t_request),POINTER :: req 
    1558     INTEGER, ALLOCATABLE :: mpi_req(:) 
    1559     INTEGER, ALLOCATABLE :: status(:,:) 
    1560     INTEGER :: irecv,isend 
     1549    INTEGER :: irecv 
    15611550    INTEGER :: ireq,nreq 
    1562     INTEGER :: ind,n,l,m,i 
     1551    INTEGER :: ind,n 
    15631552    INTEGER :: dim3,dim4,d3,d4,lbegin,lend 
    15641553    INTEGER :: offset 
     
    17411730    TYPE(t_request),POINTER :: req 
    17421731    INTEGER :: n 
    1743     REAL(rstd) :: var1,var2 
    17441732     
    17451733    DO ind=1,ndomain 
Note: See TracChangeset for help on using the changeset viewer.