Ignore:
Timestamp:
Sep 23, 2009, 4:47:40 PM (15 years ago)
Author:
Laurent Fairhead
Message:
  • En deconnectant les aérosols (ok_ade=ok_aie=n) on a les mêmes

résultats avant et après les modifs.

  • preindustrial readin fields are used to compute natural aerosol fields

to allow for clean double calls to radiation

  • full forcing diagnostics (NAT, ANT, ZERO, Cloud forcing, CS,AS) are

activated with lev_histmth 4, If lev_histmth is not 4, the call to the
radiation is minimized, for efficiency, but ade and aie are computed and
applied (however for species wise forcing one would need to do
difference runs) (still quite a bit new forcing info, requires probably

some more explanation)

  • there is a hardcoded key in sw_aeroAR4.F90 which lets you choose to use the zero aerosol, or natural aerosol perturbation acting on the meteorology, but still would put out the full forcing diagnostics.
  • aod fields from offline aerosol fields are also output in histmth for

all aerosol tracers read in and available for evaluation

  • aeropt contains the ss humidity correction from nicolas&yves
File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ4/branches/LMDZ4-dev/libf/phylmd/sw_aeroAR4.F90

    r1237 r1246  
    1717     PTOPSWAERO,PTOPSW0AERO,&
    1818     PSOLSWAERO,PSOLSW0AERO,&
     19     PTOPSWCFAERO,PSOLSWCFAERO,&
    1920     ok_ade, ok_aie )
    2021
    2122  USE dimphy
     23
    2224  IMPLICIT NONE
    2325
    2426#include "YOMCST.h"
     27#include "clesphys.h"
    2528  !
    2629  !     ------------------------------------------------------------------
     
    144147  REAL(KIND=8) PTOPSWAIAERO(KDLON)     ! SHORTWAVE FLUX AT T.O.A.(+AEROSOL IND)
    145148  REAL(KIND=8) PSOLSWAIAERO(KDLON)     ! SHORTWAVE FLUX AT SURFACE(+AEROSOL IND)
    146   REAL(KIND=8) PTOPSWAERO(KDLON,9)
    147   REAL(KIND=8) PTOPSW0AERO(KDLON,9)
    148   REAL(KIND=8) PSOLSWAERO(KDLON,9)
    149   REAL(KIND=8) PSOLSW0AERO(KDLON,9)
     149  REAL(KIND=8) PTOPSWAERO(KDLON,9)       ! SW TOA AS DRF nat & ant
     150  REAL(KIND=8) PTOPSW0AERO(KDLON,9)      ! SW SRF AS DRF nat & ant
     151  REAL(KIND=8) PSOLSWAERO(KDLON,9)       ! SW TOA CS DRF nat & ant
     152  REAL(KIND=8) PSOLSW0AERO(KDLON,9)      ! SW SRF CS DRF nat & ant
     153  REAL(KIND=8) PTOPSWCFAERO(KDLON,3)   !  SW TOA AS cloudRF nat & ant
     154  REAL(KIND=8) PSOLSWCFAERO(KDLON,3)   !  SW SRF AS cloudRF nat & ant
    150155
    151156  !jq - Fluxes including aerosol effects
     
    172177  !$OMP THREADPRIVATE(ZFSDN0_AERO)
    173178
    174 !
    175   LOGICAL :: AEROSOLFEEDBACK_ACTIVE=.true.
     179! Key to define the aerosol effect acting on climate
     180! 0: aerosol feedback active according to ok_ade, ok_aie  DEFAULT
     181! 1: no feedback , zero aerosol fluxes are used for climate, diagnostics according to ok_ade_ok_aie
     182! 2: feedback according to total aerosol direct effect used for climate, diagnostics according to ok_ade, ok_aie
     183! 3: feedback according to natural aerosol direct effect used for climate, diagnostics according to ok_ade_ok_aie
     184
     185  INTEGER :: AEROSOLFEEDBACK_ACTIVE = 0
     186
     187  IF ((.not. ok_ade) .and. (AEROSOLFEEDBACK_ACTIVE .ge. 2)) THEN
     188     print*,'Error: direct effect is not activated but assumed to be active - see sw_aeroAR4.F90'
     189     stop
     190  ENDIF
     191  AEROSOLFEEDBACK_ACTIVE=MIN(MAX(AEROSOLFEEDBACK_ACTIVE,0),3)
     192  IF  (AEROSOLFEEDBACK_ACTIVE .gt. 3) THEN
     193     print*,'Error: AEROSOLFEEDBACK_ACTIVE options go only until 3'
     194     stop
     195  ENDIF
    176196
    177197  IF(.NOT.initialized) THEN
     
    200220  ENDIF
    201221
    202 
    203222  IF (appel1er) THEN
    204223     PRINT*, 'SW calling frequency : ', swpas
     
    217236     ENDDO
    218237
    219 
    220      ! clear-sky:
     238! clear sky is either computed IF no direct effect is asked for, or for extended diag)
     239     IF (( lev_histmth .eq. 4 ) .or. ( .not. ok_ade )) THEN   
     240
     241     ! clear-sky: zero aerosol effect
    221242     flag_aer=0.0
    222243     CALL SWU_LMDAR4(PSCT,ZCLDSW0,PPMB,PPSOL,&
     
    242263        ENDDO
    243264     ENDDO
    244 
    245 
    246      ! cloudy-sky:
     265     ENDIF
     266
     267! cloudy sky is either computed IF no indirect effect is asked for, or for extended diag)
     268     IF (( lev_histmth .eq. 4 ) .or. ( .not. ok_aie )) THEN   
     269     ! cloudy-sky: zero aerosol effect
    247270     flag_aer=0.0
    248271     CALL SWU_LMDAR4(PSCT,PCLDSW,PPMB,PPSOL,&
     
    269292        ENDDO
    270293     ENDDO
    271 
     294     ENDIF
    272295
    273296
    274297     IF (ok_ade) THEN
    275298
    276         ! clear sky (Anne Cozic 03/07/2007)
     299        ! clear sky (Anne Cozic 03/07/2007) direct effect of total aerosol
    277300        ! CAS AER (2)
    278301        flag_aer=1.0
     
    301324        ENDDO
    302325
    303         ! cloudy-sky + aerosol dir OB
    304         ! ACo AER
     326! cloudy sky is either computed IF no indirect effect is asked for, or for extended diag)
     327        IF (( lev_histmth .eq. 4 ) .or. (.not. ok_aie)) THEN 
     328        ! cloudy-sky aerosol direct effect of total aerosol
    305329        flag_aer=1.0
    306330        CALL SWU_LMDAR4(PSCT,PCLDSW,PPMB,PPSOL,&
     
    327351           ENDDO
    328352        ENDDO
    329 
    330 
    331 
    332         !CAS NAT
    333         ! clear sky
     353        ENDIF
     354
     355! natural aeroosl clear sky is  computed  for extended diag)
     356        IF ( lev_histmth .eq. 4 ) THEN           
     357        ! clear sky direct effect natural aerosol
    334358        flag_aer=1.0
    335359        CALL SWU_LMDAR4(PSCT,ZCLDSW0,PPMB,PPSOL,&
     
    350374             ZFDOWN, ZFUP)
    351375
    352 ! Natural aerosol fluxes
    353376        DO JK = 1 , KFLEV+1
    354377           DO JL = 1, KDLON
     
    357380           ENDDO
    358381        ENDDO
    359 
    360         ! cloudy-sky
    361         ! ACo NAT
     382        ENDIF
     383
     384! cloud sky natural is for extended diagnostics
     385        IF ( lev_histmth .eq. 4 ) THEN
     386        ! cloudy-sky direct effect natural aerosol
    362387        flag_aer=1.0
    363388        CALL SWU_LMDAR4(PSCT,PCLDSW,PPMB,PPSOL,&
     
    384409           ENDDO
    385410        ENDDO
    386 
     411        ENDIF
    387412
    388413     ENDIF ! ok_ade
    389414
    390 
     415! cloudy sky needs to be computed in all cases IF ok_aie is activated
    391416     IF (ok_aie) THEN
    392         !jq   cloudy-sky + aerosol direct + aerosol indirect
     417        !jq   cloudy-sky + aerosol direct + aerosol indirect of total aerosol
    393418        flag_aer=1.0
    394419        CALL SWU_LMDAR4(PSCT,PCLDSW,PPMB,PPSOL,&
     
    420445  itapsw = itapsw + 1
    421446
    422 
     447  IF  ( AEROSOLFEEDBACK_ACTIVE .eq. 0) THEN
    423448  IF ( ok_ade .and. ok_aie  ) THEN
    424449    ZFSUP(:,:) =    ZFSUP_AERO(:,:,4)
     
    433458    ZFSDN0(:,:) =   ZFSDN0_AERO(:,:,2)
    434459  ENDIF
    435 !MS the following combination would include the direct aerosol effect in cloud regions
    436 !   because it takes the total aerosol effect
     460
    437461  IF ( (.not. ok_ade) .and. ok_aie  )  THEN
     462    print*,'Warning: indirect effect in cloudy regions includes direct aerosol effect'
    438463    ZFSUP(:,:) =    ZFSUP_AERO(:,:,4)
    439464    ZFSDN(:,:) =    ZFSDN_AERO(:,:,4)
     
    450475! MS the following allows to compute the forcing diagostics without
    451476! letting the aerosol forcing act on the meteorology
    452 ! assuming that the no-aerosol case creates the reference meteorological state
    453 ! for the natural aerosol state use: *_AERO(:,:3)
    454   IF  (.not. AEROSOLFEEDBACK_ACTIVE) THEN
    455     ZFSUP(:,:) =    ZFSUP_AERO(:,:,1)
    456     ZFSDN(:,:) =    ZFSDN_AERO(:,:,1)
    457     ZFSUP0(:,:) =   ZFSUP0_AERO(:,:,1)
    458     ZFSDN0(:,:) =   ZFSDN0_AERO(:,:,1)
     477! SEE logic above
     478  ELSEIF  ( AEROSOLFEEDBACK_ACTIVE .gt. 0) THEN
     479    ZFSUP(:,:) =    ZFSUP_AERO(:,:,AEROSOLFEEDBACK_ACTIVE)
     480    ZFSDN(:,:) =    ZFSDN_AERO(:,:,AEROSOLFEEDBACK_ACTIVE)
     481    ZFSUP0(:,:) =   ZFSUP0_AERO(:,:,AEROSOLFEEDBACK_ACTIVE)
     482    ZFSDN0(:,:) =   ZFSDN0_AERO(:,:,AEROSOLFEEDBACK_ACTIVE)
    459483  ENDIF
    460484 
     
    463487     kpl1 = k+1
    464488     DO i = 1, KDLON
    465 
    466489        PHEAT(i,k) = -(ZFSUP(i,kpl1)-ZFSUP(i,k))-(ZFSDN(i,k)-ZFSDN(i,kpl1))
    467490        PHEAT(i,k) = PHEAT(i,k) * RDAY*RG/RCPD / PDP(i,k)
    468491        PHEAT0(i,k) = -(ZFSUP0(i,kpl1)-ZFSUP0(i,k))-(ZFSDN0(i,k)-ZFSDN0(i,kpl1))
    469492        PHEAT0(i,k) = PHEAT0(i,k) * RDAY*RG/RCPD / PDP(i,k)
    470 
    471493     ENDDO
    472494  ENDDO
    473495
    474496  DO i = 1, KDLON
     497! effective SW surface albedo calculation
    475498     PALBPLA(i) = ZFSUP(i,KFLEV+1)/(ZFSDN(i,KFLEV+1)+1.0e-20)
    476      ! clear sky
     499     
     500! clear sky net fluxes at TOA and SRF
    477501     PSOLSW0(i) = ZFSDN0(i,1) - ZFSUP0(i,1)
    478502     PTOPSW0(i) = ZFSDN0(i,KFLEV+1) - ZFSUP0(i,KFLEV+1)
    479503
     504! cloudy sky net fluxes at TOA and SRF
    480505     PSOLSW(i) = ZFSDN(i,1) - ZFSUP(i,1)
    481506     PTOPSW(i) = ZFSDN(i,KFLEV+1) - ZFSUP(i,KFLEV+1)
    482507
    483 ! MS the following is not output, so commented
    484 !     PSOLSW0AERO(i,:) = ZFSDN0_AERO(i,1,:) - ZFSUP0_AERO(i,1,:)
    485 !     PTOPSW0AERO(i,:) = &
    486 !          ZFSDN0_AERO(i,KFLEV+1,:) - ZFSUP0_AERO(i,KFLEV+1,:)
    487 
    488 !     PSOLSWAERO(i,:) = ZFSDN_AERO(i,1,:) - ZFSUP_AERO(i,1,:)
    489 !     PTOPSWAERO(i,:) = &
    490 !          ZFSDN_AERO(i,KFLEV+1,:) - ZFSUP_AERO(i,KFLEV+1,:)
    491 
    492 
    493 if (ok_ade) then
    494      PSOLSWADAERO(i) = (ZFSDN_AERO(i,1,2) - ZFSUP_AERO(i,1,2))-(ZFSDN_AERO(i,1,3) - ZFSUP_AERO(i,1,3))
    495      PTOPSWADAERO(i) = (ZFSDN_AERO(i,KFLEV+1,2) - ZFSUP_AERO(i,KFLEV+1,2))- (ZFSDN_AERO(i,KFLEV+1,3) - ZFSUP_AERO(i,KFLEV+1,3))
    496 
    497      PSOLSWAD0AERO(i) = (ZFSDN0_AERO(i,1,2) - ZFSUP0_AERO(i,1,2))-(ZFSDN0_AERO(i,1,3) - ZFSUP0_AERO(i,1,3))
    498      PTOPSWAD0AERO(i) = (ZFSDN0_AERO(i,KFLEV+1,2) - ZFSUP0_AERO(i,KFLEV+1,2))-(ZFSDN0_AERO(i,KFLEV+1,3) - ZFSUP0_AERO(i,KFLEV+1,3))
    499 endif
    500 
    501 if (ok_aie) then
     508
     509! net anthropogenic forcing direct and 1st indirect effect diagnostics
     510! requires a natural aerosol field read and used
     511! Difference of net fluxes from double call to radiation
     512
     513
     514IF (ok_ade) THEN
     515
     516! indices 1: natural; 2 anthropogenic
     517! TOA/SRF all sky natural forcing
     518     PSOLSWAERO(i,1) = (ZFSDN_AERO(i,1,3) - ZFSUP_AERO(i,1,3))-(ZFSDN_AERO(i,1,1) - ZFSUP_AERO(i,1,1))
     519     PTOPSWAERO(i,1) = (ZFSDN_AERO(i,KFLEV+1,3) - ZFSUP_AERO(i,KFLEV+1,3))- (ZFSDN_AERO(i,KFLEV+1,1) - ZFSUP_AERO(i,KFLEV+1,1))
     520
     521! TOA/SRF all sky anthropogenic forcing
     522     PSOLSWAERO(i,2) = (ZFSDN_AERO(i,1,2) - ZFSUP_AERO(i,1,2))-(ZFSDN_AERO(i,1,3) - ZFSUP_AERO(i,1,3))
     523     PTOPSWAERO(i,2) = (ZFSDN_AERO(i,KFLEV+1,2) - ZFSUP_AERO(i,KFLEV+1,2))- (ZFSDN_AERO(i,KFLEV+1,3) - ZFSUP_AERO(i,KFLEV+1,3))
     524
     525! TOA/SRF clear sky natural forcing
     526     PSOLSW0AERO(i,1) = (ZFSDN0_AERO(i,1,3) - ZFSUP0_AERO(i,1,3))-(ZFSDN0_AERO(i,1,1) - ZFSUP0_AERO(i,1,1))
     527     PTOPSW0AERO(i,1) = (ZFSDN0_AERO(i,KFLEV+1,3) - ZFSUP0_AERO(i,KFLEV+1,3))-(ZFSDN0_AERO(i,KFLEV+1,1) - ZFSUP0_AERO(i,KFLEV+1,1))
     528
     529! TOA/SRF clear sky anthropogenic forcing
     530     PSOLSW0AERO(i,2) = (ZFSDN0_AERO(i,1,2) - ZFSUP0_AERO(i,1,2))-(ZFSDN0_AERO(i,1,3) - ZFSUP0_AERO(i,1,3))
     531     PTOPSW0AERO(i,2) = (ZFSDN0_AERO(i,KFLEV+1,2) - ZFSUP0_AERO(i,KFLEV+1,2))-(ZFSDN0_AERO(i,KFLEV+1,3) - ZFSUP0_AERO(i,KFLEV+1,3))
     532
     533! Cloud forcing indices 1: natural; 2 anthropogenic; 3: zero aerosol direct effect
     534! Instantaneously computed cloudy sky direct aerosol effect, cloud forcing due to aerosols above clouds
     535! natural
     536     PSOLSWCFAERO(i,1) = PSOLSWAERO(i,1) - PSOLSW0AERO(i,1)
     537     PTOPSWCFAERO(i,1) = PTOPSWAERO(i,1) - PTOPSW0AERO(i,1)
     538
     539! Instantaneously computed cloudy SKY DIRECT aerosol effect, cloud forcing due to aerosols above clouds
     540! anthropogenic
     541     PSOLSWCFAERO(i,2) = PSOLSWAERO(i,2) - PSOLSW0AERO(i,2)
     542     PTOPSWCFAERO(i,2) = PTOPSWAERO(i,2) - PTOPSW0AERO(i,2)
     543
     544! Cloudforcing without aerosol
     545! zero
     546     PSOLSWCFAERO(i,3) = (ZFSDN_AERO(i,1,1) - ZFSUP_AERO(i,1,1))-(ZFSDN0_AERO(i,1,1) - ZFSUP0_AERO(i,1,1))
     547     PTOPSWCFAERO(i,3) = (ZFSDN_AERO(i,KFLEV+1,1) - ZFSUP_AERO(i,KFLEV+1,1))- (ZFSDN0_AERO(i,KFLEV+1,1) - ZFSUP0_AERO(i,KFLEV+1,1))
     548
     549! direct anthropogenic forcing , as in old LMDzT, however differences of net fluxes
     550     PSOLSWADAERO(i) = PSOLSWAERO(i,2)
     551     PTOPSWADAERO(i) = PTOPSWAERO(i,2)
     552     PSOLSWAD0AERO(i) = PSOLSW0AERO(i,2)
     553     PTOPSWAD0AERO(i) = PTOPSW0AERO(i,2)
     554
     555ENDIF
     556
     557
     558IF (ok_aie) THEN
    502559     PSOLSWAIAERO(i) = (ZFSDN_AERO(i,1,4) - ZFSUP_AERO(i,1,4))-(ZFSDN_AERO(i,1,2) - ZFSUP_AERO(i,1,2))
    503560     PTOPSWAIAERO(i) = (ZFSDN_AERO(i,KFLEV+1,4) - ZFSUP_AERO(i,KFLEV+1,4))-(ZFSDN_AERO(i,KFLEV+1,2) - ZFSUP_AERO(i,KFLEV+1,2))
    504 endif
     561ENDIF
    505562
    506563  ENDDO
    507564END SUBROUTINE SW_AEROAR4
    508 
Note: See TracChangeset for help on using the changeset viewer.