Changeset 3515 for trunk


Ignore:
Timestamp:
Nov 14, 2024, 10:21:27 AM (7 days ago)
Author:
emillour
Message:

Generic PCM:
Add a controle_descriptor to restartfi.nc file, describing contents of the
controle array stored therein. Remove obsolete unused variables "lmixmin"
and "emin_turb" in the process.
EM

Location:
trunk/LMDZ.GENERIC
Files:
6 edited

Legend:

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

    r3436 r3515  
    19851985Updated version of "volcano.F90" : add setting duration of eruption
    19861986also added a vocano.def example in deftank
     1987
     1988== 14/11/2024 == EM
     1989Add a controle_descriptor to restartfi.nc file, describing contents of the
     1990controle array stored therein. Remove obsolete unused variables "lmixmin"
     1991and "emin_turb" in the process.
  • trunk/LMDZ.GENERIC/libf/phystd/dyn1d/rcm1d.F

    r3441 r3515  
    1717      use geometry_mod, only: init_geometry
    1818      use planete_mod, only: apoastr,periastr,year_day,peri_day,
    19      &         obliquit,nres,z0,lmixmin,emin_turb,coefvis,coefir,
     19     &         obliquit,nres,z0,coefvis,coefir,
    2020     &         timeperi,e_elips,p_elips
    2121      use comcstfi_mod, only: pi, cpp, rad, g, r,
     
    239239c     --------------------------------------
    240240      z0 =  1.e-2                ! surface roughness (m) ~0.01
    241       emin_turb = 1.e-6          ! energie minimale ~1.e-8
    242       lmixmin = 30               ! longueur de melange ~100
    243241 
    244242c     propriete optiques des calottes et emissivite du sol
  • trunk/LMDZ.GENERIC/libf/phystd/iostart.F90

    r3311 r3515  
    1616    INTEGER,SAVE :: idim7 ! "Time" dimension
    1717    INTEGER,SAVE :: idim8 ! "ocean_layers" dimension
     18!$OMP THREADPRIVATE(idim1,idim2,idim3,idim4,idim5,idim6,idim7,idim8)
     19    INTEGER,SAVE :: idim10 ! "descriptor" dimension
     20    INTEGER,SAVE :: idim11 ! "description_size" dimension
    1821    INTEGER,SAVE :: timeindex ! current time index (for time-dependent fields)
    19 !$OMP THREADPRIVATE(idim1,idim2,idim3,idim4,idim5,idim6,idim7,timeindex)
     22!$OMP THREADPRIVATE(idim10,idim11,timeindex)
    2023    INTEGER,PARAMETER :: length=100 ! size of tab_cntrl array
    21    
     24    INTEGER,PARAMETER :: ldscrpt = 35 ! size of dscrpt_tab_cntrl array
     25    INTEGER,PARAMETER :: ndscrpt = 50 ! size of characters in dscrpt_tab_cntrl array
     26   
    2227    INTERFACE get_field
    2328      MODULE PROCEDURE Get_field_r1,Get_field_r2,Get_field_r3
     
    3338
    3439    INTERFACE put_var
    35       MODULE PROCEDURE put_var_r0,put_var_r1,put_var_r2,put_var_r3
     40      MODULE PROCEDURE put_var_r0,put_var_r1,put_var_r2,put_var_r3,put_var_c1
    3641    END INTERFACE put_var
    3742
    38     PUBLIC nid_start, length
     43    PUBLIC nid_start, length, ldscrpt, ndscrpt
    3944    PUBLIC get_field,get_var,put_field,put_var
    4045    PUBLIC inquire_dimension, inquire_dimension_length
     
    5661        write(*,*)'open_startphy: problem opening file '//trim(filename)
    5762        write(*,*)trim(nf90_strerror(ierr))
    58         CALL ABORT
     63        CALL abort_physic("open_startphy","Cannot open file",1)
    5964      ENDIF
    6065    ENDIF
     
    120125                  //trim(field_name)
    121126        write(*,*)trim(nf90_strerror(ierr))
    122         CALL ABORT
     127        CALL abort_physic("inquire_field_ndims","Failed to get ndims",1)
    123128      ENDIF
    124129    ENDIF
     
    171176                  //trim(field_name)
    172177        write(*,*)trim(nf90_strerror(ierr))
    173         CALL ABORT
     178        CALL abort_physic("inquire_field_ndims","Failed to get length",1)
    174179      ENDIF
    175180    ENDIF
     
    430435        IF (ierr/=NF90_NOERR) THEN
    431436          PRINT*, 'phyetat0: Failed loading <'//trim(var_name)//'>'
    432           CALL abort
     437          CALL abort_physic("get_var_rgen","Failed to read variable",1)
    433438        ENDIF
    434439        tmp_found=.TRUE.
     
    450455      IF (.NOT. tmp_found) THEN
    451456        PRINT*, 'phyetat0: Variable <'//trim(var_name)//'> not found'
    452         CALL abort
     457        CALL abort_physic("get_var_rgen","Failed to read variable",1)
    453458      ENDIF
    454459    ENDIF
     
    480485                          nid_restart)
    481486        IF (ierr/=NF90_NOERR) THEN
    482           write(*,*)'open_restartphy: problem creating file '//trim(filename)
     487          write(*,*)'create_restartphy: problem creating file '//trim(filename)
    483488          write(*,*)trim(nf90_strerror(ierr))
    484           CALL ABORT
     489          CALL abort_physic("create_restartphy","Failed creating file",1)
    485490        ENDIF
    486491
     
    488493                        "Physics start file")
    489494      IF (ierr/=NF90_NOERR) THEN
    490         write(*,*)'open_restartphy: problem writing title '
     495        write(*,*)'create_restartphy: problem writing title '
    491496        write(*,*)trim(nf90_strerror(ierr))
    492497      ENDIF
     
    494499      ierr=NF90_DEF_DIM(nid_restart,"index",length,idim1)
    495500      IF (ierr/=NF90_NOERR) THEN
    496         write(*,*)'open_restartphy: problem defining index dimension '
    497         write(*,*)trim(nf90_strerror(ierr))
    498         CALL ABORT
     501        write(*,*)'create_restartphy: problem defining index dimension '
     502        write(*,*)trim(nf90_strerror(ierr))
     503        CALL abort_physic("create_restartphy","Failed defining index",1)
    499504      ENDIF
    500505     
    501506      ierr=NF90_DEF_DIM(nid_restart,"physical_points",klon_glo,idim2)
    502507      IF (ierr/=NF90_NOERR) THEN
    503         write(*,*)'open_restartphy: problem defining physical_points dimension '
    504         write(*,*)trim(nf90_strerror(ierr))
    505         CALL ABORT
     508        write(*,*)'create_restartphy: problem defining physical_points dimension '
     509        write(*,*)trim(nf90_strerror(ierr))
     510        CALL abort_physic("create_restartphy","Failed defining physical_points",1)
    506511      ENDIF
    507512     
    508513      ierr=NF90_DEF_DIM(nid_restart,"subsurface_layers",nsoilmx,idim3)
    509514      IF (ierr/=NF90_NOERR) THEN
    510         write(*,*)'open_restartphy: problem defining subsurface_layers dimension '
    511         write(*,*)trim(nf90_strerror(ierr))
    512         CALL ABORT
     515        write(*,*)'create_restartphy: problem defining subsurface_layers dimension '
     516        write(*,*)trim(nf90_strerror(ierr))
     517        CALL abort_physic("create_restartphy","Failed defining subsurface_layers",1)
    513518      ENDIF
    514519     
    515520      ierr=NF90_DEF_DIM(nid_restart,"nlayer_plus_1",klevp1,idim4)
    516521      IF (ierr/=NF90_NOERR) THEN
    517         write(*,*)'open_restartphy: problem defining nlayer_plus_1 dimension '
    518         write(*,*)trim(nf90_strerror(ierr))
    519         CALL ABORT
     522        write(*,*)'create_restartphy: problem defining nlayer_plus_1 dimension '
     523        write(*,*)trim(nf90_strerror(ierr))
     524        CALL abort_physic("create_restartphy","Failed defining nlayer_plus_1",1)
    520525      ENDIF
    521526     
     
    524529        ierr=NF90_DEF_DIM(nid_restart,"number_of_advected_fields",nqtot,idim5)
    525530        IF (ierr/=NF90_NOERR) THEN
    526           write(*,*)'open_restartphy: problem defining number_of_advected_fields dimension '
     531          write(*,*)'create_restartphy: problem defining number_of_advected_fields dimension '
    527532          write(*,*)trim(nf90_strerror(ierr))
    528           CALL ABORT
     533          CALL abort_physic("create_restartphy","Failed defining number_of_advected_fields",1)
    529534        ENDIF
    530535      endif
     
    532537      ierr=NF90_DEF_DIM(nid_restart,"nlayer",klev,idim6)
    533538      IF (ierr/=NF90_NOERR) THEN
    534         write(*,*)'open_restartphy: problem defining nlayer dimension '
    535         write(*,*)trim(nf90_strerror(ierr))
    536         CALL ABORT
     539        write(*,*)'create_restartphy: problem defining nlayer dimension '
     540        write(*,*)trim(nf90_strerror(ierr))
     541        CALL abort_physic("create_restartphy","Failed defining nlayer",1)
    537542      ENDIF
    538543     
    539544      ierr=NF90_DEF_DIM(nid_restart,"Time",NF90_UNLIMITED,idim7)
    540545      IF (ierr/=NF90_NOERR) THEN
    541         write(*,*)'open_restartphy: problem defining Time dimension '
    542         write(*,*)trim(nf90_strerror(ierr))
    543         CALL ABORT
     546        write(*,*)'create_restartphy: problem defining Time dimension '
     547        write(*,*)trim(nf90_strerror(ierr))
     548        CALL abort_physic("create_restartphy","Failed defining Time",1)
    544549      ENDIF
    545550
    546551      ierr=NF90_DEF_DIM(nid_restart,"ocean_layers",nslay,idim8)
    547552      IF (ierr/=NF90_NOERR) THEN
    548         write(*,*)'open_restartphy: problem defining oceanic layer dimension '
    549         write(*,*)trim(nf90_strerror(ierr))
    550         CALL ABORT
    551       ENDIF
    552 
     553        write(*,*)'create_restartphy: problem defining oceanic layer dimension '
     554        write(*,*)trim(nf90_strerror(ierr))
     555        CALL abort_physic("create_restartphy","Failed defining nslay",1)
     556      ENDIF
     557
     558      ierr=NF90_DEF_DIM(nid_restart,"descriptor",ldscrpt,idim10)
     559      IF (ierr/=NF90_NOERR) THEN
     560        write(*,*)'create_restartphy: problem defining descriptor dimension '
     561        write(*,*)trim(nf90_strerror(ierr))
     562        CALL abort_physic("create_restartphy","Failed defining descriptor",1)
     563      ENDIF
     564     
     565      ierr=NF90_DEF_DIM(nid_restart,"description_size",ndscrpt,idim11)
     566      IF (ierr/=NF90_NOERR) THEN
     567        write(*,*)'create_restartphy: problem defining description_size dimension '
     568        write(*,*)trim(nf90_strerror(ierr))
     569        CALL abort_physic("create_restartphy","Failed defining description_size",1)
     570      ENDIF
    553571
    554572      ierr=NF90_ENDDEF(nid_restart)
    555573      IF (ierr/=NF90_NOERR) THEN
    556         write(*,*)'open_restartphy: problem ending definition mode '
    557         write(*,*)trim(nf90_strerror(ierr))
    558         CALL ABORT
     574        write(*,*)'create_restartphy: problem ending definition mode '
     575        write(*,*)trim(nf90_strerror(ierr))
     576        CALL abort_physic("create_restartphy","Failed ending definition mode",1)
    559577      ENDIF
    560578    ENDIF
     
    575593          write(*,*)'open_restartphy: problem opening file '//trim(filename)
    576594          write(*,*)trim(nf90_strerror(ierr))
    577           CALL ABORT
     595          CALL abort_physic("open_restartphy","Failed opening file",1)
    578596        ENDIF
    579597    ENDIF
     
    886904        PRINT *, "Error phyredem(put_field_rgen) : wrong dimension for ",trim(field_name)
    887905        write(*,*) "  field_size =",field_size
    888         CALL ABORT
     906        CALL abort_physic("put_field_rgen","wrong field dimension",1)
    889907      ENDIF
    890908
     
    893911        write(*,*) " Error phyredem(put_field_rgen) : failed writing ",trim(field_name)
    894912        write(*,*)trim(nf90_strerror(ierr))
    895         call abort
     913        CALL abort_physic("put_field_rgen","Failed writing field",1)
    896914      endif
    897915
     
    9991017          write(*,*)'put_var_rgen: problem writing Time'
    10001018          write(*,*)trim(nf90_strerror(ierr))
    1001           CALL ABORT
     1019          CALL abort_physic("put_var_rgen","Failed to write Time",1)
    10021020        ENDIF
    10031021        return ! nothing left to do
     
    10141032        PRINT *, "put_var_rgen error : wrong dimension"
    10151033        write(*,*) "  var_size =",var_size
    1016         CALL abort
     1034        CALL abort_physic("put_var_rgen","Wrong variable dimension",1)
    10171035
    10181036      ENDIF ! of IF (var_size==length) THEN
     
    10351053        write(*,*)'put_var_rgen: problem writing '//trim(var_name)
    10361054        write(*,*)trim(nf90_strerror(ierr))
    1037         CALL ABORT
     1055        CALL abort_physic("put_var_rgen","Failed writing variable",1)
    10381056      ENDIF
    10391057    ENDIF ! of IF (is_master)
     
    10411059  END SUBROUTINE put_var_rgen     
    10421060
     1061  SUBROUTINE put_var_c1(var_name,title,var)
     1062  ! Put a vector of characters in file
     1063
     1064  USE netcdf, only: NF90_REDEF, NF90_DEF_VAR, NF90_ENDDEF, NF90_PUT_VAR, &
     1065                    NF90_CHAR, &
     1066                    NF90_PUT_ATT, NF90_NOERR, nf90_strerror, &
     1067                    nf90_inq_dimid, nf90_inquire_dimension, NF90_INQ_VARID
     1068  USE mod_phys_lmdz_para, only: is_master
     1069
     1070   IMPLICIT NONE
     1071     CHARACTER(LEN=*),INTENT(IN) :: var_name
     1072     CHARACTER(LEN=*),INTENT(IN) :: title
     1073     CHARACTER(LEN=*),INTENT(IN) :: var(:)
     1074
     1075     INTEGER :: ierr
     1076     INTEGER :: nvarid
     1077     INTEGER :: idim1d_1, idim1d_2
     1078     INTEGER :: var_size
     1079
     1080    IF (is_master) THEN
     1081
     1082      var_size = size(var)
     1083      IF (var_size==ldscrpt) THEN
     1084        ! We know it is a "controle descriptor" kind of 1D array
     1085        idim1d_1=idim11
     1086        idim1d_2=idim10
     1087      ELSE
     1088        PRINT *, "put_var_cgen error : wrong dimension"
     1089        write(*,*) "  var_size =",var_size
     1090        CALL abort_physic("put_var_cgen","Wrong variable dimension",1)
     1091
     1092      ENDIF ! of IF (var_size==length) THEN
     1093
     1094      ! Swich to NetCDF define mode
     1095      ierr=NF90_REDEF (nid_restart)
     1096      ! Define the variable
     1097      ierr=NF90_DEF_VAR(nid_restart,var_name,NF90_CHAR,(/idim1d_1,idim1d_2/),nvarid)
     1098      ! Add a "title" attribute
     1099      IF (LEN_TRIM(title)>0) ierr=NF90_PUT_ATT(nid_restart,nvarid,"title",title)
     1100      ! Swich out of define mode
     1101      ierr=NF90_ENDDEF(nid_restart)
     1102      ! Write variable to file
     1103      ierr=NF90_PUT_VAR(nid_restart,nvarid,var)
     1104      IF (ierr/=NF90_NOERR) THEN
     1105        write(*,*)'put_var_cgen: problem writing '//trim(var_name)
     1106        write(*,*)trim(nf90_strerror(ierr))
     1107        CALL abort_physic("put_var_cgen","Failed writing variable",1)
     1108      ENDIF
     1109    ENDIF ! of IF (is_master)
     1110
     1111  END SUBROUTINE put_var_c1
     1112
    10431113END MODULE iostart
  • trunk/LMDZ.GENERIC/libf/phystd/phyredem.F90

    r3397 r3515  
    1515                       iceradius, dtemisice, phisfi
    1616  use iostart, only : create_restartphy, close_restartphy, &
    17                       put_var, put_field, length
     17                      put_var, put_field, length, ldscrpt, ndscrpt
    1818  use mod_grid_phy_lmdz, only : klon_glo
    1919  use planete_mod, only: year_day, periastr, apoastr, peri_day, &
    20                          obliquit, z0, lmixmin, emin_turb
     20                         obliquit, z0
    2121  use comcstfi_mod, only: rad, omeg, g, mugaz, rcp
    2222  use time_phylmdz_mod, only: daysec
     
    4343  real,intent(in) :: pzthe(ngrid)
    4444 
     45  character(ndscrpt), dimension(ldscrpt), parameter :: dscrpt_tab_cntrl = (/ &
     46      "(1)  Number of atmospheric columns in physics     ", &
     47      "(2)  Number of atmospheric layers                 ", &
     48      "(3)  Final day                                    ", &
     49      "(4)  Final time of day                            ", &
     50      "(5)  Planet radius (m)                            ", &
     51      "(6)  Rotation rate (rad.s-1)                      ", &
     52      "(7)  Gravity (m.s-2)                              ", &
     53      "(8)  Molar mass of the atmosphere (g.mol-1)       ", &
     54      "(9)  = r/Cp           (=kappa in the dynamics)    ", &
     55      "(10) Length of a solar day (s)                    ", &
     56      "(11) Physics time step (s)                        ", &
     57      "(12) -                                            ", &
     58      "(13) -                                            ", &
     59      "(14) Length of year (in solar days)               ", &
     60      "(15) Minimum star-planet distance (AU)            ", &
     61      "(16) Maximum star-planet distance (AU)            ", &
     62      "(17) Date of periastro (sols since N. spring)     ", &
     63      "(18) Obliquity of the planet (deg)                ", &
     64      "(19) Default surface roughness (m)                ", &
     65      "(20) -                                            ", &
     66      "(21) -                                            ", &
     67      "(22) -                                            ", &
     68      "(23) -                                            ", &
     69      "(24) Emissivity of northern cap ~0.95             ", &
     70      "(25) Emissivity of southern cap ~0.95             ", &
     71      "(26) Emissivity of martian soil ~.95              ", &
     72      "(27) -                                            ", &
     73      "(28) -                                            ", &
     74      "(29) -                                            ", &
     75      "(30) -                                            ", &
     76      "(31) Mean scat radius of CO2 snow (north)         ", &
     77      "(32) Mean scat radius of CO2 snow (south)         ", &
     78      "(33) Time scale for snow metamorphism (north)     ", &
     79      "(34) Time scale for snow metamorphism (south)     ", &
     80      "(35) Soil volumetric heat capacity                "/)
    4581  real :: tab_cntrl(length) ! nb "length=100" defined in iostart module
    4682 
     
    5490!cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
    5591! Informations on the physics grid
    56   tab_cntrl(1) = float(klon_glo)  ! number of nodes on physics grid
     92  tab_cntrl(1) = float(klon_glo)  ! number of atmospheric columns in physics
    5793  tab_cntrl(2) = float(nlay) ! number of atmospheric layers
    5894  tab_cntrl(3) = day_ini + int(time)         ! final day
    5995  tab_cntrl(4) = time -int(time)            ! final time of day
    6096
    61 ! Informations about Mars, used by dynamics and physics
    62   tab_cntrl(5) = rad      ! radius of Mars (m) ~3397200
     97! Informations about the planet, used by dynamics and physics
     98  tab_cntrl(5) = rad      ! planet radius (m)
    6399  tab_cntrl(6) = omeg     ! rotation rate (rad.s-1)
    64   tab_cntrl(7) = g        ! gravity (m.s-2) ~3.72
    65   tab_cntrl(8) = mugaz    ! Molar mass of the atmosphere (g.mol-1) ~43.49
    66   tab_cntrl(9) = rcp      !  = r/cp  ~0.256793 (=kappa dans dynamique)
    67   tab_cntrl(10) = daysec  ! length of a sol (s)  ~88775
    68 
    69   tab_cntrl(11) = phystep  ! time step in the physics
     100  tab_cntrl(7) = g        ! gravity (m.s-2)
     101  tab_cntrl(8) = mugaz    ! Molar mass of the atmosphere (g.mol-1)
     102  tab_cntrl(9) = rcp      !  = r/cp  (=kappa in the dynamics)
     103  tab_cntrl(10) = daysec  ! length of a solar day (s)
     104
     105  tab_cntrl(11) = phystep  ! physics time step (s)
    70106  tab_cntrl(12) = 0.
    71107  tab_cntrl(13) = 0.
    72108
    73 ! Informations about Mars, only for physics
    74   tab_cntrl(14) = year_day  ! length of year (sols) ~668.6
    75   tab_cntrl(15) = periastr  ! min. star-planet distance (AU)
    76   tab_cntrl(16) = apoastr   ! max. star-planet distance (AU)
     109! Informations about the planet, only for physics
     110  tab_cntrl(14) = year_day  ! length of year (in solar days)
     111  tab_cntrl(15) = periastr  ! minimum star-planet distance (AU)
     112  tab_cntrl(16) = apoastr   ! maximum star-planet distance (AU)
    77113  tab_cntrl(17) = peri_day  ! date of periastron (sols since N. spring)
    78   tab_cntrl(18) = obliquit  ! Obliquity of the planet (deg) ~23.98
     114  tab_cntrl(18) = obliquit  ! Obliquity of the planet (deg)
    79115
    80116! Boundary layer and turbulence
    81   tab_cntrl(19) = z0        ! surface roughness (m) ~0.01
    82   tab_cntrl(20) = lmixmin   ! mixing length ~100
    83   tab_cntrl(21) = emin_turb ! minimal energy ~1.e-8
     117  tab_cntrl(19) = z0        ! surface roughness (m)
     118!  tab_cntrl(20) = lmixmin   ! mixing length (m)
     119!  tab_cntrl(21) = emin_turb ! minimal energy
    84120
    85121! Optical properties of polar caps and ground emissivity
     
    98134  tab_cntrl(35) = volcapa ! soil volumetric heat capacity
    99135
     136  ! Write the controle array
    100137  call put_var("controle","Control parameters",tab_cntrl)
     138 
     139  ! Write the controle array descriptor
     140  call put_var("controle_descriptor",&
     141               "Description of control parameters",dscrpt_tab_cntrl)
    101142 
    102143  ! Write the mid-layer depths
  • trunk/LMDZ.GENERIC/libf/phystd/planete_mod.F90

    r1520 r3515  
    1010  REAL,SAVE :: nres ! tidal resonance ratio
    1111  REAL,SAVE :: z0 ! surface roughness (m)
    12   REAL,SAVE :: lmixmin ! mixing length
    13   REAL,SAVE :: emin_turb ! minimal energy
    14 !$OMP THREADPRIVATE(nres,z0,lmixmin,emin_turb)
     12!$OMP THREADPRIVATE(nres,z0)
    1513  REAL,SAVE :: coefvis
    1614  REAL,SAVE :: coefir
  • trunk/LMDZ.GENERIC/libf/phystd/tabfi_mod.F90

    r2635 r3515  
    5858      use mod_phys_lmdz_para, only: is_parallel
    5959      use planete_mod, only: year_day, periastr, apoastr, peri_day, &
    60                              obliquit, z0, lmixmin, emin_turb
     60                             obliquit, z0
    6161      use comcstfi_mod, only: rad, omeg, g, mugaz, rcp, cpp, r
    6262      use time_phylmdz_mod, only: dtphys, daysec
     
    141141! boundary layer and turbulence
    142142        z0=1.e-2 ! surface roughness length (m)
    143         lmixmin=30
    144         emin_turb=1.e-6
     143
    145144! optical properties of polar caps and ground emissivity
    146145        emisice(:)=0
     
    192191! boundary layer and turbulence
    193192      z0 = tab_cntrl(tab0+19)
    194       lmixmin = tab_cntrl(tab0+20)
    195       emin_turb = tab_cntrl(tab0+21)
    196193! optical properties of polar caps and ground emissivity
    197194      emisice(1) = tab_cntrl(tab0+24)
     
    244241
    245242      write(*,6) '(19)             z0',tab_cntrl(tab0+19),z0
    246       write(*,6) '(21)      emin_turb',tab_cntrl(tab0+21),emin_turb
    247       write(*,5) '(20)        lmixmin',tab_cntrl(tab0+20),lmixmin
    248243
    249244      write(*,5) '(26)        emissiv',tab_cntrl(tab0+26),emissiv
     
    279274      write(*,*) '(3)          day_ini : Initial day (=0 at Ls=0)'
    280275      write(*,*) '(19)              z0 :  surface roughness (m)'
    281       write(*,*) '(21)       emin_turb :  minimal energy (PBL)'
    282       write(*,*) '(20)         lmixmin : mixing length (PBL)'
    283276      write(*,*) '(26)         emissiv : ground emissivity'
    284277      write(*,*) '(24 et 25)   emisice : CO2 ice max emissivity '
     
    331324          write(*,*) ' z0 (new value):',z0
    332325
    333         else if (modif(1:len_trim(modif)) .eq. 'emin_turb') then
    334           write(*,*) 'current value:',emin_turb
    335           write(*,*) 'enter new value:'
    336  103      read(*,*,iostat=ierr) emin_turb
    337           if(ierr.ne.0) goto 103
    338           write(*,*) ' '
    339           write(*,*) ' emin_turb (new value):',emin_turb
    340 
    341         else if (modif(1:len_trim(modif)) .eq. 'lmixmin') then
    342           write(*,*) 'current value:',lmixmin
    343           write(*,*) 'enter new value:'
    344  104      read(*,*,iostat=ierr) lmixmin
    345           if(ierr.ne.0) goto 104
    346           write(*,*) ' '
    347           write(*,*) ' lmixmin (new value):',lmixmin
    348 
    349326        else if (modif(1:len_trim(modif)) .eq. 'emissiv') then
    350327          write(*,*) 'current value:',emissiv
     
    551528 
    552529      write(*,6) '(19)             z0',tab_cntrl(tab0+19),z0
    553       write(*,6) '(21)      emin_turb',tab_cntrl(tab0+21),emin_turb
    554       write(*,5) '(20)        lmixmin',tab_cntrl(tab0+20),lmixmin
    555530 
    556531      write(*,5) '(26)        emissiv',tab_cntrl(tab0+26),emissiv
Note: See TracChangeset for help on using the changeset viewer.