! ! File: run_def.f95 ! Author: josephalevin ! ! Created on August 1, 2011, 3:19 PM ! module run_def use barrierlist_def, barrierlist => LIST implicit none private public :: run public :: run_new public :: run_destroy public :: run_print type run !required model name character (len = 100) :: name type(barrierlist), pointer :: barriers end type contains !run constructor function run_new() type(run), pointer :: run_new !allocate the memory allocate (run_new) !init the variables run_new%name="" end function !run destruction subroutine run_destroy(mp) type(run), pointer :: mp if (.not.associated(mp)) return !TODO: handle variables ? deallocate (mp) end subroutine !debug subroutine prints the contents of the run subroutine run_print(mp, depth) use model_util type(run), pointer, intent(in) :: mp integer, intent(in), optional :: depth integer :: d = 0, i !just quit if there is no run if (.not.associated(mp)) then call modelPrint(unit=6, depth=d, root=.true., name="RUN (NULL)") return end if if(present(depth)) then d = depth end if call modelPrint(unit=6, depth=d, root=.true., name="RUN") call modelPrint(unit=6, depth=d, name="name", value=mp%name) call modelPrint(unit=6, depth=d, root=.false., name="barriers") ! do i=1, barrierlist_(mp) ! call mocklayer_print(depth=d+1, mlp=mock_layer(mp, i)) ! end do end subroutine end module