!  $Id: GEOS_RadiationGridComp.F90,v 1.44.6.1.2.2 2007/09/24 02:18:06 trayanov Exp $

#include "MAPL_Generic.h"

!BOP


module GEOS_RadiationGridCompMod 1,3

! !MODULE: GEOS_RadiationGridCompMod

! !DESCRIPTION: A container Module FOR longwave and shortwave radiation modules.
!    It simply calls the two children and combines their results to produce
!    total radiative exports. 

! !USES:

  use ESMF_Mod
  use MAPL_Mod

  use GEOS_SolarGridCompMod, only : solarSetServices => SetServices
  use GEOS_IrradGridCompMod, only : irradSetServices => SetServices

  implicit none
  private

! !PUBLIC MEMBER FUNCTIONS:

  public SetServices

!EOP

  integer ::          SOL
  integer ::          IRR

   contains

!BOP

! !IROUTINE: SetServices -- Sets ESMF services for this component

! !INTERFACE:


  subroutine SetServices ( GC, RC ),1759

! !ARGUMENTS:

    type(ESMF_GridComp), intent(INOUT) :: GC  ! gridded component
    integer, optional                  :: RC  ! return code

! !DESCRIPTION:  This version uses the MAPL_GenericSetServices, which sets
!                DEFAULT the Initialize and Finalize services, as well as allocating
!   our instance of a generic state and putting it in the 
!   gridded component (GC). Here we only need to set the Run method and
!   add the state variable specifications (also generic) to our instance
!   of the generic state. This module does not have any internal states. 

!EOP

! ErrLog Variables

    character(len=ESMF_MAXSTR)              :: IAm
    integer                                 :: STATUS
    character(len=ESMF_MAXSTR)              :: COMP_NAME

! Locals

    integer                                 :: I
    type (ESMF_Config)                      :: CF

! Begin...

! Get my name and set-up traceback handle
! ---------------------------------------

    call ESMF_GridCompGet ( GC, name=COMP_NAME, CONFIG=CF, RC=STATUS )
    VERIFY_(STATUS)
    Iam = trim(COMP_NAME) // 'SetServices'

! Set the Run entry point
! -----------------------

    call MAPL_GridCompSetEntryPoint ( GC, ESMF_SETINIT,  Initialize, RC=status )
    VERIFY_(STATUS)
    call MAPL_GridCompSetEntryPoint ( GC, ESMF_SETRUN,  Run, RC=STATUS)
    VERIFY_(STATUS)

    SOL = MAPL_AddChild(GC, NAME='SOLAR', SS=solarSetServices, RC=STATUS)
    VERIFY_(STATUS)
    IRR = MAPL_AddChild(GC, NAME='IRRAD', SS=irradSetServices, RC=STATUS)
    VERIFY_(STATUS)
    

! Set the state variable specs.
! -----------------------------

!BOP

! !IMPORT COUPLINGS:

     call MAPL_AddImportSpec(GC,                             &
        SHORT_NAME         = 'PLEINST',                           &
        LONG_NAME          = 'air_pressure',                      &
        UNITS              = 'Pa',                                &
        DIMS               = MAPL_DimsHorzVert,                   &
        VLOCATION          = MAPL_VLocationEdge,                  &
                                                       RC=STATUS  )
     VERIFY_(STATUS)

