!*==intfaces.f90 created by SPAG 6.70Rc at 15:33 on 10 Dec 2012 MODULE S_ERODIN INTERFACE subroutine erodin(i_unit,o_unit,cmdebugflag,already_read_inputs) use i_p1werm use i_c1gen use i_p1const use i_m1sim use i_m1flag use i_m1subr use i_m1geo use i_b1glob use i_c1glob use i_d1glob use i_s1layr use i_s1phys use i_s1dbh use i_s1agg use i_s1surf use i_s1sgeo use i_h1db1 use i_w1wind use i_w1pavg use i_p1erode use c_flags use c_plot implicit none ! ! PARAMETER definitions ! integer,parameter :: mrcl = 512 integer :: already_read_inputs,cmdebugflag,i_unit,o_unit intent (in) already_read_inputs,cmdebugflag,o_unit END SUBROUTINE ERODIN END INTERFACE END MODULE S_ERODIN !*==intfaces.f90 created by SPAG 6.70Rc at 15:33 on 10 Dec 2012 MODULE S_GETLINE INTERFACE function getline(i_unit) use c_flags implicit none integer :: i_unit character(*) :: getline intent (in) i_unit END FUNCTION GETLINE END INTERFACE END MODULE S_GETLINE !*==intfaces.f90 created by SPAG 6.70Rc at 15:33 on 10 Dec 2012 MODULE S_ERODOUT INTERFACE subroutine erodout(o_unit,o_e_unit,sgrd_u,&input_filename, & & hagen_plot_flag) use i_p1werm use i_m1geo use i_m1flag use i_e2erod use i_m2geo use c_datetime use c_plot implicit none logical :: hagen_plot_flag character(1024) :: input_filename integer :: o_e_unit,o_unit,sgrd_u intent (in) hagen_plot_flag,input_filename,o_e_unit,o_unit,sgrd_u END SUBROUTINE ERODOUT END INTERFACE END MODULE S_ERODOUT !*==intfaces.f90 created by SPAG 6.70Rc at 15:33 on 10 Dec 2012 MODULE S_PLOTOUT INTERFACE subroutine plotout(yplot,ycharin,yin) use c_plot implicit none integer :: yplot character(12),dimension(30) :: ycharin real,dimension(30) :: yin intent (in) ycharin,yin,yplot END SUBROUTINE PLOTOUT END INTERFACE END MODULE S_PLOTOUT