/[lmdze]/trunk/phylmd/physiq.f90
ViewVC logotype

Diff of /trunk/phylmd/physiq.f90

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

revision 62 by guez, Thu Jul 26 14:37:37 2012 UTC revision 68 by guez, Wed Nov 14 16:59:30 2012 UTC
# Line 14  contains Line 14  contains
14    
15      use aaam_bud_m, only: aaam_bud      use aaam_bud_m, only: aaam_bud
16      USE abort_gcm_m, ONLY: abort_gcm      USE abort_gcm_m, ONLY: abort_gcm
17        use aeropt_m, only: aeropt
18      use ajsec_m, only: ajsec      use ajsec_m, only: ajsec
19      USE calendar, ONLY: ymds2ju      USE calendar, ONLY: ymds2ju
20      use calltherm_m, only: calltherm      use calltherm_m, only: calltherm
# Line 36  contains Line 37  contains
37      USE dimsoil, ONLY: nsoilmx      USE dimsoil, ONLY: nsoilmx
38      use drag_noro_m, only: drag_noro      use drag_noro_m, only: drag_noro
39      USE fcttre, ONLY: foeew, qsatl, qsats, thermcep      USE fcttre, ONLY: foeew, qsatl, qsats, thermcep
40        use fisrtilp_m, only: fisrtilp
41      USE hgardfou_m, ONLY: hgardfou      USE hgardfou_m, ONLY: hgardfou
42      USE histsync_m, ONLY: histsync      USE histsync_m, ONLY: histsync
43      USE histwrite_m, ONLY: histwrite      USE histwrite_m, ONLY: histwrite
# Line 44  contains Line 46  contains
46      USE ini_histhf_m, ONLY: ini_histhf      USE ini_histhf_m, ONLY: ini_histhf
47      USE ini_histday_m, ONLY: ini_histday      USE ini_histday_m, ONLY: ini_histday
48      USE ini_histins_m, ONLY: ini_histins      USE ini_histins_m, ONLY: ini_histins
49        use newmicro_m, only: newmicro
50      USE oasis_m, ONLY: ok_oasis      USE oasis_m, ONLY: ok_oasis
51      USE orbite_m, ONLY: orbite, zenang      USE orbite_m, ONLY: orbite, zenang
52      USE ozonecm_m, ONLY: ozonecm      USE ozonecm_m, ONLY: ozonecm
# Line 56  contains Line 59  contains
59      use sugwd_m, only: sugwd      use sugwd_m, only: sugwd
60      USE suphec_m, ONLY: ra, rcpd, retv, rg, rlvtt, romega, rsigma, rtt      USE suphec_m, ONLY: ra, rcpd, retv, rg, rlvtt, romega, rsigma, rtt
61      USE temps, ONLY: annee_ref, day_ref, itau_phy      USE temps, ONLY: annee_ref, day_ref, itau_phy
62        use unit_nml_m, only: unit_nml
63      USE yoethf_m, ONLY: r2es, rvtmp2      USE yoethf_m, ONLY: r2es, rvtmp2
64    
65      ! Arguments:      ! Arguments:
# Line 116  contains Line 120  contains
120      logical rnpb      logical rnpb
121      parameter(rnpb = .true.)      parameter(rnpb = .true.)
122    
123      character(len = 6), save:: ocean      character(len = 6):: ocean = 'force '
124      ! (type de modèle océan à utiliser: "force" ou "slab" mais pas "couple")      ! (type de modèle océan à utiliser: "force" ou "slab" mais pas "couple")
125    
126      logical ok_ocean      logical ok_ocean
# Line 129  contains Line 133  contains
133      REAL fluxg(klon) ! flux turbulents ocean-atmosphere      REAL fluxg(klon) ! flux turbulents ocean-atmosphere
134    
135      ! Modele thermique du sol, a activer pour le cycle diurne:      ! Modele thermique du sol, a activer pour le cycle diurne:
136      logical, save:: ok_veget      logical:: ok_veget = .false. ! type de modele de vegetation utilise
     LOGICAL, save:: ok_journe ! sortir le fichier journalier  
137    
138      LOGICAL ok_mensuel ! sortir le fichier mensuel      logical:: ok_journe = .false., ok_mensuel = .true., ok_instan = .false.
139        ! sorties journalieres, mensuelles et instantanees dans les
140      LOGICAL ok_instan ! sortir le fichier instantane      ! fichiers histday, histmth et histins
     save ok_instan  