! !EXPORT COUPLINGS:

    call MAPL_AddExportSpec ( GC,                                   &
         SHORT_NAME = 'DTDT',                                            &
         LONG_NAME  = 'pressure_weighted_air_temperature_tendency_due_to_radiation',&
         UNITS      = 'Pa K s-1',                                        &
         DIMS       = MAPL_DimsHorzVert,                                 &
         VLOCATION  = MAPL_VLocationCenter,                              &
                                                              RC=STATUS  )
    VERIFY_(STATUS)

    call MAPL_AddExportSpec ( GC,                                   &
         SHORT_NAME = 'RADLW',                                           &
         LONG_NAME  = 'air_temperature_tendency_due_to_longwave',        &
         UNITS      = 'K s-1',                                           &
         DIMS       = MAPL_DimsHorzVert,                                 &
         VLOCATION  = MAPL_VLocationCenter,                              &
                                                              RC=STATUS  )
    VERIFY_(STATUS)

    call MAPL_AddExportSpec ( GC,                                   &
         SHORT_NAME = 'RADSW',                                           &
         LONG_NAME  = 'air_temperature_tendency_due_to_shortwave',       &
         UNITS      = 'K s-1',                                           &
         DIMS       = MAPL_DimsHorzVert,                                 &
         VLOCATION  = MAPL_VLocationCenter,                              &
                                                              RC=STATUS  )
    VERIFY_(STATUS)

    call MAPL_AddExportSpec ( GC,                                   &
         SHORT_NAME = 'RADLWC',                                          &
         LONG_NAME  = 'air_temperature_tendency_due_to_longwave_for_clear_skies',&
         UNITS      = 'K s-1',                                           &
         DIMS       = MAPL_DimsHorzVert,                                 &
         VLOCATION  = MAPL_VLocationCenter,                              &
                                                              RC=STATUS  )
    VERIFY_(STATUS)

    call MAPL_AddExportSpec ( GC,                                   &
         SHORT_NAME = 'RADSWC',                                          &
         LONG_NAME  = 'air_temperature_tendency_due_to_shortwave_for_clear_skies',&
         UNITS      = 'K s-1',                                           &
         DIMS       = MAPL_DimsHorzVert,                                 &
         VLOCATION  = MAPL_VLocationCenter,                              &
                                                              RC=STATUS  )
    VERIFY_(STATUS)

    call MAPL_AddExportSpec ( GC,                                   &
         SHORT_NAME = 'RADSWNA',                                         &
         LONG_NAME  = 'air_temperature_tendency_due_to_shortwave_no_aerosol', &
         UNITS      = 'K s-1',                                           &
         DIMS       = MAPL_DimsHorzVert,                                 &
         VLOCATION  = MAPL_VLocationCenter,                              &
                                                              RC=STATUS  )
    VERIFY_(STATUS)

    call MAPL_AddExportSpec ( GC,                                   &
         SHORT_NAME = 'RADLWCNA',                                        &
         LONG_NAME  = 'air_temperature_tendency_due_to_longwave_for_clear_skies_no_aerosol',&
         UNITS      = 'K s-1',                                           &
         DIMS       = MAPL_DimsHorzVert,                                 &
         VLOCATION  = MAPL_VLocationCenter,                              &
                                                              RC=STATUS  )
    VERIFY_(STATUS)

    call MAPL_AddExportSpec ( GC,                                   &
         SHORT_NAME = 'RADSWCNA',                                        &
         LONG_NAME  = 'air_temperature_tendency_due_to_shortwave_for_clear_skies_no_aerosol',&
         UNITS      = 'K s-1',                                           &
         DIMS       = MAPL_DimsHorzVert,                                 &
         VLOCATION  = MAPL_VLocationCenter,                              &
                                                              RC=STATUS  )
    VERIFY_(STATUS)

    call MAPL_AddExportSpec ( GC,                                   &
         SHORT_NAME = 'RADSRF',                                          &
         LONG_NAME  = 'net_downwelling_radiation_at_surface',            &
         UNITS      = 'W m-2',                                           &
         DIMS       = MAPL_DimsHorzOnly,                                 &
         VLOCATION  = MAPL_VLocationNone,                                &
                                                              RC=STATUS  )
    VERIFY_(STATUS)

    call MAPL_AddExportSpec ( GC,                                   &
         SHORT_NAME = 'ALW',                                             &
         LONG_NAME  = 'linearization_of_surface_upwelling_longwave_flux',&
         UNITS      = 'W m-2',                                           &
         DIMS       = MAPL_DimsHorzOnly,                                 &
         VLOCATION  = MAPL_VLocationNone,                                &
                                                              RC=STATUS  )
    VERIFY_(STATUS)

    call MAPL_AddExportSpec ( GC,                                   &
         SHORT_NAME = 'BLW',                                             &
         LONG_NAME  = 'linearization_of_surface_upwelling_longwave_flux',&
         UNITS      = 'W m-2 K-1',                                       &
         DIMS       = MAPL_DimsHorzOnly,                                 &
         VLOCATION  = MAPL_VLocationNone,                                &
                                                              RC=STATUS  )
    VERIFY_(STATUS)

