Leaf_ Derived Type

type, public :: Leaf_


Components

Type Visibility Attributes Name Initial
type(FEMDomain_), public :: FEMDomain
real(kind=real64), public, allocatable :: LeafSurfaceNode2D(:,:)
real(kind=real64), public :: ShapeFactor
real(kind=real64), public :: Thickness
real(kind=real64), public :: length
real(kind=real64), public :: width
real(kind=real64), public :: center(3)
real(kind=real64), public :: MaxThickness
real(kind=real64), public :: Maxlength
real(kind=real64), public :: Maxwidth
real(kind=real64), public :: center_bottom(3)
real(kind=real64), public :: center_top(3)
real(kind=real64), public :: outer_normal_bottom(3)
real(kind=real64), public :: outer_normal_top(3)
real(kind=real64), public, allocatable :: source(:)
real(kind=real64), public, allocatable :: ppfd(:)
real(kind=real64), public, allocatable :: A(:)
integer(kind=int32), public :: Division
type(Leaf_), public, pointer :: pleaf
type(Peti_), public, pointer :: pPeti
real(kind=real64), public :: rot_x = 0.0d0
real(kind=real64), public :: rot_y = 0.0d0
real(kind=real64), public :: rot_z = 0.0d0
real(kind=real64), public :: disp_x = 0.0d0
real(kind=real64), public :: disp_y = 0.0d0
real(kind=real64), public :: disp_z = 0.0d0
real(kind=real64), public :: shaperatio = 0.30d0
real(kind=real64), public :: minwidth
real(kind=real64), public :: minlength
real(kind=real64), public :: MinThickness
integer(kind=int32), public :: LeafID = -1
logical, public :: already_grown = .false.
integer(kind=int32), public, allocatable :: I_planeNodeID(:)
integer(kind=int32), public, allocatable :: I_planeElementID(:)
integer(kind=int32), public, allocatable :: II_planeNodeID(:)
integer(kind=int32), public, allocatable :: II_planeElementID(:)
integer(kind=int32), public :: A_PointNodeID
integer(kind=int32), public :: B_PointNodeID
integer(kind=int32), public :: C_PointNodeID
integer(kind=int32), public :: D_PointNodeID
integer(kind=int32), public :: A_PointElementID
integer(kind=int32), public :: B_PointElementID
integer(kind=int32), public :: C_PointElementID
integer(kind=int32), public :: D_PointElementID
integer(kind=int32), public :: xnum = 10
integer(kind=int32), public :: ynum = 10
integer(kind=int32), public :: znum = 10
real(kind=real64), public :: V_cmax = 100.0d0
real(kind=real64), public :: V_omax = 100.0d0
real(kind=real64), public :: CO2 = 380.0d0
real(kind=real64), public :: O2 = 202000.0d0
real(kind=real64), public :: R_d = 1.0d0
real(kind=real64), public :: K_c = 272.380d0
real(kind=real64), public :: K_o = 165820.0d0
real(kind=real64), public :: J_ = 0.0d0
real(kind=real64), public :: I_ = 0.0d0
real(kind=real64), public :: phi = 0.0d0
real(kind=real64), public :: J_max = 180.0d0
real(kind=real64), public :: theta_r = 0.0d0
real(kind=real64), public :: maxPPFD = 1000.0d0
real(kind=real64), public :: Lambda = 37.430d0
real(kind=real64), public :: temp = 303.0d0
real(kind=real64), public, allocatable :: DryDensity(:)
real(kind=real64), public, allocatable :: WaterContent(:)
real(kind=real64), public, allocatable :: YoungModulus(:)
real(kind=real64), public, allocatable :: PoissonRatio(:)
real(kind=real64), public, allocatable :: Density(:)
real(kind=real64), public, allocatable :: CarbonDiffusionCoefficient(:)
real(kind=real64), public, allocatable :: Stress(:,:,:)
real(kind=real64), public, allocatable :: Displacement(:,:)
real(kind=real64), public, allocatable :: BoundaryTractionForce(:,:)
real(kind=real64), public, allocatable :: BoundaryDisplacement(:,:)
real(kind=real64), public :: my_time = 0.0d0
real(kind=real64), public :: initial_width = 0.0010d0
real(kind=real64), public :: initial_length = 0.0010d0
real(kind=real64), public :: final_width = 0.060d0
real(kind=real64), public :: final_length = 0.100d0
real(kind=real64), public :: width_growth_ratio = 1.0d0/4.0d0
real(kind=real64), public :: length_growth_ratio = 1.0d0/4.0d0
real(kind=real64), public :: default_CarbonDiffusionCoefficient = 0.0010d0

