Ignore:
Timestamp:
Apr 5, 2022, 3:44:30 PM (2 years ago)
Author:
dcugnet
Message:
  • New water names: H2Ov, H2Ol, H2Oi, H2Or -> H2O_g, H2O_l, H2O_s, H2O_r.
  • Corrections for the lOldCode=.FALSE., not activated yet.
Location:
LMDZ6/trunk/libf/dyn3d
Files:
2 edited
1 moved

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/dyn3d/dynetat0.F90

    r4119 r4120  
    66! Purpose: Initial state reading.
    77!-------------------------------------------------------------------------------
    8   USE infotrac,    ONLY: nqtot, tracers, iqiso, iso_indnum, tnat, alpha_ideal, &
    9                          ok_isotopes
    10   USE strings_mod, ONLY: maxlen
    11   USE netcdf,      ONLY: NF90_OPEN,  NF90_NOWRITE, NF90_INQ_VARID, NF90_NoErr, &
    12                          NF90_CLOSE, NF90_GET_VAR
     8  USE infotrac,    ONLY: nqtot, tracers, niso, iqiso, iso_indnum, iso_num, tnat, alpha_ideal, ok_isotopes, iH2O
     9  USE strings_mod, ONLY: maxlen, msg, strStack, real2str
     10  USE netcdf,      ONLY: NF90_OPEN,  NF90_NOWRITE, NF90_INQ_VARID, &
     11                         NF90_CLOSE, NF90_GET_VAR, NF90_NoErr
     12  USE readTracFiles_mod, ONLY: new2oldName
    1313  USE control_mod, ONLY: planet_type
    1414  USE assert_eq_m, ONLY: assert_eq
     
    3838!===============================================================================
    3939! Local variables:
    40   CHARACTER(LEN=maxlen) :: msg, var, modname
     40  CHARACTER(LEN=maxlen) :: mesg, var, modname, oldVar
    4141  INTEGER, PARAMETER :: length=100
    4242  INTEGER :: iq, fID, vID, idecal, iqParent, iName, iZone, iPhase
     
    5353!!!     .... while keeping everything OK for LMDZ EARTH
    5454  IF(planet_type=="generic") THEN
    55     WRITE(lunout,*)'NOTE NOTE NOTE : Planeto-like start files'
     55    CALL msg('NOTE NOTE NOTE : Planeto-like start files', modname)
    5656    idecal = 4
    5757    annee_ref  = 2000
    5858  ELSE
    59     WRITE(lunout,*)'NOTE NOTE NOTE : Earth-like start files'
     59    CALL msg('NOTE NOTE NOTE : Earth-like start files', modname)
    6060    idecal = 5
    6161    annee_ref  = tab_cntrl(5)
     
    101101
    102102!-------------------------------------------------------------------------------
    103   WRITE(lunout,*)TRIM(modname)//': rad,omeg,g,cpp,kappa',rad,omeg,g,cpp,kappa
     103  CALL msg('rad, omeg, g, cpp, kappa = '//TRIM(strStack(real2str([rad,omeg,g,cpp,kappa]))), modname)
    104104  CALL check_dim(im,iim,'im','im')
    105105  CALL check_dim(jm,jjm,'jm','jm')
     
    114114  var="temps"
    115115  IF(NF90_INQ_VARID(fID,var,vID)/=NF90_NoErr) THEN
    116     WRITE(lunout,*)TRIM(modname)//": missing field <temps>"
    117     WRITE(lunout,*)TRIM(modname)//": trying with <Time>"; var="Time"
     116    CALL msg('missing field <temps> ; trying with <Time>', modname)
     117    var="Time"
    118118    CALL err(NF90_INQ_VARID(fID,var,vID),"inq",var)
    119119  END IF
     
    128128!--- Tracers
    129129  DO iq=1,nqtot
    130     var=TRIM(tracers(iq)%name)
    131     IF(NF90_INQ_VARID(fID,var,vID)==NF90_NoErr) THEN
    132       CALL err(NF90_GET_VAR(fID,vID,q(:,:,:,iq)),"get",var); CYCLE
     130    var = tracers(iq)%name
     131    oldVar = new2oldName(var)
     132    !--------------------------------------------------------------------------------------------------------------------------
     133    IF(NF90_INQ_VARID(fID, var, vID) == NF90_NoErr) THEN                                 !=== REGULAR CASE
     134      CALL err(NF90_GET_VAR(fID,vID,q(:,:,:,iq)),"get",var)
     135    !--------------------------------------------------------------------------------------------------------------------------
     136    ELSE IF(NF90_INQ_VARID(fID, oldVar, vID) == NF90_NoErr) THEN                         !=== OLD NAME
     137      CALL msg('Tracer <'//TRIM(var)//'> is missing => initialized to <'//TRIM(oldVar)//'>', modname)
     138      CALL err(NF90_GET_VAR(fID,vID,q(:,:,:,iq)),"get",oldVar)
     139    !--------------------------------------------------------------------------------------------------------------------------
     140#ifdef INCA
     141    ELSE IF(NF90_INQ_VARID(fID, 'OX',   vID) == NF90_NoErr .AND. var == 'O3') THEN       !=== INCA: OX INSTEAD OF O3
     142      CALL msg('Tracer <O3> is missing => initialized to <OX>', modname)
     143      CALL err(NF90_GET_VAR(fID,vID,q(:,:,:,iq)),"get",'OX')
     144    !--------------------------------------------------------------------------------------------------------------------------
     145#endif
     146    ELSE IF(tracers(iq)%iso_iGroup == iH2O .AND. niso > 0) THEN                          !=== WATER ISOTOPES
     147!     iName    = tracers(iq)%iso_iName  ! (next commit)
     148      iName    = iso_num(iq)
     149      iPhase   = tracers(iq)%iso_iPhase
     150      iqParent = tracers(iq)%iqParent
     151      IF(tracers(iq)%iso_iZone == 0) THEN
     152         CALL msg('Tracer <'//TRIM(var)//'> is missing => initialized with a simplified Rayleigh distillation law.', modname)
     153         q(:,:,:,iq) = q(:,:,:,iqParent)*tnat(iName)*(q(:,:,:,iqParent)/30.e-3)**(alpha_ideal(iName)-1.)
     154      ELSE
     155         CALL msg('Tracer <'//TRIM(var)//'> is missing => initialized to its parent isotope concentration.', modname)
     156         q(:,:,:,iq) = q(:,:,:,iqiso(iso_indnum(iq),iPhase))
     157      END IF
     158    !--------------------------------------------------------------------------------------------------------------------------
     159    ELSE                                                                                 !=== MISSING: SET TO 0
     160      CALL msg('Tracer <'//TRIM(var)//'> is missing => initialized to zero', modname)
     161      q(:,:,:,iq)=0.
     162    !--------------------------------------------------------------------------------------------------------------------------
    133163    END IF
    134     WRITE(lunout,*)TRIM(modname)//": Tracer <"//TRIM(var)//"> is missing"
    135     WRITE(lunout,*)"         It is hence initialized to zero"
    136     q(:,:,:,iq)=0.
    137    !--- CRisi: for isotops, theoretical initialization using very simplified
    138    !           Rayleigh distillation law.
    139     iName = tracers(iq)%iso_iName
    140     IF(.NOT.ok_isotopes .OR. iName<=0) CYCLE
    141     iZone = tracers(iq)%iso_iZone
    142     iPhase= tracers(iq)%iso_iPhase
    143     iqParent = tracers(iq)%iqParent
    144     IF(iZone==0) q(:,:,:,iq) = q(:,:,:,iqParent)*tnat(iName)    &
    145                              *(q(:,:,:,iqParent)/30.e-3)**(alpha_ideal(iName)-1.)
    146     IF(iZone==1) q(:,:,:,iq) = q(:,:,:,iqiso(iso_indnum(iq),iPhase))
    147164  END DO
    148165
     
    162179    s1='value of '//TRIM(str1)//' ='
    163180    s2=' read in starting file differs from parametrized '//TRIM(str2)//' ='
    164     WRITE(msg,'(10x,a,i4,2x,a,i4)')TRIM(ADJUSTL(s1)),n1,TRIM(ADJUSTL(s2)),n2
    165     CALL ABORT_gcm(TRIM(modname),TRIM(msg),1)
     181    WRITE(mesg,'(10x,a,i4,2x,a,i4)')TRIM(ADJUSTL(s1)),n1,TRIM(ADJUSTL(s2)),n2
     182    CALL ABORT_gcm(TRIM(modname),TRIM(mesg),1)
    166183  END IF
    167184END SUBROUTINE check_dim
     
    198215  IF(ierr==NF90_NoERR) RETURN
    199216  SELECT CASE(typ)
    200     CASE('inq');   msg="Field <"//TRIM(nam)//"> is missing"
    201     CASE('get');   msg="Reading failed for <"//TRIM(nam)//">"
    202     CASE('open');  msg="File opening failed for <"//TRIM(nam)//">"
    203     CASE('close'); msg="File closing failed for <"//TRIM(nam)//">"
     217    CASE('inq');   mesg="Field <"//TRIM(nam)//"> is missing"
     218    CASE('get');   mesg="Reading failed for <"//TRIM(nam)//">"
     219    CASE('open');  mesg="File opening failed for <"//TRIM(nam)//">"
     220    CASE('close'); mesg="File closing failed for <"//TRIM(nam)//">"
    204221  END SELECT
    205   CALL ABORT_gcm(TRIM(modname),TRIM(msg),1)
     222  CALL ABORT_gcm(TRIM(modname),TRIM(mesg),ierr)
    206223END SUBROUTINE err
    207224
  • LMDZ6/trunk/libf/dyn3d/iniacademic.F90

    r4056 r4120  
    66  USE filtreg_mod, ONLY: inifilr
    77  USE infotrac,    ONLY: nqtot, niso_possibles, ok_isotopes, ok_iso_verif, tnat, alpha_ideal, &
    8                          iqiso, tracers, iso_indnum
     8                         iqiso, tracers, iso_indnum, iso_num
    99  USE control_mod, ONLY: day_step,planet_type
    1010  use exner_hyb_m, only: exner_hyb
     
    2222  USE temps_mod, ONLY: annee_ref, day_ini, day_ref
    2323  USE ener_mod, ONLY: etot0,ptot0,ztot0,stot0,ang0
     24  USE readTracFiles_mod, ONLY: addPhase
    2425
    2526  !   Author:    Frederic Hourdin      original: 15/01/93
     
    6263  real tetastrat ! potential temperature in the stratosphere, in K
    6364  real tetajl(jjp1,llm)
    64   INTEGER i,j,l,lsup,ij, iq, iName, iZone, iPhase, iqParent
     65  INTEGER i,j,l,lsup,ij, iq, iName, iPhase, iqParent
    6566
    6667  REAL teta0,ttp,delt_y,delt_z,eps ! Constantes pour profil de T
     
    276277           do iq=1,nqtot
    277278              q(:,:,iq)=0.
    278 !              IF(tracers(iq)%name == 'H2O'//phases_sep//'g') q(:,:,iq)=1.e-10
    279 !              IF(tracers(iq)%name == 'H2O'//phases_sep//'l') q(:,:,iq)=1.e-15
    280               IF(tracers(iq)%name == 'H2Ov') q(:,:,iq)=1.e-10
    281               IF(tracers(iq)%name == 'H2Ol') q(:,:,iq)=1.e-15
     279              IF(tracers(iq)%name == addPhase('H2O', 'g')) q(:,:,iq)=1.e-10
     280              IF(tracers(iq)%name == addPhase('H2O', 'l')) q(:,:,iq)=1.e-15
    282281
    283282              ! CRisi: init des isotopes
    284283              ! distill de Rayleigh très simplifiée
    285               iName = tracers(iq)%iso_iName
     284!             iName    = tracers(iq)%iso_iName  ! (next commit)
     285              iName    = iso_num(iq)
    286286              if (.NOT.ok_isotopes .OR. iName <= 0) CYCLE
    287               iZone    = tracers(iq)%iso_iZone
    288287              iPhase   = tracers(iq)%iso_iPhase
    289288              iqParent = tracers(iq)%iqParent
    290               if (iZone == 0) q(:,:,iq) = q(:,:,iqParent)*tnat(iName) &
    291                                         *(q(:,:,iqParent)/30.e-3)**(alpha_ideal(iName)-1)
    292               if (iZone == 1) q(:,:,iq) = q(:,:,iqiso(iso_indnum(iq),iPhase))
     289              IF(tracers(iq)%iso_iZone == 0) THEN
     290                 q(:,:,iq) = q(:,:,iqParent)*tnat(iName)*(q(:,:,iqParent)/30.e-3)**(alpha_ideal(iName)-1.)
     291              ELSE
     292                 q(:,:,iq) = q(:,:,iqiso(iso_indnum(iq),iPhase))
     293              END IF
    293294           enddo
    294295        else
  • LMDZ6/trunk/libf/dyn3d/leapfrog.F

    r3947 r4120  
    451451c+jld
    452452
    453 c  Diagnostique de conservation de l'énergie : initialisation
     453c  Diagnostique de conservation de l'energie : initialisation
    454454         IF (ip_ebil_dyn.ge.1 ) THEN
    455455          ztit='bil dyn'
     
    498498       
    499499c
    500 c  Diagnostique de conservation de l'énergie : difference
     500c  Diagnostique de conservation de l'energie : difference
    501501         IF (ip_ebil_dyn.ge.1 ) THEN
    502502          ztit='bil phys'
Note: See TracChangeset for help on using the changeset viewer.