!EOP

    call MAPL_AddExportSpec ( GC   ,                                &
         SHORT_NAME = 'DRPAR',                                           &
         CHILD_ID = SOL,                                                 &
         RC=STATUS  )
    VERIFY_(STATUS)

    call MAPL_AddExportSpec ( GC   ,                                &
         SHORT_NAME = 'DFPAR',                                           &
         CHILD_ID = SOL,                                                 &
         RC=STATUS  )
    VERIFY_(STATUS)

    call MAPL_AddExportSpec ( GC   ,                                &
         SHORT_NAME = 'DRNIR',                                           &
         CHILD_ID = SOL,                                                 &
         RC=STATUS  )
    VERIFY_(STATUS)

    call MAPL_AddExportSpec ( GC   ,                                &
         SHORT_NAME = 'DFNIR',                                           &
         CHILD_ID = SOL,                                                 &
         RC=STATUS  )
    VERIFY_(STATUS)

    call MAPL_AddExportSpec ( GC   ,                                &
         SHORT_NAME = 'DRUVR',                                           &
         CHILD_ID = SOL,                                                 &
         RC=STATUS  )
    VERIFY_(STATUS)

    call MAPL_AddExportSpec ( GC   ,                                &
         SHORT_NAME = 'DFUVR',                                           &
         CHILD_ID = SOL,                                                 &
         RC=STATUS  )
    VERIFY_(STATUS)

    call MAPL_AddExportSpec ( GC   ,                                &
         SHORT_NAME = 'DRPARN',                                          &
         CHILD_ID = SOL,                                                 &
         RC=STATUS  )
    VERIFY_(STATUS)

    call MAPL_AddExportSpec ( GC   ,                                &
         SHORT_NAME = 'DFPARN',                                          &
         CHILD_ID = SOL,                                                 &
         RC=STATUS  )
    VERIFY_(STATUS)

    call MAPL_AddExportSpec ( GC   ,                                &
         SHORT_NAME = 'DRNIRN',                                          &
         CHILD_ID = SOL,                                                 &
         RC=STATUS  )
    VERIFY_(STATUS)

    call MAPL_AddExportSpec ( GC   ,                                &
         SHORT_NAME = 'DFNIRN',                                          &
         CHILD_ID = SOL,                                                 &
         RC=STATUS  )
    VERIFY_(STATUS)

    call MAPL_AddExportSpec ( GC   ,                                &
         SHORT_NAME = 'DRUVRN',                                          &
         CHILD_ID = SOL,                                                 &
         RC=STATUS  )
    VERIFY_(STATUS)

    call MAPL_AddExportSpec ( GC   ,                                &
         SHORT_NAME = 'DFUVRN',                                          &
         CHILD_ID = SOL,                                                 &
         RC=STATUS  )
    VERIFY_(STATUS)

    call MAPL_AddExportSpec ( GC   ,                                &
         SHORT_NAME = 'FCLD',                                            &
         CHILD_ID = SOL,                                                 &
         RC=STATUS  )
    VERIFY_(STATUS)

    call MAPL_AddExportSpec ( GC   ,                            &
         SHORT_NAME =  'TAUCLI',                                         &
         CHILD_ID = SOL,                                                 &
         RC=STATUS  )
    VERIFY_(STATUS)

        call MAPL_AddExportSpec ( GC   ,                            &
         SHORT_NAME =  'TAUCLW',                                         &
         CHILD_ID = SOL,                                                 &
         RC=STATUS  )
    VERIFY_(STATUS)

    call MAPL_AddExportSpec ( GC   ,                                &
         SHORT_NAME = 'LWS',                                             &
         CHILD_ID = IRR,                                                 &
         RC=STATUS  )
    VERIFY_(STATUS)


! Set generic init and final methods for us and for our children
! --------------------------------------------------------------

    call MAPL_GenericSetServices    ( gc, RC=STATUS)
    VERIFY_(STATUS)



    call Create_AeroOptProp(CF,STATUS)
    VERIFY_(STATUS)

    RETURN_(ESMF_SUCCESS)

  end subroutine SetServices


!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
! !IROUTINE: Initialize -- Initialize method for the composite SuperDyn Gridded Component

! !INTERFACE:


  subroutine Initialize ( GC, IMPORT, EXPORT, CLOCK, RC ),148

! !ARGUMENTS:

  type(ESMF_GridComp), intent(inout) :: GC     ! Gridded component 
  type(ESMF_State),    intent(inout) :: IMPORT ! Import state
  type(ESMF_State),    intent(inout) :: EXPORT ! Export state
  type(ESMF_Clock),    intent(inout) :: CLOCK  ! The clock
  integer, optional,   intent(  out) :: RC     ! Error code

