Ignore:
Timestamp:
Apr 30, 2015, 3:22:39 PM (10 years ago)
Author:
millour
Message:

A couple of bug fixes.
Now the bench (in debug mode) yields identical results in seq/mpi/omp/mpi_omp, and also identical restart files to rev 5 (ie before any modifications to LMDZ5 source files).
EM

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

Legend:

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

    r3817 r3822  
    9999  REAL, ALLOCATABLE, DIMENSION(:,:,:):: q! champs advectes
    100100  REAL ps(ip1jmp1)                       ! pression  au sol
    101   REAL p (ip1jmp1,llmp1  )               ! pression aux interfac.des couches
     101!  REAL p (ip1jmp1,llmp1  )               ! pression aux interfac.des couches
    102102  REAL masse(ip1jmp1,llm)                ! masse d'air
    103103  REAL phis(ip1jmp1)                     ! geopotentiel au sol
    104   REAL phi(ip1jmp1,llm)                  ! geopotentiel
    105   REAL w(ip1jmp1,llm)                    ! vitesse verticale
     104!  REAL phi(ip1jmp1,llm)                  ! geopotentiel
     105!  REAL w(ip1jmp1,llm)                    ! vitesse verticale
    106106
    107107  ! variables dynamiques intermediaire pour le transport
     
    410410       tetagdiv, tetagrot , tetatemp, vert_prof_dissip)
    411411
    412   !-----------------------------------------------------------------------
    413   !   Initialisation de la physique :
    414   !   -------------------------------
    415 
    416   IF ((iflag_phys==1).or.(iflag_phys>=100)) THEN
    417      ! Physics:
    418 #ifdef CPP_PHYS
    419      CALL iniphysiq(iim,jjm,llm,daysec,day_ini,dtphys/nsplit_phys, &
    420           rlatu,rlatv,rlonu,rlonv,aire,cu,cv,rad,g,r,cpp, &
    421           iflag_phys)
    422 #endif
    423   ENDIF ! of IF ((iflag_phys==1).or.(iflag_phys>=100))
    424 
    425412  !  numero de stockage pour les fichiers de redemarrage:
    426413
     
    446433302 FORMAT('1'/,15x,'    au ', i2,'/',i2,'/',i4)
    447434#endif
     435
     436  !-----------------------------------------------------------------------
     437  !   Initialisation de la physique :
     438  !   -------------------------------
     439
     440  IF ((iflag_phys==1).or.(iflag_phys>=100)) THEN
     441     ! Physics:
     442#ifdef CPP_PHYS
     443     CALL iniphysiq(iim,jjm,llm,daysec,day_ini,dtphys/nsplit_phys, &
     444          rlatu,rlatv,rlonu,rlonv,aire,cu,cv,rad,g,r,cpp, &
     445          iflag_phys)
     446#endif
     447  ENDIF ! of IF ((iflag_phys==1).or.(iflag_phys>=100))
    448448
    449449  !      if (planet_type.eq."earth") then
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/dyn3dmem/gcm.F

    r3818 r3822  
    401401
    402402c-----------------------------------------------------------------------
     403c   Initialisation des I/O :
     404c   ------------------------
     405
     406
     407      if (nday>=0) then
     408         day_end = day_ini + nday
     409      else
     410         day_end = day_ini - nday/day_step
     411      endif
     412 
     413      WRITE(lunout,300)day_ini,day_end
     414 300  FORMAT('1'/,15x,'run du jour',i7,2x,'au jour',i7//)
     415
     416#ifdef CPP_IOIPSL
     417      call ju2ymds(jD_ref + day_ini - day_ref, an, mois, jour, heure)
     418      write (lunout,301)jour, mois, an
     419      call ju2ymds(jD_ref + day_end - day_ref, an, mois, jour, heure)
     420      write (lunout,302)jour, mois, an
     421 301  FORMAT('1'/,15x,'run du ', i2,'/',i2,'/',i4)
     422 302  FORMAT('1'/,15x,'    au ', i2,'/',i2,'/',i4)
     423#endif
     424
     425c-----------------------------------------------------------------------
    403426c   Initialisation de la physique :
    404427c   -------------------------------
     
    424447!$OMP END PARALLEL
    425448      END IF
    426 
    427 c-----------------------------------------------------------------------
    428 c   Initialisation des I/O :
    429 c   ------------------------
    430 
    431 
    432       if (nday>=0) then
    433          day_end = day_ini + nday
    434       else
    435          day_end = day_ini - nday/day_step
    436       endif
    437  
    438       WRITE(lunout,300)day_ini,day_end
    439  300  FORMAT('1'/,15x,'run du jour',i7,2x,'au jour',i7//)
    440 
    441 #ifdef CPP_IOIPSL
    442       call ju2ymds(jD_ref + day_ini - day_ref, an, mois, jour, heure)
    443       write (lunout,301)jour, mois, an
    444       call ju2ymds(jD_ref + day_end - day_ref, an, mois, jour, heure)
    445       write (lunout,302)jour, mois, an
    446  301  FORMAT('1'/,15x,'run du ', i2,'/',i2,'/',i4)
    447  302  FORMAT('1'/,15x,'    au ', i2,'/',i2,'/',i4)
    448 #endif
    449449
    450450!      if (planet_type.eq."earth") then
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/dyn3dpar/gcm.F

    r3818 r3822  
    402402
    403403c-----------------------------------------------------------------------
     404c   Initialisation des I/O :
     405c   ------------------------
     406
     407
     408      if (nday>=0) then
     409         day_end = day_ini + nday
     410      else
     411         day_end = day_ini - nday/day_step
     412      endif
     413
     414      WRITE(lunout,300)day_ini,day_end
     415 300  FORMAT('1'/,15x,'run du jour',i7,2x,'au jour',i7//)
     416
     417#ifdef CPP_IOIPSL
     418      call ju2ymds(jD_ref + day_ini - day_ref, an, mois, jour, heure)
     419      write (lunout,301)jour, mois, an
     420      call ju2ymds(jD_ref + day_end - day_ref, an, mois, jour, heure)
     421      write (lunout,302)jour, mois, an
     422 301  FORMAT('1'/,15x,'run du ', i2,'/',i2,'/',i4)
     423 302  FORMAT('1'/,15x,'    au ', i2,'/',i2,'/',i4)
     424#endif
     425
     426c-----------------------------------------------------------------------
    404427c   Initialisation de la physique :
    405428c   -------------------------------
     
    425448!$OMP END PARALLEL
    426449      END IF
    427 
    428 c-----------------------------------------------------------------------
    429 c   Initialisation des I/O :
    430 c   ------------------------
    431 
    432 
    433       if (nday>=0) then
    434          day_end = day_ini + nday
    435       else
    436          day_end = day_ini - nday/day_step
    437       endif
    438 
    439       WRITE(lunout,300)day_ini,day_end
    440  300  FORMAT('1'/,15x,'run du jour',i7,2x,'au jour',i7//)
    441 
    442 #ifdef CPP_IOIPSL
    443       call ju2ymds(jD_ref + day_ini - day_ref, an, mois, jour, heure)
    444       write (lunout,301)jour, mois, an
    445       call ju2ymds(jD_ref + day_end - day_ref, an, mois, jour, heure)
    446       write (lunout,302)jour, mois, an
    447  301  FORMAT('1'/,15x,'run du ', i2,'/',i2,'/',i4)
    448  302  FORMAT('1'/,15x,'    au ', i2,'/',i2,'/',i4)
    449 #endif
    450450
    451451!      if (planet_type.eq."earth") then
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/dynlonlat_phylonlat/phylmd/iniphysiq.F90

    r3817 r3822  
    139139  ENDIF ! of IF (klon_glo>1)
    140140
    141 !$OMP PARALLEL
     141!$OMP PARALLEL DEFAULT(SHARED) COPYIN(/temps/)
    142142  ! Now generate local lon/lat/cu/cv/area arrays
    143143  CALL initcomgeomphy(klon_omp)
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/infotrac_phy.f90

    r3820 r3822  
    5050    CHARACTER(len=20),INTENT(IN) :: tname_(nqtot_) ! tracer short name for restart and diagnostics
    5151    CHARACTER(len=23),INTENT(IN) :: ttext_(nqtot_) ! tracer long name for diagnostics
    52     CHARACTER(len=4),INTENT(IN) :: type_trac_(nqtot_)
     52    CHARACTER(len=4),INTENT(IN) :: type_trac_
    5353    INTEGER,INTENT(IN) :: niadv_ (nqtot_) ! equivalent dyn / physique
    5454    INTEGER,INTENT(IN) :: conv_flg_(nbtr_)
     
    6363    ALLOCATE(ttext(nqtot))
    6464    ttext(:) = ttext_(:)
    65     ALLOCATE(type_trac(nqtot))
    66     type_trac(:) = type_trac_(:)
     65    type_trac = type_trac_
    6766    ALLOCATE(niadv(nqtot))
    6867    niadv(:)=niadv_(:)
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/inifis_mod.F90

    r3817 r3822  
    1212  INTEGER,SAVE :: anneeref ! reference year, ase deifined in run.def
    1313  INTEGER,SAVE :: nday ! number of days to run
    14 !$THREADPRIVATE(daysec,dtphys,day_step,iphysiq,dayref,anneeref,nday)
     14!$OMP THREADPRIVATE(daysec,dtphys,day_step,iphysiq,dayref,anneeref,nday)
    1515  INTEGER,SAVE :: annee_ref ! reference year as read from start file
    1616  INTEGER,SAVE :: day_ini
    1717  INTEGER,SAVE :: day_end
    18 !$THREADPRIVATE(annee_ref,day_ini,day_end)
     18!$OMP THREADPRIVATE(annee_ref,day_ini,day_end)
    1919  INTEGER,SAVE :: itau_phy
    2020  INTEGER,SAVE :: itaufin
     
    2222  INTEGER,SAVE :: day_ref
    2323  REAL,SAVE :: jD_ref
    24 !$THREADPRIVATE(itau_phy,itaufin,start_time,day_ref,JD_ref)
     24!$OMP THREADPRIVATE(itau_phy,itaufin,start_time,day_ref,JD_ref)
    2525  LOGICAL,SAVE :: offline
    2626  INTEGER,SAVE :: raz_date
     
    2929  INTEGER,SAVE :: prt_level ! Output level
    3030  LOGICAL,SAVE :: debug ! flag to specify if in "debug mode"
    31 !$THREADPRIVATE(offline,raz_date,config_inca,lunout,prt_level,debug)
     31!$OMP THREADPRIVATE(offline,raz_date,config_inca,lunout,prt_level,debug)
    3232
    3333CONTAINS
Note: See TracChangeset for help on using the changeset viewer.