141    
142      LOGICAL ok_region ! sortir le fichier regional      LOGICAL ok_region ! sortir le fichier regional
143      PARAMETER (ok_region = .FALSE.)      PARAMETER (ok_region = .FALSE.)
# Line 391  contains Line 393  contains
393      EXTERNAL alboc ! calculer l'albedo sur ocean      EXTERNAL alboc ! calculer l'albedo sur ocean
394      !KE43      !KE43
395      EXTERNAL conema3 ! convect4.3      EXTERNAL conema3 ! convect4.3
     EXTERNAL fisrtilp ! schema de condensation a grande echelle (pluie)  
396      EXTERNAL nuage ! calculer les proprietes radiatives      EXTERNAL nuage ! calculer les proprietes radiatives
397      EXTERNAL transp ! transport total de l'eau et de l'energie      EXTERNAL transp ! transport total de l'eau et de l'energie
398    
# Line 535  contains Line 536  contains
536      REAL d_u_lif(klon, llm), d_v_lif(klon, llm)      REAL d_u_lif(klon, llm), d_v_lif(klon, llm)
537      REAL d_t_lif(klon, llm)      REAL d_t_lif(klon, llm)
538    
539      REAL ratqs(klon, llm), ratqss(klon, llm), ratqsc(klon, llm)      REAL, save:: ratqs(klon, llm)
540      real ratqsbas, ratqshaut      real ratqss(klon, llm), ratqsc(klon, llm)
541      save ratqsbas, ratqshaut, ratqs      real:: ratqsbas = 0.01, ratqshaut = 0.3
542    
543      ! Parametres lies au nouveau schema de nuages (SB, PDF)      ! Parametres lies au nouveau schema de nuages (SB, PDF)
544      real, save:: fact_cldcon      real:: fact_cldcon = 0.375
545      real, save:: facttemps      real:: facttemps = 1.e-4
546      logical ok_newmicro      logical:: ok_newmicro = .true.
     save ok_newmicro  
547      real facteur      real facteur
548    
549      integer iflag_cldcon      integer:: iflag_cldcon = 1
     save iflag_cldcon  
   
550      logical ptconv(klon, llm)      logical ptconv(klon, llm)
551    
552      ! Variables locales pour effectuer les appels en série :      ! Variables locales pour effectuer les appels en série :
# Line 594  contains Line 592  contains
592      REAL zero_v(klon)      REAL zero_v(klon)
593      CHARACTER(LEN = 15) tit      CHARACTER(LEN = 15) tit
594      INTEGER:: ip_ebil = 0 ! print level for energy conservation diagnostics      INTEGER:: ip_ebil = 0 ! print level for energy conservation diagnostics
595      INTEGER, SAVE:: if_ebil ! level for energy conservation diagnostics      INTEGER:: if_ebil = 0 ! verbosity for diagnostics of energy conservation
596    
597      REAL d_t_ec(klon, llm) ! tendance due à la conversion Ec -> E thermique      REAL d_t_ec(klon, llm) ! tendance due à la conversion Ec -> E thermique
598      REAL ZRCPD      REAL ZRCPD
# Line 616  contains Line 614  contains
614      REAL fl(klon, llm) ! denominator of re      REAL fl(klon, llm) ! denominator of re
615    
616      ! Aerosol optical properties      ! Aerosol optical properties
617      REAL tau_ae(klon, llm, 2), piz_ae(klon, llm, 2)      REAL, save:: tau_ae(klon, llm, 2), piz_ae(klon, llm, 2)
618      REAL cg_ae(klon, llm, 2)      REAL, save:: cg_ae(klon, llm, 2)
619    
620      REAL topswad(klon), solswad(klon) ! Aerosol direct effect.      REAL topswad(klon), solswad(klon) ! aerosol direct effect
621      ! ok_ade = True -ADE = topswad-topsw      ! ok_ade --> ADE = topswad - topsw
622    
623      REAL topswai(klon), solswai(klon) ! aerosol indirect effect      REAL topswai(klon), solswai(klon) ! aerosol indirect effect
624      ! ok_aie = True ->      ! ok_aie .and. ok_ade --> AIE = topswai - topswad
625      ! ok_ade = True -AIE = topswai-topswad      ! ok_aie .and. .not. ok_ade --> AIE = topswai - topsw
     ! ok_ade = F -AIE = topswai-topsw  
