Changeset 3826 for dynamico_lmdz


Ignore:
Timestamp:
May 7, 2015, 6:14:45 PM (10 years ago)
Author:
ymipsl
Message:

Bug fix. Works now on one proc, but always some problems in parallel.

YM

Location:
dynamico_lmdz/aquaplanet/LMDZ5/libf
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/dyn3dmem/bands.F90

    r3809 r3826  
    105105   SUBROUTINE  Set_Bands
    106106     USE parallel_lmdz
    107 #ifdef CPP_PHYS
    108 ! Ehouarn: what follows is only related to // physics
    109      USE mod_phys_lmdz_para, ONLY : jj_para_begin,jj_para_end
    110 #endif
    111107     IMPLICIT NONE
    112108     INCLUDE 'dimensions.h'   
    113      INTEGER :: i
     109     INTEGER :: i, ij
     110     INTEGER :: jj_para_begin(0:mpi_size-1)
     111     INTEGER :: jj_para_end(0:mpi_size-1)
    114112       
    115113      do i=0,mpi_size-1
     
    118116      enddo
    119117         
    120 #ifdef CPP_PHYS
    121       do i=0,MPI_Size-1
     118      jj_para_begin(0)=1
     119      ij=distrib_phys(0)+iim-1
     120      jj_para_end(0)=((ij-1)/iim)+1
     121     
     122      DO i=1,mpi_Size-1
     123        ij=ij+1
     124        jj_para_begin(i)=((ij-1)/iim)+1
     125        ij=ij+distrib_phys(i)-1
     126        jj_para_end(i)=((ij-1)/iim)+1
     127      ENDDO
     128 
     129       do i=0,MPI_Size-1
    122130        jj_Nb_physic(i)=jj_para_end(i)-jj_para_begin(i)+1
    123131        if (i/=0) then
     
    139147        endif
    140148      enddo
    141 #endif     
     149
    142150      CALL create_distrib(jj_Nb_Caldyn,distrib_caldyn)
    143151      CALL create_distrib(jj_Nb_vanleer,distrib_vanleer)
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/dyn3dmem/gcm.F

    r3825 r3826  
    420420! Physics:
    421421#ifdef CPP_PHYS
    422          CALL iniphysiq(iim,jjm, distrib_phys(mpi_rank), comm_lmdz, llm, daysec, day_ini, dtphys/nsplit_phys,
    423      &                rlatu,rlatv,rlonu,rlonv,aire,cu,cv,rad,g,r,cpp,
    424      &                iflag_phys)
     422         CALL iniphysiq(iim,jjm, distrib_phys(mpi_rank), comm_lmdz, llm,
     423     &                  daysec, day_ini, dtphys/nsplit_phys,
     424     &                  rlatu,rlatv,rlonu,rlonv,aire,cu,cv,rad,g,r,cpp,
     425     &                  iflag_phys)
    425426#endif
    426427      ENDIF ! of IF ((iflag_phys==1).or.(iflag_phys>=100))
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/dynlonlat_phylonlat/phylmd/iniphysiq.F90

    r3825 r3826  
    105105  boundslat_reg(1,south)= rlatv(1)
    106106  DO j=2,jj
    107    boundslat_reg(i,north)=rlatv(j-1)
    108    boundslat_reg(i,south)=rlatv(j)
     107   boundslat_reg(j,north)=rlatv(j-1)
     108   boundslat_reg(j,south)=rlatv(j)
    109109  ENDDO
    110110  boundslat_reg(jj+1,north)= rlatv(jj)
     
    162162    cufi_glo(klon_glo) = cu((ii+1)*jj+1)
    163163    cvfi_glo(klon_glo) = cv((ii+1)*jj-ii)
    164     boundslonfi_glo(klon_glo,north_east)=0
    165     boundslatfi_glo(klon_glo,north_east)=rlatv(jj)
    166     boundslonfi_glo(klon_glo,north_west)=2*PI
    167     boundslatfi_glo(klon_glo,north_west)=rlatv(jj)
    168     boundslonfi_glo(klon_glo,south_west)=2*PI
    169     boundslatfi_glo(klon_glo,south_west)=-PI/2
    170     boundslonfi_glo(klon_glo,south_east)=rlonu(0)
    171     boundslatfi_glo(klon_glo,south_east)=-Pi/2
     164    boundslonfi_glo(klon_glo,north_east)= 0
     165    boundslatfi_glo(klon_glo,north_east)= rlatv(jj)
     166    boundslonfi_glo(klon_glo,north_west)= 2*PI
     167    boundslatfi_glo(klon_glo,north_west)= rlatv(jj)
     168    boundslonfi_glo(klon_glo,south_west)= 2*PI
     169    boundslatfi_glo(klon_glo,south_west)= -PI/2
     170    boundslonfi_glo(klon_glo,south_east)= 0
     171    boundslatfi_glo(klon_glo,south_east)= -Pi/2
    172172
    173173    ! build airefi(), mesh area on physics grid
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/inifis_mod.F90

    r3822 r3826  
    2626  INTEGER,SAVE :: raz_date
    2727  CHARACTER(len=4),SAVE :: config_inca
    28   INTEGER,SAVE :: lunout ! default output file identifier (6==screen)
     28  INTEGER,SAVE :: lunout=6 ! default output file identifier (6==screen)
    2929  INTEGER,SAVE :: prt_level ! Output level
    3030  LOGICAL,SAVE :: debug ! flag to specify if in "debug mode"
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/mod_phys_lmdz_mpi_data.F90

    r3825 r3826  
    8787    IF (is_using_mpi) THEN   
    8888#ifdef CPP_MPI
    89     CALL MPI_ALLGATHER(nbp,1,MPI_REAL8,distrib,1,MPI_REAL_LMDZ,COMM_LMDZ_PHY)
     89    CALL MPI_ALLGATHER(nbp,1,MPI_REAL8,distrib,1,MPI_REAL_LMDZ,COMM_LMDZ_PHY,ierr)
    9090#endif
    9191    ELSE
Note: See TracChangeset for help on using the changeset viewer.