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

subroutine da_llxy_new (info, outside, outside_all) 1,8

   !-----------------------------------------------------------------------
   ! Purpose: TBD
   !-----------------------------------------------------------------------

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

   implicit none

   type(infa_type),   intent(inout) :: info
   logical,           intent(inout) :: outside(:,:)      ! wrt local domain
   logical, optional, intent(out)   :: outside_all(:,:)  ! wrt all domains

   if (trace_use) call da_trace_entry("da_llxy_new")

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

   if (fg_format == fg_format_wrf_arw_regional) then
      call da_llxy_wrf_new(map_info, info)
   else if (fg_format == fg_format_wrf_nmm_regional) then
      write(unit=message(1),fmt='(A,I5)') &amp;
         "Needs to be developed for fg_format_nmm_regional = ",fg_format
      call da_error(__FILE__,__LINE__,message(1:1))
   else if (global) then
      call da_llxy_global_new (info)
   else
      call da_llxy_default_new (info)
   end if

   call da_togrid_new (info%x, its-2, ite+2, info%i, info%dx, info%dxm)
   call da_togrid_new (info%y, jts-2, jte+2, info%j, info%dy, info%dym)

   ! 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 
         where ((int(info%x(:,:)) &lt; ids) .or. (int(info%x(:,:)) &gt;= ide) .or. &amp;
            (int(info%y(:,:)) &lt; jds) .or. (int(info%y(:,:)) &gt;= jde))
            outside_all(:,:) = .true. 
            outside(:,:) = .true. 
         end where
         if (def_sub_domain) then
            where (x_start_sub_domain &gt; info%x(:,:) .or. y_start_sub_domain &gt; info%y(:,:) .or. &amp;
                x_end_sub_domain   &lt; info%x(:,:) .or. y_end_sub_domain   &lt; info%y(:,:))
               outside_all(:,:) = .true.
               outside(:,:) = .true. 
            end where
         end if
      end if
   end if

   if (fg_format == fg_format_kma_global) then
      where ((info%j(:,:) &lt; jts-1) .or. (info%j(:,:)  &gt; jte))
         outside(:,:) = .true.
      end where

      where (info%j(:,:) == jde)
         info%j(:,:) = info%j(:,:) - 1
         info%dy(:,:)  = 1.0
         info%dym(:,:) = 0.0
      end where

      return
   end if

   ! Check for edge of domain:

   where ((info%i(:,:) &lt; ids) .or. (info%i(:,:) &gt;= ide) .or. &amp;
      (info%j(:,:) &lt; jds) .or. (info%j(:,:) &gt;= jde))
      outside     = .true. 
   end where

   ! FIX? hack
   where ((info%i(:,:) &lt; its-1) .or. (info%i(:,:) &gt; ite) .or. &amp;
      (info%j(:,:) &lt; jts-1) .or. (info%j(:,:) &gt; jte))
      outside(:,:) = .true.
   end where

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

   if (trace_use) call da_trace_exit("da_llxy_new")

end subroutine da_llxy_new