Type-Bound Procedures

procedure, public :: Init => initLeaf

  • public subroutine initLeaf(obj, config, regacy, Thickness, length, width, ShapeFactor, MaxThickness, Maxlength, Maxwidth, rotx, roty, rotz, location, species, SoyWidthRatio, curvature, x_num, y_num, z_num)

    Arguments

    Type IntentOptional Attributes Name
    class(Leaf_), intent(inout) :: obj
    character(len=*), intent(in), optional :: config
    logical, intent(in), optional :: regacy
    real(kind=real64), intent(in), optional :: Thickness
    real(kind=real64), intent(in), optional :: length
    real(kind=real64), intent(in), optional :: width
    real(kind=real64), intent(in), optional :: ShapeFactor
    real(kind=real64), intent(in), optional :: MaxThickness
    real(kind=real64), intent(in), optional :: Maxlength
    real(kind=real64), intent(in), optional :: Maxwidth
    real(kind=real64), intent(in), optional :: rotx
    real(kind=real64), intent(in), optional :: roty
    real(kind=real64), intent(in), optional :: rotz
    real(kind=real64), intent(in), optional :: location(3)
    integer(kind=int32), intent(in), optional :: species
    real(kind=real64), intent(in), optional :: SoyWidthRatio
    real(kind=real64), intent(in), optional :: curvature
    integer(kind=int32), intent(in), optional :: x_num
    integer(kind=int32), intent(in), optional :: y_num
    integer(kind=int32), intent(in), optional :: z_num

procedure, public :: change_length_or_width => change_length_or_width_Leaf

  • public subroutine change_length_or_width_Leaf(this, dt)

    Arguments

    Type IntentOptional Attributes Name
    class(Leaf_), intent(inout) :: this
    real(kind=real64), intent(in) :: dt

procedure, public :: rotate => rotateleaf

  • public recursive subroutine rotateleaf(obj, x, y, z, reset)

    Arguments

    Type IntentOptional Attributes Name
    class(Leaf_), intent(inout) :: obj
    real(kind=real64), intent(in), optional :: x
    real(kind=real64), intent(in), optional :: y
    real(kind=real64), intent(in), optional :: z
    logical, intent(in), optional :: reset

procedure, public :: move => moveleaf

  • public recursive subroutine moveleaf(obj, x, y, z, reset)

    Arguments

    Type IntentOptional Attributes Name
    class(Leaf_), intent(inout) :: obj
    real(kind=real64), intent(in), optional :: x
    real(kind=real64), intent(in), optional :: y
    real(kind=real64), intent(in), optional :: z
    logical, intent(in), optional :: reset

procedure, public :: curve => curveleaf

  • public subroutine curveleaf(obj, curvature)

    Arguments

    Type IntentOptional Attributes Name
    class(Leaf_), intent(inout) :: obj
    real(kind=real64), intent(in) :: curvature

procedure, public :: create => createLeaf

  • public subroutine createLeaf(obj, SurfacePoints, filename, x_num, y_num, x_len, y_len)

    Arguments

    Type IntentOptional Attributes Name
    class(Leaf_), intent(inout) :: obj
    real(kind=real64), intent(in), optional :: SurfacePoints(:,:)
    character(len=*), intent(in), optional :: filename
    integer(kind=int32), intent(in), optional :: x_num
    integer(kind=int32), intent(in), optional :: y_num
    real(kind=real64), intent(in), optional :: x_len
    real(kind=real64), intent(in), optional :: y_len

