module mock_def use mocklayer_list implicit none private public :: mock public :: mock_new public :: mock_destroy public :: mock_print public :: mock_layercount public :: mock_addlayer public :: mock_layer type Mock !required model name character (len = 100) :: name !parameters character (len = 100) :: p_string logical :: p_boolean real :: p_real integer :: p_integer type(LIST), pointer :: layers end type contains !constructor for mocks function mock_new() type(Mock), pointer :: mock_new !allocate the memory allocate (mock_new) !init null/empty list call list_new(mock_new%layers) !init the values mock_new% p_boolean = .false. mock_new% p_string = "" mock_new% p_integer = 0 end function subroutine mock_destroy(mp) type(Mock), pointer :: mp if (.not.associated(mp)) return !todo, destroy the layers deallocate (mp) end subroutine !debug subroutine prints the contents of the mock subroutine mock_print(mp, depth) use model_util type(Mock), pointer, intent(in) :: mp integer, intent(in), optional :: depth integer :: d = 0, i !just quit if there is no mock if (.not.associated(mp)) then call modelPrint(unit=6, depth=d, root=.true., name="MOCK (NULL)") return end if if(present(depth)) then d = depth end if call modelPrint(unit=6, depth=d, root=.true., name="MOCK") call modelPrint(unit=6, depth=d, name="name", value=mp%name) call modelPrint(unit=6, depth=d, name="p_string", value=mp%p_string) call modelPrint(unit=6, depth=d, name="p_boolean", value=mp%p_boolean) call modelPrint(unit=6, depth=d, name="p_real", value=mp%p_real) call modelPrint(unit=6, depth=d, name="p_integer", value=mp%p_integer) call modelPrint(unit=6, depth=d, root=.false., name="layers") do i=1, mock_layercount(mp) call mocklayer_print(depth=d+1, mlp=mock_layer(mp, i)) end do end subroutine subroutine mock_addlayer(mp, lp) use mocklayer_def type(mock), intent(in), pointer :: mp type(mocklayer), intent(in), pointer :: lp call list_add(mp%layers, lp) end subroutine function mock_layercount(mp) use mocklayer_def integer :: mock_layercount type(Mock), pointer :: mp mock_layercount = list_size(mp%layers) end function function mock_layer(mp, index) use mocklayer_def type(MockLayer), pointer :: mock_layer type(mock), intent(in), pointer :: mp integer, intent(in) :: index mock_layer => list_get(mp%layers, index) end function end module