Changeset 815


Ignore:
Timestamp:
Oct 25, 2012, 10:11:15 AM (12 years ago)
Author:
slebonnois
Message:

SL: petites modifs Titan et Venus pour tableau controle dans la physique ; pour Titan, petits details lies a raz_date ; modif chemin ioipsl sur gnome ; + elimination d'un warning etrange dans gcm.F

Location:
trunk
Files:
2 added
1 deleted
14 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.COMMON/arch/arch-GNOMEs.path

    r270 r815  
    11NETCDF_LIBDIR="-L/usr/local/lib -lnetcdf"
    22NETCDF_INCDIR=-I/usr/local/include
    3 IOIPSL_INCDIR=$HOME/LMDZ5/ioipsl/lib
    4 IOIPSL_LIBDIR=$HOME/LMDZ5/ioipsl/lib
     3IOIPSL_INCDIR=$HOME/ioipsl/modipsl/lib
     4IOIPSL_LIBDIR=$HOME/ioipsl/modipsl/lib
    55ORCH_INCDIR=$LMDGCM/../../lib
    66ORCH_LIBDIR=$LMDGCM/../../lib
  • trunk/LMDZ.COMMON/libf/dyn3d/gcm.F

    r780 r815  
    452452         zcvfi(ngridmx) = cv(ip1jm-iim)
    453453         CALL gr_dyn_fi(1,iip1,jjp1,ngridmx,aire,airefi)
    454          WRITE(lunout,*)
    455      .       'GCM: WARNING!!! vitesse verticale nulle dans la physique'
    456454
    457455! Initialisation de la physique: pose probleme quand on tourne
  • trunk/LMDZ.COMMON/libf/dyn3dpar/gcm.F

    r776 r815  
    467467         zcvfi(ngridmx) = cv(ip1jm-iim)
    468468         CALL gr_dyn_fi(1,iip1,jjp1,ngridmx,aire,airefi)
    469          WRITE(lunout,*)
    470      .       'GCM: WARNING!!! vitesse verticale nulle dans la physique'
    471469! Physics
    472470#ifdef CPP_PHYS
  • trunk/LMDZ.TITAN/libf/phytitan/conf_phys.F90

    r495 r815  
    400400  call getin('clouds',clouds)
    401401  if (microfi.lt.1) clouds = 0      ! On  ne fait pas de nuages sans microphysique !
     402  if (clouds.eq.1) cutoff = 0       ! si nuages, il faut mettre ca
    402403
    403404!
  • trunk/LMDZ.TITAN/libf/phytitan/phyetat0.F

    r814 r815  
    44c
    55c
    6       SUBROUTINE phyetat0 (fichnom,dtime,
     6      SUBROUTINE phyetat0 (fichnom,
    77     .            rlat,rlon, tsol,tsoil,
    88     .           albe, solsw, sollw,
    99     .           fder,radsol,resch4,
    10      .           tabcntr0,
    1110     .           t_ancien,ancien_ok)
    1211c======================================================================
     
    2120#include "dimsoil.h"
    2221#include "clesphys.h"
     22#include "tabcontrol.h"
    2323#include "temps.h"
    2424c======================================================================
    2525      CHARACTER*(*) fichnom
    26       REAL dtime
    27       INTEGER radpas,chimpas
    2826      REAL rlat(klon), rlon(klon)   ! in degrees
    2927      REAL tsol(klon)
     
    4846      INTEGER nid, nvarid
    4947      INTEGER ierr, i, nsrf, isoil
    50       INTEGER length
    51       PARAMETER (length=100)
    52       REAL tab_cntrl(length), tabcntr0(length)
     48      REAL tab_cntrl(length)
    5349      CHARACTER*2 str2
    5450c
     
    8884         radpas       = tab_cntrl(2)
    8985         chimpas      = tab_cntrl(3)
     86         lsinit       = tab_cntrl(17)
    9087
    9188      ENDIF
     
    9491
    9592c Attention si raz_date est active :
    96 c il faut remettre a zero itau_phy apres phyetat0 !
     93c il faut remettre a zero itau_phy apres phyetat0
     94c et verifier que lsinit est proche de 0.
    9795      IF (raz_date.eq.1) THEN
    9896        itau_phy=0
     97        if ((lsinit.gt.3.).and.(lsinit.lt.357.)) then
     98          PRINT*, 'phyetat0: raz_date=1 and ls different from 0.'
     99          PRINT*, 'When raz_date=1, we reset the initial date'
     100          PRINT*, 'to spring equinox, Ls=0., so the start files'
     101          PRINT*, 'should be within a couple of degrees from Ls=0.'
     102          PRINT*, 'or the circulation will be too far from equilibrium'
     103          CALL abort
     104        endif
    99105      ENDIF
    100106
  • trunk/LMDZ.TITAN/libf/phytitan/phyredem.F

    r175 r815  
    33!
    44c
    5       SUBROUTINE phyredem (fichnom,dtime,radpas,chimpas,
     5      SUBROUTINE phyredem (fichnom,
    66     .           rlat,rlon, tsol,tsoil,
    77     .           albedo,
     
    2121#include "dimsoil.h"
    2222#include "clesphys.h"
     23#include "tabcontrol.h"
    2324#include "temps.h"
    2425c======================================================================
    2526      CHARACTER*13 fichnom
    26       REAL dtime
    27       INTEGER radpas,chimpas
    2827      REAL rlat(klon), rlon(klon)
    2928      REAL tsol(klon)
     
    3938      INTEGER nid, nvarid, idim1, idim2, idim3
    4039      INTEGER ierr
    41       INTEGER length
    42       PARAMETER (length=100)
    4340      REAL tab_cntrl(length)
    4441c
     
    7370      tab_cntrl(6) = nbapp_rad
    7471      tab_cntrl(16)= nbapp_chim
     72      tab_cntrl(17)= lsinit
    7573
    7674      IF( cycle_diurne ) tab_cntrl( 7 ) = 1.
  • trunk/LMDZ.TITAN/libf/phytitan/physiq.F

    r808 r815  
    7676#include "temps.h"
    7777#include "iniprint.h"
    78 #include "timerad.h"
    7978#include "logic.h"
    8079#include "comorbit.h"
    8180#include "microtab.h"
    8281#include "diagmuphy.h"
     82#include "tabcontrol.h"
    8383#include "itemps.h"
    8484c======================================================================
     
    140140c
    141141c Variables propres a la physique
    142 c
    143       REAL dtime
    144       SAVE dtime                  ! pas temporel de la physique
    145 c
    146       INTEGER radpas
    147       SAVE radpas                 ! frequence d'appel rayonnement
    148 c
    149       INTEGER chimpas
    150       SAVE chimpas                 ! frequence d'appel chimie
    151142c
    152143      REAL,save,allocatable :: radsol(:) ! bilan radiatif au sol calcule par code radiatif
     
    271262      REAL tmpout(klon,klev)  ! K s-1
    272263
     264      REAL    dtimerad
    273265      INTEGER itaprad
    274       SAVE itaprad
     266      SAVE itaprad,dtimerad
    275267      REAL zdtime
    276268c
     
    286278      REAL dist, rmu0(klon), fract(klon), pdecli
    287279      REAL zday
    288       REAL zls,zlsm1
     280      REAL zls,zlsdeg
    289281c
    290282      INTEGER i, k, iq, ig, j, ll, l
     
    338330c
    339331      REAL tr_seri(klon,klev,nqmax)
    340 
    341       INTEGER        length
    342       PARAMETER    ( length = 100 )
    343       REAL tabcntr0( length       )
    344332c
    345333c pour ioipsl
     
    492480c
    493481c REMETTRE TOUS LES PARAMETRES POUR OROGW...  A FAIRE POUR TITAN
    494          CALL phyetat0 ("startphy.nc",dtime,
     482         CALL phyetat0 ("startphy.nc",
    495483     .       rlatd,rlond,ftsol,ftsoil,
    496484     .       falbe, solsw, sollw,
    497485     .       dlw,radsol,reservoir,
    498486c     .      zmea,zstd,zsig,zgam,zthe,zpic,zval,
    499      .       tabcntr0,
    500487     .       t_ancien, ancien_ok)
    501488
    502 c dtime est lu dans startphy
     489c dtime est defini dans tabcontrol.h et lu dans startphy
    503490c pdtphys est calcule a partir des nouvelles conditions:
    504491c Reinitialisation du pas de temps physique quand changement
     
    519506         chimpas =   radpas*nbapp_rad/nbapp_chim
    520507
    521          CALL printflag( tabcntr0,radpas,chimpas,ok_mensuel,
    522      .                             ok_journe, ok_instan )
     508         CALL printflag( ok_mensuel,ok_journe, ok_instan )
    523509
    524510c
     
    861847c  calcul de la longitude solaire
    862848          CALL solarlong(rjourvrai+gmtime,zls)
    863           print*,'Ls',zls*180./RPI      ! zls est en radians !!
     849          zlsdeg = zls*180./RPI      ! zls est en radians !!
     850          print*,'Ls',zlsdeg
     851
    864852      CALL orbite(zls,dist,pdecli)
    865       IF (debut) zlsm1=zls
    866853
    867854c dans zenang, Ls en degres ; dans mucorr, Ls en radians
    868855      IF (cycle_diurne) THEN
    869856        zdtime=dtime*FLOAT(radpas) ! pas de temps du rayonnement (s)
    870         CALL zenang(zls*180./RPI,gmtime,zdtime,rlatd,rlond,rmu0,fract)
     857        CALL zenang(zlsdeg,gmtime,zdtime,rlatd,rlond,rmu0,fract)
    871858      ELSE
    872859        call mucorr(klon,zls,rlatd,rmu0,fract)
     
    16001587      IF (lafin) THEN
    16011588         itau_phy = itau_phy + itap
     1589         lsinit   = zlsdeg
    16021590c REMETTRE TOUS LES PARAMETRES POUR OROGW... A FAIRE POUR TITAN
    1603          CALL phyredem ("restartphy.nc",dtime,radpas,chimpas,
     1591         CALL phyredem ("restartphy.nc",
    16041592     .      rlatd, rlond, ftsol, ftsoil,
    16051593     .      falbe,
  • trunk/LMDZ.TITAN/libf/phytitan/printflag.F

    r102 r815  
    22! $Header: /home/cvsroot/LMDZ4/libf/phylmd/printflag.F,v 1.1.1.1 2004/05/19 12:53:09 lmdzadmin Exp $
    33!
    4        SUBROUTINE  printflag( tabcntr0, radpas, chimpas, ok_mensuel,
    5      ,                        ok_journe, ok_instan )
     4       SUBROUTINE  printflag( ok_mensuel, ok_journe, ok_instan )
    65c
    76
     
    1110       IMPLICIT NONE
    1211
    13        REAL tabcntr0( 100 )
    1412       LOGICAL cycle_diurn0,soil_model0,ok_orodr0
    1513       LOGICAL ok_orolf0,ok_gw_nonoro0
    1614       LOGICAL ok_mensuel, ok_journe, ok_instan
    17        INTEGER radpas , radpas0
    18        INTEGER chimpas, chimpas0
     15       INTEGER radpas0
     16       INTEGER chimpas0
    1917c
    2018#include "clesphys.h"
     19#include "tabcontrol.h"
    2120#include "YOMCST.h"
    2221c
  • trunk/LMDZ.TITAN/libf/phytitan/radlwsw.F

    r495 r815  
    1       SUBROUTINE radlwsw(dist, rmu0, fract, falbe, dtimerad, zzlev,
     1      SUBROUTINE radlwsw(dist, rmu0, fract, falbe, zzlev,
    22     .                  paprs, pplay,tsol, pt, nq, nmicro, pq,
    33     .                  qaer,
     
    1515c fract----input-R- duree d'ensoleillement normalisee
    1616c falbe----input-R- surface albedo
    17 c dtimerad-input-R- intervalle de temps du radiatif
    1817c zzlev----input-R- altitudes des inter-couches (m)
    1918c paprs----input-R- pression a inter-couche (Pa)
     
    4948c ARGUMENTS
    5049      INTEGER nq,nmicro
    51       real rmu0(klon), fract(klon), falbe(klon), dist, dtimerad
     50      real rmu0(klon), fract(klon), falbe(klon), dist
    5251c
    5352      real zzlev(klon,klev+1),paprs(klon,klev+1), pplay(klon,klev)
  • trunk/LMDZ.TITAN/libf/phytitan/radtitan.F

    r808 r815  
    138138       print*,'FHIR   = ',FHIR
    139139c      on initialise le paquet optcld
    140        call iniqcld()
     140       if (clouds.eq.1) call iniqcld()
    141141       iprem=1
    142142       endif
  • trunk/LMDZ.VENUS/libf/phyvenus/phyetat0.F

    r101 r815  
    44c
    55c
    6       SUBROUTINE phyetat0 (fichnom,dtime,
     6      SUBROUTINE phyetat0 (fichnom,
    77     .            rlat,rlon, tsol,tsoil,
    88     .           albe, solsw, sollw,
     
    1313
    1414      use dimphy
     15      use control_mod
    1516      IMPLICIT none
    1617c======================================================================
     
    2223#include "dimsoil.h"
    2324#include "clesphys.h"
     25#include "tabcontrol.h"
    2426#include "temps.h"
    2527c======================================================================
    2628      CHARACTER*(*) fichnom
    27       REAL dtime
    28       INTEGER radpas
    2929      REAL rlat(klon), rlon(klon)
    3030      REAL tsol(klon)
     
    4949      INTEGER nid, nvarid
    5050      INTEGER ierr, i, nsrf, isoil
    51       INTEGER length
    52       PARAMETER (length=100)
    53       REAL tab_cntrl(length), tabcntr0(length)
     51      REAL tab_cntrl(length)
    5452      CHARACTER*2 str2
    5553c
     
    9290
    9391      itau_phy = tab_cntrl(15)
     92
     93c Attention si raz_date est active :
     94c il faut remettre a zero itau_phy apres phyetat0 !
     95      IF (raz_date.eq.1) THEN
     96        itau_phy=0
     97      ENDIF
    9498
    9599c
  • trunk/LMDZ.VENUS/libf/phyvenus/phyredem.F

    r101 r815  
    33!
    44c
    5       SUBROUTINE phyredem (fichnom,dtime,radpas,
     5      SUBROUTINE phyredem (fichnom,
    66     .           rlat,rlon, tsol,tsoil,
    77     .           albedo,
     
    2222#include "dimsoil.h"
    2323#include "clesphys.h"
     24#include "tabcontrol.h"
    2425#include "temps.h"
    2526c======================================================================
    2627      CHARACTER*13 fichnom
    27       REAL dtime
    28       INTEGER radpas
    2928      REAL rlat(klon), rlon(klon)
    3029      REAL tsol(klon)
     
    4241      INTEGER nid, nvarid, idim1, idim2, idim3
    4342      INTEGER ierr
    44       INTEGER length
    45       PARAMETER (length=100)
    4643      REAL tab_cntrl(length)
    4744c
  • trunk/LMDZ.VENUS/libf/phyvenus/physiq.F

    r808 r815  
    7878#include "timerad.h"
    7979#include "logic.h"
     80#include "tabcontrol.h"
    8081c======================================================================
    8182      LOGICAL ok_journe ! sortir le fichier journalier
     
    147148
    148149c Variables propres a la physique
    149 c
    150       REAL dtime
    151       SAVE dtime                  ! pas temporel de la physique
    152 c
    153       INTEGER radpas
    154       SAVE radpas                 ! frequence d'appel rayonnement
    155150c
    156151      REAL,save,allocatable :: radsol(:) ! bilan radiatif au sol calcule par code radiatif
     
    324319      REAL tr_seri(klon,klev,nqmax)
    325320      REAL d_tr(klon,klev,nqmax)
    326 
    327       INTEGER        length
    328       PARAMETER    ( length = 100 )
    329       REAL tabcntr0( length       )
    330321c
    331322c pour ioipsl
     
    438429c
    439430c REMETTRE TOUS LES PARAMETRES POUR OROGW...
    440          CALL phyetat0 ("startphy.nc",dtime,
     431         CALL phyetat0 ("startphy.nc",
    441432     .       rlatd,rlond,ftsol,ftsoil,
    442433     .       falbe, solsw, sollw,
    443434     .       dlw,radsol,
    444435     .      zmea,zstd,zsig,zgam,zthe,zpic,zval,
    445      .       tabcntr0,
    446436     .       t_ancien, ancien_ok)
    447437
    448 c dtime est lu dans startphy
     438c dtime est defini dans tabcontrol.h et lu dans startphy
    449439c pdtphys est calcule a partir des nouvelles conditions:
    450440c Reinitialisation du pas de temps physique quand changement
     
    464454         radpas = NINT( RDAY/pdtphys/nbapp_rad)
    465455
    466          CALL printflag( tabcntr0,radpas,ok_journe,ok_instan )
     456         CALL printflag( ok_journe,ok_instan )
    467457c
    468458c---------
     
    13531343         itau_phy = itau_phy + itap
    13541344c REMETTRE TOUS LES PARAMETRES POUR OROGW...
    1355          CALL phyredem ("restartphy.nc",dtime,radpas,
     1345         CALL phyredem ("restartphy.nc",
    13561346     .      rlatd, rlond, ftsol, ftsoil,
    13571347     .      falbe,
  • trunk/LMDZ.VENUS/libf/phyvenus/printflag.F

    r102 r815  
    22! $Header: /home/cvsroot/LMDZ4/libf/phylmd/printflag.F,v 1.1.1.1 2004/05/19 12:53:09 lmdzadmin Exp $
    33!
    4        SUBROUTINE  printflag( tabcntr0, radpas,
    5      ,                        ok_journe,ok_instan )
     4       SUBROUTINE  printflag( ok_journe,ok_instan )
    65c
    76
     
    1110       IMPLICIT NONE
    1211
    13        REAL tabcntr0( 100 )
    1412       LOGICAL cycle_diurn0,soil_model0,ok_orodr0
    1513       LOGICAL ok_orolf0,ok_gw_nonoro0
    1614       LOGICAL ok_journe,ok_instan
    17        INTEGER radpas , radpas0
     15       INTEGER radpas0
    1816c
    1917#include "clesphys.h"
     18#include "tabcontrol.h"
    2019#include "YOMCST.h"
    2120c
Note: See TracChangeset for help on using the changeset viewer.