!$Author: wjr $ !$Date: 2011-11-06 $ !$Revison: 0.1 $ !$Source: grid.f95,v $ !----------------------------------------------------------------------------------- !! Grid routines !! MODULE SoilSurface IMPLICIT NONE !! Methods defined in this module PUBLIC :: Load_SoilSurface_File !! Methods to be defined in this module ! PUBLIC :: Dummy !! Data structures defined in this module TYPE, PUBLIC :: SoilSurfRec integer :: id real :: crustFraction real :: crustThickness real :: looseMaterialFraction real :: looseMaterialMass real :: density real :: stability real :: randomRoughness real :: ridgeHeight real :: ridgeSpacing real :: ridgeWidth real :: ridgeOrientation real :: dikeSpacing type (SoilSurfRec), pointer :: nxtSoilSurfRec END TYPE CONTAINS FUNCTION Load_SoilSurface_File (filNam) result (SoilSurface_Ptr) character (len=*), intent(in) :: filNam type (SoilSurfRec), pointer :: SoilSurface_Ptr integer :: eofFlg integer :: cnt integer :: x1, y1, x2, y2 type (SoilSurfRec), pointer :: basp type (SoilSurfRec), pointer :: curp type (SoilSurfRec), pointer :: prvp open(11, file=filNam, status="old", action="read") read(11, fmt=*) ! skip header line allocate(basp) prvp => basp cnt = 1 do allocate(curp) curp%id = cnt cnt = cnt + 1 prvp%nxtSoilSurfRec => curp ! read(unit=11, fmt=*, iostat=eofFlg) curp%x1, curp%y1, curp%x2, curp%y2, & ! curp%height, curp%porosity, curp%width if (eofFlg<0) then exit end if ! write(*,*) 'read ', curp%x1 prvp => curp end do curp%id = -1 close(11) SoilSurface_Ptr => basp%nxtSoilSurfRec END FUNCTION Load_SoilSurface_File END MODULE SoilSurface