Ignore:
Timestamp:
Nov 21, 2019, 4:43:45 PM (5 years ago)
Author:
lguez
Message:

Merge revisions 3427:3600 of trunk into branch Ocean_skin

Location:
LMDZ6/branches/Ocean_skin
Files:
12 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Ocean_skin

  • LMDZ6/branches/Ocean_skin/libf/dyn3dmem/caladvtrac_mod.F90

    r1907 r3605  
    4444    CALL allocate_u(massem,llm,d)
    4545    CALL allocate_u(pbaruc,llm,d)
     46    pbaruc(:,:)=0
    4647    CALL allocate_v(pbarvc,llm,d)
     48    pbarvc(:,:)=0
    4749    CALL allocate_u(pbarug,llm,d)
    4850    CALL allocate_v(pbarvg,llm,d)
  • LMDZ6/branches/Ocean_skin/libf/dyn3dmem/call_calfis_mod.F90

    r2603 r3605  
    5252    CALL allocate_u(p,llmp1,d)
    5353    CALL allocate_u(pks,d)
     54    pks(:)=0
    5455    CALL allocate_u(pk,llm,d)
     56    pk(:,:)=0
    5557    CALL allocate_u(pkf,llm,d)
    5658    CALL allocate_u(phi,llm,d)
  • LMDZ6/branches/Ocean_skin/libf/dyn3dmem/call_dissip_mod.F90

    r1987 r3605  
    3131
    3232    CALL allocate_u(ucov,llm,d)
     33    ucov(:,:)=0
    3334    CALL allocate_v(vcov,llm,d)
     35    vcov(:,:)=0
    3436    CALL allocate_u(teta,llm,d)
    3537    CALL allocate_u(p,llmp1,d)
  • LMDZ6/branches/Ocean_skin/libf/dyn3dmem/conf_gcm.F90

    r2665 r3605  
    2525  USE serre_mod, ONLY: clon,clat,grossismx,grossismy,dzoomx,dzoomy, &
    2626                       alphax,alphay,taux,tauy
    27   USE temps_mod, ONLY: calend
     27  USE temps_mod, ONLY: calend, year_len
    2828
    2929  IMPLICIT NONE
     
    144144  !Config         
    145145  calend = 'earth_360d'
     146! initialize year_len for aquaplanets and 1D
    146147  CALL getin('calend', calend)
     148     if (calend == 'earth_360d') then
     149        year_len=360
     150      else if (calend == 'earth_365d') then
     151        year_len=365
     152      else if (calend == 'earth_366d') then
     153        year_len=366
     154      else
     155        year_len=1
     156      endif
     157 
    147158
    148159  !Config  Key  = dayref
  • LMDZ6/branches/Ocean_skin/libf/dyn3dmem/gcm.F90

    r2622 r3605  
    233233       'GCM: AVANT iniacademic AVANT AVANT AVANT AVANT'
    234234  if (.not.read_start) then
     235     start_time=0.
     236     annee_ref=anneeref
    235237     CALL iniacademic_loc(vcov,ucov,teta,q,masse,ps,phis,time_0)
    236238  endif
     
    368370
    369371  !-----------------------------------------------------------------------
     372  !   Initialisation des I/O :
     373  !   ------------------------
     374
     375
     376  if (nday>=0) then
     377     day_end = day_ini + nday
     378  else
     379     day_end = day_ini - nday/day_step
     380  endif
     381
     382  WRITE(lunout,300)day_ini,day_end
     383300 FORMAT('1'/,15x,'run du jour',i7,2x,'au jour',i7//)
     384
     385#ifdef CPP_IOIPSL
     386  call ju2ymds(jD_ref + day_ini - day_ref, an, mois, jour, heure)
     387  write (lunout,301)jour, mois, an
     388  call ju2ymds(jD_ref + day_end - day_ref, an, mois, jour, heure)
     389  write (lunout,302)jour, mois, an
     390301 FORMAT('1'/,15x,'run du ', i2,'/',i2,'/',i4)
     391302 FORMAT('1'/,15x,'    au ', i2,'/',i2,'/',i4)
     392#endif
     393
     394  !-----------------------------------------------------------------------
    370395  !   Initialisation de la physique :
    371396  !   -------------------------------
     
    381406  ENDIF ! of IF ((iflag_phys==1).or.(iflag_phys>=100))
    382407
    383 
    384   !-----------------------------------------------------------------------
    385   !   Initialisation des I/O :
    386   !   ------------------------
    387 
    388 
    389   if (nday>=0) then
    390      day_end = day_ini + nday
    391   else
    392      day_end = day_ini - nday/day_step
    393   endif
    394 
    395   WRITE(lunout,300)day_ini,day_end
    396 300 FORMAT('1'/,15x,'run du jour',i7,2x,'au jour',i7//)
    397 
    398 #ifdef CPP_IOIPSL
    399   call ju2ymds(jD_ref + day_ini - day_ref, an, mois, jour, heure)
    400   write (lunout,301)jour, mois, an
    401   call ju2ymds(jD_ref + day_end - day_ref, an, mois, jour, heure)
    402   write (lunout,302)jour, mois, an
    403 301 FORMAT('1'/,15x,'run du ', i2,'/',i2,'/',i4)
    404 302 FORMAT('1'/,15x,'    au ', i2,'/',i2,'/',i4)
    405 #endif
    406408
    407409  !      if (planet_type.eq."earth") then
  • LMDZ6/branches/Ocean_skin/libf/dyn3dmem/guide_loc_mod.F90

    r2740 r3605  
    12121212              enddo
    12131213            endif
    1214             if (pole_nord) then
     1214            if (pole_sud) then
    12151215              do i=1,iip1
    12161216                qgui1(ip1jm+i,l)=qgui1(ip1jm+1,l)
  • LMDZ6/branches/Ocean_skin/libf/dyn3dmem/iniacademic_loc.F90

    r2622 r3605  
    101101  time_0=0.
    102102  day_ref=1
    103   annee_ref=0
     103  ! annee_ref=0
    104104
    105105  im         = iim
  • LMDZ6/branches/Ocean_skin/libf/dyn3dmem/integrd_mod.F90

    r1907 r3605  
    2323    CALL allocate_u(deltap,llm,d)
    2424    CALL allocate_u(ps,d)
     25    ps(:)=0
    2526
    2627   
  • LMDZ6/branches/Ocean_skin/libf/dyn3dmem/leapfrog_loc.F

    r2622 r3605  
    2929       USE call_dissip_mod, ONLY : call_dissip
    3030       USE call_calfis_mod, ONLY : call_calfis
    31        USE leapfrog_mod
     31       USE leapfrog_mod, ONLY : ucov,vcov,teta,ps,masse,phis,q,dq
     32     & ,ucovm1,vcovm1,tetam1,massem1,psm1,p,pks,pk,pkf,flxw
     33     & ,pbaru,pbarv,du,dv,dteta,phi,dp,w
     34     & ,leapfrog_allocate,leapfrog_switch_caldyn,leapfrog_switch_dissip
     35
    3236       use exner_hyb_loc_m, only: exner_hyb_loc
    3337       use exner_milieu_loc_m, only: exner_milieu_loc
     
    15351539
    15361540#ifdef INCA
    1537          call finalize_inca
     1541         if (type_trac == 'inca') then
     1542            call finalize_inca
     1543         endif
    15381544#endif
    15391545
     
    15831589
    15841590#ifdef INCA
    1585               call finalize_inca
     1591              if (type_trac == 'inca') then
     1592                 call finalize_inca
     1593              endif
    15861594#endif
    15871595
     
    17321740
    17331741#ifdef INCA
    1734                  call finalize_inca
     1742                 if (type_trac == 'inca') then
     1743                    call finalize_inca
     1744                 endif
    17351745#endif
    17361746
     
    18201830
    18211831#ifdef INCA
    1822       call finalize_inca
     1832      if (type_trac == 'inca') then
     1833         call finalize_inca
     1834      endif
    18231835#endif
    18241836
  • LMDZ6/branches/Ocean_skin/libf/dyn3dmem/temps_mod.F90

    r2601 r3605  
    1313  INTEGER   annee_ref
    1414  INTEGER   day_ref
     15  INTEGER   year_len
    1516  REAL      dt ! (dynamics) time step (changes if doing Matsuno or LF step)
    1617  REAL      jD_ref ! reference julian day date (beginning of experiment)
  • LMDZ6/branches/Ocean_skin/libf/dyn3dmem/vlsplt_loc.F

    r2765 r3605  
    1919      include "dimensions.h"
    2020      include "paramet.h"
     21      include "iniprint.h"
    2122c
    2223c
     
    872873      include "dimensions.h"
    873874      include "paramet.h"
     875      include "iniprint.h"
    874876c
    875877c
     
    10271029      ELSE ! countcfl>=1
    10281030
    1029       PRINT*,'vlz passage dans le non local'
     1031      IF (prt_level>9) THEN
     1032        WRITE(lunout,*)'vlz passage dans le non local'
     1033      ENDIF
    10301034c ---------------------------------------------------------------
    10311035c  Debut du traitement du cas ou on viole le CFL : w > masse
     
    10591063c  le critère
    10601064      DO WHILE (countcfl>=1)
    1061       print*,'On viole le CFL Vertical sur ',countcfl,' pts'
     1065        IF (prt_level>9) THEN
     1066          WRITE(lunout,*)'On viole le CFL Vertical sur ',countcfl,' pts'
     1067        ENDIF
    10621068      countcfl=0
    10631069
Note: See TracChangeset for help on using the changeset viewer.