!$Author: joelevin $
!$Date: 2011-03-24 11:33:26 -0500 (Thu, 24 Mar 2011) $
!$Revision: 11724 $
!$HeadURL: https://svn.weru.ksu.edu/weru/weps1/trunk/weps.src/src/lib_erosion/erodinit.for $
!**********************************************************************
      subroutine erodinit
!
!     +++ PURPOSE +++
!
!     Controls calls to subroutines that:
!       create the Erosion submodel grid (setupGrid)    
!       initialize Erosion submodel output array to zero (zeroGrid).
!       calculate normalized effect of hills on friction velocity 
!        on grid for each wind direction (not activated)
!       calculate normalized effect of barriers on friction velocity
!        on grid for each wind direction (calcOpenFldFricVelc)
!       initialize reporting variables that need to have a value even
!        when erosion is not being called.
!     + + + GLOBAL COMMON BLOCKS + + +
!
      include  'p1werm.inc'
      include  'm1flag.inc'
      include  'm1geo.inc'
      include  'm1subr.inc'
      include  'erosion/m2geo.inc'
      include  'erosion/e2grid.inc'  !needed for initialization of csr(*,*)
      include  'erosion/threshold.inc'
      include  's1surf.inc'
      
!     +++ SUBROUTINES CALLED +++
!     setupGrid
!     zeroGrid
!     sbhill (not activated)
!     calcOpenFldFricVelc

!     +++ LOCAL VARIABLES +++

      integer i, j, sr

!     + + + LOCAL VARIABLE DEFINITIONS + + +
!     nbr  = number of barriers (from m1geo.inc)

!     +++ END SPECIFICATIONS +++

      ! Grid is created at least once.
      if (am0eif .eqv. .true.) then
         ! check to see if grid dimensions specified via cmdline args
         if ((xgdpt > 0) .and. (ygdpt > 0)) then
           imax = xgdpt + 1
           jmax = ygdpt + 1
           ix = (amxsim(1,2) - amxsim(1,1)) / xgdpt
           jy = (amxsim(2,2) - amxsim(2,1)) / ygdpt

           !code lifted from setupGrid because it is initialized there - LEW
           do j = 0, jmax
             do i = 0, imax
               csr(i,j) = 1          ! icsr = 1
             end do 
           end do 

         else          !use Hagen's grid dimensioning as the default
           call setupGrid
         endif

         ! set grid cell output arrays to zero
         call zeroGrid

         ! check for hills - sbhill not implemented
!        if (nhill .gt. 0) then
!        call sbhill
!        endif

         ! check for barriers
         if (nbr .gt. 0) then
         call calcOpenFldFricVelc
         endif

         ! Turn off grid creation flag
         am0eif = .false.
      endif

      do sr = 1, numSubr
           ! initalize erosion threshold trigger variables
           ne_erosion(sr) = 0
           ne_snowdepth(sr) = 0

           ne_wus_anemom(sr) = 0
           ne_wus_random(sr) = 0
           ne_wus_ridge(sr) = 0
           ne_wus_biodrag(sr) = 0
           ne_wus(sr) = 0

           ne_bare(sr) = 0
           ne_flat_cov(sr) = 0
           ne_surf_wet(sr) = 0
           ne_ag_den(sr) = 0
           ne_wust(sr) = 0

           ne_sfd84(sr) = 0
           ne_asvroc(sr) = 0
           ne_wzzo(sr) = 0
           ne_sfcv(sr) = 0

           ! initialize surface condition reporting values
           acoefAbraAgg(sr) = 0
           acoefAbraCrst(sr) = 0
      end do

      return
      end
!++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++