Changeset 97 for trunk/libf/dyn3dpar


Ignore:
Timestamp:
Mar 22, 2011, 5:25:44 PM (14 years ago)
Author:
slebonnois
Message:

Serie de modifs SL pour homogeneisation des phytitan et phyvenus
Ca touche aussi aux liens phy/dyn (surtout a propos de clesphy0),
a verifier avec les autres, donc...

Location:
trunk/libf/dyn3dpar
Files:
7 edited

Legend:

Unmodified
Added
Removed
  • trunk/libf/dyn3dpar/calfis_p.F

    r52 r97  
    2121     $                  pdq,
    2222     $                  flxw,
    23      $                  clesphy0,
    2423     $                  pdufi,
    2524     $                  pdvfi,
     
    144143      REAL pdqfi(iip1,jjp1,llm,nqtot)
    145144      REAL pdpsfi(iip1,jjp1)
    146 
    147       INTEGER        longcles
    148       PARAMETER    ( longcles = 20 )
    149       REAL clesphy0( longcles )
    150145
    151146#ifdef CPP_PHYS
     
    691686     .             zphis_omp,
    692687     .             presnivs_omp,
    693      .             clesphy0,
    694688     .             zufi_omp,
    695689     .             zvfi_omp,
     
    720714     .             zphis_omp,
    721715     .             presnivs_omp,
    722      .             clesphy0,
    723716     .             zufi_omp,
    724717     .             zvfi_omp,
  • trunk/libf/dyn3dpar/ce0l.F90

    r66 r97  
    4242#include "temps.h"
    4343#include "logic.h"
    44   INTEGER, PARAMETER            :: longcles=20
    45   REAL,    DIMENSION(longcles)  :: clesphy0
    4644  REAL,    DIMENSION(iip1,jjp1) :: masque
    4745  CHARACTER(LEN=15)             :: calnd
    4846!-------------------------------------------------------------------------------
    49   CALL conf_gcm( 99, .TRUE. , clesphy0 )
     47  CALL conf_gcm( 99, .TRUE. )
    5048
    5149  CALL init_mpi
  • trunk/libf/dyn3dpar/conf_gcm.F

    r7 r97  
    44c
    55c
    6       SUBROUTINE conf_gcm( tapedef, etatinit, clesphy0 )
     6      SUBROUTINE conf_gcm( tapedef, etatinit )
    77c
    88#ifdef CPP_IOIPSL
     
    2626c     etatinit  :     = TRUE   , on ne  compare pas les valeurs des para-
    2727c     -metres  du zoom  avec  celles lues sur le fichier start .
    28 c      clesphy0 :  sortie  .
    2928c
    3029       LOGICAL etatinit
    3130       INTEGER tapedef
    3231
    33        INTEGER        longcles
    34        PARAMETER(     longcles = 20 )
    35        REAL clesphy0( longcles )
    36 c
    3732c   Declarations :
    3833c   --------------
     
    157152      CALL getin('raz_date', raz_date)
    158153
     154!Config  Key  = resetvarc
     155!Config  Desc = Reinit des variables de controle
     156!Config  Def  = n
     157!Config  Help = Reinit des variables de controle
     158      resetvarc = .false.
     159      CALL getin('resetvarc',resetvarc)
     160
    159161!Config  Key  = nday
    160162!Config  Desc = Nombre de jours d'integration
     
    164166      nday = 10
    165167      CALL getin('nday',nday)
     168
     169!Config  Key  = less1day
     170!Config  Desc = Possibilite d'integrer moins d'un jour
     171!Config  Def  = n
     172!Config  Help = Possibilite d'integrer moins d'un jour
     173      less1day = .false.
     174      CALL getin('less1day',less1day)
     175
     176!Config  Key  = fractday
     177!Config  Desc = integration sur une fraction de jour
     178!Config  Def  = 0.01
     179!Config  Help = integration sur une fraction de jour
     180      fractday = 0.01
     181      CALL getin('fractday',fractday)
    166182
    167183!Config  Key  = day_step
     
    628644      write(lunout,*)' anneeref = ', anneeref
    629645      write(lunout,*)' nday = ', nday
     646      if (less1day) then
     647      write(lunout,*)' Run only for a fraction of day ! '
     648      write(lunout,*)' fractday = ', fractday
     649      endif
    630650      write(lunout,*)' day_step = ', day_step
    631651      write(lunout,*)' iperiod = ', iperiod
  • trunk/libf/dyn3dpar/control_mod.F90

    r1 r97  
    2424  LOGICAL ok_dyn_ave ! output averaged values of fields in the dynamics
    2525                     ! in NetCDF files dyn_hist*ave.nc
     26  LOGICAL :: resetvarc  ! allows to reset the variables in sortvarc
     27  LOGICAL :: less1day   ! allows to run less than 1 day (for Venus)
     28  REAL    :: fractday   ! fraction of the day to run in this case
    2629
    2730END MODULE
  • trunk/libf/dyn3dpar/gcm.F

    r52 r97  
    7979#include "indicesol.h"
    8080#endif
    81       INTEGER         longcles
    82       PARAMETER     ( longcles = 20 )
    83       REAL  clesphy0( longcles )
    84       SAVE  clesphy0
    85 
    8681
    8782
     
    175170! Ehouarn: dump possibility of using defrun
    176171!#ifdef CPP_IOIPSL
    177       CALL conf_gcm( 99, .TRUE. , clesphy0 )
     172      CALL conf_gcm( 99, .TRUE. )
    178173!#else
    179174!      CALL defrun( 99, .TRUE. , clesphy0 )
     
    240235        call ioconf_calendar('gregorian')
    241236        write(lunout,*)'CALENDRIER CHOISI: Terrestre bissextile'
     237      else if (calend == 'titan') then
     238!        call ioconf_calendar('titan')
     239        write(lunout,*)'CALENDRIER CHOISI: Titan'
     240        abort_message = 'A FAIRE...'
     241        call abort_gcm(modname,abort_message,1)
     242      else if (calend == 'venus') then
     243!        call ioconf_calendar('venus')
     244        write(lunout,*)'CALENDRIER CHOISI: Venus'
     245        abort_message = 'A FAIRE...'
     246        call abort_gcm(modname,abort_message,1)
    242247      else
    243248        abort_message = 'Mauvais choix de calendrier'
     
    382387      mois = 1
    383388      heure = 0.
     389! Ce n'est defini pour l'instant que pour la Terre...
     390      if (planet_type.eq.'earth') then
    384391      call ymds2ju(annee_ref, mois, day_ref, heure, jD_ref)
    385392      jH_ref = jD_ref - int(jD_ref)
     
    394401      write(lunout,*)'jD_ref+jH_ref,an, mois, jour, heure'
    395402      write(lunout,*)jD_ref+jH_ref,an, mois, jour, heure
     403      else
     404! A voir pour Titan et Venus
     405        jD_ref=0
     406        jH_ref=0
     407      write(lunout,*)'A VOIR POUR VENUS ET TITAN: jD_ref, jH_ref'
     408      write(lunout,*)jD_ref,jH_ref
     409      endif ! planet_type
    396410#else
    397411! Ehouarn: we still need to define JD_ref and JH_ref
     
    491505
    492506#ifdef CPP_IOIPSL
     507! Ce n'est defini pour l'instant que pour la Terre...
     508      if (planet_type.eq.'earth') then
    493509      call ju2ymds(jD_ref + day_ini - day_ref, an, mois, jour, heure)
    494510      write (lunout,301)jour, mois, an
    495511      call ju2ymds(jD_ref + day_end - day_ref, an, mois, jour, heure)
    496512      write (lunout,302)jour, mois, an
     513      else
     514! A voir pour Titan et Venus
     515      write(lunout,*)'A VOIR POUR VENUS ET TITAN: separation en annees...'
     516      endif ! planet_type
     517
    497518 301  FORMAT('1'/,15x,'run du ', i2,'/',i2,'/',i4)
    498519 302  FORMAT('1'/,15x,'    au ', i2,'/',i2,'/',i4)
     
    554575
    555576c$OMP PARALLEL DEFAULT(SHARED) COPYIN(/temps/,/logic/)
    556       CALL leapfrog_p(ucov,vcov,teta,ps,masse,phis,q,clesphy0,
     577      CALL leapfrog_p(ucov,vcov,teta,ps,masse,phis,q,
    557578     .              time_0)
    558579c$OMP END PARALLEL
  • trunk/libf/dyn3dpar/leapfrog_p.F

    r52 r97  
    55c
    66
    7       SUBROUTINE leapfrog_p(ucov,vcov,teta,ps,masse,phis,q,clesphy0,
     7      SUBROUTINE leapfrog_p(ucov,vcov,teta,ps,masse,phis,q,
    88     &                    time_0)
    99
     
    7070#include "academic.h"
    7171     
    72       INTEGER         longcles
    73       PARAMETER     ( longcles = 20 )
    74       REAL  clesphy0( longcles )
    75 
    7672      real zqmin,zqmax
    7773      INTEGER nbetatmoy, nbetatdem,nbetat
     
    219215     
    220216      itaufin   = nday*day_step
     217      if (less1day) then
     218c MODIF VENUS: to run less than one day:
     219        itaufin   = int(fractday*day_step)
     220      endif
    221221      itaufinp1 = itaufin +1
    222222      modname="leapfrog_p"
     
    820820     $               du,dv,dteta,dq,
    821821     $               flxw,
    822      $               clesphy0, dufi,dvfi,dtetafi,dqfi,dpfi  )
     822     $               dufi,dvfi,dtetafi,dqfi,dpfi  )
    823823!        CALL FTRACE_REGION_END("calfis")
    824824        ijb=ij_begin
  • trunk/libf/dyn3dpar/sortvarc.F

    r1 r97  
    5555
    5656      REAL       SSUM
     57
     58      logical  firstcal
     59      data     firstcal/.true./
     60      save     firstcal
    5761
    5862c-----------------------------------------------------------------------
     
    129133      ang   = SSUM(     llm,  angl, 1 )
    130134
    131 c      rday = REAL(INT ( day_ini + time ))
    132 c
     135      IF (firstcal.and.resetvarc) then
    133136       rday = REAL(INT(time-jD_ref-jH_ref))
    134       IF(ptot0.eq.0.)  THEN
    135137         PRINT 3500, itau, rday, heure,time
    136138         PRINT*,'WARNING!!! On recalcule les valeurs initiales de :'
     
    151153      ang = ang /ang0
    152154
     155      firstcal = .false.
    153156
    154157      PRINT 3500, itau, rday, heure, time
Note: See TracChangeset for help on using the changeset viewer.