Ignore:
Timestamp:
Nov 28, 2014, 4:36:29 PM (10 years ago)
Author:
Laurent Fairhead
Message:

Merged trunk changes -r2070:2158 into testing branch. Compilation problems introduced by revision r2155 have been corrected by hand

Location:
LMDZ5/branches/testing
Files:
1 deleted
8 edited
1 copied

Legend:

Unmodified
Added
Removed
  • LMDZ5/branches/testing

  • LMDZ5/branches/testing/libf/dyn3dpar/abort_gcm.F

    r1910 r2160  
    2727C         ierr    = severity of situation ( = 0 normal )
    2828
    29       character(len=*) modname
     29      character(len=*), intent(in):: modname
    3030      integer ierr, ierror_mpi
    31       character(len=*) message
     31      character(len=*), intent(in):: message
    3232
    3333      write(lunout,*) 'in abort_gcm'
     
    5353        write(lunout,*) 'Everything is cool'
    5454      else
    55         write(lunout,*) 'Houston, we have a problem ', ierr
     55        write(lunout,*) 'Houston, we have a problem, ierr = ', ierr
    5656#ifdef CPP_MPI
    5757C$OMP CRITICAL (MPI_ABORT_GCM)
  • LMDZ5/branches/testing/libf/dyn3dpar/gcm.F

    r2056 r2160  
    175175!#ifdef CPP_IOIPSL
    176176      CALL conf_gcm( 99, .TRUE. , clesphy0 )
     177      if (mod(iphysiq, iperiod) /= 0) call abort_gcm("conf_gcm",
     178     s "iphysiq must be a multiple of iperiod", 1)
    177179!#else
    178180!      CALL defrun( 99, .TRUE. , clesphy0 )
  • LMDZ5/branches/testing/libf/dyn3dpar/getparam.F90

    r1910 r2160  
    1111
    1212   INTERFACE getpar
    13      MODULE PROCEDURE ini_getparam,fin_getparam,getparamr,getparami,getparaml
     13     MODULE PROCEDURE getparamr,getparami,getparaml
    1414   END INTERFACE
     15   private getparamr,getparami,getparaml
    1516
    1617   INTEGER, PARAMETER :: out_eff=99
  • LMDZ5/branches/testing/libf/dyn3dpar/guide_p_mod.F90

    r2056 r2160  
    6767
    6868  SUBROUTINE guide_init
    69    
     69
    7070    USE control_mod
     71
    7172    IMPLICIT NONE
    7273 
     
    7475    INCLUDE "paramet.h"
    7576    INCLUDE "netcdf.inc"
     77
     78    ! For grossismx:
     79    include "serre.h"
    7680
    7781    INTEGER                :: error,ncidpl,rid,rcod
     
    9397    CALL getpar('guide_add',.false.,guide_add,'for�age constant?')
    9498    CALL getpar('guide_zon',.false.,guide_zon,'guidage moy zonale')
     99    if (guide_zon .and. abs(grossismx - 1.) > 0.01) &
     100         call abort_gcm("guide_init", &
     101         "zonal nudging requires grid regular in longitude", 1)
    95102
    96103!   Constantes de rappel. Unite : fraction de jour
     
    113120    ! frequences f>0: fx/jour; f<0: tous les f jours; f=0: 1 seule fois.
    114121    IF (iguide_sav.GT.0) THEN
    115         iguide_sav=day_step/iguide_sav
     122       iguide_sav=day_step/iguide_sav
     123    ELSE if (iguide_sav == 0) then
     124       iguide_sav = huge(0)
    116125    ELSE
    117         iguide_sav=day_step*iguide_sav
     126       iguide_sav=day_step*iguide_sav
    118127    ENDIF
    119128
     
    155164    ncidpl=-99
    156165    if (guide_plevs.EQ.1) then
    157        if (ncidpl.eq.-99) then 
     166       if (ncidpl.eq.-99) then
    158167          rcod=nf90_open('apbp.nc',Nf90_NOWRITe, ncidpl)
    159168          if (rcod.NE.NF_NOERR) THEN
     
    163172       endif
    164173    elseif (guide_plevs.EQ.2) then
    165        if (ncidpl.EQ.-99) then 
     174       if (ncidpl.EQ.-99) then
    166175          rcod=nf90_open('P.nc',Nf90_NOWRITe,ncidpl)
    167176          if (rcod.NE.NF_NOERR) THEN
     
    374383    ENDIF
    375384     
    376      PRINT *,'---> on rentre dans guide_main'
    377385!    CALL AllGather_Field(ucov,ip1jmp1,llm)
    378386!    CALL AllGather_Field(vcov,ip1jm,llm)
     
    12501258        enddo
    12511259    ENDIF ! guide_reg
     1260
     1261    if (.not. guide_add) alpha = 1. - exp(- alpha)
    12521262
    12531263  END SUBROUTINE tau2alpha
  • LMDZ5/branches/testing/libf/dyn3dpar/iniacademic.F90

    r2056 r2160  
    44SUBROUTINE iniacademic(vcov,ucov,teta,q,masse,ps,phis,time_0)
    55
    6   use exner_hyb_m, only: exner_hyb
    7   use exner_milieu_m, only: exner_milieu
    8   USE filtreg_mod
     6  USE filtreg_mod, ONLY: inifilr
    97  USE infotrac, ONLY : nqtot
    108  USE control_mod, ONLY: day_step,planet_type
    119#ifdef CPP_IOIPSL
    12   USE IOIPSL
     10  USE IOIPSL, ONLY: getin
    1311#else
    1412  ! if not using IOIPSL, we still need to use (a local version of) getin
    15   USE ioipsl_getincom
     13  USE ioipsl_getincom, ONLY: getin
    1614#endif
    1715  USE Write_Field
     16  use exner_hyb_m, only: exner_hyb
     17  use exner_milieu_m, only: exner_milieu
    1818
    1919  !   Author:    Frederic Hourdin      original: 15/01/93
     
    4040  !   ----------
    4141
    42   real time_0
    43 
    44   !   variables dynamiques
    45   REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm) ! vents covariants
    46   REAL teta(ip1jmp1,llm)                 ! temperature potentielle
    47   REAL q(ip1jmp1,llm,nqtot)               ! champs advectes
    48   REAL ps(ip1jmp1)                       ! pression  au sol
    49   REAL masse(ip1jmp1,llm)                ! masse d'air
    50   REAL phis(ip1jmp1)                     ! geopotentiel au sol
     42  REAL,INTENT(OUT) :: time_0
     43
     44  !   fields
     45  REAL,INTENT(OUT) :: vcov(ip1jm,llm) ! meridional covariant wind
     46  REAL,INTENT(OUT) :: ucov(ip1jmp1,llm) ! zonal covariant wind
     47  REAL,INTENT(OUT) :: teta(ip1jmp1,llm) ! potential temperature (K)
     48  REAL,INTENT(OUT) :: q(ip1jmp1,llm,nqtot) ! advected tracers (.../kg_of_air)
     49  REAL,INTENT(OUT) :: ps(ip1jmp1) ! surface pressure (Pa)
     50  REAL,INTENT(OUT) :: masse(ip1jmp1,llm) ! air mass in grid cell (kg)
     51  REAL,INTENT(OUT) :: phis(ip1jmp1) ! surface geopotential
    5152
    5253  !   Local:
     
    7677  character(len=80) :: abort_message
    7778
     79
     80  ! Sanity check: verify that options selected by user are not incompatible
     81  if ((iflag_phys==1).and. .not. read_start) then
     82    write(lunout,*) trim(modname)," error: if read_start is set to ", &
     83    " false then iflag_phys should not be 1"
     84    write(lunout,*) "You most likely want an aquaplanet initialisation", &
     85    " (iflag_phys >= 100)"
     86    call abort_gcm(modname,"incompatible iflag_phys==1 and read_start==.false.",1)
     87  endif
     88 
    7889  !-----------------------------------------------------------------------
    7990  ! 1. Initializations for Earth-like case
     
    224235        CALL pression ( ip1jmp1, ap, bp, ps, p       )
    225236        if (pressure_exner) then
    226           CALL exner_hyb( ip1jmp1, ps, p, pks, pk )
     237          CALL exner_hyb( ip1jmp1, ps, p, pks, pk)
    227238        else
    228239          call exner_milieu(ip1jmp1,ps,p,pks,pk)
  • LMDZ5/branches/testing/libf/dyn3dpar/integrd_p.F

    r1910 r2160  
    137137       
    138138        IF( .NOT. checksum ) THEN
    139          write(lunout,*) "integrd: negative surface pressure ",
    140      &                                                ps(stop_it)
     139           write(lunout,*) "integrd: ps = ", ps(stop_it)
    141140         write(lunout,*) " at node ij =", stop_it
    142141         ! since ij=j+(i-1)*jjp1 , we have
     
    145144         write(lunout,*) " lon = ",rlonv(i)*180./pi, " deg",
    146145     &                   " lat = ",rlatu(j)*180./pi, " deg"
     146         call abort_gcm("integrd_p", "negative surface pressure", 1)
    147147        ENDIF
    148148
  • LMDZ5/branches/testing/libf/dyn3dpar/leapfrog_p.F

    r2056 r2160  
    717717           CALL exner_milieu_p( ip1jmp1, ps, p, pks, pk, pkf )
    718718         endif
     719c$OMP BARRIER
    719720! Appel a geopot ajoute le 2014/05/08 pour garantir la convergence numerique
    720721! avec dyn3dmem
    721       CALL geopot  ( ip1jmp1, teta  , pk , pks,  phis  , phi   )
    722 c$OMP BARRIER
     722      CALL geopot_p  ( ip1jmp1, teta  , pk , pks,  phis  , phi   )
     723
    723724           jD_cur = jD_ref + day_ini - day_ref
    724725     $        + itau/day_step
Note: See TracChangeset for help on using the changeset viewer.