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/dyn3dpar
Files:
6 edited

Legend:

Unmodified
Added
Removed
  • 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!-----------------------------------------------------------------------
Note: See TracChangeset for help on using the changeset viewer.