Ignore:
Timestamp:
Jan 28, 2016, 5:02:13 PM (9 years ago)
Author:
Laurent Fairhead
Message:

Merged trunk changes r2396:2434 into testing branch

Location:
LMDZ5/branches/testing
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/branches/testing

  • LMDZ5/branches/testing/libf/phylmd/cosp/cosp_radar.F90

    r2298 r2435  
    2626  USE MOD_COSP_CONSTANTS
    2727  USE MOD_COSP_TYPES
     28  USE MOD_COSP_UTILS
    2829  use radar_simulator_types
    2930  use array_lib
     
    3132  use format_input
    3233  IMPLICIT NONE
    33  
     34
    3435  INTERFACE
    35     subroutine radar_simulator(freq,k2,do_ray,use_gas_abs,use_mie_table,mt, &
    36         nhclass,hp,nprof,ngate,nsizes,D,hgt_matrix,hm_matrix,re_matrix,p_matrix,t_matrix, &
    37         rh_matrix,Ze_non,Ze_ray,h_atten_to_vol,g_atten_to_vol,dBZe, &
     36    subroutine radar_simulator(hp,nprof,ngate,undef, &
     37        hgt_matrix,hm_matrix,re_matrix,Np_matrix, &
     38        p_matrix,t_matrix,rh_matrix, &
     39        Ze_non,Ze_ray,g_to_vol,a_to_vol,dBZe, &
    3840        g_to_vol_in,g_to_vol_out)
    39  
    40         use m_mrgrnk 
     41
     42        use m_mrgrnk
    4143        use array_lib
    4244        use math_lib
     
    4446        use radar_simulator_types
    4547        implicit none
     48
    4649        ! ----- INPUTS ----- 
    47         type(mie), intent(in) :: mt
    4850        type(class_param) :: hp
    49         real*8, intent(in) :: freq,k2
    50         integer, intent(in) ::  do_ray,use_gas_abs,use_mie_table, &
    51             nhclass,nprof,ngate,nsizes
    52         real*8, dimension(nsizes), intent(in) :: D
     51
     52        integer, intent(in) :: nprof,ngate
     53
     54        real undef
    5355        real*8, dimension(nprof,ngate), intent(in) :: hgt_matrix, p_matrix, &
    5456            t_matrix,rh_matrix
    55         real*8, dimension(nhclass,nprof,ngate), intent(in) :: hm_matrix
    56         real*8, dimension(nhclass,nprof,ngate), intent(inout) :: re_matrix
     57        real*8, dimension(hp%nhclass,nprof,ngate), intent(in) :: hm_matrix
     58        real*8, dimension(hp%nhclass,nprof,ngate), intent(inout) :: re_matrix
     59        real*8, dimension(hp%nhclass,nprof,ngate), intent(inout) :: Np_matrix
     60
    5761        ! ----- OUTPUTS -----
    5862        real*8, dimension(nprof,ngate), intent(out) :: Ze_non,Ze_ray, &
    59             g_atten_to_vol,dBZe,h_atten_to_vol   
     63            g_to_vol,dBZe,a_to_vol
    6064        ! ----- OPTIONAL -----
    61         real*8, optional, dimension(ngate,nprof) :: &
     65        real*8, optional, dimension(nprof,ngate) :: &
    6266            g_to_vol_in,g_to_vol_out
    6367     end subroutine radar_simulator
     
    7377
    7478  ! Arguments
    75   type(cosp_gridbox),intent(in) :: gbx  ! Gridbox info
     79  type(cosp_gridbox),intent(inout) :: gbx  ! Gridbox info
    7680  type(cosp_subgrid),intent(in) :: sgx  ! Subgrid info
    7781  type(cosp_sghydro),intent(in) :: sghydro  ! Subgrid info for hydrometeors
     
    8084  ! Local variables
    8185  integer :: &
    82   nsizes                        ! num of discrete drop sizes
     86  nsizes            ! num of discrete drop sizes
    8387
    84   real*8 :: &
    85   freq, &                       ! radar frequency (GHz)
    86   k2                            ! |K|^2, -1=use frequency dependent default
    87  
    8888  real*8, dimension(:,:), allocatable :: &
    8989  g_to_vol ! integrated atten due to gases, r>v (dB)
    90  
     90
    9191  real*8, dimension(:,:), allocatable :: &
    92   Ze_non, &                     ! radar reflectivity withOUT attenuation (dBZ)
    93   Ze_ray, &                     ! Rayleigh reflectivity (dBZ)
    94   h_atten_to_vol, &             ! attenuation by hydromets, radar to vol (dB)
    95   g_atten_to_vol, &             ! gaseous atteunation, radar to vol (dB)
    96   dBZe, &                       ! effective radar reflectivity factor (dBZ)
    97   hgt_matrix, &                 ! height of hydrometeors (km)
     92  Ze_non, &         ! radar reflectivity withOUT attenuation (dBZ)
     93  Ze_ray, &         ! Rayleigh reflectivity (dBZ)
     94  h_atten_to_vol, &     ! attenuation by hydromets, radar to vol (dB)
     95  g_atten_to_vol, &     ! gaseous atteunation, radar to vol (dB)
     96  dBZe, &           ! effective radar reflectivity factor (dBZ)
     97  hgt_matrix, &         ! height of hydrometeors (km)
    9898  t_matrix, &                   !temperature (k)
    9999  p_matrix, &                   !pressure (hPa)
    100100  rh_matrix                     !relative humidity (%)
    101  
     101
    102102  real*8, dimension(:,:,:), allocatable :: &
    103   hm_matrix, &                  ! hydrometeor mixing ratio (g kg^-1)
    104   re_matrix
     103  hm_matrix, &          ! hydrometeor mixing ratio (g kg^-1)
     104  re_matrix, &          ! effective radius (microns).   Optional. 0 ==> use Np_matrix or defaults
     105  Np_matrix         ! total number concentration (kg^-1).   Optional 0==> use defaults
    105106
    106107  integer, parameter :: one = 1
    107   logical :: hgt_reversed
    108   integer :: pr,i,j,k,unt
     108  ! logical :: hgt_reversed
     109  logical :: hgt_descending
     110  integer :: pr,i,j,k,unt,ngate
    109111
    110112! ----- main program settings ------
    111 
    112   freq = gbx%radar_freq
    113   k2 = gbx%k2
    114  
    115   !
    116   ! note:  intitialization section that was here has been relocated to SUBROUTINE CONSTRUCT_COSP_GRIDBOX by roj, Feb 2008
    117   !
    118   mt_ttl=gbx%mt_ttl  ! these variables really should be moved into the mt structure rather than kept as global arrays.
    119   mt_tti=gbx%mt_tti
    120113
    121114  ! Inputs to Quickbeam
    122115  allocate(hgt_matrix(gbx%Npoints,gbx%Nlevels),p_matrix(gbx%Npoints,gbx%Nlevels), &
    123116           t_matrix(gbx%Npoints,gbx%Nlevels),rh_matrix(gbx%Npoints,gbx%Nlevels))
    124   allocate(hm_matrix(gbx%Nhydro,gbx%Npoints,gbx%Nlevels)) 
     117  allocate(hm_matrix(gbx%Nhydro,gbx%Npoints,gbx%Nlevels))
    125118  allocate(re_matrix(gbx%Nhydro,gbx%Npoints,gbx%Nlevels))
     119  allocate(Np_matrix(gbx%Nhydro,gbx%Npoints,gbx%Nlevels))
    126120
    127121  ! Outputs from Quickbeam
     
    131125  allocate(g_atten_to_vol(gbx%Npoints,gbx%Nlevels))
    132126  allocate(dBZe(gbx%Npoints,gbx%Nlevels))
    133  
     127
    134128  ! Optional argument. It is computed and returned in the first call to
    135129  ! radar_simulator, and passed as input in the rest
    136   allocate(g_to_vol(gbx%Nlevels,gbx%Npoints))
    137  
     130  allocate(g_to_vol(gbx%Npoints,gbx%Nlevels))
     131
     132  ! Even if there is no unit conversion, they are needed for type conversion
    138133  p_matrix   = gbx%p/100.0     ! From Pa to hPa
    139134  hgt_matrix = gbx%zlev/1000.0 ! From m to km
    140   t_matrix   = gbx%T-273.15    ! From K to C
     135  t_matrix   = gbx%T
    141136  rh_matrix  = gbx%q
    142137  re_matrix  = 0.0
    143  
    144   ! Quickbeam assumes the first row is closest to the radar
    145   call order_data(hgt_matrix,hm_matrix,p_matrix,t_matrix, &
    146       rh_matrix,gbx%surface_radar,hgt_reversed)
    147  
     138
     139
     140  ! set flag denoting position of radar relative to hgt_matrix orientation
     141          ngate = size(hgt_matrix,2)
     142
     143          hgt_descending = hgt_matrix(1,1) > hgt_matrix(1,ngate)
     144
     145          if ( &
     146             (gbx%surface_radar == 1 .and. hgt_descending) .or.  &
     147             (gbx%surface_radar == 0 .and. (.not. hgt_descending)) &
     148             ) &
     149          then
     150            gbx%hp%radar_at_layer_one = .false.
     151          else
     152            gbx%hp%radar_at_layer_one = .true.
     153          endif
     154
    148155  ! ----- loop over subcolumns -----
    149156  do pr=1,sgx%Ncolumns
     157
     158      !  NOTE:
    150159      !  atmospheric profiles are the same within the same gridbox
    151       !  only hydrometeor profiles will be different
    152       if (hgt_reversed) then 
    153          do i=1,gbx%Nhydro 
    154             hm_matrix(i,:,:) = sghydro%mr_hydro(:,pr,gbx%Nlevels:1:-1,i)*1000.0 ! Units from kg/kg to g/kg
    155             if (gbx%use_reff) then
    156               re_matrix(i,:,:) = sghydro%Reff(:,pr,gbx%Nlevels:1:-1,i)*1.e6     ! Units from m to micron
    157             endif
    158          enddo 
    159       else 
     160      !  only hydrometeor profiles will be different for each subgridbox
     161
    160162         do i=1,gbx%Nhydro
    161163            hm_matrix(i,:,:) = sghydro%mr_hydro(:,pr,:,i)*1000.0 ! Units from kg/kg to g/kg
    162164            if (gbx%use_reff) then
    163165              re_matrix(i,:,:) = sghydro%Reff(:,pr,:,i)*1.e6       ! Units from m to micron
     166              Np_matrix(i,:,:) = sghydro%Np(:,pr,:,i)              ! Units [#/kg]
    164167            endif
    165168         enddo
    166       endif 
    167169
    168170      !   ----- call radar simulator -----
    169171      if (pr == 1) then ! Compute gaseous attenuation for all profiles
    170          j=0
    171          if (gbx%Npoints == 53) then
    172            unt=10
    173            j=1
    174          endif
    175          if (gbx%Npoints == 153) then
    176            unt=11
    177            j=101
    178          endif
    179          call radar_simulator(freq,k2,gbx%do_ray,gbx%use_gas_abs,gbx%use_mie_tables,gbx%mt, &    !  v0.2: mt changed to gbx%mt, roj
    180            gbx%Nhydro,gbx%hp,gbx%Npoints,gbx%Nlevels,gbx%nsizes,gbx%D, &                         !  v0.2: hp->gbx%hp, D->gbx%d, nsizes->gbx%nsizes, roj
    181            hgt_matrix,hm_matrix,re_matrix,p_matrix,t_matrix,rh_matrix, &
     172         call radar_simulator(gbx%hp,gbx%Npoints,gbx%Nlevels,R_UNDEF, &
     173           hgt_matrix,hm_matrix,re_matrix,Np_matrix, &
     174           p_matrix,t_matrix,rh_matrix, &
    182175           Ze_non,Ze_ray,h_atten_to_vol,g_atten_to_vol,dBZe,g_to_vol_out=g_to_vol)
    183176      else ! Use gaseous atteunuation for pr = 1
    184          call radar_simulator(freq,k2,gbx%do_ray,gbx%use_gas_abs,gbx%use_mie_tables,gbx%mt, &
    185            gbx%Nhydro,gbx%hp,gbx%Npoints,gbx%Nlevels,gbx%nsizes,gbx%D, &
    186            hgt_matrix,hm_matrix,re_matrix,p_matrix,t_matrix,rh_matrix, &
     177         call radar_simulator(gbx%hp,gbx%Npoints,gbx%Nlevels,R_UNDEF, &
     178           hgt_matrix,hm_matrix,re_matrix,Np_matrix, &
     179           p_matrix,t_matrix,rh_matrix, &
    187180           Ze_non,Ze_ray,h_atten_to_vol,g_atten_to_vol,dBZe,g_to_vol_in=g_to_vol)
    188181      endif
    189       ! ----- BEGIN output section -----
    190       ! spaceborne radar : from TOA to SURFACE
    191       if (gbx%surface_radar == 1) then
    192         z%Ze_tot(:,pr,:)=dBZe(:,:)
    193       else if (gbx%surface_radar == 0) then ! Spaceborne
    194         z%Ze_tot(:,pr,:)=dBZe(:,gbx%Nlevels:1:-1)
    195       endif
    196182
     183      ! store caluculated dBZe values for later output/processing
     184      z%Ze_tot(:,pr,:)=dBZe(:,:)
    197185  enddo !pr
    198  
    199   ! Change undefined value to one defined in COSP
    200   where (z%Ze_tot == -999.0) z%Ze_tot = R_UNDEF
    201186
    202187  deallocate(hgt_matrix,p_matrix,t_matrix,rh_matrix)
     
    204189      Ze_non,Ze_ray,h_atten_to_vol,g_atten_to_vol,dBZe)
    205190  deallocate(g_to_vol)
    206  
    207   ! deallocate(mt_ttl,mt_tti)   !v0.2: roj feb 2008 can not be done here,
    208                                 !these variables now part of gbx structure and dealocated later
    209 
    210191END SUBROUTINE COSP_RADAR
    211192
Note: See TracChangeset for help on using the changeset viewer.