! !DESCRIPTION: The Initialize method of the SuperDyn Composite Gridded Component first 
!   calls the Initialize method of the child Dynamics.  The Dynamics Initialize method will
!   create the ESMF GRID, which will then be used to set the GRID associated with the
!   GWD child and the SuperDyn Composite Component itself.  It should be noted that the 
!   SuperDyn Initialize method also invokes the GEOS Topo Utility which creates all
!   topography related quantities.

!EOP

! ErrLog Variables

  character(len=ESMF_MAXSTR)          :: IAm
  integer                             :: STATUS
  character(len=ESMF_MAXSTR)          :: COMP_NAME

! Local derived type aliases

   type (MAPL_MetaComp),      pointer  :: MAPl
   type (ESMF_State),         pointer  :: GIM(:)
  
   type (ESMF_Bundle)                  :: BUNDLE


!=============================================================================

! Begin... 

! Get the target components name and set-up traceback handle.
! -----------------------------------------------------------

    Iam = "Initialize"
    call ESMF_GridCompGet( GC, NAME=COMP_NAME, RC=STATUS )
    VERIFY_(STATUS)
    Iam = trim(COMP_NAME) // trim(Iam)

! Get my internal MAPL_Generic state
!-----------------------------------

    call MAPL_GetObjectFromGC ( GC, MAPL, RC=STATUS )
    VERIFY_(STATUS)

! Get parameters from generic state.
!-----------------------------------

    call MAPL_Get ( MAPL, GIM=GIM, RC=STATUS )
    VERIFY_(STATUS)

    call MAPL_GenericInitialize ( GC, IMPORT, EXPORT, CLOCK, RC=STATUS )
    VERIFY_(STATUS)

! GG does not automatically put children's import bundles in parent's imports state
!----------------------------------------------------------------------------------

! propagate AERO from Solar to Radiation
    call ESMF_StateGetBundle ( GIM(SOL), 'AERO', BUNDLE, RC=STATUS )
    VERIFY_(STATUS)
    call ESMF_StateAddBundle ( IMPORT,          BUNDLE, RC=STATUS )
    VERIFY_(STATUS)

! Copy content of Aero to Irrad

    call ESMF_StateAddBundle ( GIM(IRR),          BUNDLE, RC=STATUS )
    VERIFY_(STATUS)

! All done
!---------

   RETURN_(ESMF_SUCCESS)
  end subroutine Initialize

!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!

!BOP

! !IROUTINE: RUN -- Run method for the composite radiation component

! !INTERFACE:


subroutine RUN ( GC, IMPORT, EXPORT, CLOCK, RC ),296

! !ARGUMENTS:

  type(ESMF_GridComp),  intent(inout) :: GC     ! Gridded component 
  type(ESMF_State),     intent(inout) :: IMPORT ! Import state
  type(ESMF_State),     intent(inout) :: EXPORT ! Export state
  type(ESMF_Clock),     intent(inout) :: CLOCK  ! The clock
  integer, optional,    intent(  out) :: RC     ! Error code:

! !DESCRIPTION: Calls the run methods of solar and irrad and combines
!     their fluxes into a single pressure-weighted temperature tendency.

!EOP

! ErrLog Variables

  character(len=ESMF_MAXSTR)          :: IAm
  integer                             :: STATUS
  character(len=ESMF_MAXSTR)          :: COMP_NAME

! Local derived type aliases

  type (MAPL_MetaComp),  pointer  :: MAPL
  type (ESMF_State       ),  pointer  :: GEX(:  )
  
  integer                             :: I, L

!  Pointers to IR exports

  real, pointer, dimension(:,:  )     :: SFCEM
  real, pointer, dimension(:,:  )     :: DSFDTS
  real, pointer, dimension(:,:  )     :: TRD
  real, pointer, dimension(:,:,:)     :: FLW
  real, pointer, dimension(:,:,:)     :: FLWCLR
  real, pointer, dimension(:,:,:)     :: FLA

!  Pointers to SOLAR exports

  real, pointer, dimension(:,:,:)     :: FSW
  real, pointer, dimension(:,:,:)     :: FSWCLR
  real, pointer, dimension(:,:,:)     :: FSWNA
  real, pointer, dimension(:,:,:)     :: FSCNA  
 
!  Pointers to imports

  real, pointer, dimension(:,:,:)     :: PLE

