container Derived Type

type, public, abstract :: container

An abstract derived type which contains data. This type can be used for a sort of unlimited polymorphism. It is extended to create different classes capable of holding particular data-types. Extensions must implement the procedure typeguard in order to provide the ability to transfer data out of the container and into a variable. Assuming that you are creating a concrete class called example_container, this should be implemented as follows:

 module example_container_mod

   use abstract_container_mod
   implicit none
   private

   type example
     integer, public :: i
   end type example

   type, extends(container) :: example_container
   contains
     private
     procedure :: typeguard => example_guard
   end type example_container

 contains

   logical function example_guard(this, lhs) result(ret)
     class(example_container), intent(in) :: this
     class(*), intent(inout) :: lhs
     select type(lhs)
       type is(example)
         lhs = transfer(this%contents(), lhs)
         ret = .true.
       class default
         ret = .false.
     end select
   end function example_guard

 end module example_container_mod

Inherited By

type~~container~~InheritedByGraph type~container container type~array_list array_list type~container->type~array_list contents type~node node type~container->type~node contents type~iterator iterator type~container->type~iterator contents type~int4_container int4_container type~container->type~int4_container type~logical_container logical_container type~container->type~logical_container type~int2_container int2_container type~container->type~int2_container type~complex8_container complex8_container type~container->type~complex8_container type~int_container int_container type~container->type~int_container type~real_container real_container type~container->type~real_container type~complex16_container complex16_container type~container->type~complex16_container type~real4_container real4_container type~container->type~real4_container type~complex_container complex_container type~container->type~complex_container type~int1_container int1_container type~container->type~int1_container type~complex4_container complex4_container type~container->type~complex4_container type~int8_container int8_container type~container->type~int8_container type~character_container character_container type~container->type~character_container type~real16_container real16_container type~container->type~real16_container type~real8_container real8_container type~container->type~real8_container type~linked_node linked_node type~node->type~linked_node type~linked_node->type~linked_node next type~bidir_node bidir_node type~linked_node->type~bidir_node type~bidir_node->type~bidir_node prev
Help

Components

TypeVisibility AttributesNameInitial
integer(kind=i1), private, dimension(:), allocatable:: storage

Variable in which to place data contents

logical, private :: filled =.false.

.true. if container is set, .false. otherwise


Type-Bound Procedures

procedure(guard), private, deferred :: typeguard

Performs the actual transfer of the container's contents to another variable.

  • function guard(this, lhs) Prototype

    Arguments

    Type IntentOptional AttributesName
    class(container), intent(in) :: this
    class(*), intent(inout) :: lhs

    The variable which the container contents are to be transferred to.

    Return Value logical

procedure, public :: contents

Retrieves the contents of the container, in the form of an integer array.

  • private pure function contents(this)

    Arguments

    Type IntentOptional AttributesName
    class(container), intent(in) :: this

    Return Value integer(kind=i1), dimension(:),allocatable

    Description

    Author
    Chris MacMackin
    Date
    December 2015

    Returns the contents, encoded as a character array, of the container.

procedure, public :: is_filled

Returns whether contents have been assigned to the container

  • private elemental function is_filled(this)

    Arguments

    Type IntentOptional AttributesName
    class(container), intent(in) :: this

    Return Value logical

    Description

    Author
    Chris MacMackin
    Date
    March 2016

    Returns .true. if a value has been assigned to the container, .false. otherwise.

procedure, public :: set

Sets the contents of the container.

  • private subroutine set(this, content)

    Arguments

    Type IntentOptional AttributesName
    class(container), intent(out) :: this
    class(*), intent(in) :: content

    The value to be placed in the container

    Description

    Author
    Chris MacMackin
    Date
    December 2015

    Sets the contents of the storage array to value passed. The type of the variable provided must be the same as the container variable is designed to accept (as determined by the concrete type implementation of the typeguard method in the extension) or be of the same type of container. Otherwise an error message will be printed and the program will exit. If gfortran was used to compile then a backtrace will also be printed.

procedure, private, pass(rhs) :: assign_container

