Ignore:
Timestamp:
Sep 14, 2007, 4:01:10 PM (17 years ago)
Author:
Laurent Fairhead
Message:

Création de la branche LMDZ4_V3_patches: à partir de la version de référence LMDZ4_V3,

on corrige différents bugs qui sont sur la branche de développement HEAD pour établir
une version de référence LMDZ4_V3 pour les utilisateurs non-développeurs

Cette branche ne servira que pour les corrections de bugs et les version y seront tagguées

LF

Location:
LMDZ4/branches/LMDZ4_V3_patches/libf/phylmd
Files:
12 edited

Legend:

Unmodified
Added
Removed
  • LMDZ4/branches/LMDZ4_V3_patches/libf/phylmd/albedo.F

    r766 r845  
    2121cym#include "dimphy.h"
    2222#include "YOMCST.h"
     23#include "clesphys.h"
    2324c
    24       REAL fmagic ! un facteur magique pour regler l'albedo
     25c fmagic -> clesphys.h/.inc
     26c     REAL fmagic ! un facteur magique pour regler l'albedo
    2527ccc      PARAMETER (fmagic=0.7)
    2628cccIM => a remplacer 
    2729c       PARAMETER (fmagic=1.32)
    28         PARAMETER (fmagic=1.0)
     30c       PARAMETER (fmagic=1.0)
    2931c       PARAMETER (fmagic=0.7)
    3032      INTEGER npts ! il controle la precision de l'integration
     
    144146cym#include "dimensions.h"
    145147cym#include "dimphy.h"
     148#include "clesphys.h"
    146149      REAL rmu0(klon), albedo(klon)
    147150c
    148       REAL fmagic ! un facteur magique pour regler l'albedo
     151c     REAL fmagic ! un facteur magique pour regler l'albedo
    149152ccc      PARAMETER (fmagic=0.7)
    150153cccIM => a remplacer 
    151154c       PARAMETER (fmagic=1.32)
    152         PARAMETER (fmagic=1.0)
     155c       PARAMETER (fmagic=1.0)
    153156c       PARAMETER (fmagic=0.7)
    154157c
  • LMDZ4/branches/LMDZ4_V3_patches/libf/phylmd/calcul_simulISCCP.h

    r766 r845  
    1010c
    1111      nbapp_isccp=30 !appel toutes les 15h
    12       isccppas=NINT((itap*dtime)/3600.) !Nb. d'heures de la physique
     12cIM 170107      isccppas=NINT((itap*dtime)/3600.) !Nb. d'heures de la physique
    1313      freqin_pdt(n)=ifreq_isccp(n)
    1414c
  • LMDZ4/branches/LMDZ4_V3_patches/libf/phylmd/clesphys.h

    r793 r845  
    3131!IM ok_kzmin : clef calcul Kzmin dans la CL de surface cf FH
    3232       LOGICAL ok_kzmin
     33!IM fmagic : parametre pour regler l albedo sur ocean
     34       REAL fmagic
    3335!IM lev_histhf  : niveau sorties 6h
    3436!IM lev_histday : niveau sorties journalieres
     
    4042       REAL ecrit_ins, ecrit_hf, ecrit_hf2mth, ecrit_day
    4143       REAL ecrit_mth, ecrit_tra, ecrit_reg
    42        REAL freqin_isccp, freqout_isccp
     44       REAL freq_ISCCP, ecrit_ISCCP
    4345       INTEGER :: ip_ebil_phy
    4446       LOGICAL ok_slab_sicOBS
     
    4951     &     , CH4_ppb, N2O_ppb, CFC11_ppt, CFC12_ppt                     &
    5052     &     , top_height, overlap, cdmmax, cdhmax, ksta, ksta_ter        &
    51      &     , ok_kzmin, lev_histhf, lev_histday, lev_histmth             &
     53     &     , ok_kzmin, fmagic, lev_histhf, lev_histday, lev_histmth     &
    5254     &     , type_run, ok_isccp, ok_regdyn                              &
    5355     &     , lonmin_ins, lonmax_ins, latmin_ins, latmax_ins             &
    5456     &     , ecrit_ins, ecrit_hf, ecrit_hf2mth, ecrit_day               &
    5557     &     , ecrit_mth, ecrit_tra, ecrit_reg                            &
    56      &     , freqin_isccp, freqout_isccp, ip_ebil_phy                   &
     58     &     , freq_ISCCP, ecrit_ISCCP, ip_ebil_phy                       &
    5759     &     , ok_slab_sicOBS, ok_lic_melt, cvl_corr
    5860     
  • LMDZ4/branches/LMDZ4_V3_patches/libf/phylmd/conf_phys.F90

    r793 r845  
    55!
    66
    7   subroutine conf_phys(ocean, ok_veget, ok_journe, ok_mensuel, ok_instan, &
     7  subroutine conf_phys(ocean, ok_veget, ok_journe, ok_mensuel, ok_instan, ok_hf, &
    88 &                     fact_cldcon, facttemps,ok_newmicro,iflag_cldcon, &
    99!IM&                   ratqsbas,ratqshaut,ip_ebil_phy, &
     
    1919 include "fisrtilp.h"
    2020 include "nuage.h"
    21    include "YOMCST.h"
     21 include "YOMCST.h"
    2222!IM : on inclut/initialise les taux de CH4, N2O, CFC11 et CFC12
    2323include "clesphys.h"
     
    3535! ok_veget:   type de modele de vegetation
    3636! ok_journe:  sorties journalieres
     37! ok_hf:  sorties haute frequence
    3738! ok_mensuel: sorties mensuelles
    3839! ok_instan:  sorties instantanees
     
    4546  character (len = 6)  :: ocean
    4647  logical              :: ok_veget, ok_newmicro
    47   logical              :: ok_journe, ok_mensuel, ok_instan       
     48  logical              :: ok_journe, ok_mensuel, ok_instan, ok_hf
    4849  LOGICAL              :: ok_ade, ok_aie
    4950  REAL                 :: bl95_b0, bl95_b1
     
    5354  character (len = 6),SAVE  :: ocean_omp
    5455  logical,SAVE              :: ok_veget_omp, ok_newmicro_omp
    55   logical,SAVE        :: ok_journe_omp, ok_mensuel_omp, ok_instan_omp       
     56  logical,SAVE        :: ok_journe_omp, ok_mensuel_omp, ok_instan_omp, ok_hf_omp       
    5657  LOGICAL,SAVE        :: ok_ade_omp, ok_aie_omp
    5758  REAL,SAVE           :: bl95_b0_omp, bl95_b1_omp
     59  REAL,SAVE           :: freq_ISCCP_omp, ecrit_ISCCP_omp
    5860  real,SAVE           :: fact_cldcon_omp, facttemps_omp,ratqsbas_omp
    5961  real,SAVE           :: ratqshaut_omp
     
    8082  REAL,SAVE :: cdmmax_omp,cdhmax_omp,ksta_omp,ksta_ter_omp
    8183  LOGICAL,SAVE :: ok_kzmin_omp
     84  REAL, SAVE ::  fmagic_omp
    8285  INTEGER,SAVE :: iflag_pbl_omp,lev_histhf_omp,lev_histday_omp,lev_histmth_omp
    8386  CHARACTER*4, SAVE :: type_run_omp
     
    119122  call getin('OK_journe', ok_journe_omp)
    120123!
     124!Config Key  = ok_hf
     125!Config Desc = Pour des sorties haute frequence
     126!Config Def  = .false.
     127!Config Help = Pour creer le fichier histhf contenant les sorties
     128!              haute frequence ( 3h ou 6h)
     129!
     130  ok_hf_omp = .false.
     131  call getin('ok_hf', ok_hf_omp)
     132!
    121133!Config Key  = OK_mensuel
    122134!Config Desc = Pour des sorties mensuelles
     
    171183  call getin('bl95_b1', bl95_b1_omp)
    172184
    173 !
     185!Config Key  = freq_ISCCP
     186!Config Desc = Frequence d'appel du simulateur ISCCP en secondes;
     187!              par defaut 10800, i.e. 3 heures
     188!Config Def  = 10800.
     189!Config Help = Used in ini_histISCCP.h
     190!
     191  freq_ISCCP_omp = 10800.
     192  call getin('freq_ISCCP', freq_ISCCP_omp)
     193!
     194!Config Key  = ecrit_ISCCP
     195!Config Desc = Frequence d'ecriture des resultats du simulateur ISCCP en nombre de jours;
     196!              par defaut 1., i.e. 1 jour
     197!Config Def  = 1.
     198!Config Help = Used in ini_histISCCP.h
     199!
     200!
     201  ecrit_ISCCP_omp = 1.
     202  call getin('ecrit_ISCCP', ecrit_ISCCP_omp)
    174203!
    175204!Config Key  = ip_ebil_phy
     
    562591  call getin('ok_kzmin',ok_kzmin_omp)
    563592
     593!
     594!Config Key  = fmagic
     595!Config Desc =
     596!Config Def  = 1.
     597!Config Help = Used in albedo.F
     598!
     599  fmagic_omp = 1.
     600  call getin('fmagic',fmagic_omp)
     601
    564602!Config Key = ok_lic_melt
    565603!Config Desc = Prise en compte de la fonte de la calotte dans le bilan d'eau
     
    636674  call getin('type_run',type_run_omp)
    637675
    638   !
     676!
    639677!Config Key  = ok_isccp
    640678!Config Desc =
     
    693731!Config Desc =
    694732!Config Def  = 1.0 !tous les jours
    695 !Config Help =
     733!Config Help = nombre de jours pour ecriture fichier histday.nc
    696734!
    697735  ecrit_day_omp = 1.0
     
    773811    ksta_ter = ksta_ter_omp
    774812    ok_kzmin = ok_kzmin_omp
     813    fmagic = fmagic_omp
    775814    iflag_pbl = iflag_pbl_omp
    776815    lev_histhf = lev_histhf_omp
     
    782821    ok_newmicro = ok_newmicro_omp
    783822    ok_journe = ok_journe_omp
     823    ok_hf = ok_hf_omp
    784824    ok_mensuel = ok_mensuel_omp
    785825    ok_instan = ok_instan_omp
     826    freq_ISCCP = freq_ISCCP_omp
     827    ecrit_ISCCP = ecrit_ISCCP_omp
    786828    ok_ade = ok_ade_omp
    787829    ok_aie = ok_aie_omp
     
    818860  write(numout,*)' Config veget = ', ok_veget
    819861  write(numout,*)' Sortie journaliere = ', ok_journe
     862  write(numout,*)' Sortie haute frequence = ', ok_hf
    820863  write(numout,*)' Sortie mensuelle = ', ok_mensuel
    821864  write(numout,*)' Sortie instantanee = ', ok_instan
     865  write(numout,*)' Frequence appel simulateur ISCCP, freq_ISCCP =', freq_ISCCP
     866  write(numout,*)' Frequence appel simulateur ISCCP, ecrit_ISCCP =', ecrit_ISCCP
    822867  write(numout,*)' Sortie bilan d''energie, ip_ebil_phy =', ip_ebil_phy
    823868  write(numout,*)' Excentricite = ',R_ecc
     
    858903  write(numout,*)' ksta_ter = ',ksta_ter
    859904  write(numout,*)' ok_kzmin = ',ok_kzmin
     905  write(numout,*)' fmagic = ',fmagic
    860906  write(numout,*)' ok_ade = ',ok_ade
    861907  write(numout,*)' ok_aie = ',ok_aie
     
    871917  write(numout,*)' lonmin lonmax latmin latmax bilKP_ins =',&
    872918 & lonmin_ins, lonmax_ins, latmin_ins, latmax_ins
    873   write(numout,*)' ecrit_ hf, day, mth, reg',&
    874  & ecrit_hf, ecrit_day, ecrit_mth, ecrit_reg, ecrit_tra
     919  write(numout,*)' ecrit_ hf, day, mth, reg, tra, ISCCP',&
     920 & ecrit_hf, ecrit_day, ecrit_mth, ecrit_reg, ecrit_tra, ecrit_ISCCP
    875921
    876922!$OMP END MASTER
  • LMDZ4/branches/LMDZ4_V3_patches/libf/phylmd/cpl_mod.F90

    r793 r845  
    1717! Use statements
    1818!*************************************************************************************
    19   USE dimphy, ONLY : klon, zmasq
     19  USE dimphy, ONLY : klon
    2020  USE mod_phys_lmdz_para
    2121  USE ioipsl
     
    7171  REAL, ALLOCATABLE, DIMENSION(:,:), SAVE   :: pctsrf_sav   
    7272  !$OMP THREADPRIVATE(pctsrf_sav)
    73   REAL, ALLOCATABLE, DIMENSION(:,:), SAVE   :: zmasq2D
    74   !$OMP THREADPRIVATE(zmasq2D)
    7573  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE  :: unity
    7674  !$OMP THREADPRIVATE(unity)
     
    181179    ALLOCATE(read_alb_sic(iim, jj_nb), stat = error)
    182180    sum_error = sum_error + error
    183     ALLOCATE(zmasq2D(iim, jj_nb), stat = error)
    184     sum_error = sum_error + error   
    185    
    186181
    187182    IF (sum_error /= 0) THEN
     
    202197    cpl_taux = 0.   ; cpl_tauy = 0.  ; cpl_rriv2D = 0. ; cpl_rcoa2D = 0.
    203198    cpl_rlic2D = 0. ; cpl_windsp = 0.
    204 
    205 !*************************************************************************************
    206 ! Transform the land-ocean mask into 2D grid.
    207 ! Colorize zmasq2D with 99 so that after gath2cpl points not valid can be recognized.
    208 !
    209 !*************************************************************************************
    210     zmasq2D(:,:) = 99.
    211     CALL gath2cpl(zmasq, zmasq2D, klon, unity)
    212199
    213200!*************************************************************************************
     
    936923    INTEGER, DIMENSION(iim*(jjm+1))                      :: ndexct
    937924    REAL                                                 :: Up, Down
    938     REAL, DIMENSION(iim, jj_nb)                       :: tmp_lon, tmp_lat
    939     REAL, DIMENSION(iim, jj_nb, 4)                    :: pctsrf2D
    940     REAL, DIMENSION(iim, jj_nb)                       :: deno
     925    REAL, DIMENSION(iim, jj_nb)                          :: tmp_lon, tmp_lat
     926    REAL, DIMENSION(iim, jj_nb, 4)                       :: pctsrf2D
     927    REAL, DIMENSION(iim, jj_nb)                          :: deno
    941928    CHARACTER(len = 20)                                  :: modname = 'cpl_send_all'
    942929    CHARACTER(len = 80)                                  :: abort_message
    943930   
    944931! Variables with fields to coupler
    945     REAL, DIMENSION(iim, jj_nb)                       :: tmp_taux
    946     REAL, DIMENSION(iim, jj_nb)                       :: tmp_tauy
    947     REAL, DIMENSION(iim, jj_nb)                       :: tmp_calv
     932    REAL, DIMENSION(iim, jj_nb)                          :: tmp_taux
     933    REAL, DIMENSION(iim, jj_nb)                          :: tmp_tauy
     934    REAL, DIMENSION(iim, jj_nb)                          :: tmp_calv
    948935! Table with all fields to send to coupler
    949     REAL, DIMENSION(iim, jj_nb, jpflda2o1+jpflda2o2)  :: tab_flds
     936    REAL, DIMENSION(iim, jj_nb, jpflda2o1+jpflda2o2)     :: tab_flds
    950937#ifdef CPP_PARA
    951938    INCLUDE 'mpif.h'
     
    10361023    tmp_tauy(:,:)    = 0.0
    10371024   
    1038     ! For all valid grid cells not entier land
    1039     WHERE (zmasq2D /= 1. .AND. zmasq2D /=99. )
    1040        deno =  pctsrf2D(:,:,is_oce) + pctsrf2D(:,:,is_sic) ! fraction oce+seaice
     1025
     1026    ! fraction oce+seaice
     1027    deno =  pctsrf2D(:,:,is_oce) + pctsrf2D(:,:,is_sic)
     1028    ! For all valid grid cells containing some fraction of ocean or sea-ice
     1029    WHERE ( deno(:,:) /= 0 )
     1030       tab_flds(:,:,15) = cpl_rain2D(:,:,1) * pctsrf2D(:,:,is_oce) / deno(:,:) +    &
     1031            cpl_rain2D(:,:,2) * pctsrf2D(:,:,is_sic) / deno(:,:)
     1032       tab_flds(:,:,16) = cpl_snow2D(:,:,1) * pctsrf2D(:,:,is_oce) / deno(:,:) +    &
     1033            cpl_snow2D(:,:,2) * pctsrf2D(:,:,is_sic) / deno(:,:)
    10411034       
    1042        tab_flds(:,:,15) = cpl_rain2D(:,:,1) * pctsrf2D(:,:,is_oce) / deno +    &
    1043             cpl_rain2D(:,:,2) * pctsrf2D(:,:,is_sic) / deno
    1044        tab_flds(:,:,16) = cpl_snow2D(:,:,1) * pctsrf2D(:,:,is_oce) / deno +    &
    1045             cpl_snow2D(:,:,2) * pctsrf2D(:,:,is_sic) / deno
    1046        
    1047        tmp_taux = cpl_taux2D(:,:,1) * pctsrf2D(:,:,is_oce) / deno +    &
    1048             cpl_taux2D(:,:,2) * pctsrf2D(:,:,is_sic) / deno
    1049        tmp_tauy = cpl_tauy2D(:,:,1) * pctsrf2D(:,:,is_oce) / deno +    &
    1050             cpl_tauy2D(:,:,2) * pctsrf2D(:,:,is_sic) / deno
     1035       tmp_taux = cpl_taux2D(:,:,1) * pctsrf2D(:,:,is_oce) / deno(:,:) +    &
     1036            cpl_taux2D(:,:,2) * pctsrf2D(:,:,is_sic) / deno(:,:)
     1037       tmp_tauy = cpl_tauy2D(:,:,1) * pctsrf2D(:,:,is_oce) / deno(:,:) +    &
     1038            cpl_tauy2D(:,:,2) * pctsrf2D(:,:,is_sic) / deno(:,:)
    10511039    ENDWHERE
    10521040
  • LMDZ4/branches/LMDZ4_V3_patches/libf/phylmd/cv3_routines.F

    r776 r845  
    10751075        endif
    10761076 506   continue
    1077        buoy(icb(i),k)=buoybase(i)
     1077cIM cf. CRio/JYG 270807   buoy(icb(i),k)=buoybase(i)
     1078       buoy(i,icb(i))=buoybase(i)
    10781079 505  continue
    10791080
     
    12041205        enddo
    12051206      enddo
    1206      
     1207
    12071208      do 600 k=minorig+1,nl
    12081209        do 590 i=1,ncum
  • LMDZ4/branches/LMDZ4_V3_patches/libf/phylmd/ini_histISCCP.h

    r776 r845  
    1515cIM 300505     zstophy = dtime
    1616c appel du simulateur toutes les 3heures
    17           zcals(1) = dtime *6.  !toutes les 3h (en s)
     17!IM on lit la frequence d'appel dans physiq.def
     18!         zcals(1) = dtime *6.  !toutes les 3h (en s)
     19          zcals(1) = freq_ISCCP !toutes les freq_ISCCP secondes
    1820        DO n=1, napisccp
    1921          zcalh(n) = zcals(n)/3600. !stoutes les Xh (en heures)
     
    2931c       IF(freqout_isccp.EQ.1.) THEN
    3032c ecriture jounaliere
    31           zout_isccp(1) = ecrit_day !(en s)
     33!IM on ecrit les resultats du simulateur ISCCP toutes les
     34! ecrit_ISCCP secondes      zout_isccp(1) = ecrit_day !(en s)
     35          zout_isccp(1) = ecrit_ISCCP !(en s)
    3236c ecriture mensuelle
    3337c         zout = dtime * ecrit_mth !(en s)
     
    3741c le nombre de sous-colonnes ncol : ncol=(100.*zcalh)/zoutd
    3842          ncol(n)=NINT((100.*zcalh(n))/zoutj(n))
    39           PRINT*,'n ncol',n,ncol(n)
     43          IF(ncol(n).GT.ncolmx) THEN
     44           PRINT*,'Warning: Augmenter le nombre colonnes du simulateur'
     45           PRINT*,'         ISCCP ncol=', ncol,' ncolmx=',ncolmx
     46c          PRINT*,'n ncol',n,ncol(n)
     47           CALL abort
     48          ENDIF
    4049c
    4150        DO l=1, ncol(n)
     
    8089cym          enddo
    8190c
    82           print*,'On stoke le fichier histISCCP instantanne sur ',
     91          print*,'On stoke le fichier histISCCP sur ',
    8392     s   imin_ins,imax_ins,jmin_ins,jmax_ins
    8493cym          print*,'On stoke le fichier histISCCP instantanne sur ',
     
    94103         CALL histbeg_phy("histISCCP.nc", itau_phy, zjulian, dtime,
    95104     .                 nhori, nid_isccp)
    96 
    97105        ENDIF !(1.EQ.0) THEN
    98106c
     
    106114         CALL histbeg_phy("histISCCP.nc", itau_phy, zjulian, dtime,
    107115     .                 nhori, nid_isccp)
    108 
    109116c
    110117        IF(type_run.EQ."ENSP".OR.type_run.EQ."CLIM") THEN
     
    128135c
    129136         DO k=1, kmaxm1
    130           CALL histdef(nid_isccp, "cldISCCP_"//taulev(k)//typinout(n),
     137          CALL histdef(nid_isccp, "cldISCCP_"//taulev(k)//verticaxe(n),
    131138     .                "LMDZ ISCCP cld", "%",
    132139     .                iim, jj_nb,nhori,lmaxm1,1,lmaxm1,nvert,32,
     
    134141         ENDDO
    135142c
    136          CALL histdef(nid_isccp, "nsunlit"//typinout(n),
     143         CALL histdef(nid_isccp, "nsunlit"//verticaxe(n),
    137144     .                "Nb of calls with sunlit ", "%",
    138145     .                iim, jj_nb,nhori,1,1,1,-99,32,
     
    150157           DO l=1, lmaxm1
    151158c
    152            CALL histdef(nid_isccp, pclev(l)//taulev(k)//typinout(n),
     159           CALL histdef(nid_isccp, pclev(l)//taulev(k)//verticaxe(n),
    153160     .                "LMDZ ISCCP cld "//cnameisccp(l,k), "%",
    154161     .                iim, jj_nb,nhori,1,1,1,-99,32,
     
    159166c
    160167c         print*,'n=',n,' avant histdef(..Nb of calls sunlit'
    161           CALL histdef(nid_isccp, "nsunlit"//typinout(n),
     168          CALL histdef(nid_isccp, "nsunlit"//verticaxe(n),
    162169     .                "Nb of calls with sunlit ", "%",
    163170     .                iim, jj_nb,nhori,1,1,1,-99,32,
  • LMDZ4/branches/LMDZ4_V3_patches/libf/phylmd/ini_histmth.h

    r776 r845  
    833833C
    834834         if (nqmax.GE.3) THEN
    835          DO iq=1,nqmax-2
    836          IF (iq.LE.99) THEN
    837          WRITE(str2,'(i2.2)') iq
    838          CALL histdef(nid_mth, "trac"//str2, "Tracer No."//str2, "-",
    839      .                iim,jj_nb,nhori, klev,1,klev,nvert, 32,
    840      .                "ave(X)", zstophy,zout)
    841          ELSE
    842          PRINT*, "Trop de traceurs"
    843          CALL abort
    844          ENDIF
    845          ENDDO
     835           DO iq=3,nqmax
     836           iiq=niadv(iq)
     837             CALL histdef(nid_mth, tnom(iq), ttext(iiq), "-",
     838     .                iim,jj_nb,nhori, klev,1,klev,nvert, 32,
     839     .                "ave(X)", zstophy,zout)
     840           ENDDO
    846841         ENDIF
    847842c
     
    17451740C
    17461741         if (nqmax.GE.3) THEN
    1747          DO iq=3,nqmax
    1748          iiq=niadv(iq)
    1749          CALL histdef(nid_mth, tnom(iq), ttext(iiq), "-",
    1750      .                iim,jj_nb,nhori, klev,1,klev,nvert, 32,
    1751      .                "ave(X)", zstophy,zout)
    1752          ENDDO
    1753          ENDIF
     1742           DO iq=3,nqmax
     1743             iiq=niadv(iq)
     1744             CALL histdef(nid_mth, tnom(iq), ttext(iiq), "-",
     1745     .                iim,jj_nb,nhori, klev,1,klev,nvert, 32,
     1746     .                "ave(X)", zstophy,zout)
     1747             ENDDO
     1748           ENDIF
    17541749
    17551750      ENDIF !lev_histmth.GE.4
  • LMDZ4/branches/LMDZ4_V3_patches/libf/phylmd/ini_paramLMDZ_phy.h

    r776 r845  
    347347     .                "once", zstophy,zout)
    348348c
    349        CALL histdef(nid_ctesGCM, "freqin_isccp",
    350      .                "freqin_isccp", "-",
    351      .                iim,jjmp1,nhori, 1,1,1, -99, 32,
    352      .                "once", zstophy,zout)
    353 c
    354        CALL histdef(nid_ctesGCM, "freqout_isccp",
    355      .                "freqout_isccp", "-",
     349       CALL histdef(nid_ctesGCM, "freq_ISCCP",
     350     .                "freq_ISCCP", "-",
     351     .                iim,jjmp1,nhori, 1,1,1, -99, 32,
     352     .                "once", zstophy,zout)
     353c
     354       CALL histdef(nid_ctesGCM, "ecrit_ISCCP",
     355     .                "ecrit_ISCCP", "-",
    356356     .                iim,jjmp1,nhori, 1,1,1, -99, 32,
    357357     .                "once", zstophy,zout)
  • LMDZ4/branches/LMDZ4_V3_patches/libf/phylmd/physiq.F

    r800 r845  
    385385      INTEGER jmin_debut, nbptj
    386386cIM parametres ISCCP BEG
    387       INTEGER nbapp_isccp,isccppas
     387      INTEGER nbapp_isccp
     388!     INTEGER nbapp_isccp,isccppas
     389!     PARAMETER(isccppas=6) !appel du simulateurs tous les 6pas de temps de la physique
     390!                           !i.e. toutes les 3 heures
    388391      INTEGER n, napisccp
    389392c     PARAMETER(napisccp=3)
     
    419422      INTEGER ncolmx, seed(klon,napisccp)
    420423      REAL nbsunlit(nregISCtot,klon,napisccp)  !nbsunlit : moyenne de sunlit
    421       PARAMETER(ncolmx=350)
     424c     PARAMETER(ncolmx=1500)
     425      PARAMETER(ncolmx=300)
    422426c
    423427cIM verif boxptop BEG
     
    495499c$OMP THREADPRIVATE(nid_isccp)
    496500
    497 c     data ok_isccp,ecrit_isccp/.true.,0.125/     
    498 c     data ok_isccp,ecrit_isccp/.true.,1./     
    499 cIM 190504     data ok_isccp/.true./     
    500 cIM 190504 #else
    501 cIM 190504     data ok_isccp/.false./
    502 cIM 190504 #endif
    503 
    504501      REAL zx_tau(kmaxm1), zx_pc(lmaxm1), zx_o500(iwmax)
    505502      DATA zx_tau/0.0, 0.3, 1.3, 3.6, 9.4, 23., 60./
    506503      SAVE zx_tau
    507 cIM bad 151205     DATA zx_pc/50., 180., 310., 440., 560., 680., 800./
    508504      DATA zx_pc/180., 310., 440., 560., 680., 800., 1000./
    509505      SAVE zx_pc
     
    600596c  QUESTION : noms de variables ?
    601597
    602 #ifdef histhf
    603       data ok_hf/.true./
    604 #else
    605       data ok_hf/.false./
    606 #endif
     598c#ifdef histhf
     599c      data ok_hf/.true./
     600c#else
     601c      data ok_hf/.false./
     602c#endif
    607603      INTEGER        longcles
    608604      PARAMETER    ( longcles = 20 )
     
    11671163      REAL tabcntr0( length       )
    11681164c
    1169 
    11701165      INTEGER ndex2d(iim*jjmp1),ndex3d(iim*jjmp1*klev)
    11711166cIM
     
    15261521c
    15271522         call conf_phys(ocean, ok_veget, ok_journe, ok_mensuel,
    1528      .                  ok_instan, fact_cldcon, facttemps,ok_newmicro,
     1523     .                  ok_instan, ok_hf,
     1524     .                  fact_cldcon, facttemps,ok_newmicro,
    15291525cIM  .                  iflag_cldcon,ratqsbas,ratqshaut, if_ebil,
    15301526     .                  iflag_cldcon,ratqsbas,ratqshaut,
     
    16961692cIM on passe les frequences de jours en secondes : ecrit_ins, ecrit_hf, ecrit_day, ecrit_mth, ecrit_tra, ecrit_reg
    16971693         ecrit_hf = ecrit_hf * un_jour
    1698          ecrit_day = ecrit_day * un_jour
     1694!IM
     1695         IF(ecrit_day.LE.1.) THEN
     1696          ecrit_day = ecrit_day * un_jour !en secondes
     1697         ENDIF
     1698!IM
    16991699         ecrit_mth = ecrit_mth * un_jour
    17001700         ecrit_reg = ecrit_reg * un_jour
    17011701         ecrit_tra = ecrit_tra * un_jour
     1702         ecrit_ISCCP = ecrit_ISCCP * un_jour
     1703c
     1704         PRINT*,'physiq ecrit_ hf day mth reg tra ISCCP',ecrit_hf,
     1705     .   ecrit_day,ecrit_mth,ecrit_reg,ecrit_tra,ecrit_ISCCP
    17021706cIM 030306 END
    17031707
     
    17441748#endif
    17451749
    1746 c#include "ini_histday_seri.h"
    17471750#include "ini_histday_seri.h"
    17481751
     
    25322535cIM calcul nuages par le simulateur ISCCP
    25332536c
     2537#ifdef histISCCP
    25342538      IF (ok_isccp) THEN
     2539cIM appel simulateur toutes les  NINT(freq_ISCCP/dtime) heures
     2540       IF (MOD(itap,NINT(freq_ISCCP/dtime)).EQ.0) THEN
    25352541#include "calcul_simulISCCP.h"
     2542       ENDIF !(MOD(itap,NINT(freq_ISCCP/dtime))
    25362543      ENDIF !ok_isccp
     2544#endif
    25372545
    25382546c   On prend la somme des fractions nuageuses et des contenus en eau
  • LMDZ4/branches/LMDZ4_V3_patches/libf/phylmd/surf_land_orchidee_mod.F90

    r812 r845  
    371371#endif
    372372#ifdef ORC_PREPAR
    373           ! Interface for version 1.8 or earlier of ORCHIDEE
     373          ! Interface for ORCHIDEE version 1.9 or earlier compiled in sequential mode(without preprocessing flag CPP_PARA)
    374374          CALL intersurf_main (itime+itau_phy-1, iim, jjm+1, knon, ktindex, dtime, &
    375375               lrestart_read, lrestart_write, lalo, &
     
    383383
    384384#else         
     385          ! Interface for ORCHIDEE version 1.9 compiled in parallel mode(with preprocessing flag CPP_PARA)
    385386          CALL intersurf_main (itime+itau_phy-1, iim, jjm+1, offset, knon, ktindex, &
    386387               orch_comm, dtime, lrestart_read, lrestart_write, lalo, &
     
    406407   
    407408#ifdef ORC_PREPAR
    408        ! Interface for version 1.8 or earlier of ORCHIDEE
    409        CALL intersurf_main (itime+itau_phy-1, iim, jjm+1, knon, ktindex, dtime, &
     409       ! Interface for ORCHIDEE version 1.9 or earlier compiled in sequential mode(without preprocessing flag CPP_PARA)
     410       CALL intersurf_main (itime+itau_phy, iim, jjm+1, knon, ktindex, dtime, &
    410411            lrestart_read, lrestart_write, lalo, &
    411412            contfrac, neighbours, resolution, date0, &
    412413            zlev,  u1_lay, v1_lay, spechum, temp_air, epot_air, ccanopy, &
    413414            cdrag, petA_orc, peqA_orc, petB_orc, peqB_orc, &
    414             precip_rain, precip_snow, lwdown, swnet, swdown, ps, &
     415            precip_rain, precip_snow, lwdown, swnet, swdown_vrai, ps, &
    415416            evap, fluxsens, fluxlat, coastalflow, riverflow, &
    416417            tsol_rad, tsurf_new, qsurf, albedo_out, emis_new, z0_new, &
     
    418419       
    419420#else
    420 
     421       ! Interface for ORCHIDEE version 1.9 compiled in parallel mode(with preprocessing flag CPP_PARA)
    421422       CALL intersurf_main (itime+itau_phy, iim, jjm+1,offset, knon, ktindex, &
    422423            orch_comm,dtime, lrestart_read, lrestart_write, lalo, &
  • LMDZ4/branches/LMDZ4_V3_patches/libf/phylmd/write_histISCCP.h

    r776 r845  
    2020cIM: champ 3d : (lon,lat,pres) pour un tau fixe
    2121c
    22        CALL histwrite_phy(nid_isccp,"cldISCCP_"//taulev(k)//typinout(n),
     22       CALL histwrite_phy(nid_isccp,"cldISCCP_"//taulev(k)//verticaxe(n),
    2323     .                  itau_w,zx_tmp_fi3d)
    2424        ENDDO !k
    2525c
    2626cym        CALL gr_fi_ecrit(1, klon,iim,jjmp1,nbsunlit(1,:,n),zx_tmp_2d)
    27         CALL histwrite_phy(nid_isccp,"nsunlit"//typinout(n),itau_w,
     27        CALL histwrite_phy(nid_isccp,"nsunlit"//verticaxe(n),itau_w,
    2828     .                 nbsunlit(1,:,n))
    2929c
     
    5555cIM: champ 2d : (lon,lat) pour un tau et une pc fixes
    5656c
    57          CALL histwrite_phy(nid_isccp,pclev(l)//taulev(k)//typinout(n),
    58      .                  itau_w,fq_is_true(:,:,l,n))
     57         CALL histwrite_phy(nid_isccp,pclev(l)//taulev(k)//verticaxe(n),
     58     .                  itau_w,fq_is_true(:,k,l,n))
    5959         ENDDO !l
    6060        ENDDO !k
     
    6262c       print*,'n=',n,' write_ISCCP avant nbsunlit'
    6363cym        CALL gr_fi_ecrit(1, klon,iim,jjmp1,nbsunlit(1,:,n),zx_tmp_2d)
    64         CALL histwrite_phy(nid_isccp,"nsunlit"//typinout(n),
     64        CALL histwrite_phy(nid_isccp,"nsunlit"//verticaxe(n),
    6565     .                 itau_w,nbsunlit(1,:,n))
    6666c
Note: See TracChangeset for help on using the changeset viewer.