626    
627      REAL aerindex(klon) ! POLDER aerosol index      REAL aerindex(klon) ! POLDER aerosol index
628    
629      ! Parameters      LOGICAL:: ok_ade = .false. ! apply aerosol direct effect
630      LOGICAL, save:: ok_ade ! apply aerosol direct effect      LOGICAL:: ok_aie = .false. ! apply aerosol indirect effect
631      LOGICAL, save:: ok_aie ! Apply aerosol indirect effect  
632      REAL bl95_b0, bl95_b1 ! Parameter in Boucher and Lohmann (1995)      REAL:: bl95_b0 = 2., bl95_b1 = 0.2
633        ! Parameters in the formula to link CDNC to aerosol mass conc
634        ! (Boucher and Lohmann, 1995), used in nuage.F
635    
     SAVE bl95_b0, bl95_b1  
636      SAVE u10m      SAVE u10m
637      SAVE v10m      SAVE v10m
638      SAVE t2m      SAVE t2m
639      SAVE q2m      SAVE q2m
640      SAVE ffonte      SAVE ffonte
641      SAVE fqcalving      SAVE fqcalving
     SAVE piz_ae  
     SAVE tau_ae  
     SAVE cg_ae  
642      SAVE rain_con      SAVE rain_con
643      SAVE snow_con      SAVE snow_con
644      SAVE topswai      SAVE topswai
# Line 660  contains Line 655  contains
655    
656      real, parameter:: dobson_u = 2.1415e-05 ! Dobson unit, in kg m-2      real, parameter:: dobson_u = 2.1415e-05 ! Dobson unit, in kg m-2
657    
658        namelist /physiq_nml/ ocean, ok_veget, ok_journe, ok_mensuel, ok_instan, &
659             fact_cldcon, facttemps, ok_newmicro, iflag_cldcon, ratqsbas, &
660             ratqshaut, if_ebil, ok_ade, ok_aie, bl95_b0, bl95_b1, iflag_thermals, &
661             nsplit_thermals
662    
663      !----------------------------------------------------------------      !----------------------------------------------------------------
664    
665      modname = 'physiq'      modname = 'physiq'
# Line 714  contains Line 714  contains
714    
715         IF (if_ebil >= 1) d_h_vcol_phy = 0.         IF (if_ebil >= 1) d_h_vcol_phy = 0.
716    
717           iflag_thermals = 0
718           nsplit_thermals = 1
719           print *, "Enter namelist 'physiq_nml'."
720           read(unit=*, nml=physiq_nml)
721           write(unit_nml, nml=physiq_nml)
722    
723         ! Appel à la lecture du run.def physique         ! Appel à la lecture du run.def physique
724         call conf_phys(ocean, ok_veget, ok_journe, ok_mensuel, ok_instan, &         call conf_phys
             fact_cldcon, facttemps, ok_newmicro, iflag_cldcon, ratqsbas, &  
             ratqshaut, if_ebil, ok_ade, ok_aie, bl95_b0, bl95_b1, &  
             iflag_thermals, nsplit_thermals)  
725    
726         ! Initialiser les compteurs:         ! Initialiser les compteurs:
727    
# Line 1472  contains Line 1475  contains
1475      ENDDO      ENDDO
1476    
1477      ! Introduce the aerosol direct and first indirect radiative forcings:      ! Introduce the aerosol direct and first indirect radiative forcings:
     ! Johannes Quaas, 27/11/2003  
1478      IF (ok_ade .OR. ok_aie) THEN      IF (ok_ade .OR. ok_aie) THEN
1479         ! Get sulfate aerosol distribution         ! Get sulfate aerosol distribution :
1480         CALL readsulfate(rdayvrai, firstcal, sulfate)         CALL readsulfate(rdayvrai, firstcal, sulfate)
1481         CALL readsulfate_preind(rdayvrai, firstcal, sulfate_pi)         CALL readsulfate_preind(rdayvrai, firstcal, sulfate_pi)
1482    
        ! Calculate aerosol optical properties (Olivier Boucher)  
1483         CALL aeropt(play, paprs, t_seri, sulfate, rhcl, tau_ae, piz_ae, cg_ae, &         CALL aeropt(play, paprs, t_seri, sulfate, rhcl, tau_ae, piz_ae, cg_ae, &
1484              aerindex)              aerindex)
1485      ELSE      ELSE

Legend:
Removed from v.62  
changed lines
  Added in v.68

  ViewVC Help
Powered by ViewVC 1.1.21