Changeset 52 for trunk/libf/dyn3dpar


Ignore:
Timestamp:
Jan 31, 2011, 12:42:42 AM (14 years ago)
Author:
aslmd
Message:

chantier principal du commit
--- version LMDZ5 qui fonctionne pour tests geantes
--- prochaine etape, tests sur GNOME

M libf/dyn3dpar/comconst.h
M libf/dyn3dpar/conf_planete.F90
ajout du flux de chaleur intrinseque: ihf
[par defaut il est nul]

M libf/dyn3dpar/gcm.F
changements cosmetiques
[pour diff plus efficace avec version non par]

M libf/dyn3dpar/iniacademic.F
possibilites de variations latitudinales
de temperature plus originales
[seulement pour planet_type.eq."giant"]

M libf/dyn3dpar/leapfrog_p.F

  1. ajout d'une tendance causee par le flux de chaleur intrinseque

(seulement prise en compte si planet_type.eq."giant")

  1. correction bugs problematiques a la compilation et au run

--> probleme dans les boucles (l'indice etait llm et non l)
--> ajout de SAVE pour les variables paralleles
--> correction des declarations de variables manquantes

M libf/dyn3dpar/calfis_p.F
correction d'une deuxieme parenthese manquante sur ALLOCATE(zteta(klon,llm))

M libf/phylmd/regr_lat_time_climoz_m.F90
erreur a la compilation avec FCM... il s'agit d'une routine terrestre
il y a visiblement un probleme avec o3_in
en attendant, les lignes sont commentees avec !AS

A deftanks/giant 8 fichiers
ajout de fichiers de configuration typiques pour les geantes gazeuses
[experimental pour le moment... on est loin de jupiter]

--> comparaisons entre un run ancien [avec LMDZ5-dev sur SVN ipsl sans cp var]
et run avec version sur ce SVN planeto donne des resultats similaires

pratique

A ioipsl
A ioipsl/compile_ioipsl.bash
A ioipsl/util 16 fichiers
script et utilitaire pour compiler IOIPSL de facon independante
il suffit d'executer ./compile_ioipsl.bash

M arch/arch-AMD64_CICLAD.path
si IOIPSL a ete compile avec la methode precedente, les bons
PATH sont definis dans ce fichier [le NETCDF est aussi OK]

M 000-README-svn
mise a jour options "svn status"

M mars/libf/phymars/meso_callkeys.h
mise a jour mineure du fichier
[ecri_phys etait defini mais pas dans la liste]

Location:
trunk/libf/dyn3dpar
Files:
6 edited

Legend:

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

    r8 r52  
    288288      ALLOCATE(flxwfi(klon,llm))
    289289! ADAPTATION GCM POUR CP(T)
    290       ALLOCATE(zteta(klon,llm)
     290      ALLOCATE(zteta(klon,llm))
    291291      ALLOCATE(zpk(klon,llm))
    292292c$OMP END MASTER
  • trunk/libf/dyn3dpar/comconst.h

    r8 r52  
    1111     &                   ,dissip_factz,dissip_deltaz,dissip_zref        &
    1212     &                   ,tau_top_bound,                                &
    13      & daylen,year_day,molmass
     13     & daylen,year_day,molmass, ihf
    1414      COMMON/cpdetvenus/nu_venus,t0_venus
    1515
     
    3636
    3737      REAL nu_venus,t0_venus ! coeffs needed for Cp(T), Venus atmosphere
     38      REAL ihf  ! (W/m2) intrinsic heat flux for giant planets
    3839
    3940
  • trunk/libf/dyn3dpar/conf_planete.F90

    r1 r52  
    6464CALL getin('omeg',omeg)
    6565
     66! Intrinsic heat flux [default is none]
     67! Aymeric -- for giant planets
     68! [matters only if planet_type="giant"]
     69ihf = 0.
     70CALL getin('ihf',ihf)
     71
     72
     73
    6674END SUBROUTINE conf_planete
  • trunk/libf/dyn3dpar/gcm.F

    r8 r52  
    5959c   Declarations:
    6060c   -------------
     61
    6162#include "dimensions.h"
    6263#include "paramet.h"
     
    6768#include "logic.h"
    6869#include "temps.h"
     70!!!!!!!!!!!#include "control.h"
    6971#include "ener.h"
    7072#include "description.h"
     
    7375#include "iniprint.h"
    7476#include "tracstoke.h"
    75 
    7677#ifdef INCA
    7778! Only INCA needs these informations (from the Earth's physics)
    7879#include "indicesol.h"
    7980#endif
    80 
    8181      INTEGER         longcles
    8282      PARAMETER     ( longcles = 20 )
     
    9393      REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm) ! vents covariants
    9494      REAL teta(ip1jmp1,llm)                 ! temperature potentielle
    95       REAL, ALLOCATABLE, DIMENSION(:,:,:) :: q ! champs advectes
     95      REAL, ALLOCATABLE, DIMENSION(:,:,:):: q! champs advectes
    9696      REAL ps(ip1jmp1)                       ! pression  au sol
    9797c      REAL p (ip1jmp1,llmp1  )               ! pression aux interfac.des couches
     
    219219#endif
    220220!      endif ! of if (planet_type.eq."earth")
    221 
     221!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     222c
    222223c Initialisations pour Cp(T) Venus
    223224      call ini_cpdet
    224 
     225c
    225226c-----------------------------------------------------------------------
    226227c   Choix du calendrier
     
    244245      endif
    245246#endif
     247c-----------------------------------------------------------------------
    246248
    247249      IF (config_inca /= 'none') THEN
     
    289291     &              teta,q,masse,ps,phis, time_0)
    290292        endif ! of if (planet_type.eq."mars")
    291 
     293       
    292294c       write(73,*) 'ucov',ucov
    293295c       write(74,*) 'vcov',vcov
     
    304306         CALL iniacademic(vcov,ucov,teta,q,masse,ps,phis,time_0)
    305307      endif
     308
    306309
    307310c-----------------------------------------------------------------------
     
    350353        write(lunout,*)' Pas de remise a zero'
    351354      ENDIF
     355
    352356c      if (annee_ref .ne. anneeref .or. day_ref .ne. dayref) then
    353357c        write(lunout,*)
     
    432436c   Initialisation de la physique :
    433437c   -------------------------------
    434       IF (call_iniphys.and.iflag_phys.eq.1) THEN
     438
     439      IF (call_iniphys.and.(iflag_phys.eq.1)) THEN
    435440         latfi(1)=rlatu(1)
    436441         lonfi(1)=0.
     
    450455         zcvfi(ngridmx) = cv(ip1jm-iim)
    451456         CALL gr_dyn_fi(1,iip1,jjp1,ngridmx,aire,airefi)
    452 
    453457         WRITE(lunout,*)
    454458     .       'GCM: WARNING!!! vitesse verticale nulle dans la physique'
     459
    455460! Initialisation de la physique: pose probleme quand on tourne
    456461! SANS physique, car iniphysiq.F est dans le repertoire phy[]...
     
    462467         call_iniphys=.false.
    463468      ENDIF ! of IF (call_iniphys.and.(iflag_phys.eq.1))
    464 
     469!#endif
    465470
    466471c-----------------------------------------------------------------------
     
    508513      IF (mpi_rank==0) then
    509514        if (ok_dyn_ins) then
    510           ! initialize output file for instantaneous outputs
    511           ! t_ops = iecri * daysec ! do operations every t_ops
    512           t_ops =((1.0*iecri)/day_step) * daysec 
    513           t_wrt = daysec ! iecri * daysec ! write output every t_wrt
    514           t_wrt = daysec ! iecri * daysec ! write output every t_wrt
    515           CALL inithist(day_ref,annee_ref,time_step,
     515        ! initialize output file for instantaneous outputs
     516        ! t_ops = iecri * daysec ! do operations every t_ops
     517        t_ops =((1.0*iecri)/day_step) * daysec 
     518        t_wrt = daysec ! iecri * daysec ! write output every t_wrt
     519        CALL inithist(day_ref,annee_ref,time_step,
    516520     &                  t_ops,t_wrt)
    517521        endif
  • trunk/libf/dyn3dpar/iniacademic.F

    r7 r52  
    9696! --------------------------------------
    9797c
     98
     99        print *, 'This is iniacademic'
     100
    98101        ! initialize planet radius, rotation rate,...
    99102        call conf_planete
     
    155158          teta0=315.     ! mean Teta (S.H. 315K)
    156159          CALL getin('teta0',teta0)
     160          print *, 'iniacademic - teta0 ', teta0
     161          print *, 'iniacademic - rad ', rad
    157162          ttp=200.       ! Tropopause temperature (S.H. 200K)
    158163          CALL getin('ttp',ttp)
     
    200205             tetajl(j,l)=teta0-delt_y*ddsin*ddsin+eps*ddsin
    201206     &           -delt_z*(1.-ddsin*ddsin)*log(zsig)
     207             !! Aymeric -- tests particuliers
     208             if (planet_type=="giant") then
     209             tetajl(j,l)=teta0+(delt_y*
     210     &          ((sin(rlatu(j)*3.14159*eps+0.0001))**2)
     211     &          / ((rlatu(j)*3.14159*eps+0.0001)**2))
     212     &          -delt_z*log(zsig)
     213!!!             ddsin=sin(2.5*3.14159*rlatu(j))
     214!!!             tetajl(j,l)=teta0-delt_y*ddsin*ddsin
     215!!!!     &           -delt_z*(1.-ddsin*ddsin)*log(zsig)
     216             endif
    202217             ! Profil stratospherique isotherme (+vortex)
    203218             w_pv=(1.-tanh((rlatu(j)-phi_pv)/dphi_pv))/2.
     
    217232            enddo
    218233          enddo
     234          PRINT *, 'iniacademic - check',tetajl(:,int(llm/2)),rlatu(:)
    219235
    220236
  • trunk/libf/dyn3dpar/leapfrog_p.F

    r8 r52  
    117117      REAL,DIMENSION(:,:,:),ALLOCATABLE,SAVE :: dqfi
    118118
     119       !! Aymeric -- cp(T) comme dans leapfrog.F, SAVE OK ???
     120      REAL,SAVE :: duspg(ip1jmp1,llm) ! for bilan_dyn
     121
     122
    119123c   variables pour le fichier histoire
    120124      REAL dtav      ! intervalle de temps elementaire
     
    177181
    178182      logical , parameter :: flag_verif = .false.
    179      
     183
     184      ! for CP(T)  -- Aymeric
     185      real :: dtec
     186      real,external :: cpdet
     187      real,save :: ztetaec(ip1jmp1,llm)  !!SAVE ???
     188
    180189c declaration liees au parallelisme
    181190      INTEGER :: ierr
     
    560569!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
    561570      do l=1,llm
    562         tsurpk(ijb:ije,llm)=cpp*temp(ijb:ije,llm)/pk(ijb:ije,llm)
     571        tsurpk(ijb:ije,l)=cpp*temp(ijb:ije,l)/pk(ijb:ije,l)
    563572      enddo
    564573!$OMP END DO
     
    9991008       enddo ! of do l=1,llm
    10001009!$OMP END DO
     1010
     1011       if (planet_type.eq."giant") then
     1012          ! Intrinsic heat flux
     1013          ! Aymeric -- for giant planets
     1014          if (ihf .gt. 1.e-6) then
     1015          !print *, '**** INTRINSIC HEAT FLUX ****', ihf
     1016          teta(ijb:ije,1) = teta(ijb:ije,1)
     1017     &        + dtvr * aire(ijb:ije) * ihf / cpp / masse(ijb:ije,1)
     1018          !print *, '**** d teta '
     1019          !print *, dtvr * aire(ijb:ije) * ihf / cpp / masse(ijb:ije,1)
     1020          endif
     1021       endif
    10011022
    10021023       call Register_Hallo(ucov,ip1jmp1,llm,0,1,1,0,Request_Physic)
     
    14631484!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
    14641485      do l=1,llm
    1465         tsurpk(ijb:ije,llm)=cpp*temp(ijb:ije,llm)/pk(ijb:ije,llm)
     1486        tsurpk(ijb:ije,l)=cpp*temp(ijb:ije,l)/pk(ijb:ije,l)
    14661487      enddo
    14671488!$OMP END DO
     
    16851706                ije=ij_end
    16861707!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
    1687                 do l=1,llm
    1688                   tsurpk(ijb:ije,llm)=cpp*temp(ijb:ije,llm)/
    1689      &                                             pk(ijb:ije,llm)
     1708                do l=1,llm     
     1709                  tsurpk(ijb:ije,l)=cpp*temp(ijb:ije,l)/
     1710     &                                             pk(ijb:ije,l)
    16901711                enddo
    16911712!$OMP END DO
Note: See TracChangeset for help on using the changeset viewer.