<HTML> <BODY BGCOLOR=#ccccdd LINK=#0000aa VLINK=#0000ff ALINK=#ff0000 ><BASE TARGET="bottom_target"><PRE>
<A NAME='DA_LLXY'><A href='../../html_code/tools/da_llxy.inc.html#DA_LLXY' TARGET='top_target'><IMG SRC="../../gif/bar_red.gif" border=0></A>

subroutine da_llxy (info, loc, outside, outside_all) 33,8

   !-----------------------------------------------------------------------
   ! Purpose: TBD
   !    Updated for Analysis on Arakawa-C grid
   !    Author: Syed RH Rizvi,  MMM/ESSL/NCAR,  Date: 10/22/2008
   !-----------------------------------------------------------------------

   ! This routine converts (lat, lon) into (x,y) coordinates

   implicit none

   type(info_type),       intent(in)    :: info
   type(model_loc_type),  intent(inout) :: loc
   logical      ,         intent(out)   :: outside      !wrt local domain
   logical, optional,     intent(out)   :: outside_all  !wrt all domains

   ! too many return statments to trace
   ! if (trace_use_frequent) call da_trace_entry("da_llxy")

   outside = .false.
   loc % x   = -1.0
   loc % y   = -1.0
   
   ! get the (x, y) coordinates

   if ( fg_format == fg_format_wrf_arw_regional ) then
      call da_llxy_wrf(map_info, info%lat, info%lon, loc%x, loc%y)
   else if (fg_format == fg_format_wrf_nmm_regional) then
      call da_llxy_rotated_latlon(info%lat, info%lon, map_info, loc%x, loc%y)
   else if (global) then
      call da_llxy_global (info%lat, info%lon, loc%x, loc%y)
   else
      call da_llxy_default (info%lat, info%lon, loc%x, loc%y)
   end if

#ifdef A2C
   call da_togrid (loc%x, its-3, ite+3, loc%i, loc%dx, loc%dxm)!

   call da_togrid (loc%y, jts-3, jte+3, loc%j, loc%dy, loc%dym)
#else
   call da_togrid (loc%x, its-2, ite+2, loc%i, loc%dx, loc%dxm)!

   call da_togrid (loc%y, jts-2, jte+2, loc%j, loc%dy, loc%dym)

#endif
   ! refactor to remove this ugly duplication later
   if (present(outside_all)) then
      outside_all = .false.
      ! Do not check for global options 
      if (.not. global) then 
         if ((int(loc%x) &lt; ids) .or. (int(loc%x) &gt;= ide) .or. &amp;
            (int(loc%y) &lt; jds) .or. (int(loc%y) &gt;= jde)) then
            outside_all = .true. 
            outside = .true. 
            return
         end if
         if (def_sub_domain) then
            if (x_start_sub_domain &gt; loc%x .or. y_start_sub_domain &gt; loc%y .or. &amp;
                x_end_sub_domain   &lt; loc%x .or. y_end_sub_domain   &lt; loc%y) then
               outside_all = .true.
            outside = .true. 
            return
            end if
         end if
      end if
   end if

   if (fg_format == fg_format_kma_global) then
      if ((loc%j &lt; jts-1) .or. (loc%j &gt; jte)) then
         outside = .true.
         return
      end if

      if (loc%j == jde) then
         loc%j = loc%j - 1
         loc%dy  = 1.0
         loc%dym = 0.0
      end if

      return
   end if

   ! Check for edge of domain:

   if ((loc%i &lt; ids) .or. (loc%i &gt;= ide) .or. &amp;
      (loc%j &lt; jds) .or. (loc%j &gt;= jde)) then
      outside     = .true. 
      return
   end if

   ! FIX? hack
#ifdef A2C
!rizviupdt   if ((loc%i &lt; its-1) .or. (loc%i &gt; ite) .or. &amp;
!rizviupdt      (loc%j &lt; jts-1) .or. (loc%j &gt; jte)) then
   if ((loc%i &lt; its-2) .or. (loc%i &gt; ite) .or. &amp;
      (loc%j &lt; jts-2) .or. (loc%j &gt; jte)) then
#else
   if ((loc%i &lt; its-1) .or. (loc%i &gt; ite) .or. &amp;
      (loc%j &lt; jts-1) .or. (loc%j &gt; jte)) then
#endif
   ! if ((loc%i &lt; its-1) .or. (loc%i &gt;= ite) .or. &amp;
   !     (loc%j &lt; jts-1) .or. (loc%j &gt;= jte)) then
      outside = .true.
      return

      if (def_sub_domain) then
         if (x_start_sub_domain &gt; loc%x .or. y_start_sub_domain &gt; loc%y .or. &amp;
             x_end_sub_domain   &lt; loc%x .or. y_end_sub_domain   &lt; loc%y) then
             outside = .true.
         end if
      end if
   end if

   ! if (trace_use_frequent) call da_trace_exit("da_llxy")

end subroutine da_llxy