Changeset 3908


Ignore:
Timestamp:
Sep 2, 2025, 4:07:53 PM (3 months ago)
Author:
emillour
Message:

Generic PCM:
Fix some missing initializations in newstart and add
option "Lmodif=2" when calling tabi from newstart to skip some checks
which only make sense when called during a regular GCM run.
EM

Location:
trunk/LMDZ.GENERIC
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.GENERIC/changelog.txt

    r3893 r3908  
    20982098== 13/08/2025 == GM
    20992099Remove all "call abort" and "stop" statement in LMDZ.GENERIC and replacing them by call abort_physic().
     2100
     2101== 02/09/2025 == EM
     2102Fix some missing initializations in newstart and add
     2103option "Lmodif=2" when calling tabi from newstart to skip some checks
     2104which only make sense when called during a regular GCM run.
  • trunk/LMDZ.GENERIC/libf/dynphy_lonlat/phystd/newstart.F

    r3893 r3908  
    2828      use datafile_mod, only: datadir, surfdir
    2929      use ioipsl_getin_p_mod, only: getin_p
    30       use control_mod, only: day_step, iphysiq, anneeref, planet_type
     30      use control_mod, only: day_step, iphysiq, anneeref, planet_type,
     31     &                       timestart
    3132      use phyredem, only: physdem0, physdem1
    3233      use iostart, only: nid_start, open_startphy
     
    4243      USE ener_mod, ONLY: etot0,ptot0,ztot0,stot0,ang0
    4344      use tabfi_mod, only: tabfi
     45      use time_phylmdz_mod, only: init_time
    4446      use dimphy, only: init_dimphy
    4547      use iniphysiq_mod, only: iniphysiq
     
    149151!      REAL dteta(ip1jmp1,llm)
    150152
    151 c Variable de l'ancienne grille
    152 c------------------------------
    153153      real time
    154154      real tab_cntrl(100)
    155155      real tab_cntrl_bis(100)
    156156
    157 c variables diverses
     157c other variables
    158158c-------------------
    159       real choix_1,pp
     159      integer :: infile_type
     160      integer,parameter :: start_archive_file = 0
     161      integer,parameter :: start_startfi_files = 1
     162      real pp
    160163      character*80      fichnom
    161164      character*250  filestring
     
    243246
    244247      DO
    245          read(*,*,iostat=ierr) choix_1
    246          if ((choix_1 /= 0).OR.(choix_1 /=1)) EXIT
     248         read(*,*,iostat=ierr) infile_type
     249         if ((infile_type /= start_archive_file).OR.
     250     &       (infile_type /= start_startfi_files)) EXIT
    247251      ENDDO
    248252
    249253c     Open start_archive
    250254c     ~~~~~~~~~~~~~~~~~~~~~~~~~~
    251       if (choix_1.eq.0) then
     255      if (infile_type.eq.start_archive_file) then
    252256
    253257        write(*,*) 'Creating start files from:'
     
    296300
    297301c=======================================================================
    298 INITIALISATIONS DIVERSES
     302VARIOUS INITIALIZATIONS
    299303c=======================================================================
    300304
     
    313317c Lecture du tableau des parametres du run (pour la dynamique)
    314318c-----------------------------------------------------------------------
    315       if (choix_1.eq.0) then
     319      if (infile_type.eq.start_archive_file) then
    316320
    317321        write(*,*) 'reading tab_cntrl START_ARCHIVE'
     
    324328#endif
    325329c
    326       else if (choix_1.eq.1) then
     330      else if (infile_type.eq.start_startfi_files) then
    327331
    328332        write(*,*) 'reading tab_cntrl START'
     
    354358        write(*,*) 'Reading file START'
    355359        fichnom = 'start.nc'
     360        ! initialization required for dynetat0:
     361        timestart=-9999 ! default value; if <0, use last stored time
    356362        CALL dynetat0(fichnom,vcov,ucov,teta,q,masse,
    357363     .       ps,phis,time)
     
    430436        read(*,*) pa
    431437      endif
    432 c-----------------------------------------------------------------------
    433 c   Lecture du tab_cntrl et initialisation des constantes physiques
    434 c  - pour start:  Lmodif = 0 => pas de modifications possibles
    435 c                  (modif dans le tabfi de readfi + loin)
    436 c  - pour start_archive:  Lmodif = 1 => modifications possibles
    437 c-----------------------------------------------------------------------
    438       if (choix_1.eq.0) then
     438!-----------------------------------------------------------------------
     439!   Load tab_cntrl array and initialize physics constants
     440!  - with Lmodif == 0 => values cannot be modified
     441!  - with Lmodif == 1 => values can be modified
     442!  - with Lmodif == 2 => values can be modified ; remove some extra
     443!                        checks/tests done in tabfi not valid when
     444!-----------------------------------------------------------------------
     445      if (infile_type.eq.start_archive_file) then
    439446         ! tabfi requires that input file be first opened by open_startphy(fichnom)
    440447         fichnom = 'start_archive.nc'
    441448         call open_startphy(fichnom,nid_start)
     449         ! let tabfi know it is called from newstart
     450         Lmodif=2
    442451         call tabfi (ngridmx,nid,Lmodif,tab0,day_ini,lllm,p_rad,
    443452     .            p_omeg,p_g,p_cpp,p_mugaz,p_daysec,time)
    444       else if (choix_1.eq.1) then
     453      else if (infile_type.eq.start_startfi_files) then
    445454         fichnom = 'startfi.nc'
    446455         call open_startphy(fichnom,nid_start)
     
    482491
    483492! Initialize the physics for start_archive only
    484       IF (choix_1.eq.0) THEN
     493      IF (infile_type.eq.start_archive_file) THEN
    485494         CALL iniphysiq(iim,jjm,llm,
    486495     &                  (jjm-1)*iim+2,comm_lmdz,
     
    495504c=======================================================================
    496505
    497       if (choix_1.eq.0) then  ! for start_archive files,
     506      if (infile_type.eq.start_archive_file) then  ! for start_archive files,
    498507                              ! where an external "surface.nc" file is needed
    499508
     
    565574        CALL gr_dyn_fi(1,iip1,jjp1,ngridmx,ztheS,zthe)
    566575
    567       endif ! of if (choix_1.eq.0)
     576      endif ! of if (infile_type.eq.start_archive_file)
    568577
    569578
     
    572581c=======================================================================
    573582
    574       if (choix_1.eq.0) then
     583      if (infile_type.eq.start_archive_file) then
    575584
    576585        write(*,*) 'Reading file START_ARCHIVE'
     
    587596        ierr= NF_CLOSE(nid)
    588597
    589       else if (choix_1.eq.1) then
     598      else if (infile_type.eq.start_startfi_files) then
    590599         !do nothing, start and startfi have already been read
    591600      else
     
    15841593
    15851594
    1586       if ((choix_1.eq.0).and.(.not.flagps0)) then
     1595      if ((infile_type.eq.start_archive_file).and.(.not.flagps0)) then
    15871596        r = 1000.*8.31/mugaz
    15881597
     
    15951604        end do
    15961605
    1597 c periodicite de ps en longitude
     1606c  ps periodicity in longitude
    15981607        do j=1,jjp1
    15991608          ps(1,j) = ps(iip1,j)
     
    16061615
    16071616c=======================================================================
    1608 c    Initialisation de la physique / ecriture de newstartfi :
     1617c    Initialize / write the new start files :
    16091618c=======================================================================
    16101619
     
    16181627
    16191628      CALL exner_hyb(ip1jmp1, ps, p3d, pks, pk, pkf)
    1620 ! Calcul de la temperature potentielle teta
     1629! Compute potential temperature teta
    16211630
    16221631      if (flagtset) then
     
    16291638             ENDDO
    16301639          ENDDO
    1631       else if (choix_1.eq.0) then
     1640      else if (infile_type.eq.start_archive_file) then
    16321641         DO l=1,llm
    16331642            DO j=1,jjp1
     
    16421651C Calcul intermediaire
    16431652c
    1644       if (choix_1.eq.0) then
     1653      if (infile_type.eq.start_archive_file) then
    16451654         CALL massdair( p3d, masse  )
    16461655c
     
    16631672
    16641673      itau=0
    1665       if (choix_1.eq.0) then
     1674      if (infile_type.eq.start_archive_file) then
    16661675         day_ini=int(date)
    16671676      endif
     
    16761685      CALL dynredem1("restart.nc",0.0,vcov,ucov,teta,q,masse,ps)
    16771686C
    1678 C Ecriture etat initial physique
     1687C Write physics initial state
    16791688C
    16801689
  • trunk/LMDZ.GENERIC/libf/phystd/tabfi_mod.F90

    r3893 r3908  
    7676! Arguments
    7777! ---------
    78       INTEGER,INTENT(IN) :: ngrid,nid,tab0
     78      INTEGER,INTENT(IN) :: ngrid
     79      INTEGER,INTENT(IN) :: nid ! 0: no file to read controle array from
     80                                ! /= 0 : read controle array from file
     81      INTEGER,INTENT(IN) :: tab0
    7982      INTEGER*4,INTENT(OUT) :: day_ini
    80       INTEGER,INTENT(IN) :: Lmodif
     83      INTEGER,INTENT(IN) :: Lmodif ! 0: do not modifications
     84                                   ! 1: enable modifications
     85                                   ! 2: enable modifications but no sanity test
     86                                   !    (needed when called from newstart)
    8187      INTEGER,INTENT(OUT) :: lmax
    8288      REAL,INTENT(OUT) :: p_rad,p_omeg,p_g,p_cpp,p_mugaz,p_daysec,time
     
    208214      volcapa = tab_cntrl(tab0+35) ! volumetric heat capacity
    209215! warn user if there has been a change in daysec or dtphys
    210       if (daysec.ne.cntrl_daysec) then
     216      if (Lmodif < 2) then
     217       ! this is meaningful if called in PCM, but not when called from newstart
     218       if (daysec.ne.cntrl_daysec) then
    211219        write(*,*) modname//" Warning: lenght of day daysec changed from ", &
    212220                   cntrl_daysec," to ",daysec
    213       endif
    214       if (dtphys.ne.cntrl_dtphys) then
     221       endif
     222       if (dtphys.ne.cntrl_dtphys) then
    215223        write(*,*) modname//" Warning: time step dtphys changed from ", &
    216224                   cntrl_dtphys," to ",dtphys
    217       endif
     225       endif
     226      else
     227        ! set dtphys and daysec to those from controle
     228        daysec=cntrl_daysec
     229        dtphys=cntrl_dtphys
     230      endif ! of if (Lmodif < 2)
     231
    218232!-----------------------------------------------------------------------
    219233!       Save some constants for later use (as routine arguments)
     
    273287!        Modifications...
    274288! NB: Modifying controls should only be done by newstart, and in seq mode
    275       if ((Lmodif.eq.1).and.is_parallel) then
     289      if ((Lmodif >= 1).and.is_parallel) then
    276290        write(*,*) "tabfi: Error modifying tab_control should", &
    277291                   " only happen in serial mode (eg: by newstart)"
     
    280294!-----------------------------------------------------------------------
    281295
    282       IF(Lmodif.eq.1) then
     296      IF(Lmodif >= 1) then
    283297
    284298      write(*,*)
     
    557571      write(*,*)
    558572
    559       ENDIF ! of if (Lmodif == 1)
     573      ENDIF ! of if (Lmodif >= 1)
    560574
    561575!-----------------------------------------------------------------------
Note: See TracChangeset for help on using the changeset viewer.