Fortran Coder

标题: 能将其中的部分代码进行抽象吗 [打印本页]

作者: qingchong    时间: 2016-11-26 22:07
标题: 能将其中的部分代码进行抽象吗
[Fortran] 纯文本查看 复制代码
Module MInteger_Array

  implicit none


  !整数数组抽象
   !策略模板(不同的type对应同一个subroutine)
   type, abstract :: int_ary
    integer                        :: iNs = 0
    integer          , allocatable :: iAry(:)
     contains
       procedure(strategy_procedure), deferred, pass :: SRead_int_ary
   end type int_ary

   abstract interface
      subroutine strategy_procedure(this, iunit)
         import  :: int_ary
         implicit none
         class(int_ary) , intent(inout) :: this
         integer        , intent(in)    :: iunit
      end subroutine strategy_procedure
   end interface

  !2位整数
  type, extends(int_ary) :: int_ary_2P
    character(len=2) , allocatable :: CAry(:)
    contains
      procedure      , pass        :: SRead_int_ary => SRead_int_ary_2p
  end type

  !3位整数
  type, extends(int_ary) :: int_ary_3P
    character(len=3) , allocatable :: CAry(:)
    contains
      procedure      , pass        :: SRead_int_ary => SRead_int_ary_3p
  end type

  contains

    Subroutine SRead_int_ary_2p(this, iunit)
      implicit none
      class(int_ary_2P), intent(inout) :: this
      integer          , intent(in)    :: iunit
      read(iunit,*) this%iNs
      allocate(this%iAry(this%iNs))
      read(iunit,*) this%iAry
      allocate(this%CAry(this%iNs))
      call SInt_to_2Char(this%iAry, this%CAry)
      Return
    End Subroutine

    Subroutine SRead_int_ary_3p(this, iunit)
      implicit none
      class(int_ary_3P), intent(inout) :: this
      integer          , intent(in)    :: iunit
      read(iunit,*) this%iNs
      allocate(this%iAry(this%iNs))
      read(iunit,*) this%iAry
      allocate(this%CAry(this%iNs))
      call SInt_to_3Char(this%iAry, this%CAry)
      Return
    End Subroutine

End Module





这段代码中的
read(iunit,*) this%iNs
allocate(this%iAry(this%iNs))
read(iunit,*) this%iAry
allocate(this%CAry(this%iNs))

每次都是重复的吗,能提炼出来,抽象成一个函数吗

作者: 楚香饭    时间: 2016-11-27 10:53
本帖最后由 楚香饭 于 2016-11-27 11:14 编辑

这一问题,根本就不需要抽象类和子类。

[Fortran] 纯文本查看 复制代码
Module MInteger_Array
  implicit none
  private
  type , public :: int_ary
   integer , private              :: iNs   = 0
   integer                        :: Lens = 2!default 2
   integer , private, allocatable :: iAry(:)
   character(len=:) ,private , allocatable :: CAry(:)
  contains
     procedure      , pass        :: SRead_int_ary
     final                        :: SRead_Uninit
  end type int_ary
contains
  Subroutine SRead_int_ary(this , iunit )
    class(int_ary), intent(inout) :: this
    integer       , intent(in)    :: iunit
    read(iunit,*) this%iNs
    allocate(this%iAry(this%iNs))
    read(iunit,*) this%iAry
    if ( this%Lens < 1 ) this%Lens = 2
    allocate( character(len=this%Lens)::this%CAry(this%iNs))
    !call SInt_to_2Char(this%iAry, this%CAry)
  End Subroutine SRead_int_ary
  Subroutine SRead_Uninit(this)
    type(int_ary), intent(inout) :: this
    deallocate(this%iAry,this%CAry)
  End Subroutine SRead_Uninit
End Module

Program main
  use MInteger_Array
  type(int_ary) :: m2p=int_ary(Lens=2) , m3p=int_ary(Lens=3)
  Open(3,File="filename.txt")
  call m2p%SRead_Int_Ary( 3 )
  call m3p%SRead_Int_Ary( 3 )
  Close(3)
End Program main







欢迎光临 Fortran Coder (http://bbs.fcode.cn/) Powered by Discuz! X3.2