Changeset 1201 for LMDZ4


Ignore:
Timestamp:
Jul 7, 2009, 4:01:00 PM (15 years ago)
Author:
Laurent Fairhead
Message:

Modifications nécessaires a l'inclusion d'un calendrier réaliste.
La date courante est calculée dans leapfrog.F et exprimée en Jour Julien
(modifié). On en a profité pour faire un peu de ménage dans la gestion des dates
du modèle.
Dans la physique, on utilise les routines de passages entre calendrier Julien et
Gregorien incluses dans IOIPSL pour calculer le nombre de jours écoulés depuis le
1er janvier (pour les conditions aux limites) ou l'equinoxe (pour le calcul de
la longitude solaire). Le calcul de l'orbite reprend celui du gcm planétaire
(codé par FH)
On décide du calendrier à utiliser à l'aide du paramètre calend du run.def. Par
défaut celui-ci est à earth_360d
LF

Location:
LMDZ4/branches/LMDZ4-dev/libf
Files:
2 added
16 edited

Legend:

Unmodified
Added
Removed
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3d/calfis.F

    r1114 r1201  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44C
    55C
    66      SUBROUTINE calfis(lafin,
    7      $                  rdayvrai,
    8      $                  heure,
     7     $                  jD_cur, jH_cur,
    98     $                  pucov,
    109     $                  pvcov,
     
    102101c    -----------
    103102      LOGICAL  lafin
    104       REAL heure
     103
    105104
    106105      REAL pvcov(iip1,jjm,llm)
     
    170169      DATA firstcal/.true./
    171170      SAVE firstcal,debut
    172       REAL rdayvrai
     171!      REAL rdayvrai
     172      REAL :: jD_cur, jH_cur
    173173c
    174174c-----------------------------------------------------------------------
     
    445445     .             debut,
    446446     .             lafin,
    447      .             rdayvrai,
    448      .             heure,
     447     .             jD_cur,
     448     .             jH_cur,
    449449     .             dtphys,
    450450     .             zplev,
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3d/conf_gcm.F

    r1190 r1201  
    3838#include "serre.h"
    3939#include "comdissnew.h"
     40#include "temps.h"
    4041#include "comconst.h"
    4142
     
    111112      planet_type="earth"
    112113      CALL getin('planet_type',planet_type)
     114
     115!Config  Key  = calend
     116!Config  Desc = type de calendrier utilise
     117!Config  Def  = earth_360d
     118!Config  Help = valeur possible: earth_360d, earth_365d, earth_366d
     119!Config         
     120      calend = 'earth_360d'
     121      CALL getin('calend', calend)
    113122
    114123!Config  Key  = dayref
     
    576585      write(lunout,*)' Configuration des parametres du gcm: '
    577586      write(lunout,*)' planet_type = ', planet_type
     587      write(lunout,*)' calend = ', calend
    578588      write(lunout,*)' dayref = ', dayref
    579589      write(lunout,*)' anneeref = ', anneeref
     
    762772      write(lunout,*)' Configuration des parametres du gcm: '
    763773      write(lunout,*)' planet_type = ', planet_type
     774      write(lunout,*)' calend = ', calend
    764775      write(lunout,*)' dayref = ', dayref
    765776      write(lunout,*)' anneeref = ', anneeref
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3d/gcm.F

    r1200 r1201  
    113113      real time_step, t_wrt, t_ops
    114114
    115       REAL rdayvrai,rdaym_ini,rday_ecri
    116115      LOGICAL first
    117116
     
    135134      character (len=20) :: modname
    136135      character (len=80) :: abort_message
    137 
    138 C Calendrier
    139       LOGICAL true_calendar
    140       PARAMETER (true_calendar = .false.)
     136! locales pour gestion du temps
     137      INTEGER :: an, mois, jour
     138      REAL :: heure
     139
    141140
    142141c-----------------------------------------------------------------------
     
    163162
    164163
    165 c-----------------------------------------------------------------------
    166 c   Choix du calendrier
    167 c   -------------------
    168 
    169 #ifdef CPP_IOIPSL
    170       if (true_calendar) then
    171         call ioconf_calendar('gregorian')
    172       else
    173         call ioconf_calendar('360d')
    174       endif
    175 #endif
    176164c----------------------------------------------------------------------
    177165c  lecture des fichiers gcm.def ou run.def
     
    197185      endif
    198186!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     187c-----------------------------------------------------------------------
     188c   Choix du calendrier
     189c   -------------------
     190
     191c      calend = 'earth_365d'
     192
     193#ifdef CPP_IOIPSL
     194      if (calend == 'earth_360d') then
     195        call ioconf_calendar('360d')
     196        write(lunout,*)'CALENDRIER CHOISI: Terrestre a 360 jours/an'
     197      else if (calend == 'earth_365d') then
     198        call ioconf_calendar('noleap')
     199        write(lunout,*)'CALENDRIER CHOISI: Terrestre a 365 jours/an'
     200      else if (calend == 'earth_366d') then
     201        call ioconf_calendar('gregorian')
     202        write(lunout,*)'CALENDRIER CHOISI: Terrestre bissextile'
     203      else
     204        abort_message = 'Mauvais choix de calendrier'
     205        call abort_gcm(modname,abort_message,1)
     206      endif
     207#endif
     208c-----------------------------------------------------------------------
    199209
    200210      IF (config_inca /= 'none') THEN
     
    303313          annee_ref = anneeref
    304314          day_ref = dayref
    305           day_ini = dayref
     315          day_ini = 1
    306316          itau_dyn = 0
    307317          itau_phy = 0
     
    314324      endif
    315325
     326      mois = 1
     327      heure = 0.
     328      call ymds2ju(annee_ref, mois, day_ref, heure, jD_ref)
     329      jH_ref = jD_ref - int(jD_ref)
     330      jD_ref = int(jD_ref)
     331
    316332#ifdef CPP_IOIPSL
    317333      call ioconf_startdate(annee_ref,0,day_ref, 0.)
    318334#endif
    319335
     336      write(lunout,*)'DEBUG'
     337      write(lunout,*)'annee_ref, mois, day_ref, heure, jD_ref'
     338      write(lunout,*)annee_ref, mois, day_ref, heure, jD_ref
     339      call ju2ymds(jD_ref+jH_ref,an, mois, jour, heure)
     340      write(lunout,*)'jD_ref+jH_ref,an, mois, jour, heure'
     341      write(lunout,*)jD_ref+jH_ref,an, mois, jour, heure
    320342
    321343c  nombre d'etats dans les fichiers demarrage et histoire
     
    391413      WRITE(lunout,300)day_ini,day_end
    392414 300  FORMAT('1'/,15x,'run du jour',i7,2x,'au jour',i7//)
     415      call ju2ymds(jD_ref+day_ini-1,an, mois, jour, heure)
     416      write (lunout,301)jour, mois, an
     417      call ju2ymds(jD_ref+day_end-1,an, mois, jour, heure)
     418      write (lunout,302)jour, mois, an
     419 301  FORMAT('1'/,15x,'run du ', i2,'/',i2,'/',i4)
     420 302  FORMAT('1'/,15x,'    au ', i2,'/',i2,'/',i4)
    393421
    394422      if (planet_type.eq."earth") then
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3d/ini_paramLMDZ_dyn.h

    r956 r1201  
    22      dt_cum = dtvr*day_step
    33
    4       zan = annee_ref
    5       dayref = day_ref
    6       CALL ymds2ju(zan, 1, dayref, 0.0, zjulian)
     4!      zan = annee_ref
     5!      dayref = day_ref
     6!      CALL ymds2ju(zan, 1, dayref, 0.0, zjulian)
    77      tau0 = itau_dyn
    88c
     
    1515     .                 iip1,rlong, jjp1,rlatg,
    1616     .                 1,1,1,1,
    17      .                 tau0, zjulian, dt_cum,
     17     .                 tau0, jD_ref+jH_ref , dt_cum,
    1818     .                 thoriid, nid_ctesGCM)
    1919c
     
    134134c
    135135         CALL histdef(nid_ctesGCM, "true_calendar",
    136      ."Choix du calendrier: 1=gregorien ,0=calen. a 360 j",
     136     ."Choix du calendrier",
    137137     .                "-",iip1,jjp1,thoriid, 1,1,1, -99, 32,
    138138     .                "once", dt_cum,dt_cum)
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3d/leapfrog.F

    r1190 r1201  
     1!
     2! $Id$
    13!
    24c
     
    112114c
    113115      INTEGER itau,itaufinp1,iav
    114       INTEGER*4  iday ! jour julien
    115       REAL       time ! Heure de la journee en fraction d'1 jour
     116!      INTEGER  iday ! jour julien
     117      REAL       time
    116118
    117119      REAL  SSUM
     
    125127      real time_step, t_wrt, t_ops
    126128
    127       REAL rdayvrai,rdaym_ini
     129!      REAL rdayvrai,rdaym_ini
     130! jD_cur: jour julien courant
     131! jH_cur: heure julienne courante
     132      REAL :: jD_cur, jH_cur
     133      INTEGER :: an, mois, jour
     134      REAL :: secondes
     135
    128136      LOGICAL first,callinigrads
    129137cIM : pour sortir les param. du modele dans un fis. netcdf 110106
    130138      save first
    131139      data first/.true./
    132       real dt_cum, zjulian
     140      real dt_cum
    133141      character*10 infile
    134142      integer zan, tau0, thoriid
     
    167175      character*80 abort_message
    168176
    169 C Calendrier
    170       LOGICAL true_calendar
    171       PARAMETER (true_calendar = .false.)
    172 
    173177      logical dissip_conservative
    174178      save dissip_conservative
     
    193197
    194198      itau = 0
    195       iday = day_ini+itau/day_step
    196       time = FLOAT(itau-(iday-day_ini)*day_step)/day_step+time_0
    197          IF(time.GT.1.) THEN
    198           time = time-1.
    199           iday = iday+1
    200          ENDIF
     199c$$$      iday = day_ini+itau/day_step
     200c$$$      time = FLOAT(itau-(iday-day_ini)*day_step)/day_step+time_0
     201c$$$         IF(time.GT.1.) THEN
     202c$$$          time = time-1.
     203c$$$          iday = iday+1
     204c$$$         ENDIF
    201205
    202206
     
    214218
    215219   1  CONTINUE
     220
     221      jD_cur = jD_ref + (day_ini - 1) + int (itau * dtvr / daysec)
     222      jH_cur = jH_ref +                                                 &
     223     &          (itau * dtvr / daysec - int(itau * dtvr / daysec))
    216224
    217225
     
    284292      CALL geopot  ( ip1jmp1, teta  , pk , pks,  phis  , phi   )
    285293
     294      time = jD_cur + jH_cur
    286295      CALL caldyn
    287296     $  ( itau,ucov,vcov,teta,ps,masse,pk,pkf,phis ,
    288      $    phi,conser,du,dv,dteta,dp,w, pbaru,pbarv, time+iday-day_ini )
     297     $    phi,conser,du,dv,dteta,dp,w, pbaru,pbarv, time )
    289298
    290299
     
    345354         CALL exner_hyb(  ip1jmp1, ps, p,alpha,beta,pks, pk, pkf )
    346355
    347            rdaym_ini  = itau * dtvr / daysec
    348            rdayvrai   = rdaym_ini  + day_ini
    349 
     356!           rdaym_ini  = itau * dtvr / daysec
     357!           rdayvrai   = rdaym_ini  + day_ini
     358           jD_cur = jD_ref + (day_ini - 1) + int (itau * dtvr / daysec)
     359           jH_cur = jH_ref +                                            &
     360     &              (itau * dtvr / daysec - int(itau * dtvr / daysec))
     361!         write(lunout,*)'itau, jD_cur = ', itau, jD_cur, jH_cur
     362!         call ju2ymds(jD_cur+jH_cur, an, mois, jour, secondes)
     363!         write(lunout,*)'current date = ',an, mois, jour, secondes
    350364
    351365c rajout debug
     
    379393#endif
    380394! #endif of #ifdef CPP_IOIPSL
    381          CALL calfis( lafin ,rdayvrai,time  ,
     395         CALL calfis( lafin , jD_cur, jH_cur,
    382396     $               ucov,vcov,teta,q,masse,ps,p,pk,phis,phi ,
    383397     $               du,dv,dteta,dq,
     
    507521            IF(forward. OR. leapf) THEN
    508522              itau= itau + 1
    509               iday= day_ini+itau/day_step
    510               time= FLOAT(itau-(iday-day_ini)*day_step)/day_step+time_0
    511                 IF(time.GT.1.) THEN
    512                   time = time-1.
    513                   iday = iday+1
    514                 ENDIF
     523c$$$              iday= day_ini+itau/day_step
     524c$$$              time= FLOAT(itau-(iday-day_ini)*day_step)/day_step+time_0
     525c$$$                IF(time.GT.1.) THEN
     526c$$$                  time = time-1.
     527c$$$                  iday = iday+1
     528c$$$                ENDIF
    515529            ENDIF
    516530
     
    632646
    633647             itau =  itau + 1
    634              iday = day_ini+itau/day_step
    635              time = FLOAT(itau-(iday-day_ini)*day_step)/day_step+time_0
    636 
    637                   IF(time.GT.1.) THEN
    638                    time = time-1.
    639                    iday = iday+1
    640                   ENDIF
     648c$$$             iday = day_ini+itau/day_step
     649c$$$             time = FLOAT(itau-(iday-day_ini)*day_step)/day_step+time_0
     650c$$$
     651c$$$                  IF(time.GT.1.) THEN
     652c$$$                   time = time-1.
     653c$$$                   iday = iday+1
     654c$$$                  ENDIF
    641655
    642656               forward =  .FALSE.
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3d/sortvarc.F

    r524 r1201  
    129129      ang   = SSUM(     llm,  angl, 1 )
    130130
    131       rday = FLOAT(INT ( day_ini + time ))
     131c      rday = FLOAT(INT ( day_ini + time ))
    132132c
     133       rday = FLOAT(INT(time-jD_ref-jH_ref))
    133134      IF(ptot0.eq.0.)  THEN
    134135         PRINT 3500, itau, rday, heure,time
     
    156157      RETURN
    157158
    158 3500   FORMAT('0'10(1h*),4x,'pas'i7,5x,'jour'f5.0,'heure'f5.1,4x
    159      *   ,'date',f10.5,4x,10(1h*))
     1593500   FORMAT('0'10(1h*),4x,'pas'i7,5x,'jour'f9.0,'heure'f5.1,4x
     160     *   ,'date',f14.4,4x,10(1h*))
    1601614000   FORMAT(10x,'masse',4x,'rmsdpdt',7x,'energie',2x,'enstrophie'
    161162     * ,2x,'entropie',3x,'rmsv',4x,'mt.ang',/,'GLOB  '
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3d/temps.h

    r1154 r1201  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44!  ATTENTION!!!!: ce fichier include est compatible format fixe/format libre
     
    88!
    99!
     10! jD_ref = jour julien de la date de reference (lancement de l'experience)
     11! hD_ref = "heure" julienne de la date de reference
    1012!-----------------------------------------------------------------------
    1113! INCLUDE 'temps.h'
    1214
    1315      COMMON/temps/itaufin, dt, day_ini, day_end, annee_ref, day_ref,   &
    14      &             itau_dyn, itau_phy
     16     &             itau_dyn, itau_phy, jD_ref, jH_ref, calend
    1517
    1618      INTEGER   itaufin
    17       INTEGER(kind=4) itau_dyn, itau_phy
    18       INTEGER(kind=4) day_ini, day_end, annee_ref, day_ref
    19       REAL      dt
     19      INTEGER itau_dyn, itau_phy
     20      INTEGER day_ini, day_end, annee_ref, day_ref
     21      REAL      dt, jD_ref, jH_ref
     22      CHARACTER (len=10) :: calend
    2023
    2124!-----------------------------------------------------------------------
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3d/write_paramLMDZ_dyn.h

    r956 r1201  
    107107     .               zx_tmp_2d,iip1*jjp1,ndex2d)
    108108c
    109       IF(true_calendar) THEN
    110        zx_tmp_2d(1:iip1,1:jjp1)=1.
    111       ELSE
    112        zx_tmp_2d(1:iip1,1:jjp1)=0.
    113       ENDIF
     109      if (calend == 'earth_360d') then
     110        zx_tmp_2d(1:iip1,1:jjp1)=1.
     111      else if (calend == 'earth_365d') then
     112        zx_tmp_2d(1:iip1,1:jjp1)=2.
     113      else if (calend == 'earth_366d') then
     114        zx_tmp_2d(1:iip1,1:jjp1)=3.
     115      endif
     116
    114117      CALL histwrite(nid_ctesGCM, "true_calendar", itau_w,
    115118     .               zx_tmp_2d,iip1*jjp1,ndex2d)
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar/calfis_p.F

    r1142 r1201  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44C
    55C
    66      SUBROUTINE calfis_p(lafin,
    7      $                  rdayvrai,
     7     $                  jD_cur, jH_cur,
    88     $                  heure,
    99     $                  pucov,
     
    209209      SAVE firstcal,debut
    210210c$OMP THREADPRIVATE(firstcal,debut)
    211       REAL rdayvrai
     211      REAL :: jD_cur, jH_cur
    212212     
    213213      REAL,SAVE,dimension(1:iim,1:llm):: du_send,du_recv,dv_send,dv_recv
     
    334334c   ---------------
    335335c
    336 
     336n
    337337      DO iq=1,nqtot
    338338         iiq=niadv(iq)
     
    665665     .             debut,
    666666     .             lafin,
    667      .             rdayvrai,
    668      .             heure,
     667     .             jD_cur,
     668     .             jH_cur,
    669669     .             dtphys,
    670670     .             zplev_omp,
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar/conf_gcm.F

    r1190 r1201  
    4444!#include "clesphys.h"
    4545#include "iniprint.h"
     46#include "temps.h"
    4647#include "comconst.h"
    4748
     
    122123      CALL getin('planet_type',planet_type)
    123124
     125!Config  Key  = calend
     126!Config  Desc = type de calendrier utilise
     127!Config  Def  = earth_360d
     128!Config  Help = valeur possible: earth_360d, earth_365d, earth_366d
     129!Config         
     130      calend = 'earth_360d'
     131      CALL getin('calend', calend)
     132
    124133!Config  Key  = dayref
    125134!Config  Desc = Jour de l'etat initial
     
    588597      write(lunout,*)' Configuration des parametres du gcm: '
    589598      write(lunout,*)' planet_type = ', planet_type
     599      write(lunout,*)' calend = ', calend
    590600      write(lunout,*)' dayref = ', dayref
    591601      write(lunout,*)' anneeref = ', anneeref
     
    812822      write(lunout,*)' Configuration des parametres du gcm: '
    813823      write(lunout,*)' planet_type = ', planet_type
     824      write(lunout,*)' calend = ', calend
    814825      write(lunout,*)' dayref = ', dayref
    815826      write(lunout,*)' anneeref = ', anneeref
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar/gcm.F

    r1200 r1201  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44c
     
    113113      real time_step, t_wrt, t_ops
    114114
    115 c      REAL rdayvrai,rdaym_ini,rday_ecri
    116 c      LOGICAL first
    117115
    118116      LOGICAL call_iniphys
     
    133131
    134132      character (len=80) :: dynhist_file, dynhistave_file
    135       character (len=20) ::modname
    136       character (len=80) ::abort_message
    137 
    138 C Calendrier
    139       LOGICAL true_calendar
    140       PARAMETER (true_calendar = .false.)
     133      character (len=20) :: modname
     134      character (len=80) :: abort_message
     135! locales pour gestion du temps
     136      INTEGER :: an, mois, jour
     137      REAL :: heure
     138
    141139
    142140c-----------------------------------------------------------------------
     
    165163
    166164
    167 c-----------------------------------------------------------------------
    168 c   Choix du calendrier
    169 c   -------------------
    170 
    171 #ifdef CPP_IOIPSL
    172       if (true_calendar) then
    173         call ioconf_calendar('gregorian')
    174       else
    175         call ioconf_calendar('360d')
    176       endif
    177 #endif
     165
    178166c----------------------------------------------------------------------
    179167c  lecture des fichiers gcm.def ou run.def
     
    221209#endif
    222210      endif ! of if (planet_type.eq."earth")
     211
     212c-----------------------------------------------------------------------
     213c   Choix du calendrier
     214c   -------------------
     215
     216c      calend = 'earth_365d'
     217
     218#ifdef CPP_IOIPSL
     219      if (calend == 'earth_360d') then
     220        call ioconf_calendar('360d')
     221        write(lunout,*)'CALENDRIER CHOISI: Terrestre a 360 jours/an'
     222      else if (calend == 'earth_365d') then
     223        call ioconf_calendar('noleap')
     224        write(lunout,*)'CALENDRIER CHOISI: Terrestre a 365 jours/an'
     225      else if (calend == 'earth_366d') then
     226        call ioconf_calendar('gregorian')
     227        write(lunout,*)'CALENDRIER CHOISI: Terrestre bissextile'
     228      else
     229        abort_message = 'Mauvais choix de calendrier'
     230        call abort_gcm(modname,abort_message,1)
     231      endif
     232#endif
    223233
    224234      IF (config_inca /= 'none') THEN
     
    306316      if (annee_ref .ne. anneeref .or. day_ref .ne. dayref) then
    307317        write(lunout,*)
    308      .  ' Attention les dates initiales lues dans le fichier'
     318     .  'GCM: Attention les dates initiales lues dans le fichier'
    309319        write(lunout,*)
    310320     .  ' restart ne correspondent pas a celles lues dans '
     
    312322        if (raz_date .ne. 1) then
    313323          write(lunout,*)
    314      .    ' On garde les dates du fichier restart'
     324     .    'GCM: On garde les dates du fichier restart'
    315325        else
    316326          annee_ref = anneeref
    317327          day_ref = dayref
    318           day_ini = dayref
     328          day_ini = 1
    319329          itau_dyn = 0
    320330          itau_phy = 0
    321331          time_0 = 0.
    322332          write(lunout,*)
    323      .   ' On reinitialise a la date lue dans gcm.def'
     333     .   'GCM: On reinitialise a la date lue dans gcm.def'
    324334        endif
    325335      ELSE
     
    327337      endif
    328338
    329 #ifdef CPP_IOIPSL
    330       call ioconf_startdate(annee_ref,0,day_ref,0.)
    331 #endif
     339      mois = 1
     340      heure = 0.
     341      call ymds2ju(annee_ref, mois, day_ref, heure, jD_ref)
     342      jH_ref = jD_ref - int(jD_ref)
     343      jD_ref = int(jD_ref)
     344
     345#ifdef CPP_IOIPSL
     346      call ioconf_startdate(annee_ref,0,day_ref, 0.)
     347#endif
     348
     349      write(lunout,*)'DEBUG'
     350      write(lunout,*)'annee_ref, mois, day_ref, heure, jD_ref'
     351      write(lunout,*)annee_ref, mois, day_ref, heure, jD_ref
     352      call ju2ymds(jD_ref+jH_ref,an, mois, jour, heure)
     353      write(lunout,*)'jD_ref+jH_ref,an, mois, jour, heure'
     354      write(lunout,*)jD_ref+jH_ref,an, mois, jour, heure
    332355
    333356c  nombre d'etats dans les fichiers demarrage et histoire
     
    413436      WRITE(lunout,300)day_ini,day_end
    414437 300  FORMAT('1'/,15x,'run du jour',i7,2x,'au jour',i7//)
     438      call ju2ymds(jD_ref+day_ini-1,an, mois, jour, heure)
     439      write (lunout,301)jour, mois, an
     440      call ju2ymds(jD_ref+day_end-1,an, mois, jour, heure)
     441      write (lunout,302)jour, mois, an
     442 301  FORMAT('1'/,15x,'run du ', i2,'/',i2,'/',i4)
     443 302  FORMAT('1'/,15x,'    au ', i2,'/',i2,'/',i4)
    415444
    416445!#ifdef CPP_IOIPSL
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar/leapfrog_p.F

    r1195 r1201  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44c
     
    120120c
    121121      INTEGER itau,itaufinp1,iav
    122       INTEGER*4  iday ! jour julien
    123       REAL       time ! Heure de la journee en fraction d'1 jour
     122!      INTEGER  iday ! jour julien
     123      REAL       time
    124124
    125125      REAL  SSUM
     
    134134      real time_step, t_wrt, t_ops
    135135
    136       REAL rdayvrai,rdaym_ini
     136! jD_cur: jour julien courant
     137! jH_cur: heure julienne courante
     138      REAL :: jD_cur, jH_cur
     139      INTEGER :: an, mois, jour
     140      REAL :: secondes
     141
    137142      LOGICAL first,callinigrads
    138143
     
    162167      character*80 abort_message
    163168
    164 C Calendrier
    165       LOGICAL true_calendar
    166       PARAMETER (true_calendar = .false.)
    167169
    168170      logical,PARAMETER :: dissip_conservative=.TRUE.
     
    207209
    208210      itau = 0
    209       iday = day_ini+itau/day_step
    210       time = FLOAT(itau-(iday-day_ini)*day_step)/day_step+time_0
    211          IF(time.GT.1.) THEN
    212           time = time-1.
    213           iday = iday+1
    214          ENDIF
     211c$$$      iday = day_ini+itau/day_step
     212c$$$      time = FLOAT(itau-(iday-day_ini)*day_step)/day_step+time_0
     213c$$$         IF(time.GT.1.) THEN
     214c$$$          time = time-1.
     215c$$$          iday = iday+1
     216c$$$         ENDIF
    215217
    216218c Allocate variables depending on dynamic variable nqtot
     
    241243   1  CONTINUE
    242244
    243 c$OMP MASTER
    244 
    245       CALL barrier
    246      
    247 c$OMP END MASTER
    248 c$OMP BARRIER
     245      jD_cur = jD_ref + (day_ini - 1) + int (itau * dtvr / daysec)
     246      jH_cur = jH_ref +                                                 &
     247     &          (itau * dtvr / daysec - int(itau * dtvr / daysec))
    249248
    250249
     
    551550c$OMP BARRIER
    552551!      CALL FTRACE_REGION_BEGIN("caldyn")
     552      time = jD_cur + jH_cur
    553553      CALL caldyn_p
    554554     $  ( itau,ucov,vcov,teta,ps,masse,pk,pkf,phis ,
    555      $    phi,conser,du,dv,dteta,dp,w, pbaru,pbarv, time+iday-day_ini )
     555     $    phi,conser,du,dv,dteta,dp,w, pbaru,pbarv, time )
    556556
    557557!      CALL FTRACE_REGION_END("caldyn")
     
    684684         CALL exner_hyb_p(  ip1jmp1, ps, p,alpha,beta,pks, pk, pkf )
    685685c$OMP BARRIER
    686            rdaym_ini  = itau * dtvr / daysec
    687            rdayvrai   = rdaym_ini  + day_ini
    688 
     686           jD_cur = jD_ref + (day_ini -1) + int (itau * dtvr / daysec)
     687           jH_cur = jH_ref +                                            &
     688     &              (itau * dtvr / daysec - int(itau * dtvr / daysec))
     689         call ju2ymds(jD_cur+jH_cur, an, mois, jour, secondes)
    689690
    690691c rajout debug
     
    773774cc$OMP BARRIER
    774775!        CALL FTRACE_REGION_BEGIN("calfis")
    775         CALL calfis_p(lafin ,rdayvrai,time  ,
     776        CALL calfis_p(lafin ,jD_cur, jH_cur,
    776777     $               ucov,vcov,teta,q,masse,ps,p,pk,phis,phi ,
    777778     $               du,dv,dteta,dq,
     
    12741275            IF(forward. OR. leapf) THEN
    12751276              itau= itau + 1
    1276               iday= day_ini+itau/day_step
    1277               time= FLOAT(itau-(iday-day_ini)*day_step)/day_step+time_0
    1278                 IF(time.GT.1.) THEN
    1279                   time = time-1.
    1280                   iday = iday+1
    1281                 ENDIF
     1277c$$$              iday= day_ini+itau/day_step
     1278c$$$              time= FLOAT(itau-(iday-day_ini)*day_step)/day_step+time_0
     1279c$$$                IF(time.GT.1.) THEN
     1280c$$$                  time = time-1.
     1281c$$$                  iday = iday+1
     1282c$$$                ENDIF
    12821283            ENDIF
    12831284
     
    14441445
    14451446             itau =  itau + 1
    1446              iday = day_ini+itau/day_step
    1447              time = FLOAT(itau-(iday-day_ini)*day_step)/day_step+time_0
    1448 
    1449                   IF(time.GT.1.) THEN
    1450                    time = time-1.
    1451                    iday = iday+1
    1452                   ENDIF
     1447c$$$             iday = day_ini+itau/day_step
     1448c$$$             time = FLOAT(itau-(iday-day_ini)*day_step)/day_step+time_0
     1449c$$$
     1450c$$$                  IF(time.GT.1.) THEN
     1451c$$$                   time = time-1.
     1452c$$$                   iday = iday+1
     1453c$$$                  ENDIF
    14531454
    14541455               forward =  .FALSE.
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar/sortvarc.F

    r774 r1201  
    129129      ang   = SSUM(     llm,  angl, 1 )
    130130
    131       rday = FLOAT(INT ( day_ini + time ))
     131c      rday = FLOAT(INT ( day_ini + time ))
    132132c
     133       rday = FLOAT(INT(time-jD_ref-jH_ref))
    133134      IF(ptot0.eq.0.)  THEN
    134135         PRINT 3500, itau, rday, heure,time
     
    156157      RETURN
    157158
    158 3500   FORMAT('0'10(1h*),4x,'pas'i7,5x,'jour'f5.0,'heure'f5.1,4x
    159      *   ,'date',f10.5,4x,10(1h*))
     1593500   FORMAT('0'10(1h*),4x,'pas'i7,5x,'jour'f9.0,'heure'f5.1,4x
     160     *   ,'date',f14.4,4x,10(1h*))
    1601614000   FORMAT(10x,'masse',4x,'rmsdpdt',7x,'energie',2x,'enstrophie'
    161162     * ,2x,'entropie',3x,'rmsv',4x,'mt.ang',/,'GLOB  '
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar/temps.h

    r1154 r1201  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44!  ATTENTION!!!!: ce fichier include est compatible format fixe/format libre
     
    88!
    99!
     10! jD_ref = jour julien de la date de reference (lancement de l'experience)
     11! hD_ref = "heure" julienne de la date de reference
    1012!-----------------------------------------------------------------------
    1113! INCLUDE 'temps.h'
    1214
    1315      COMMON/temps/itaufin, dt, day_ini, day_end, annee_ref, day_ref,   &
    14      &             itau_dyn, itau_phy
     16     &             itau_dyn, itau_phy, jD_ref, jH_ref, calend
    1517
    1618      INTEGER   itaufin
    17       INTEGER(kind=4) itau_dyn, itau_phy
    18       INTEGER(kind=4) day_ini, day_end, annee_ref, day_ref
    19       REAL      dt
    20 !$OMP THREADPRIVATE(/temps/)
     19      INTEGER itau_dyn, itau_phy
     20      INTEGER day_ini, day_end, annee_ref, day_ref
     21      REAL      dt, jD_ref, jH_ref
     22      CHARACTER (len=10) :: calend
     23
     24!-----------------------------------------------------------------------
  • LMDZ4/branches/LMDZ4-dev/libf/phylmd/hgardfou.F

    r1145 r1201  
    11!
     2! $Id$
    23      SUBROUTINE hgardfou (t,tsol,text)
    34      use dimphy
     
    1213      REAL t(klon,klev), tsol(klon,nbsrf)
    1314      CHARACTER*(*) text
     15      character (len=20) :: modname = 'hgardfou'
     16      character (len=80) :: abort_message
    1417C
    1518      INTEGER i, k, nsrf
     
    124127c
    125128      IF (.NOT. ok) THEN
    126          PRINT*, 'hgardfou s arrete ', text
    127          CALL abort
     129         abort_message= 'hgardfou s arrete '//text
     130         CALL abort_gcm (modname,abort_message,1)
    128131      ENDIF
    129132
  • LMDZ4/branches/LMDZ4-dev/libf/phylmd/physiq.F

    r1196 r1201  
    44
    55      SUBROUTINE physiq (nlon,nlev,
    6      .            debut,lafin,rjourvrai,gmtime,pdtphys,
     6     .            debut,lafin,jD_cur, jH_cur,pdtphys,
    77     .            paprs,pplay,pphi,pphis,presnivs,clesphy0,
    88     .            u,v,t,qx,
     
    6060c debut---input-L-variable logique indiquant le premier passage
    6161c lafin---input-L-variable logique indiquant le dernier passage
    62 c rjour---input-R-numero du jour de l'experience
    63 c gmtime--input-R-temps universel dans la journee (0 a 86400 s)
     62c jD_cur--input-R-jour courant a l'appel de la physique (jour julien)
     63c jH_cur--input-R-heure courante a l'appel de la physique (jour julien)
    6464c pdtphys-input-R-pas d'integration pour la physique (seconde)
    6565c paprs---input-R-pression pour chaque inter-couche (en Pa)
     
    186186      INTEGER nlon
    187187      INTEGER nlev
    188       REAL rjourvrai
    189       REAL gmtime
     188      REAL :: jD_cur, jH_cur
     189
    190190      REAL pdtphys
    191191      LOGICAL debut, lafin
     
    703703c Conditions aux limites
    704704c
    705       INTEGER julien
     705!
     706! Gestion calendrier
     707!
     708      REAL :: jD_1jan, jH_1jan
     709      INTEGER :: year_cur, mth_cur, day_cur, days_elapsed
     710      REAL :: hour, day_since_equinox
     711! Date de l'equinoxe de printemps
     712      INTEGER, parameter :: mth_eq=3, day_eq=21
     713      REAL :: jD_eq
     714
     715      LOGICAL, parameter :: new_orbit = .true.
     716
    706717c
    707718      INTEGER lmt_pas
     
    10871098c$OMP THREADPRIVATE(first)
    10881099
     1100      integer iunit
     1101
    10891102      logical, save::  read_climoz ! read ozone climatology
    10901103      integer, save:: ncid_climoz ! NetCDF file containing ozone climatology
     
    11141127         write(lunout,*) 'DEBUT DE PHYSIQ !!!!!!!!!!!!!!!!!!!!'
    11151128         write(lunout,*)
    1116      s 'nlon,klev,nqtot,debut,lafin,rjourvrai,gmtime,pdtphys'
     1129     s 'nlon,klev,nqtot,debut,lafin, jD_cur, jH_cur,pdtphys'
    11171130         write(lunout,*)
    1118      s  nlon,klev,nqtot,debut,lafin,rjourvrai,gmtime,pdtphys
     1131     s  nlon,klev,nqtot,debut,lafin, jD_cur, jH_cur,pdtphys
    11191132
    11201133         write(lunout,*) 'papers, play, phi, u, v, t, omega'
     
    11841197
    11851198c======================================================================
    1186       xjour = rjourvrai
     1199! Gestion calendrier
     1200!
     1201      call ju2ymds(jD_cur+jH_cur, year_cur, mth_cur, day_cur, hour)
     1202      call ymds2ju(year_cur, 1, 1, 0., jD_1jan)
     1203      jH_1jan = jD_1jan - int (jD_1jan)
     1204      jD_1jan = int (jD_1jan)
     1205      xjour = jD_cur - jD_1jan
     1206      days_elapsed = jD_cur - jD_1jan
     1207
    11871208c
    11881209c Si c'est le debut, il faut initialiser plusieurs choses
     
    14721493
    14731494cXXXPB Positionner date0 pour initialisation de ORCHIDEE
    1474       date0 = zjulian
    1475 C      date0 = day_ini
     1495      date0 = jD_ref
    14761496      WRITE(*,*) 'physiq date0 : ',date0
    14771497c
     
    14911511         CALL VTe(VTphysiq)
    14921512         CALL VTb(VTinca)
    1493          iii = MOD(NINT(xjour),360)
    1494          calday = FLOAT(iii) + gmtime
    1495          WRITE(lunout,*) 'initial time ', xjour, calday
     1513!         iii = MOD(NINT(xjour),360)
     1514!         calday = FLOAT(iii) + jH_cur
     1515         calday = FLOAT(days_elapsed) + jH_cur
     1516         WRITE(lunout,*) 'initial time chemini', days_elapsed, calday
    14961517
    14971518         CALL chemini(
     
    15341555!
    15351556      itap   = itap + 1
    1536       julien = MOD(NINT(xjour),360)
    1537       if (julien .eq. 0) julien = 360
    1538 
    15391557!
    15401558! Update fraction of the sub-surfaces (pctsrf) and
     
    15421560! on the surface fraction.
    15431561!
    1544       CALL change_srf_frac(itap, dtime, julien,
     1562      CALL change_srf_frac(itap, dtime, days_elapsed+1,
    15451563     *     pctsrf, falb1, falb2, ftsol, u10m, v10m, pbl_tke)
    1546 
    15471564
    15481565! Tendances bidons pour les processus qui n'affectent pas certaines
     
    16971714         if (read_climoz) then
    16981715C           Ozone climatology from a NetCDF file
    1699             call regr_pr_av(ncid_climoz, "tro3", julien, press_climoz,
     1716            call regr_pr_av(ncid_climoz, "tro3", days_elapsed+1,
     1717     &           press_climoz,
    17001718     $           paprs, wo)
    17011719!           Convert from mole fraction of ozone to column density of ozone in a
     
    17071725C           "zmasse" changes a little.)
    17081726         else
    1709             CALL ozonecm(real(julien), rlat, paprs, wo)
     1727            CALL ozonecm(real(days_elapsed+1), rlat, paprs, wo)
     1728
    17101729         end if
    17111730      ENDIF
     
    17491768! doit donc etre placé avant radlwsw et pbl_surface
    17501769
     1770! calcul selon la routine utilisee pour les planetes
     1771      if (new_orbit) then
     1772        call ymds2ju(year_cur, mth_eq, day_eq,0., jD_eq)
     1773        day_since_equinox = (jD_cur + jH_cur) - jD_eq
     1774!        day_since_equinox = (jD_cur) - jD_eq
     1775        call solarlong(day_since_equinox, zlongi, dist)
     1776      else     
     1777! calcul selon la routine utilisee pour l'AR4
    17511778!   choix entre calcul de la longitude solaire vraie ou valeur fixee a
    17521779!   solarlong0
    1753 
    1754       if (solarlong0<-999.) then
    1755          CALL orbite(FLOAT(julien),zlongi,dist)
    1756       else
    1757          zlongi=solarlong0  ! longitude solaire vraie
    1758          dist=1.            ! distance au soleil / moyenne
     1780        if (solarlong0<-999.) then
     1781           CALL orbite(FLOAT(days_elapsed+1),zlongi,dist)
     1782        else
     1783           zlongi=solarlong0  ! longitude solaire vraie
     1784           dist=1.            ! distance au soleil / moyenne
     1785        endif
    17591786      endif
    1760 
    1761       if(prt_level.ge.1) print*,'Longitude solaire ',zlongi,solarlong0
     1787      if(prt_level.ge.1)                                                &
     1788     &    write(lunout,*)'Longitude solaire ',zlongi,solarlong0,dist
    17621789
    17631790!  Avec ou sans cycle diurne
    17641791      IF (cycle_diurne) THEN
    17651792        zdtime=dtime*FLOAT(radpas) ! pas de temps du rayonnement (s)
    1766         CALL zenang(zlongi,gmtime,zdtime,rlat,rlon,rmu0,fract)
     1793        CALL zenang(zlongi,jH_cur,zdtime,rlat,rlon,rmu0,fract)
    17671794      ELSE
    17681795        CALL angle(zlongi, rlat, fract, rmu0)
     
    17971824
    17981825      CALL pbl_surface(
    1799      e     dtime,     date0,     itap,    julien,
     1826     e     dtime,     date0,     itap,    days_elapsed+1,
    18001827     e     debut,     lafin,
    18011828     e     rlon,      rlat,      rugoro,  rmu0,     
     
    20942121
    20952122            if (itop_con(i).gt.klev-3) then
    2096                print*,'La convection monte trop haut '
    2097                print*,'itop_con(,',i,',)=',itop_con(i)
     2123              if(prt_level >= 9) then
     2124                write(lunout,*)'La convection monte trop haut '
     2125                write(lunout,*)'itop_con(,',i,',)=',itop_con(i)
     2126              endif
    20982127            endif
    20992128          ENDDO
     
    26352664         IF (.NOT. aerosol_couple)
    26362665     &        CALL readaerosol_optic(
    2637      &        debut, new_aod, flag_aerosol, rjourvrai, pdtphys,
     2666     &        debut, new_aod, flag_aerosol, jD_cur-jD_ref, pdtphys,
    26382667     &        pplay, paprs, t_seri, rhcl,
    26392668     &        mass_solu_aero, mass_solu_aero_pi,
     
    27642793         CALL VTe(VTphysiq)
    27652794         CALL VTb(VTinca)
    2766          calday = FLOAT(julien) + gmtime
     2795         calday = FLOAT(days_elapsed + 1) + jH_cur
    27672796
    27682797         IF (config_inca == 'aero') THEN
     
    27752804
    27762805         CALL chemhook_begin (calday,
    2777      $                          julien,
    2778      $                          gmtime,
     2806     $                          days_elapsed,
     2807     $                          jH_cur,
    27792808     $                          pctsrf(1,1),
    27802809     $                          rlat,
     
    31063135      IF (is_sequential) THEN
    31073136     
    3108         CALL aaam_bud (27,klon,klev,rjourvrai,gmtime,
     3137        CALL aaam_bud (27,klon,klev,jD_cur-jD_ref,jH_cur,
    31093138     C                 ra,rg,romega,
    31103139     C                 rlat,rlon,pphis,
     
    31333162
    31343163      call phytrac (
    3135      I     itap,     julien,    gmtime,   debut,
     3164     I     itap,     days_elapsed+1,    jH_cur,   debut,
    31363165     I     lafin,    dtime,     u, v,     t,
    31373166     I     paprs,    pplay,     pmfu,     pmfd,
     
    33513380      write(lunout,*) 'FIN DE PHYSIQ !!!!!!!!!!!!!!!!!!!!'
    33523381      write(lunout,*)
    3353      s 'nlon,klev,nqtot,debut,lafin,rjourvrai,gmtime,pdtphys pct tlos'
     3382     s 'nlon,klev,nqtot,debut,lafin,jD_cur, jH_cur, pdtphys pct tlos'
    33543383      write(lunout,*)
    3355      s  nlon,klev,nqtot,debut,lafin,rjourvrai,gmtime,pdtphys,
     3384     s  nlon,klev,nqtot,debut,lafin, jD_cur, jH_cur ,pdtphys,
    33563385     s  pctsrf(igout,is_ter), pctsrf(igout,is_lic),pctsrf(igout,is_oce),
    33573386     s  pctsrf(igout,is_sic)
     
    34473476      ENDIF
    34483477     
     3478!      first=.false.
    34493479
    34503480      RETURN
Note: See TracChangeset for help on using the changeset viewer.