procedure, public, pass :: connectLeafLeaf => connectleafleaf

  • public subroutine connectleafleaf(obj, direct, leaf)

    Arguments

    Type IntentOptional Attributes Name
    class(Leaf_), intent(inout) :: obj
    character(len=2), intent(in) :: direct
    class(Leaf_), intent(inout) :: leaf

procedure, public, pass :: connectLeafStem

  • public subroutine connectLeafStem(obj, direct, stem)

    Arguments

    Type IntentOptional Attributes Name
    class(Leaf_), intent(inout) :: obj
    character(len=2), intent(in) :: direct
    class(Stem_), intent(inout) :: stem

generic, public :: connect => connectLeafLeaf, connectLeafStem

  • public subroutine connectleafleaf(obj, direct, leaf)

    Arguments

    Type IntentOptional Attributes Name
    class(Leaf_), intent(inout) :: obj
    character(len=2), intent(in) :: direct
    class(Leaf_), intent(inout) :: leaf
  • public subroutine connectLeafStem(obj, direct, stem)

    Arguments

    Type IntentOptional Attributes Name
    class(Leaf_), intent(inout) :: obj
    character(len=2), intent(in) :: direct
    class(Stem_), intent(inout) :: stem

procedure, public :: photosynthesis => photosynthesisLeaf

  • public subroutine photosynthesisLeaf(obj, dt, air)

    Arguments

    Type IntentOptional Attributes Name
    class(Leaf_), intent(inout) :: obj
    real(kind=real64), intent(in) :: dt
    type(Air_), intent(in) :: air

procedure, public :: getPhotosynthesisSpeedPerVolume => getPhotosynthesisSpeedPerVolumeLeaf

  • public function getPhotosynthesisSpeedPerVolumeLeaf(obj, dt, air) result(Speed_PV)

    Arguments

    Type IntentOptional Attributes Name
    class(Leaf_), intent(inout) :: obj
    real(kind=real64), intent(in) :: dt
    type(Air_), intent(in) :: air

    Return Value real(kind=real64), allocatable, (:)

procedure, public :: rescale => rescaleleaf

  • public subroutine rescaleleaf(obj, x, y, z)

    Arguments

    Type IntentOptional Attributes Name
    class(Leaf_), intent(inout), optional :: obj
    real(kind=real64), intent(in), optional :: x
    real(kind=real64), intent(in), optional :: y
    real(kind=real64), intent(in), optional :: z

procedure, public :: adjust => adjustLeaf

  • public subroutine adjustLeaf(obj, width)

    Arguments

    Type IntentOptional Attributes Name
    class(Leaf_), intent(inout) :: obj
    real(kind=real64), intent(in) :: width(:,:)

procedure, public :: resize => resizeleaf

  • public subroutine resizeleaf(obj, x, y, z, Length, Width)

    Arguments

    Type IntentOptional Attributes Name
    class(Leaf_), intent(inout), optional :: obj
    real(kind=real64), intent(in), optional :: x
    real(kind=real64), intent(in), optional :: y
    real(kind=real64), intent(in), optional :: z
    real(kind=real64), intent(in), optional :: Length
    real(kind=real64), intent(in), optional :: Width

procedure, public :: empty => emptyLeaf

  • public function emptyLeaf(obj) result(leaf_is_empty)

    Arguments

    Type IntentOptional Attributes Name
    class(Leaf_), intent(in) :: obj

    Return Value logical

procedure, public :: getVolume => getVolumeLeaf

  • public function getVolumeLeaf(obj) result(ret)

    Arguments

    Type IntentOptional Attributes Name
    class(Leaf_), intent(in) :: obj

    Return Value real(kind=real64)

procedure, public :: getLength => getLengthLeaf

  • public function getLengthLeaf(obj) result(Length)

    Arguments

    Type IntentOptional Attributes Name
    class(Leaf_), intent(inout), optional :: obj

    Return Value real(kind=real64)

procedure, public :: getBiomass => getBiomassLeaf

  • public function getBiomassLeaf(obj) result(ret)

    Arguments

    Type IntentOptional Attributes Name
    class(Leaf_), intent(in) :: obj

    Return Value real(kind=real64)

