Changeset 1670 for trunk/LMDZ.TITAN/libf


Ignore:
Timestamp:
Feb 21, 2017, 11:32:17 AM (8 years ago)
Author:
jvatant
Message:

Adapts modifs of LMDZ.GENERIC r1669 to LMDZ.TITAN

cf log r1669 :
"""
Added possibility to run without a startfi.nc file (mainly usefull for
tests with coupling with dynamico dynamical core):

  • added flag "startphy_file" flag (.false. if doing an "academic" start on the physics side).
  • turned phyetat0.F90 into module phyetat0_mod.F90
  • turned tabfi.F into module tabfi_mod.F90 and added handling of startphy_file==.false. case
  • extra initializations in physiq_mod for startphy_file==.false. case.

EM
"""
JVO

Location:
trunk/LMDZ.TITAN/libf
Files:
5 edited
2 moved

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.TITAN/libf/dynphy_lonlat/phytitan/newstart.F

    r1647 r1670  
    3535      USE temps_mod, ONLY: day_ini
    3636      USE ener_mod, ONLY: etot0,ptot0,ztot0,stot0,ang0
     37      use tabfi_mod, only: tabfi
    3738      use iniphysiq_mod, only: iniphysiq
     39      use phyetat0_mod, only: phyetat0
    3840      implicit none
    3941
     
    337339        write(*,*) 'Reading file STARTFI'
    338340        fichnom = 'startfi.nc'
    339         CALL phyetat0 (ngridmx,llm,fichnom,tab0,Lmodif,nsoilmx,
     341        CALL phyetat0(.true.,ngridmx,llm,fichnom,tab0,Lmodif,nsoilmx,
    340342     .        nqtot,day_ini,time,
    341343     .        tsurf,tsoil,emis,q2,qsurf)
  • trunk/LMDZ.TITAN/libf/dynphy_lonlat/phytitan/start2archive.F

    r1647 r1670  
    3535      USE temps_mod, ONLY: day_ini
    3636      USE iniphysiq_mod, ONLY: iniphysiq
     37      use phyetat0_mod, only: phyetat0
    3738      implicit none
    3839
     
    214215
    215216
    216       CALL phyetat0 (ngridmx,llm,fichnom,0,Lmodif,nsoilmx,nqtot,
     217      CALL phyetat0(.true.,ngridmx,llm,fichnom,0,Lmodif,nsoilmx,nqtot,
    217218     .      day_ini_fi,timefi,
    218219     .      tsurf,tsoil,emis,q2,qsurf)
  • trunk/LMDZ.TITAN/libf/phytitan/callkeys_mod.F90

    r1668 r1670  
    7474!$OMP THREADPRIVATE(iscallphys)
    7575
     76      ! do we read a startphy.nc file (default=.true.)
     77      logical,save :: startphy_file=.true.
     78!$OMP THREADPRIVATE(startphy_file)
     79
    7680END MODULE callkeys_mod
  • trunk/LMDZ.TITAN/libf/phytitan/inifis_mod.F90

    r1648 r1670  
    9595  call getin_p("iphysiq",iphysiq) ! call physics every iphysiq dyn step
    9696
     97  ! do we read a startphy.nc file? (default: .true.)
     98  call getin_p("startphy_file",startphy_file)
     99 
    97100! --------------------------------------------------------------
    98101!  Reading the "callphys.def" file controlling some key options
  • trunk/LMDZ.TITAN/libf/phytitan/phyetat0_mod.F90

    r1669 r1670  
    1 subroutine phyetat0 (ngrid,nlayer,fichnom,tab0,Lmodif,nsoil,nq, &
     1module phyetat0_mod
     2
     3implicit none
     4
     5contains
     6
     7subroutine phyetat0 (startphy_file, &
     8                     ngrid,nlayer,fichnom,tab0,Lmodif,nsoil,nq, &
    29                     day_ini,time,tsurf,tsoil, &
    310                     emis,q2,qsurf)
    411
    512
     13  use tabfi_mod, only: tabfi
    614  USE tracer_h, ONLY: noms
    715  USE surfdat_h, only: phisfi, albedodat, zmea, zstd, zsig, zgam, zthe
     
    1321
    1422!======================================================================
    15 ! Auteur(s) Z.X. Li (LMD/CNRS) date: 19930818
    16 !  Adaptation à Mars : Yann Wanherdrick
    17 ! Objet: Lecture de l etat initial pour la physique
    18 !======================================================================
    19 #include "netcdf.inc"
    20 
    21 !======================================================================
    22 !  INTEGER nbsrf !Mars nbsrf a 1 au lieu de 4
    23 !  PARAMETER (nbsrf=1) ! nombre de sous-fractions pour une maille
    24 !======================================================================
    2523!  Arguments:
    2624!  ---------
    2725!  inputs:
     26  logical,intent(in) :: startphy_file ! .true. if reading start file
    2827  integer,intent(in) :: ngrid
    2928  integer,intent(in) :: nlayer
     
    3332  integer,intent(in) :: nsoil ! # of soil layers
    3433  integer,intent(in) :: nq
    35   integer,intent(in) :: day_ini
    36   real,intent(in) :: time
     34  integer,intent(out) :: day_ini
     35  real,intent(out) :: time
    3736
    3837!  outputs:
     
    7170      INTEGER :: indextime=1 ! index of selected time, default value=1
    7271      logical :: found
     72     
     73      character(len=8) :: modname="phyetat0"
    7374
    7475!
     
    8384IF (.not. ALLOCATED(zthe)) ALLOCATE(zthe(ngrid))
    8485
    85 
    86 ! open physics initial state file:
    87 call open_startphy(fichnom)
    88 
    89 
    90 ! possibility to modify tab_cntrl in tabfi
    91 write(*,*)
    92 write(*,*) 'TABFI in phyeta0: Lmodif=',Lmodif," tab0=",tab0
    93 call tabfi (ngrid,nid_start,Lmodif,tab0,day_ini,lmax,p_rad, &
     86if (startphy_file) then
     87  ! open physics initial state file:
     88  call open_startphy(fichnom)
     89
     90  ! possibility to modify tab_cntrl in tabfi
     91  write(*,*)
     92  write(*,*) 'TABFI in phyeta0: Lmodif=',Lmodif," tab0=",tab0
     93  call tabfi (ngrid,nid_start,Lmodif,tab0,day_ini,lmax,p_rad, &
    9494                   p_omeg,p_g,p_cpp,p_mugaz,p_daysec,time)
    9595
    96 !c
    97 !c Lecture des latitudes (coordonnees):
    98 !c
    99 !      ierr = NF_INQ_VARID (nid, "latitude", nvarid)
    100 !      IF (ierr.NE.NF_NOERR) THEN
    101 !         PRINT*, 'phyetat0: Le champ <latitude> est absent'
    102 !         CALL abort
    103 !      ENDIF
    104 !#ifdef NC_DOUBLE
    105 !      ierr = NF_GET_VARA_DOUBLE(nid,nvarid,sta,ngrid,lati)
    106 !#else
    107 !      ierr = NF_GET_VARA_REAL(nid,nvarid,sta,ngrid,lati)
    108 !#endif
    109 !      IF (ierr.NE.NF_NOERR) THEN
    110 !         PRINT*, 'phyetat0: Lecture echouee pour <latitude>'
    111 !         CALL abort
    112 !      ENDIF
    113 !c
    114 !c Lecture des longitudes (coordonnees):
    115 !c
    116 !      ierr = NF_INQ_VARID (nid, "longitude", nvarid)
    117 !      IF (ierr.NE.NF_NOERR) THEN
    118 !         PRINT*, 'phyetat0: Le champ <longitude> est absent'
    119 !         CALL abort
    120 !      ENDIF
    121 !#ifdef NC_DOUBLE
    122 !      ierr = NF_GET_VARA_DOUBLE(nid,nvarid,sta,ngrid,long)
    123 !#else
    124 !      ierr = NF_GET_VARA_REAL(nid,nvarid,sta,ngrid,long)
    125 !#endif
    126 !      IF (ierr.NE.NF_NOERR) THEN
    127 !         PRINT*, 'phyetat0: Lecture echouee pour <longitude>'
    128 !         CALL abort
    129 !      ENDIF
    130 !c
    131 !c Lecture des aires des mailles:
    132 !c
    133 !      ierr = NF_INQ_VARID (nid, "area", nvarid)
    134 !      IF (ierr.NE.NF_NOERR) THEN
    135 !         PRINT*, 'phyetat0: Le champ <area> est absent'
    136 !         CALL abort
    137 !      ENDIF
    138 !#ifdef NC_DOUBLE
    139 !      ierr = NF_GET_VARA_DOUBLE(nid,nvarid,sta,ngrid,area)
    140 !#else
    141 !      ierr = NF_GET_VARA_REAL(nid,nvarid,sta,ngrid,area)
    142 !#endif
    143 !      IF (ierr.NE.NF_NOERR) THEN
    144 !         PRINT*, 'phyetat0: Lecture echouee pour <area>'
    145 !         CALL abort
    146 !      ENDIF
    147 !      xmin = 1.0E+20
    148 !      xmax = -1.0E+20
    149 !      xmin = MINVAL(area)
    150 !      xmax = MAXVAL(area)
    151 !      PRINT*,'Aires des mailles <area>:', xmin, xmax
    152 
    153 ! Load surface geopotential:
    154 call get_field("phisfi",phisfi,found)
    155 if (.not.found) then
    156   write(*,*) "phyetat0: Failed loading <phisfi>"
    157   call abort
    158 else
    159   write(*,*) "phyetat0: surface geopotential <phisfi> range:", &
    160              minval(phisfi), maxval(phisfi)
    161 endif
    162 
    163 ! Load bare ground albedo:
    164 call get_field("albedodat",albedodat,found)
    165 if (.not.found) then
    166   write(*,*) "phyetat0: Failed loading <albedodat>"
    167   call abort
    168 else
    169   write(*,*) "phyetat0: Bare ground albedo <albedodat> range:", &
     96else ! "academic" initialization of planetary parameters via tabfi
     97  call tabfi (ngrid,0,0,0,day_ini,lmax,p_rad, &
     98                   p_omeg,p_g,p_cpp,p_mugaz,p_daysec,time)
     99endif ! of if (startphy_file)
     100
     101if (startphy_file) then
     102  ! Load surface geopotential:
     103  call get_field("phisfi",phisfi,found)
     104  if (.not.found) then
     105    call abort_physic(modname,"Failed loading <phisfi>",1)
     106  endif
     107else
     108  phisfi(:)=0
     109endif ! of if (startphy_file)
     110write(*,*) "phyetat0: surface geopotential <phisfi> range:", &
     111               minval(phisfi), maxval(phisfi)
     112
     113if (startphy_file) then
     114  ! Load bare ground albedo:
     115  call get_field("albedodat",albedodat,found)
     116  if (.not.found) then
     117    call abort_physic(modname,"Failed loading <albedodat>",1)
     118  endif
     119else
     120  albedodat(:)=0.5 ! would be better to read value from def file...
     121endif ! of if (startphy_file)
     122write(*,*) "phyetat0: Bare ground albedo <albedodat> range:", &
    170123             minval(albedodat), maxval(albedodat)
    171 endif
    172124
    173125! ZMEA
    174 call get_field("ZMEA",zmea,found)
    175 if (.not.found) then
    176   write(*,*) "phyetat0: Failed loading <ZMEA>"
    177   call abort
    178 else
    179   write(*,*) "phyetat0: <ZMEA> range:", &
     126if (startphy_file) then
     127  call get_field("ZMEA",zmea,found)
     128  if (.not.found) then
     129    call abort_physic(modname,"Failed loading <ZMEA>",1)
     130  endif
     131else
     132  zmea(:)=0
     133endif ! of if (startphy_file)
     134write(*,*) "phyetat0: <ZMEA> range:", &
    180135             minval(zmea), maxval(zmea)
    181 endif
    182136
    183137! ZSTD
    184 call get_field("ZSTD",zstd,found)
    185 if (.not.found) then
    186   write(*,*) "phyetat0: Failed loading <ZSTD>"
    187   call abort
    188 else
    189   write(*,*) "phyetat0: <ZSTD> range:", &
     138if (startphy_file) then
     139  call get_field("ZSTD",zstd,found)
     140  if (.not.found) then
     141    call abort_physic(modname,"Failed loading <ZSTD>",1)
     142  endif
     143else
     144  zstd(:)=0
     145endif ! of if (startphy_file)
     146write(*,*) "phyetat0: <ZSTD> range:", &
    190147             minval(zstd), maxval(zstd)
    191 endif
    192148
    193149! ZSIG
    194 call get_field("ZSIG",zsig,found)
    195 if (.not.found) then
    196   write(*,*) "phyetat0: Failed loading <ZSIG>"
    197   call abort
    198 else
    199   write(*,*) "phyetat0: <ZSIG> range:", &
     150if (startphy_file) then
     151  call get_field("ZSIG",zsig,found)
     152  if (.not.found) then
     153    call abort_physic(modname,"Failed loading <ZSIG>",1)
     154  endif
     155else
     156  zsig(:)=0
     157endif ! of if (startphy_file)
     158write(*,*) "phyetat0: <ZSIG> range:", &
    200159             minval(zsig), maxval(zsig)
    201 endif
    202160
    203161! ZGAM
    204 call get_field("ZGAM",zgam,found)
    205 if (.not.found) then
    206   write(*,*) "phyetat0: Failed loading <ZGAM>"
    207   call abort
    208 else
    209   write(*,*) "phyetat0: <ZGAM> range:", &
     162if (startphy_file) then
     163  call get_field("ZGAM",zgam,found)
     164  if (.not.found) then
     165    call abort_physic(modname,"Failed loading <ZGAM>",1)
     166  endif
     167else
     168  zgam(:)=0
     169endif ! of if (startphy_file)
     170write(*,*) "phyetat0: <ZGAM> range:", &
    210171             minval(zgam), maxval(zgam)
    211 endif
    212172
    213173! ZTHE
    214 call get_field("ZTHE",zthe,found)
    215 if (.not.found) then
    216   write(*,*) "phyetat0: Failed loading <ZTHE>"
    217   call abort
    218 else
    219   write(*,*) "phyetat0: <ZTHE> range:", &
     174if (startphy_file) then
     175  call get_field("ZTHE",zthe,found)
     176  if (.not.found) then
     177    call abort_physic(modname,"Failed loading <ZTHE>",1)
     178  endif
     179else
     180  zthe(:)=0
     181endif ! of if (startphy_file)
     182write(*,*) "phyetat0: <ZTHE> range:", &
    220183             minval(zthe), maxval(zthe)
    221 endif
    222184
    223185! Surface temperature :
    224 call get_field("tsurf",tsurf,found,indextime)
    225 if (.not.found) then
    226   write(*,*) "phyetat0: Failed loading <tsurf>"
    227   call abort
    228 else
    229   write(*,*) "phyetat0: Surface temperature <tsurf> range:", &
     186if (startphy_file) then
     187  call get_field("tsurf",tsurf,found,indextime)
     188  if (.not.found) then
     189    call abort_physic(modname,"Failed loading <tsurf>",1)
     190  endif
     191else
     192  tsurf(:)=0 ! will be updated afterwards in physiq !
     193endif ! of if (startphy_file)
     194write(*,*) "phyetat0: Surface temperature <tsurf> range:", &
    230195             minval(tsurf), maxval(tsurf)
    231 endif
    232196
    233197! Surface emissivity
    234 call get_field("emis",emis,found,indextime)
    235 if (.not.found) then
    236   write(*,*) "phyetat0: Failed loading <emis>"
    237   call abort
    238 else
    239   write(*,*) "phyetat0: Surface emissivity <emis> range:", &
     198if (startphy_file) then
     199  call get_field("emis",emis,found,indextime)
     200  if (.not.found) then
     201    call abort_physic(modname,"Failed loading <emis>",1)
     202  endif
     203else
     204  emis(:)=1 ! would be better to read value from def file...
     205endif ! of if (startphy_file)
     206write(*,*) "phyetat0: Surface emissivity <emis> range:", &
    240207             minval(emis), maxval(emis)
    241 endif
    242208
    243209! pbl wind variance
    244 call get_field("q2",q2,found,indextime)
    245 if (.not.found) then
    246   write(*,*) "phyetat0: Failed loading <q2>"
    247   call abort
    248 else
    249   write(*,*) "phyetat0: PBL wind variance <q2> range:", &
     210if (startphy_file) then
     211  call get_field("q2",q2,found,indextime)
     212  if (.not.found) then
     213    call abort_physic(modname,"Failed loading <q2>",1)
     214  endif
     215else
     216  q2(:,:)=0
     217endif ! of if (startphy_file)
     218write(*,*) "phyetat0: PBL wind variance <q2> range:", &
    250219             minval(q2), maxval(q2)
    251 endif
    252220
    253221! tracer on surface
     
    255223  do iq=1,nq
    256224    txt=noms(iq)
    257    
    258     !! There was a bug here. MT2015.
    259    
    260     !if (txt.eq."h2o_vap") then
    261       ! There is no surface tracer for h2o_vap;
    262       ! "h2o_ice" should be loaded instead
    263      ! txt="h2o_ice"
    264      ! write(*,*) 'phyetat0: loading surface tracer', &
    265      !                      ' h2o_ice instead of h2o_vap'
    266     !endif
    267    
    268     call get_field(txt,qsurf(:,iq),found,indextime)
    269     if (.not.found) then
    270       write(*,*) "phyetat0: Failed loading <",trim(txt),">"
    271       write(*,*) "         ",trim(txt)," is set to zero"
    272       qsurf(:,iq) = 0.
     225    if (startphy_file) then
     226      call get_field(txt,qsurf(:,iq),found,indextime)
     227      if (.not.found) then
     228        write(*,*) "phyetat0: Failed loading <",trim(txt),">"
     229        write(*,*) "         ",trim(txt)," is set to zero"
     230        qsurf(:,iq) = 0.
     231      endif
    273232    else
    274       write(*,*) "phyetat0: Surface tracer <",trim(txt),"> range:", &
     233      qsurf(:,iq)=0
     234    endif ! of if (startphy_file)
     235    write(*,*) "phyetat0: Surface tracer <",trim(txt),"> range:", &
    275236                 minval(qsurf(:,iq)), maxval(qsurf(:,iq))
    276     endif
    277   enddo
     237  enddo! of do iq=1,nq
    278238endif ! of if (nq.ge.1)
    279239
    280240
    281 ! Call to soil_settings, in order to read soil temperatures,
    282 ! as well as thermal inertia and volumetric heat capacity
    283 call soil_settings(nid_start,ngrid,nsoil,tsurf,tsoil,indextime)
     241if (startphy_file) then
     242  ! Call to soil_settings, in order to read soil temperatures,
     243  ! as well as thermal inertia and volumetric heat capacity
     244  call soil_settings(nid_start,ngrid,nsoil,tsurf,tsoil,indextime)
     245endif ! of if (startphy_file)
    284246!
    285247! close file:
    286248!
    287 call close_startphy
    288 
    289 END SUBROUTINE phyetat0
     249if (startphy_file) call close_startphy
     250
     251end subroutine phyetat0
     252
     253end module phyetat0_mod
  • trunk/LMDZ.TITAN/libf/phytitan/physiq_mod.F90

    r1668 r1670  
    2525                          alpha_lift, alpha_devil, qextrhor
    2626      use time_phylmdz_mod, only: ecritphy, iphysiq, nday
     27      use phyetat0_mod, only: phyetat0
    2728      use phyredem, only: physdem0, physdem1
    2829      use planetwide_mod, only: planetwide_minval,planetwide_maxval,planetwide_sumval
     
    146147!    ------------------
    147148
    148 #include "netcdf.inc"
     149include "netcdf.inc"
    149150
    150151! Arguments :
     
    225226      real pw(ngrid,nlayer)               ! Vertical velocity (m/s). (NOTE : >0 WHEN DOWNWARDS !!)
    226227
    227       integer l,ig,ierr,iq,nw
     228      integer l,ig,ierr,iq,nw,isoil
    228229     
    229230      ! FOR DIAGNOSTIC :
     
    432433!        Read 'startfi.nc' file.
    433434!        ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    434          call phyetat0(ngrid,nlayer,"startfi.nc",0,0,nsoilmx,nq,      &
     435         call phyetat0(startphy_file,                                 &
     436                       ngrid,nlayer,"startfi.nc",0,0,nsoilmx,nq,      &
    435437                       day_ini,time_phys,tsurf,tsoil,emis,q2,qsurf)
     438         if (.not.startphy_file) then
     439           ! additionnal "academic" initialization of physics
     440           if (is_master) write(*,*) "Physiq: initializing tsurf(:) to pt(:,1) !!"
     441           tsurf(:)=pt(:,1)
     442           if (is_master) write(*,*) "Physiq: initializing tsoil(:) to pt(:,1) !!"
     443           do isoil=1,nsoilmx
     444             tsoil(1:ngrid,isoil)=tsurf(1:ngrid)
     445           enddo
     446           if (is_master) write(*,*) "Physiq: initializing day_ini to pdat !"
     447           day_ini=pday
     448         endif
    436449
    437450         if (pday.ne.day_ini) then
  • trunk/LMDZ.TITAN/libf/phytitan/tabfi_mod.F90

    r1669 r1670  
    1 c=======================================================================
    2       SUBROUTINE tabfi(ngrid,nid,Lmodif,tab0,day_ini,lmax,p_rad,
    3      .                 p_omeg,p_g,p_cpp,p_mugaz,p_daysec,time)
    4 c=======================================================================
    5 c
    6 c   C. Hourdin 15/11/96
    7 c
    8 c   Object:        Lecture du tab_cntrl physique dans un fichier
    9 c   ------            et initialisation des constantes physiques
    10 c
    11 c   Arguments:
    12 c   ----------
    13 c
    14 c     Inputs:
    15 c     ------
    16 c
    17 c      - nid:    unitne logique du fichier ou on va lire le tab_cntrl   
    18 c                      (ouvert dans le programme appellant)
    19 c
    20 c                 si nid=0:
    21 c                       pas de lecture du tab_cntrl mais
    22 c                       Valeurs par default des constantes physiques
    23 c       
    24 c      - tab0:    Offset de tab_cntrl a partir duquel sont ranges
    25 c                  les parametres physiques (50 pour start_archive)
    26 c
    27 c      - Lmodif:  si on souhaite modifier les constantes  Lmodif = 1 = TRUE
    28 c
    29 c
    30 c     Outputs:
    31 c     --------
    32 c
    33 c      - day_ini: tab_cntrl(tab0+3) (Dans les cas ou l'on souhaite
    34 c                              comparer avec le day_ini dynamique)
    35 c
    36 c      - lmax:    tab_cntrl(tab0+2) (pour test avec nlayer)
    37 c
    38 c      - p_rad
    39 c      - p_omeg   !
    40 c      - p_g      ! Constantes physiques ayant des
    41 c      - p_mugaz  ! homonymes dynamiques
    42 c      - p_daysec !
    43 c
    44 c=======================================================================
    45 ! to use  'getin'
    46       use ioipsl_getincom , only: getin
    47 
    48       use surfdat_h, only: emisice, iceradius, dtemisice,
    49      &                     emissiv
     1MODULE tabfi_mod
     2
     3IMPLICIT NONE
     4
     5CONTAINS
     6
     7!=======================================================================
     8      SUBROUTINE tabfi(ngrid,nid,Lmodif,tab0,day_ini,lmax,p_rad, &
     9                       p_omeg,p_g,p_cpp,p_mugaz,p_daysec,time)
     10!=======================================================================
     11!
     12!   C. Hourdin 15/11/96
     13!
     14!   Object:        Lecture du tab_cntrl physique dans un fichier
     15!   ------            et initialisation des constantes physiques
     16!
     17!   Arguments:
     18!   ----------
     19!
     20!     Inputs:
     21!     ------
     22!
     23!      - nid:    unitne logique du fichier ou on va lire le tab_cntrl   
     24!                      (ouvert dans le programme appellant)
     25!
     26!                 si nid=0:
     27!                       pas de lecture du tab_cntrl mais
     28!                       Valeurs par default des constantes physiques
     29!       
     30!      - tab0:    Offset de tab_cntrl a partir duquel sont ranges
     31!                  les parametres physiques (50 pour start_archive)
     32!
     33!      - Lmodif:  si on souhaite modifier les constantes  Lmodif = 1 = TRUE
     34!
     35!
     36!     Outputs:
     37!     --------
     38!
     39!      - day_ini: tab_cntrl(tab0+3) (Dans les cas ou l'on souhaite
     40!                              comparer avec le day_ini dynamique)
     41!
     42!      - lmax:    tab_cntrl(tab0+2) (pour test avec nlayer)
     43!
     44!      - p_rad
     45!      - p_omeg   !
     46!      - p_g      ! Constantes physiques ayant des
     47!      - p_mugaz  ! homonymes dynamiques
     48!      - p_daysec !
     49!
     50!=======================================================================
     51! to use  'getin_p'
     52      use ioipsl_getin_p_mod, only: getin_p
     53
     54      use surfdat_h, only: emisice, iceradius, dtemisice, &
     55                           emissiv
    5056      use comsoil_h, only: volcapa
    5157      use iostart, only: get_var
    5258      use mod_phys_lmdz_para, only: is_parallel
    53       use planete_mod, only: year_day, periastr, apoastr, peri_day,
    54      &                       obliquit, z0, lmixmin, emin_turb
     59      use planete_mod, only: year_day, periastr, apoastr, peri_day, &
     60                             obliquit, z0, lmixmin, emin_turb
    5561      use comcstfi_mod, only: rad, omeg, g, mugaz, rcp, cpp, r
    5662      use time_phylmdz_mod, only: dtphys, daysec
     
    5864      implicit none
    5965 
    60 #include "netcdf.inc"
    61 
    62 c-----------------------------------------------------------------------
    63 c   Declarations
    64 c-----------------------------------------------------------------------
    65 
    66 c Arguments
    67 c ---------
     66      include "netcdf.inc"
     67
     68!-----------------------------------------------------------------------
     69!   Declarations
     70!-----------------------------------------------------------------------
     71
     72! Arguments
     73! ---------
    6874      INTEGER,INTENT(IN) :: ngrid,nid,tab0
    6975      INTEGER*4,INTENT(OUT) :: day_ini
     
    7278      REAL,INTENT(OUT) :: p_rad,p_omeg,p_g,p_cpp,p_mugaz,p_daysec,time
    7379
    74 c Variables
    75 c ---------
     80! Variables
     81! ---------
    7682      INTEGER,PARAMETER :: length=100
    7783      REAL tab_cntrl(length) ! array in which are stored the run's parameters
     
    8086      CHARACTER modif*20
    8187      LOGICAL :: found
     88      CHARACTER(len=5) :: modname="tabfi"
    8289     
    8390      write(*,*)"tabfi: nid=",nid," tab0=",tab0," Lmodif=",Lmodif
    8491
    8592      IF (nid.eq.0) then
    86 c-----------------------------------------------------------------------
    87 c  Initialization of various physical constants to defaut values (nid = 0 case)
    88 c-----------------------------------------------------------------------
     93!-----------------------------------------------------------------------
     94!  Initialization of various physical constants to defaut values (nid = 0 case)
     95!-----------------------------------------------------------------------
     96        tab_cntrl(:)=0
     97        lmax=0 ! not used anyways
     98        !day_ini already set via inifis
     99        time=0
     100! Informations about planet for dynamics and physics
     101        ! rad,cpp,g,r,rcp already initialized by inifis
     102        omeg=-999.
     103        call getin_p("omega",omeg)
     104        if (omeg.eq.-999.) then
     105          call abort_physic(modname,"Missing value for omega in def files!",1)
     106        endif
     107        mugaz=(8.3144621/r)*1.E3
     108        ! daysec already set by inifis
     109        ! dtphys alread set by inifis
     110! Informations about planet for the physics only
     111        year_day=-999. ! length of year, in standard days
     112        call getin_p("year_day",year_day)
     113        if (year_day.eq.-999.) then
     114          call abort_physic(modname, &
     115               "Missing value for year_day in def files!",1)
     116        endif
     117        periastr=-999.
     118        call getin_p("periastron",periastr)
     119        if (periastr.eq.-999.) then
     120          call abort_physic(modname, &
     121               "Missing value for periastron in def files!",1)
     122        endif
     123        apoastr=-999.
     124        call getin_p("apoastron",apoastr)
     125        if (apoastr.eq.-999.) then
     126          call abort_physic(modname, &
     127               "Missing value for apoastron in def files!",1)
     128        endif
     129        peri_day=-999.
     130        call getin_p("periastron_day",peri_day)
     131        if (peri_day.eq.-999.) then
     132          call abort_physic(modname, &
     133               "Missing value for periastron date in def files!",1)
     134        endif
     135        obliquit=-999.
     136        call getin_p("obliquity",obliquit)
     137        if (obliquit.eq.-999.) then
     138          call abort_physic(modname, &
     139               "Missing value for obliquity in def files!",1)
     140        endif
     141! boundary layer and turbulence
     142        z0=1.e-2 ! surface roughness length (m)
     143        lmixmin=30
     144        emin_turb=1.e-6
     145! optical properties of polar caps and ground emissivity
     146        emisice(:)=0
     147        emissiv=0
     148        iceradius(:)=1.e-6 ! mean scat radius of CO2 snow
     149        dtemisice(:)=0 !time scale for snow metamorphism
     150        volcapa=1000000 ! volumetric heat capacity of subsurface
     151
    89152      ELSE
    90 c-----------------------------------------------------------------------
    91 c  Initialization of physical constants by reading array tab_cntrl(:)
    92 c               which contains these parameters (nid != 0 case)
    93 c-----------------------------------------------------------------------
    94 c Read 'controle' array
    95 c
     153!-----------------------------------------------------------------------
     154!  Initialization of physical constants by reading array tab_cntrl(:)
     155!               which contains these parameters (nid != 0 case)
     156!-----------------------------------------------------------------------
     157! Read 'controle' array
     158!
    96159
    97160       call get_var("controle",tab_cntrl,found)
    98161       if (.not.found) then
    99          write(*,*)"tabfi: Failed reading <controle> array"
    100          call abort
     162         call abort_physic(modname,"Failed reading <controle> array",1)
    101163       else
    102164         write(*,*)'tabfi: tab_cntrl',tab_cntrl
    103165       endif
    104 c
    105 c  Initialization of some physical constants
    106 c informations on physics grid
     166!
     167!  Initialization of some physical constants
     168! informations on physics grid
    107169!      if(ngrid.ne.tab_cntrl(tab0+1)) then
    108170!         print*,'tabfi: WARNING !!! tab_cntrl(tab0+1).ne.ngrid'
     
    113175      time = tab_cntrl(tab0+4)
    114176      write (*,*) 'IN tabfi day_ini=',day_ini
    115 c Informations about planet for dynamics and physics
     177! Informations about planet for dynamics and physics
    116178      rad = tab_cntrl(tab0+5)
    117179      omeg = tab_cntrl(tab0+6)
     
    122184      daysec = tab_cntrl(tab0+10)
    123185      dtphys = tab_cntrl(tab0+11)
    124 c Informations about planet for the physics only
     186! Informations about planet for the physics only
    125187      year_day = tab_cntrl(tab0+14)
    126188      periastr = tab_cntrl(tab0+15)
     
    128190      peri_day = tab_cntrl(tab0+17)
    129191      obliquit = tab_cntrl(tab0+18)
    130 c boundary layer and turbeulence
     192! boundary layer and turbulence
    131193      z0 = tab_cntrl(tab0+19)
    132194      lmixmin = tab_cntrl(tab0+20)
    133195      emin_turb = tab_cntrl(tab0+21)
    134 c optical properties of polar caps and ground emissivity
     196! optical properties of polar caps and ground emissivity
    135197      emisice(1) = tab_cntrl(tab0+24)
    136198      emisice(2) = tab_cntrl(tab0+25)
     
    140202      dtemisice(1)= tab_cntrl(tab0+33) !time scale for snow metamorphism (north)
    141203      dtemisice(2)= tab_cntrl(tab0+34) !time scale for snow metamorphism (south)
    142 c soil properties
     204! soil properties
    143205      volcapa = tab_cntrl(tab0+35) ! volumetric heat capacity
    144 c-----------------------------------------------------------------------
    145 c       Save some constants for later use (as routine arguments)
    146 c-----------------------------------------------------------------------
     206!-----------------------------------------------------------------------
     207!       Save some constants for later use (as routine arguments)
     208!-----------------------------------------------------------------------
    147209      p_omeg = omeg
    148210      p_g = g
     
    154216      ENDIF    ! end of (nid = 0)
    155217
    156 c-----------------------------------------------------------------------
    157 c       Write physical constants to output before modifying them
    158 c-----------------------------------------------------------------------
     218!-----------------------------------------------------------------------
     219!       Write physical constants to output before modifying them
     220!-----------------------------------------------------------------------
    159221 
    160222   6  FORMAT(a20,e15.6,e15.6)
     
    198260      write(*,*) 'Lmodif in tabfi!!!!!!!',Lmodif
    199261
    200 c-----------------------------------------------------------------------
    201 c        Modifications...
     262!-----------------------------------------------------------------------
     263!        Modifications...
    202264! NB: Modifying controls should only be done by newstart, and in seq mode
    203265      if ((Lmodif.eq.1).and.is_parallel) then
    204         write(*,*) "tabfi: Error modifying tab_control should",
    205      &             " only happen in serial mode (eg: by newstart)"
     266        write(*,*) "tabfi: Error modifying tab_control should", &
     267                   " only happen in serial mode (eg: by newstart)"
    206268        stop
    207269      endif
    208 c-----------------------------------------------------------------------
     270!-----------------------------------------------------------------------
    209271
    210272      IF(Lmodif.eq.1) then
     
    222284      write(*,*) '(24 et 25)   emisice : CO2 ice max emissivity '
    223285      write(*,*) '(31 et 32) iceradius : mean scat radius of CO2 snow'
    224       write(*,*) '(33 et 34) dtemisice : time scale for snow',
    225      &           'metamorphism'
     286      write(*,*) '(33 et 34) dtemisice : time scale for snow metamorphism'
    226287      write(*,*) '(35)      volcapa : soil volumetric heat capacity'
    227288      write(*,*) '(18)     obliquit : planet obliquity (deg)'
     
    466527 999  continue
    467528
    468 c-----------------------------------------------------------------------
    469 c       Write values of physical constants after modifications
    470 c-----------------------------------------------------------------------
     529!----------------------------------------------------------------------
     530!       Write values of physical constants after modifications
     531!-----------------------------------------------------------------------
    471532 
    472533      write(*,*) '*****************************************************'
     
    509570      ENDIF ! of if (Lmodif == 1)
    510571
    511 c-----------------------------------------------------------------------
    512 c       Save some constants for later use (as routine arguments)
    513 c-----------------------------------------------------------------------
     572!-----------------------------------------------------------------------
     573!       Save some constants for later use (as routine arguments)
     574!-----------------------------------------------------------------------
    514575      p_omeg = omeg
    515576      p_g = g
     
    520581
    521582
    522       end
     583      END SUBROUTINE tabfi
     584
     585end module tabfi_mod
Note: See TracChangeset for help on using the changeset viewer.