Ignore:
Timestamp:
May 23, 2015, 8:10:21 AM (10 years ago)
Author:
millour
Message:

A couple of bug fixes and adaptations.
Results are now identical when running seq or MPI or OpenMP or mixed MPI/OpenMP bench case.
Bench results change wrt revision 5 reference, because longitudes and latitudes in physics are now inherited from dynamics and no longer loaded from startphy.nc file.
EM

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

Legend:

Unmodified
Added
Removed
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/dyn3d/gcm.F90

    r3822 r3828  
    183183  ! A nettoyer. On ne veut qu'une ou deux routines d'interface
    184184  ! dynamique -> physique pour l'initialisation
    185 #ifdef CPP_PHYS
    186   CALL Init_Phys_lmdz(iim,jjp1,llm,1,(/(jjm-1)*iim+2/),COMM_LMDZ)
    187   !      call InitComgeomphy ! now done in iniphysiq
    188 #endif
     185!#ifdef CPP_PHYS
     186!  CALL Init_Phys_lmdz(iim,jjp1,llm,1,(/(jjm-1)*iim+2/),COMM_LMDZ)
     187!  !      call InitComgeomphy ! now done in iniphysiq
     188!#endif
    189189!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    190190  !-----------------------------------------------------------------------
     
    441441     ! Physics:
    442442#ifdef CPP_PHYS
    443      CALL iniphysiq(iim,jjm,llm,daysec,day_ini,dtphys/nsplit_phys, &
     443     CALL iniphysiq(iim,jjm,(jjm-1)*iim+2-1/iim,comm_lmdz, &
     444          llm,daysec,day_ini,dtphys/nsplit_phys, &
    444445          rlatu,rlatv,rlonu,rlonv,aire,cu,cv,rad,g,r,cpp, &
    445446          iflag_phys)
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/dynlonlat_phylonlat/mod_interface_dyn_phys.F90

    r3809 r3828  
    77 
    88 
     9CONTAINS
     10 
    911#ifdef CPP_PARA
    1012! Interface with parallel physics,
    11 CONTAINS
    12  
    1313  SUBROUTINE Init_interface_dyn_phys
    1414    USE mod_phys_lmdz_mpi_data
     
    5454 
    5555  END SUBROUTINE Init_interface_dyn_phys
     56#else
     57  SUBROUTINE Init_interface_dyn_phys
     58  ! dummy routine for seq case
     59  END SUBROUTINE Init_interface_dyn_phys
    5660#endif
    5761! of #ifdef CPP_PARA
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/dynlonlat_phylonlat/phylmd/iniphysiq.F90

    r3826 r3828  
    7979  REAL,ALLOCATABLE :: boundslonfi_glo(:,:)
    8080  REAL,ALLOCATABLE :: boundslatfi_glo(:,:)
    81   REAL,ALLOCATABLE :: latfi(:)
    82   REAL,ALLOCATABLE :: lonfi(:)
    83   REAL,ALLOCATABLE :: cufi(:)
    84   REAL,ALLOCATABLE :: cvfi(:)
    85   REAL,ALLOCATABLE :: airefi(:)
    86   REAL,ALLOCATABLE :: boundslonfi(:,:)
    87   REAL,ALLOCATABLE :: boundslatfi(:,:)
     81  ! local arrays, on given MPI/OpenMP domain:
     82  REAL,ALLOCATABLE,SAVE :: latfi(:)
     83  REAL,ALLOCATABLE,SAVE :: lonfi(:)
     84  REAL,ALLOCATABLE,SAVE :: cufi(:)
     85  REAL,ALLOCATABLE,SAVE :: cvfi(:)
     86  REAL,ALLOCATABLE,SAVE :: airefi(:)
     87  REAL,ALLOCATABLE,SAVE :: boundslonfi(:,:)
     88  REAL,ALLOCATABLE,SAVE :: boundslatfi(:,:)
     89!$OMP THREADPRIVATE (latfi,lonfi,cufi,cvfi,airefi,boundslonfi,boundslatfi)
    8890
    8991  CALL init_physics_distribution(regular_lonlat, 4, nbp, ii, jj+1, nlayer, communicator)
     
    120122  ALLOCATE(boundslonfi_glo(klon_glo,4))
    121123  ALLOCATE(boundslatfi_glo(klon_glo,4))
    122  
    123   ALLOCATE(latfi(klon_glo),lonfi(klon_glo),cufi(klon_glo),cvfi(klon_glo))
    124   ALLOCATE(airefi(klon_glo))
    125   ALLOCATE(boundslonfi(klon_glo,4))
    126   ALLOCATE(boundslatfi(klon_glo,4))
    127124
    128125  IF (klon_glo>1) THEN ! general case
     
    208205
    209206!$OMP PARALLEL DEFAULT(SHARED) COPYIN(/temps/)
    210   ! Now generate local lon/lat/cu/cv/area arrays
     207  ! Now generate local lon/lat/cu/cv/area/bounds arrays
     208  ALLOCATE(latfi(klon_omp),lonfi(klon_omp),cufi(klon_omp),cvfi(klon_omp))
     209  ALLOCATE(airefi(klon_omp))
     210  ALLOCATE(boundslonfi(klon_omp,4))
     211  ALLOCATE(boundslatfi(klon_omp,4))
    211212
    212213
     
    240241              lunout,prt_level,debug)
    241242 
    242 !!$OMP END PARALLEL
    243 
    244243  ! Additional initializations for aquaplanets
    245 !!$OMP PARALLEL
    246244  IF (iflag_phys>=100) THEN
    247245    CALL iniaqua(klon_omp, iflag_phys)
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/add_phys_tend.F90

    r3825 r3828  
    223223         k=kqadrs(j)
    224224         if(prt_level.ge.debug_level) THEN
    225           print*,'WARNING  : EAU2 POUR LE POINT i itap lon lat txt jqbad zdq q zdql ql',i,itap,lon_degrees(i), lat_degrees(i), text,jqbad,&
    226        &        zdq(i,k), q_seri(i,k)-zdq(i,k), zdql(i,k), ql_seri(i,k)-zdql(i,k)
     225          print*,'WARNING  : EAU2 POUR LE POINT i itap lon lat txt jqbad zdq q zdql ql',i,itap,lon_degrees(i), lat_degrees(i), &
     226       &        text,jqbad, zdq(i,k), q_seri(i,k)-zdq(i,k), zdql(i,k), ql_seri(i,k)-zdql(i,k)
    227227!!!       if(prt_level.ge.10.and.itap.GE.229.and.i.EQ.3027) THEN
    228228          print*,'l    T     dT       Q     dQ    '
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/iophy.F90

    r3819 r3828  
    8585
    8686    ALLOCATE(io_lon(nbp_lon))
    87     io_lon(1)=rlon_glo(1)
    88     IF (nbp_lon > 1) io_lon(2:nbp_lon)=rlon_glo(3:nbp_lon+1)
     87    IF (klon_glo == 1) THEN
     88      io_lon(1)=rlon_glo(1)
     89    ELSE
     90      io_lon(1:nbp_lon)=rlon_glo(2:nbp_lon+1)
     91    ENDIF
    8992   
    9093!! (I) dtnb   : total number of domains
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/phyetat0.F90

    r3825 r3828  
    7373  CHARACTER*2 str2
    7474  LOGICAL :: found,phyetat0_get,phyetat0_srf
     75 
     76  REAL :: lon_startphy(klon), lat_startphy(klon)
    7577
    7678  ! FH1D
     
    136138  clesphy0(8)=tab_cntrl( 12 )
    137139
    138 
     140  ! Sanity check on longitudes
     141  CALL get_field("longitude",lon_startphy)
     142  do i=1,klon
     143    if (abs(lon_startphy(i)-lon_degrees(i))>=1) then
     144      write(*,*) "phyetat0: Error! Longitude discrepancy wrt startphy file:",&
     145                 " i=",i," lon_startphy(i)=",lon_startphy(i),&
     146                 " lon_degrees(i)=",lon_degrees(i)
     147      ! This is presumably serious enough to abort run
     148      call abort_physic("phyetat0","discrepancy in longitudes!",1)
     149    endif
     150    if (abs(lon_startphy(i)-lon_degrees(i))>=0.0001) then
     151      write(*,*) "phyetat0: Warning! Longitude discrepancy wrt startphy file:",&
     152                 " i=",i," lon_startphy(i)=",lon_startphy(i),&
     153                 " lon_degrees(i)=",lon_degrees(i)
     154    endif
     155  enddo
     156 
     157  ! Sanity check on latitudes
     158  CALL get_field("latitude",lat_startphy)
     159  do i=1,klon
     160    if (abs(lat_startphy(i)-lat_degrees(i))>=1) then
     161      write(*,*) "phyetat0: Error! Latitude discrepancy wrt startphy file:",&
     162                 " i=",i," lat_startphy(i)=",lat_startphy(i),&
     163                 " lat_degrees(i)=",lat_degrees(i)
     164      ! This is presumably serious enough to abort run
     165      call abort_physic("phyetat0","Discrepancy in latitudes!",1)
     166    endif
     167    if (abs(lat_startphy(i)-lat_degrees(i))>=0.0001) then
     168      write(*,*) "phyetat0: Warning! Latitude discrepancy wrt startphy file:",&
     169                 " i=",i," lat_startphy(i)=",lat_startphy(i),&
     170                 " lat_degrees(i)=",lat_degrees(i)
     171    endif
     172  enddo
     173 
    139174  ! Lecture du masque terre mer
    140175
     
    842877  ENDIF
    843878
    844   CALL init_iophy_new(lon_degrees, lat_degrees)
     879  CALL init_iophy_new(lat_degrees,lon_degrees)
    845880
    846881  ! Initilialize module fonte_neige_mod     
Note: See TracChangeset for help on using the changeset viewer.