procedure, public :: getCoordinate => getCoordinateleaf

  • public function getCoordinateleaf(obj, nodetype) result(ret)

    Arguments

    Type IntentOptional Attributes Name
    class(Leaf_), intent(inout) :: obj
    character(len=*), intent(in) :: nodetype

    Return Value real(kind=real64), allocatable, (:)

procedure, public :: getLeafArea => getLeafAreaLeaf

  • public function getLeafAreaLeaf(obj) result(LeafArea)

    Arguments

    Type IntentOptional Attributes Name
    class(Leaf_), intent(in) :: obj

    Return Value real(kind=real64)

procedure, public :: getRadius => getRadiusLeaf

  • public pure function getRadiusLeaf(obj) result(radius)

    Arguments

    Type IntentOptional Attributes Name
    class(Leaf_), intent(in) :: obj

    Return Value real(kind=real64)

procedure, public :: getCenter => getCenterLeaf

  • public pure function getCenterLeaf(obj) result(center)

    Arguments

    Type IntentOptional Attributes Name
    class(Leaf_), intent(in) :: obj

    Return Value real(kind=real64), (3)

procedure, public :: getNormalVector => getNormalVectorLeaf

  • public function getNormalVectorLeaf(obj, ElementID) result(ret)

    Arguments

    Type IntentOptional Attributes Name
    class(Leaf_), intent(inout) :: obj
    integer(kind=int32), intent(in) :: ElementID

    Return Value real(kind=real64), allocatable, (:)

procedure, public :: FullyExpanded => FullyExpandedLeaf

  • public function FullyExpandedLeaf(obj, threshold) result(ret_expanded)

    Arguments

    Type IntentOptional Attributes Name
    class(Leaf_), intent(inout), optional :: obj
    real(kind=real64), intent(in) :: threshold

    Return Value logical

procedure, public :: gmsh => gmshleaf

  • public subroutine gmshleaf(obj, name)

    Arguments

    Type IntentOptional Attributes Name
    class(Leaf_), intent(inout) :: obj
    character(len=*), intent(in) :: name

procedure, public :: msh => mshleaf

  • public subroutine mshleaf(obj, name)

    Arguments

    Type IntentOptional Attributes Name
    class(Leaf_), intent(inout) :: obj
    character(len=*), intent(in) :: name

procedure, public :: vtk => vtkleaf

  • public subroutine vtkleaf(obj, name, field_name)

    Arguments

    Type IntentOptional Attributes Name
    class(Leaf_), intent(inout) :: obj
    character(len=*), intent(in) :: name
    character(len=*), intent(in), optional :: field_name

procedure, public :: stl => stlleaf

  • public subroutine stlleaf(obj, name)

    Arguments

    Type IntentOptional Attributes Name
    class(Leaf_), intent(inout) :: obj
    character(len=*), intent(in) :: name

procedure, public :: ply => plyleaf

  • public subroutine plyleaf(obj, name)

    Arguments

    Type IntentOptional Attributes Name
    class(Leaf_), intent(inout) :: obj
    character(len=*), intent(in) :: name

procedure, public :: sync => syncleaf

  • public subroutine syncleaf(obj, from, mpid)

    Arguments

    Type IntentOptional Attributes Name
    class(Leaf_), intent(inout) :: obj
    integer(kind=int32), intent(in) :: from
    type(MPI_), intent(inout) :: mpid

procedure, public :: nn => nnLeaf

  • public function nnLeaf(this) result(ret)

    Arguments

    Type IntentOptional Attributes Name
    class(Leaf_), intent(in) :: this

    Return Value integer(kind=int32)

procedure, public :: ne => neLeaf

  • public function neLeaf(this) result(ret)

    Arguments

    Type IntentOptional Attributes Name
    class(Leaf_), intent(in) :: this

    Return Value integer(kind=int32)

procedure, public :: remove => removeLeaf

  • public subroutine removeLeaf(this)

    Arguments

    Type IntentOptional Attributes Name
    class(Leaf_), intent(inout) :: this