Changeset 901


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

trunk : Fixed compilation with --std=f2008 with gfortran

Added dynamico_abort() to replace non standard ABORT() intrinsic
Other modifications to respect the fortran standard

Location:
codes/icosagcm/trunk
Files:
1 added
9 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/trunk/bld.cfg

    r548 r901  
    5252bld::excl_dep        use::netcdf 
    5353bld::excl_dep        use::omp_lib 
    54 bld::excl_dep        inc::mpif.h 
     54bld::excl_dep        use::mpi 
    5555bld::excl_dep        use::xios 
    5656bld::excl_dep        %USE_IOIPSL 
  • codes/icosagcm/trunk/src/dcmip/dcmip2016_kessler_physic.f90

    r548 r901  
    7373  !   Input / output parameters 
    7474  !------------------------------------------------ 
    75  
     75  INTEGER, INTENT(IN) :: nz ! Number of thermodynamic levels in the column 
    7676  REAL(8), DIMENSION(nz), INTENT(INOUT) :: & 
    7777            theta   ,     & ! Potential temperature (K) 
     
    9292  REAL(8), INTENT(IN) :: &  
    9393            dt              ! Time step (s) 
    94  
    95   INTEGER, INTENT(IN) :: nz ! Number of thermodynamic levels in the column 
    9694 
    9795  !------------------------------------------------ 
  • codes/icosagcm/trunk/src/initial/etat0_heldsz.f90

    r899 r901  
    100100 
    101101  SUBROUTINE init_Teq 
     102    USE abort_mod 
    102103    USE disvert_mod, ONLY : ap,bp 
    103104    REAL(rstd),POINTER :: theta_eq(:,:)  
     
    150151 
    151152    ELSE 
    152        PRINT *, 'Init_Teq called twice' 
    153        CALL ABORT 
     153       CALL dynamico_abort( "Init_Teq called twice" ) 
    154154    END IF 
    155155 
  • codes/icosagcm/trunk/src/initial/etat0_temperature.f90

    r548 r901  
    1818    USE transfert_omp_mod, ONLY: bcast_omp 
    1919    USE free_unit_mod, ONLY : free_unit 
     20    USE abort_mod 
    2021    INTEGER :: unit,ok 
    2122    INTEGER :: l 
     
    3435    IF (ok/=0) THEN 
    3536      WRITE(*,*) "getin_etat0 error: input file ",trim(temperature_file)," not found!" 
    36       CALL ABORT 
     37      CALL dynamico_abort( "Could not open temperature file." ) 
    3738    ENDIF 
    3839    ! read in t_profile() line by line, starting from first atmospheric 
     
    4243      IF (ok/=0) THEN 
    4344        WRITE(*,*) "getin_etat0 error: failed reading t_profile(l) for l=",l 
    44         CALL ABORT 
     45        CALL dynamico_abort( "Could not read temperature file. " ) 
    4546      ENDIF 
    4647    ENDDO 
  • codes/icosagcm/trunk/src/initial/etat0_venus.f90

    r899 r901  
    150150                      3.070e-5, 1.525e-5, 7.950e-6,4.500e-6,2.925e-6,  & 
    151151                      2.265e-6/ 
    152  
    153     DO j=jj_begin-1,jj_end+1 
    154        DO i=ii_begin-1,ii_end+1 
    155           ij=(j-1)*iim+i 
    156           CALL xyz2lonlat(xyz_i(ij,:),lon,lat) 
    157           clat(ij)=cos(lat)  
    158        ENDDO 
    159     ENDDO 
    160  
    161152    data   tempCLee/ 728.187, 715.129, 697.876, 677.284, 654.078, 628.885, & 
    162153                     602.225, 574.542, 546.104, 517.339, 488.560, 459.932, & 
     
    171162                     14.001 , 9.599 , 6.504 , 4.439 , 3.126 , 2.370 ,  & 
    172163                     2.000/ 
     164 
     165    DO j=jj_begin-1,jj_end+1 
     166       DO i=ii_begin-1,ii_end+1 
     167          ij=(j-1)*iim+i 
     168          CALL xyz2lonlat(xyz_i(ij,:),lon,lat) 
     169          clat(ij)=cos(lat)  
     170       ENDDO 
     171    ENDDO     
    173172       
    174173    pressCLee = etaCLee*9.2e6 
  • codes/icosagcm/trunk/src/parallel/mpi_mod.F90

    r803 r901  
    22 
    33#ifdef CPP_USING_MPI 
    4   INCLUDE 'mpif.h' 
     4  !INCLUDE 'mpif.h' 
     5  use mpi 
    56#else 
    67  INTEGER :: MPI_COMM_WORLD 
     
    8687 SUBROUTINE MPI_GATHER 
    8788 END 
     89  
     90 SUBROUTINE MPI_ABORT(comm, err, ierr) 
     91   INTEGER :: comm, err, ierr 
     92   STOP err 
     93 END 
    8894#endif 
  • codes/icosagcm/trunk/src/parallel/transfert_mpi.f90

    r899 r901  
    11211121 
    11221122  SUBROUTINE send_message_mpi(field,message) 
     1123  USE abort_mod 
    11231124  USE profiling_mod 
    11241125  USE field_mod 
     
    11591160       PRINT *, 'send_message_mpi : message ' // TRIM(message%name) // & 
    11601161            ' is still open, no call to wait_message_mpi after last send_message_mpi' 
    1161        CALL ABORT 
     1162       CALL dynamico_abort( "send_message_mpi : message still open" ) 
    11621163    END IF 
    11631164    message%open=.TRUE. ! will be set to .FALSE. by wait_message_mpi 
     
    21302131    USE mpipara 
    21312132    IMPLICIT NONE 
    2132      
     2133    INTEGER,INTENT(IN) :: nb 
    21332134    INTEGER,DIMENSION(nb),INTENT(INOUT) :: Var 
    2134     INTEGER,INTENT(IN) :: nb 
    2135  
     2135     
    21362136    IF (.NOT. using_mpi) RETURN 
    21372137 
     
    21472147    USE mpipara 
    21482148    IMPLICIT NONE 
    2149      
     2149    INTEGER,INTENT(IN) :: nb 
    21502150    REAL,DIMENSION(nb),INTENT(INOUT) :: Var 
    2151     INTEGER,INTENT(IN) :: nb 
    21522151 
    21532152    IF (.NOT. using_mpi) RETURN 
     
    21642163    USE mpipara 
    21652164    IMPLICIT NONE 
    2166      
     2165    INTEGER,INTENT(IN) :: nb 
    21672166    LOGICAL,DIMENSION(nb),INTENT(INOUT) :: Var 
    2168     INTEGER,INTENT(IN) :: nb 
    21692167 
    21702168    IF (.NOT. using_mpi) RETURN 
  • codes/icosagcm/trunk/src/parallel/transfert_omp.f90

    r815 r901  
    827827  SUBROUTINE bcast_omp_igen(Var,Nb,Buff) 
    828828  IMPLICIT NONE 
    829      
     829    INTEGER,INTENT(IN) :: Nb 
    830830    INTEGER,DIMENSION(Nb),INTENT(INOUT) :: Var 
    831     INTEGER,DIMENSION(Nb),INTENT(INOUT) :: Buff 
    832     INTEGER,INTENT(IN) :: Nb 
     831    INTEGER,DIMENSION(Nb),INTENT(INOUT) :: Buff  
    833832 
    834833    INTEGER :: i 
     
    851850  SUBROUTINE bcast_omp_rgen(Var,Nb,Buff) 
    852851  IMPLICIT NONE 
    853      
     852    INTEGER,INTENT(IN) :: Nb 
    854853    REAL,DIMENSION(Nb),INTENT(INOUT) :: Var 
    855     REAL,DIMENSION(Nb),INTENT(INOUT) :: Buff 
    856     INTEGER,INTENT(IN) :: Nb 
     854    REAL,DIMENSION(Nb),INTENT(INOUT) :: Buff  
    857855 
    858856    INTEGER :: i 
     
    874872  SUBROUTINE bcast_omp_lgen(Var,Nb,Buff) 
    875873  IMPLICIT NONE 
    876      
     874    INTEGER,INTENT(IN) :: Nb 
    877875    LOGICAL,DIMENSION(Nb),INTENT(INOUT) :: Var 
    878876    LOGICAL,DIMENSION(Nb),INTENT(INOUT) :: Buff 
    879     INTEGER,INTENT(IN) :: Nb 
    880    
     877 
    881878    INTEGER :: i 
    882879     
  • codes/icosagcm/trunk/src/vertical/disvert_apbp.f90

    r548 r901  
    2525  SUBROUTINE disvert(ap,bp,presnivs) 
    2626!  USE icosa 
     27  USE abort_mod 
    2728  USE mpipara, ONLY: is_mpi_root 
    2829  USE omp_para, ONLY: omp_in_parallel 
     
    4647    IF (ok/=0) THEN 
    4748      WRITE(*,*) "disvert_ap_bp error: input file ",trim(filename)," not found!" 
    48       CALL ABORT 
     49      CALL dynamico_abort( "disvert_ap_bp : could not open input file" ) 
    4950    ENDIF 
    5051    ! read in ap() and b() line by line, starting from surface up 
     
    5455      IF (ok/=0) THEN 
    5556        WRITE(*,*) "disvert_ap_bp error: failed reading ap(l) and bp(l) for l=",l 
    56         CALL ABORT 
     57        CALL dynamico_abort( "disvert_ap_bp : could not read input file" ) 
    5758      ENDIF 
    5859    ENDDO 
Note: See TracChangeset for help on using the changeset viewer.