!  Pointers to exports

  real, pointer, dimension(:,:,:)     :: DTDT
  real, pointer, dimension(:,:,:)     :: RADLW
  real, pointer, dimension(:,:,:)     :: RADSW
  real, pointer, dimension(:,:,:)     :: RADLWC
  real, pointer, dimension(:,:,:)     :: RADSWC
  real, pointer, dimension(:,:,:)     :: RADSWNA
  real, pointer, dimension(:,:,:)     :: RADLWCNA
  real, pointer, dimension(:,:,:)     :: RADSWCNA
  real, pointer, dimension(:,:  )     :: ALW
  real, pointer, dimension(:,:  )     :: BLW
  real, pointer, dimension(:,:  )     :: RADSRF

! Locals

  real, pointer, dimension(:,:,:)     :: DMI
  integer                             :: IM
  integer                             :: JM
  integer                             :: LM

!=============================================================================

! Begin... 

! Get the target components name and set-up traceback handle.
! -----------------------------------------------------------

    call ESMF_GridCompGet( GC, name=COMP_NAME, RC=STATUS )
    VERIFY_(STATUS)
    Iam = trim(COMP_NAME) // "Run"

! Get my internal MAPL_Generic state
!-----------------------------------

    call MAPL_GetObjectFromGC ( GC, MAPL, RC=STATUS)
    VERIFY_(STATUS)

! Start Total timer
!------------------

    call MAPL_TimerOn(MAPL,"TOTAL")

! Get parameters from generic state.
!-----------------------------------

    call MAPL_Get(MAPL,  &
         GEX=GEX,        &
         IM=IM, JM=JM, LM=LM,         &
                            RC=STATUS )
    VERIFY_(STATUS)

! Get pointers to exports
!------------------------

    call MAPL_GetPointer ( IMPORT, PLE    , 'PLEINST'  ,  RC=STATUS )
    VERIFY_(STATUS)

! Get pointers to exports
!------------------------

    call MAPL_GetPointer ( EXPORT, DTDT    , 'DTDT'    ,  RC=STATUS )
    VERIFY_(STATUS)
    call MAPL_GetPointer ( EXPORT, ALW     , 'ALW'     ,  RC=STATUS )
    VERIFY_(STATUS)
    call MAPL_GetPointer ( EXPORT, BLW     , 'BLW'     ,  RC=STATUS )
    VERIFY_(STATUS)
    call MAPL_GetPointer ( EXPORT, RADSRF  , 'RADSRF'  ,  RC=STATUS )
    VERIFY_(STATUS)
    call MAPL_GetPointer ( EXPORT, RADLW   , 'RADLW'   ,  RC=STATUS )
    VERIFY_(STATUS)
    call MAPL_GetPointer ( EXPORT, RADSW   , 'RADSW'   ,  RC=STATUS )
    VERIFY_(STATUS)
    call MAPL_GetPointer ( EXPORT, RADLWC  , 'RADLWC'  ,  RC=STATUS )
    VERIFY_(STATUS)
    call MAPL_GetPointer ( EXPORT, RADSWC  , 'RADSWC'  ,  RC=STATUS )
    VERIFY_(STATUS)
    call MAPL_GetPointer ( EXPORT, RADSWNA , 'RADSWNA' ,  RC=STATUS )
    VERIFY_(STATUS)
    call MAPL_GetPointer ( EXPORT, RADLWCNA, 'RADLWCNA',  RC=STATUS )
    VERIFY_(STATUS)
    call MAPL_GetPointer ( EXPORT, RADSWCNA, 'RADSWCNA',  RC=STATUS )
    VERIFY_(STATUS)

