Changeset 1143


Ignore:
Timestamp:
Apr 7, 2009, 6:41:02 PM (15 years ago)
Author:
jghattas
Message:

Recuperation des developpements fait uniquement sur la branche LMDZ4_V4_patches :

  • ajoute de la nouvelle flag ok_dynzon
  • ajoute du parametre aer_type
  • optimisation : isccp_cloud_types.F

+ bug pour le slab dans conf_phys.F90

Location:
LMDZ4/branches/LMDZ4-dev/libf
Files:
12 edited

Legend:

Unmodified
Added
Removed
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3d/conf_gcm.F

    r1140 r1143  
    546546      CALL getin('config_inca',config_inca)
    547547
     548
     549!Config  Key  = ok_dynzon
     550!Config  Desc = calcul et sortie des transports
     551!Config  Def  = n
     552!Config  Help = Permet de mettre en route le calcul des transports
     553!Config         
     554      ok_dynzon = .FALSE.
     555      CALL getin('ok_dynzon',ok_dynzon)
    548556
    549557      write(lunout,*)' #########################################'
     
    583591      write(lunout,*)' offline = ', offline
    584592      write(lunout,*)' config_inca = ', config_inca
     593      write(lunout,*)' ok_dynzon = ', ok_dynzon
    585594
    586595      RETURN
     
    707716      config_inca = 'none'
    708717      CALL getin('config_inca',config_inca)
     718
     719!Config  Key  = ok_dynzon
     720!Config  Desc = calcul et sortie des transports
     721!Config  Def  = n
     722!Config  Help = Permet de mettre en route le calcul des transports
     723!Config         
     724       ok_dynzon = .FALSE.
     725       CALL getin('ok_dynzon',ok_dynzon)
    709726
    710727!Config key = ok_strato
     
    760777      write(lunout,*)' offline = ', offline
    761778      write(lunout,*)' config_inca = ', config_inca
     779      write(lunout,*)' ok_dynzon = ', ok_dynzon
    762780      write(lunout,*)' ok_strato = ', ok_strato
    763781      write(lunout,*)' ok_gradsfile = ', ok_gradsfile
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3d/control.h

    r1140 r1143  
    1515     &              periodav,iecrimoy,dayref,anneeref,                  &
    1616     &              raz_date,offline,ip_ebil_dyn,config_inca,           &
    17      &              planet_type,output_grads_dyn
     17     &              planet_type,output_grads_dyn,ok_dynzon
    1818
    1919      INTEGER   nday,day_step,iperiod,iapp_tracvl,iconser,iecri,        &
     
    2121     &          ,ip_ebil_dyn
    2222      REAL periodav
    23       logical offline
     23      LOGICAL offline
    2424      CHARACTER (len=4) :: config_inca
    2525      CHARACTER(len=10) :: planet_type ! planet type ('earth','mars',...)
    2626      LOGICAL :: output_grads_dyn ! output dynamics diagnostics in
    2727                                  ! binary grads file 'dyn.dat' (y/n)
     28      LOGICAL :: ok_dynzon
    2829!-----------------------------------------------------------------------
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3d/gcm.F

    r1140 r1143  
    404404     .              t_ops, t_wrt, histid, histvid)
    405405
    406       t_ops = iperiod * time_step
    407       t_wrt = periodav * daysec
    408       CALL initdynav(dynhistave_file,day_ref,annee_ref,time_step,
    409      .              t_ops, t_wrt, histaveid)
    410 
     406      IF (ok_dynzon) THEN
     407         t_ops = iperiod * time_step
     408         t_wrt = periodav * daysec
     409         CALL initdynav(dynhistave_file,day_ref,annee_ref,time_step,
     410     .        t_ops, t_wrt, histaveid)
     411      END IF
    411412      dtav = iperiod*dtvr/daysec
    412413      endif
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3d/leapfrog.F

    r1140 r1143  
    540540                  iav=0
    541541               ENDIF
     542               
     543               IF (ok_dynzon) THEN
    542544#ifdef CPP_IOIPSL
    543               CALL writedynav(histaveid, itau,vcov ,
    544      ,                          ucov,teta,pk,phi,q,masse,ps,phis)
    545                call bilan_dyn (2,dtvr*iperiod,dtvr*day_step*periodav,
    546      ,           ps,masse,pk,pbaru,pbarv,teta,phi,ucov,vcov,q)
    547 #endif
     545                  CALL writedynav(histaveid, itau,vcov ,
     546     ,                 ucov,teta,pk,phi,q,masse,ps,phis)
     547                  CALL bilan_dyn (2,dtvr*iperiod,dtvr*day_step*periodav,
     548     ,                 ps,masse,pk,pbaru,pbarv,teta,phi,ucov,vcov,q)
     549#endif
     550               END IF
    548551
    549552            ENDIF
     
    651654                  iav=0
    652655               ENDIF
     656
     657               IF (ok_dynzon) THEN
    653658#ifdef CPP_IOIPSL
    654                CALL writedynav(histaveid, itau,vcov ,
    655      ,                          ucov,teta,pk,phi,q,masse,ps,phis)
    656                call bilan_dyn (2,dtvr*iperiod,dtvr*day_step*periodav,
    657      ,           ps,masse,pk,pbaru,pbarv,teta,phi,ucov,vcov,q)
    658 #endif
     659                  CALL writedynav(histaveid, itau,vcov ,
     660     ,                 ucov,teta,pk,phi,q,masse,ps,phis)
     661                  CALL bilan_dyn (2,dtvr*iperiod,dtvr*day_step*periodav,
     662     ,                 ps,masse,pk,pbaru,pbarv,teta,phi,ucov,vcov,q)
     663#endif
     664               END IF
    659665
    660666              ENDIF ! of IF(MOD(itau,iperiod).EQ.0 .OR. itau.EQ.itaufin)
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar/conf_gcm.F

    r1140 r1143  
    556556      config_inca = 'none'
    557557      CALL getin('config_inca',config_inca)
     558
     559!Config  Key  = ok_dynzon
     560!Config  Desc = calcul et sortie des transports
     561!Config  Def  = n
     562!Config  Help = Permet de mettre en route le calcul des transports
     563!Config         
     564      ok_dynzon = .FALSE.
     565      CALL getin('ok_dynzon',ok_dynzon)
    558566
    559567
     
    593601      write(lunout,*)' offline = ', offline
    594602      write(lunout,*)' config_inca = ', config_inca
     603      write(lunout,*)' ok_dynzon = ', ok_dynzon
    595604
    596605      RETURN
     
    717726      config_inca = 'none'
    718727      CALL getin('config_inca',config_inca)
     728
     729!Config  Key  = ok_dynzon
     730!Config  Desc = calcul et sortie des transports
     731!Config  Def  = n
     732!Config  Help = Permet de mettre en route le calcul des transports
     733!Config         
     734      ok_dynzon = .FALSE.
     735      CALL getin('ok_dynzon',ok_dynzon)
    719736
    720737!Config  Key  = use_filtre_fft
     
    807824      write(lunout,*)' offline = ', offline
    808825      write(lunout,*)' config_inca = ', config_inca
     826      write(lunout,*)' ok_dynzon = ', ok_dynzon
    809827      write(lunout,*)' use_filtre_fft = ', use_filtre_fft
    810828      write(lunout,*)' use_mpi_alloc = ', use_mpi_alloc
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar/control.h

    r1140 r1143  
    1515     &              periodav,iecrimoy,dayref,anneeref,                  &
    1616     &              raz_date,offline,ip_ebil_dyn,config_inca,           &
    17      &              planet_type,output_grads_dyn
     17     &              planet_type,output_grads_dyn,ok_dynzon
    1818
    1919      INTEGER   nday,day_step,iperiod,iapp_tracvl,iconser,iecri,        &
     
    2626      LOGICAL :: output_grads_dyn ! output dynamics diagnostics in
    2727                                  ! binary grads file 'dyn.dat' (y/n)
     28      LOGICAL :: ok_dynzon
    2829!-----------------------------------------------------------------------
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar/gcm.F

    r1140 r1143  
    427427     .              t_ops, t_wrt, histid, histvid)
    428428
    429       t_ops = iperiod * time_step
    430       t_wrt = periodav * daysec
    431       CALL initdynav_p(dynhistave_file,day_ref,annee_ref,time_step,
    432      .              t_ops, t_wrt, histaveid)
    433 
     429      IF (ok_dynzon) THEN
     430         t_ops = iperiod * time_step
     431         t_wrt = periodav * daysec
     432         CALL initdynav_p(dynhistave_file,day_ref,annee_ref,time_step,
     433     .        t_ops, t_wrt, histaveid)
     434      END IF
    434435      dtav = iperiod*dtvr/daysec
    435436      endif
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar/leapfrog_p.F

    r1140 r1143  
    12941294               ENDIF
    12951295#ifdef CPP_IOIPSL
     1296             IF (ok_dynzon) THEN
    12961297             call Register_Hallo(vcov,ip1jm,llm,1,0,0,1,TestRequest)
    12971298             call SendRequest(TestRequest)
     
    13021303              CALL writedynav_p(histaveid, itau,vcov ,
    13031304     ,                          ucov,teta,pk,phi,q,masse,ps,phis)
    1304 c$OMP END MASTER
    1305 
     1305
     1306c ATTENTION!!! bilan_dyn_p ne marche probablement pas avec OpenMP
     1307              CALL bilan_dyn_p(2,dtvr*iperiod,dtvr*day_step*periodav,
     1308     ,             ps,masse,pk,pbaru,pbarv,teta,phi,ucov,vcov,q)
     1309c$OMP END MASTER
     1310              ENDIF !ok_dynzon
    13061311#endif
    13071312            ENDIF
     
    14561461               ENDIF
    14571462#ifdef CPP_IOIPSL
     1463               IF (ok_dynzon) THEN
    14581464c$OMP BARRIER
    14591465
     
    14671473               CALL writedynav_p(histaveid, itau,vcov ,
    14681474     ,                          ucov,teta,pk,phi,q,masse,ps,phis)
    1469                call bilan_dyn_p (2,dtvr*iperiod,dtvr*day_step*periodav,
     1475               CALL bilan_dyn_p(2,dtvr*iperiod,dtvr*day_step*periodav,
    14701476     ,           ps,masse,pk,pbaru,pbarv,teta,phi,ucov,vcov,q)
    14711477c$OMP END MASTER
     1478               END IF !ok_dynzon
    14721479#endif
    14731480              ENDIF ! of IF(MOD(itau,iperiod).EQ.0 .OR. itau.EQ.itaufin)
  • LMDZ4/branches/LMDZ4-dev/libf/phylmd/clesphys.h

    r1067 r1143  
    4040       INTEGER lev_histhf, lev_histday, lev_histmth
    4141       CHARACTER*4 type_run
     42! aer_type: pour utiliser un fichier constant dans readsulfate
     43       CHARACTER*8 :: aer_type
    4244       LOGICAL ok_isccp, ok_regdyn
    4345       REAL lonmin_ins, lonmax_ins, latmin_ins, latmax_ins
     
    6264     &     , ecrit_mth, ecrit_tra, ecrit_reg                            &
    6365     &     , freq_ISCCP, ecrit_ISCCP, ip_ebil_phy                       &
    64      &     , ok_lic_melt, cvl_corr                                      &
     66     &     , ok_lic_melt, cvl_corr, aer_type                            &
    6567     &     , qsol0, iflag_rrtm, ok_strato,ok_hines,ecrit_LES
    6668     
  • LMDZ4/branches/LMDZ4-dev/libf/phylmd/conf_phys.F90

    r1134 r1143  
    6666
    6767  character (len = 6),SAVE  :: type_ocean_omp, version_ocean_omp, ocean_omp
     68  CHARACTER(len = 8),SAVE   :: aer_type_omp
    6869  logical,SAVE              :: ok_veget_omp, ok_newmicro_omp
    6970  logical,SAVE        :: ok_journe_omp, ok_mensuel_omp, ok_instan_omp, ok_hf_omp       
     
    237238  aerosol_couple_omp = .false.
    238239  CALL getin('aerosol_couple',aerosol_couple_omp)
     240
     241!
     242!Config Key  = aer_type
     243!Config Desc = Use a constant field for the aerosols
     244!Config Def  = scenario
     245!Config Help = Used in readsulfate.F
     246!
     247  aer_type_omp = 'scenario'
     248  call getin('aer_type', aer_type_omp)
    239249
    240250!
     
    12561266    ok_aie = ok_aie_omp
    12571267    aerosol_couple = aerosol_couple_omp
     1268    aer_type = aer_type_omp
    12581269    bl95_b0 = bl95_b0_omp
    12591270    bl95_b1 = bl95_b1_omp
     
    13101321    END IF
    13111322
    1312     IF (type_ocean=='slab' .AND. version_ocean/='xxxxxx') THEN
     1323    IF (type_ocean=='slab' .AND. version_ocean=='xxxxxx') THEN
    13131324       version_ocean='sicOBS'
    13141325    ELSE IF (type_ocean=='slab' .AND. version_ocean/='sicOBS') THEN
     
    13851396  write(numout,*)' ok_aie = ',ok_aie
    13861397  write(numout,*)' aerosol_couple = ', aerosol_couple
     1398  write(numout,*)' aer_type = ',aer_type
    13871399  write(numout,*)' bl95_b0 = ',bl95_b0
    13881400  write(numout,*)' bl95_b1 = ',bl95_b1
  • LMDZ4/branches/LMDZ4-dev/libf/phylmd/isccp_cloud_types.F

    r776 r1143  
    530530!     Initialised frac_out to zero
    531531
    532       do ibox=1,ncol
    533         do ilev=1,nlev
     532      do ilev=1,nlev
     533        do ibox=1,ncol
    534534          do j=1,npoints
    535535            frac_out(j,ibox,ilev)=0.0
     
    12191219          enddo
    12201220          do 29 ilev=1,nlev-1
    1221             !cdir nodep
     1221!cdir nodep
    12221222            do j=1,npoints
    12231223              if ((at(j,ilev)   .ge. tb(j,ibox) .and.
  • LMDZ4/branches/LMDZ4-dev/libf/phylmd/readsulfate.F

    r1116 r1143  
    3636#include "chem.h"     
    3737#include "dimensions.h"     
    38 cym#include "dimphy.h"     
    3938#include "temps.h"     
     39#include "clesphys.h"
     40#include "iniprint.h"
    4041c
    4142c Input:
     
    8485
    8586      if (is_mpi_root) then
     87
     88        IF (aer_type /= 'actuel  ' .AND. aer_type /= 'preind  ' .AND.   &
     89     &      aer_type /= 'scenario') THEN
     90          WRITE(lunout,*)' *** Warning ***'
     91          WRITE(lunout,*)'Option aer_type pour les aerosols = ',        &
     92     &        aer_type
     93          WRITE(lunout,*)'Cas non prevu, force a preind'
     94          aer_type = 'preind  '
     95        ENDIF
    8696           
    8797      iday = INT(r_day)
     
    118128
    119129
    120       IF (iyr .lt. 1850) THEN
    121          cyear='.nat'
    122          WRITE(*,*) 'getso4  iyr=', iyr,'   ',cyear
    123          CALL getso4fromfile(cyear, so4_1)
    124       ELSE IF (iyr .ge. 2100) THEN
    125          cyear='2100'
    126          WRITE(*,*) 'getso4  iyr=', iyr,'   ',cyear
    127          CALL getso4fromfile(cyear, so4_1)
     130
     131      IF (aer_type == 'actuel  ') then
     132        cyear='1980'
     133        CALL getso4fromfile(cyear, so4_1)
     134      ELSE IF (aer_type == 'preind  ') THEN
     135        cyear='.nat'
     136        CALL getso4fromfile(cyear, so4_1)
    128137      ELSE
     138        IF (iyr .lt. 1850) THEN
     139           cyear='.nat'
     140           WRITE(*,*) 'getso4  iyr=', iyr,'   ',cyear
     141           CALL getso4fromfile(cyear, so4_1)
     142        ELSE IF (iyr .ge. 2100) THEN
     143           cyear='2100'
     144           WRITE(*,*) 'getso4  iyr=', iyr,'   ',cyear
     145           CALL getso4fromfile(cyear, so4_1)
     146        ELSE
    129147
    130148        ! Read in data:
    131       ! a) from actual 10-yr-period
    132 
    133       IF (iyr.LT.1900) THEN
    134          iyr1 = 1850
    135          iyr2 = 1900
    136       ELSE IF (iyr.ge.1900.and.iyr.lt.1920) THEN
    137          iyr1 = 1900
    138          iyr2 = 1920
    139       ELSE
    140          iyr1 = INT(iyr/10)*10
    141          iyr2 = INT(1+iyr/10)*10
    142       ENDIF
    143       WRITE(cyear,'(I4)') iyr1
    144       WRITE(*,*) 'getso4  iyr=', iyr,'   ',cyear
    145       CALL getso4fromfile(cyear, so4_1)
     149        ! a) from actual 10-yr-period
     150
     151          IF (iyr.LT.1900) THEN
     152             iyr1 = 1850
     153             iyr2 = 1900
     154          ELSE IF (iyr.ge.1900.and.iyr.lt.1920) THEN
     155             iyr1 = 1900
     156             iyr2 = 1920
     157          ELSE
     158             iyr1 = INT(iyr/10)*10
     159             iyr2 = INT(1+iyr/10)*10
     160          ENDIF
     161          WRITE(cyear,'(I4)') iyr1
     162        ENDIF
     163        WRITE(*,*) 'getso4  iyr=', iyr,'   ',cyear
     164        CALL getso4fromfile(cyear, so4_1)
    146165
    147166     
    148167      ! If to read two decades:
    149       IF (.NOT.lonlyone) THEN
     168        IF (.NOT.lonlyone) THEN
    150169         
    151170      ! b) from the next following one
    152       WRITE(cyear,'(I4)') iyr2
    153       WRITE(*,*) 'getso4  iyr=', iyr,'   ',cyear
    154       CALL getso4fromfile(cyear, so4_2)
    155 
     171          WRITE(cyear,'(I4)') iyr2
     172          WRITE(*,*) 'getso4  iyr=', iyr,'   ',cyear
     173          CALL getso4fromfile(cyear, so4_2)
     174
     175 
    156176      ! Interpolate linarily to the actual year:
    157       DO it=1,12
    158          DO k=1,klev
    159             DO j=1,jjm
    160                DO i=1,iim
    161                   so4_1(i,j,k,it)=so4_1(i,j,k,it)
     177        DO it=1,12
     178           DO k=1,klev
     179              DO j=1,jjm
     180                 DO i=1,iim
     181                    so4_1(i,j,k,it)=so4_1(i,j,k,it)
    162182     .                 - FLOAT(iyr-iyr1)/FLOAT(iyr2-iyr1)
    163183     .                 * (so4_1(i,j,k,it) - so4_2(i,j,k,it))
    164                ENDDO
    165             ENDDO
    166          ENDDO
    167       ENDDO                           
    168      
    169       ENDIF !lonlyone
    170       ENDIF !(iyr .lt. 1850)
    171  
     184                 ENDDO
     185              ENDDO
     186           ENDDO
     187        ENDDO                           
     188
     189
     190        ENDIF !lonlyone   
     191      ENDIF !aer_type
    172192     
    173193      ! Transform the horizontal 2D-field into the physics-field
     
    537557
    538558      SUBROUTINE getso4fromfile (cyr, so4)
    539       use dimphy
     559      USE dimphy
    540560#include "netcdf.inc"
    541561#include "dimensions.h"     
    542 cccc#include "dimphy.h"
    543562      CHARACTER*15 fname
    544563      CHARACTER*4 cyr
Note: See TracChangeset for help on using the changeset viewer.