Assigns container contents to another variable.

  • private subroutine assign_container(lhs, rhs)

    Arguments

    Type IntentOptional AttributesName
    class(*), intent(inout) :: lhs

    The variable which the container contents will be assigned to.

    class(container), intent(in) :: rhs

    The container variable.

    Description

    Author
    Chris MacMackin
    Date
    December 2015

    Transfers the contents of the container to another variable. If the other variable is another container of the same type then the contents will be transferred. If the other variable is the same type as the contents of the container (as determined by the typeguard routine provided for that concrete type extension) then it will be given the value held by the container. Otherwise, an error message will be printed and the program stopped. If compiled with gfortran then a backtrace will also be printed. In the event that the container was never set to a value, then this also constitutes an error.

procedure, private :: is_equal

Check whether two containers have the same contents.

  • private elemental function is_equal(lhs, rhs)

    Arguments

    Type IntentOptional AttributesName
    class(container), intent(in) :: lhs
    class(container), intent(in) :: rhs

    Return Value logical

    Description

    Author
    Chris MacMackin
    Date
    December 2015

    Checks whether two containers are of the same type and are storing the same contents.

generic, public :: assignment(=) => assign_container

  • private subroutine assign_container(lhs, rhs)

    Arguments

    Type IntentOptional AttributesName
    class(*), intent(inout) :: lhs

    The variable which the container contents will be assigned to.

    class(container), intent(in) :: rhs

    The container variable.

    Description

    Author
    Chris MacMackin
    Date
    December 2015

    Transfers the contents of the container to another variable. If the other variable is another container of the same type then the contents will be transferred. If the other variable is the same type as the contents of the container (as determined by the typeguard routine provided for that concrete type extension) then it will be given the value held by the container. Otherwise, an error message will be printed and the program stopped. If compiled with gfortran then a backtrace will also be printed. In the event that the container was never set to a value, then this also constitutes an error.

generic, public :: operator(==) => is_equal

  • private elemental function is_equal(lhs, rhs)

    Arguments

    Type IntentOptional AttributesName
    class(container), intent(in) :: lhs
    class(container), intent(in) :: rhs

    Return Value logical

    Description

    Author
    Chris MacMackin
    Date
    December 2015

    Checks whether two containers are of the same type and are storing the same contents.

Source Code

  type, public, abstract ::   container
    !! Author: Chris MacMackin
    !! Date: December 2015
    !! Display: Public
    !!          Private
    !!
    !! An abstract derived type which contains data. This type can be
    !! used for a sort of unlimited polymorphism. It is extended to
    !! create different classes capable of holding particular 
    !! data-types. Extensions must implement the procedure 
    !! [[container:typeguard]] in order to provide the ability to
    !! transfer data out of the container and into a variable. Assuming
    !! that you are creating a concrete class called 
    !! `example_container`, this should be implemented as follows:
    !!
    !!```fortran
    !! module example_container_mod
    !! 
    !!   use abstract_container_mod
    !!   implicit none
    !!   private
    !! 
    !!   type example
    !!     integer, public :: i
    !!   end type example
    !! 
    !!   type, extends(container) :: example_container
    !!   contains
    !!     private
    !!     procedure :: typeguard => example_guard
    !!   end type example_container
    !! 
    !! contains
    !! 
    !!   logical function example_guard(this, lhs) result(ret)
    !!     class(example_container), intent(in) :: this
    !!     class(*), intent(inout) :: lhs
    !!     select type(lhs)
    !!       type is(example)
    !!         lhs = transfer(this%contents(), lhs)
    !!         ret = .true.
    !!       class default
    !!         ret = .false.
    !!     end select
    !!   end function example_guard
    !! 
    !! end module example_container_mod
    !!```
    private
    integer(i1), dimension(:), allocatable :: storage
      !! Variable in which to place data contents
    logical ::  filled = .false.
      !! `.true.` if container is set, `.false.` otherwise
  contains
    private
    procedure(guard), deferred :: typeguard
      !! Performs the actual transfer of the container's contents to 
      !! another variable.
    procedure, public :: contents
      !! Retrieves the contents of the container, in the form of an
      !! integer array.
    procedure, public :: is_filled
      !! Returns whether contents have been assigned to the container
    procedure, public :: set
      !! Sets the contents of the container.
    procedure, pass(rhs) :: assign_container
      !! Assigns container contents to another variable.
    procedure :: is_equal
      !! Check whether two containers have the same contents.
    generic, public :: assignment(=) => assign_container
    generic, public :: operator(==) => is_equal
  end type container