! Allocate children's exports that we need
!-----------------------------------------

    if (associated(RADSW  ) .or. associated(DTDT   ) .or. associated(RADSRF) ) then
       call MAPL_GetPointer ( GEX(SOL), FSW   , 'FSW'    ,  alloc=.TRUE.,RC=STATUS )
       VERIFY_(STATUS)
    end if

    if (associated(RADSWC)                            ) then
       call MAPL_GetPointer ( GEX(SOL), FSWCLR, 'FSC'    ,  alloc=.TRUE.,RC=STATUS )
       VERIFY_(STATUS)
    end if

    if (associated(RADLW) .or. associated(DTDT   )   .or. associated(RADSRF)) then
       call MAPL_GetPointer ( GEX(IRR), FLW   , 'FLX'    ,  alloc=.TRUE.,RC=STATUS )
       VERIFY_(STATUS)
    end if

    if (associated(RADLWC)                            ) then
       call MAPL_GetPointer ( GEX(IRR), FLWCLR, 'FLC'    ,  alloc=.TRUE.,RC=STATUS )
       VERIFY_(STATUS)
    end if

    if (associated(RADSWNA) ) then
       call MAPL_GetPointer ( GEX(SOL), FSWNA , 'FSWNA'  ,  alloc=.TRUE.,RC=STATUS )
       VERIFY_(STATUS)
    end if

    if (associated(RADSWCNA)                          ) then
       call MAPL_GetPointer ( GEX(SOL), FSCNA,  'FSCNA'  ,  alloc=.TRUE.,RC=STATUS )
       VERIFY_(STATUS)
    end if

    if (associated(RADLWCNA)                          ) then
       call MAPL_GetPointer ( GEX(IRR), FLA   , 'FLA'    ,  alloc=.TRUE.,RC=STATUS )
       VERIFY_(STATUS)
    end if

    if (  associated(ALW   )  .or. associated(BLW     ) ) then
       call MAPL_GetPointer ( GEX(IRR), DSFDTS, 'DSFDTS' ,  alloc=.TRUE.,RC=STATUS )
       VERIFY_(STATUS)
       call MAPL_GetPointer ( GEX(IRR), SFCEM , 'SFCEM'  ,  alloc=.TRUE.,RC=STATUS )
       VERIFY_(STATUS)
       call MAPL_GetPointer ( GEX(IRR), TRD   , 'TSREFF' ,  alloc=.TRUE.,RC=STATUS )
       VERIFY_(STATUS)
    end if

! Run the child components and their couplers
!--------------------------------------------

    call MAPL_GenericRun (GC, IMPORT, EXPORT, CLOCK, RC=STATUS )
    VERIFY_(STATUS)

! Prepare exports
!----------------

    if( associated (BLW     ) ) BLW      =  DSFDTS
    if( associated (ALW     ) ) ALW      =  SFCEM - DSFDTS*TRD
    if( associated (RADSRF  ) ) RADSRF   =   (FSW(:,:,  LM  ) + FLW(:,:,  LM))
    if( associated (DTDT    ) ) DTDT     = ( (FLW(:,:,0:LM-1) - FLW(:,:,1:LM)) + &
                                             (FSW(:,:,0:LM-1) - FSW(:,:,1:LM)) ) * (MAPL_GRAV/MAPL_CP)

    if( associated (RADLW ) .or. associated (RADSW )   .or. &
        associated (RADLWC) .or. associated (RADSWC)   .or. &
        associated (RADSWNA).or. associated (RADSWCNA) .or. &
        associated (RADLWCNA)                             ) then

       allocate(DMI(IM,JM,LM),stat=STATUS)
       VERIFY_(STATUS)
       DMI = MAPL_GRAV/(MAPL_CP*(PLE(:,:,1:LM)-PLE(:,:,0:LM-1)))

       if( associated (RADLW   ) ) RADLW    = (FLW   (:,:,0:LM-1) - FLW   (:,:,1:LM))*DMI
       if( associated (RADSW   ) ) RADSW    = (FSW   (:,:,0:LM-1) - FSW   (:,:,1:LM))*DMI
       if( associated (RADLWC  ) ) RADLWC   = (FLWCLR(:,:,0:LM-1) - FLWCLR(:,:,1:LM))*DMI
       if( associated (RADSWC  ) ) RADSWC   = (FSWCLR(:,:,0:LM-1) - FSWCLR(:,:,1:LM))*DMI
       if( associated (RADSWNA ) ) RADSWNA  = (FSWNA (:,:,0:LM-1) - FSWNA (:,:,1:LM))*DMI
       if( associated (RADLWCNA) ) RADLWCNA = (FLA   (:,:,0:LM-1) - FLA   (:,:,1:LM))*DMI
       if( associated (RADSWCNA) ) RADSWCNA = (FSCNA (:,:,0:LM-1) - FSCNA (:,:,1:LM))*DMI

       deallocate(DMI,stat=STATUS)
       VERIFY_(STATUS)

    end if

    call MAPL_TimerOff(MAPL,"TOTAL")

    RETURN_(ESMF_SUCCESS)

  end subroutine RUN

!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!

end module GEOS_RadiationGridCompMod