What are the ways to pass a set of variable values through the subroutine to a function without common block?

后端 未结 3 626
孤独总比滥情好
孤独总比滥情好 2020-12-04 03:09

I do not want to use common blocks in my program. My main program calls a subroutine which calls a function. The function needs variables from the subroutine.

What a

相关标签:
3条回答
  • 2020-12-04 03:39

    So, basically you could solve this with something along these lines:

    SUBROUTINE CONDACT(i,j, iab11,iab22,xx2,yy2,zz2,b1,c1,f1,g1,h1,d1,b2,c2,f2,g2,h2,p2,q2,r2,d2,res)
      !declaration to all those parameters and res
      res = f(x)
    END SUBROUTINE CONDACT
    
    function f(x,iab11,iab22,xx2,yy2,zz2,b1,c1,f1,g1,h1,d1,b2,c2,f2,g2,h2,p2,q2,r2,d2)
    !declaration to all those parameters
    end function f
    
    program
      ...
    
      call CONDAT(i,j,iab11,iab22,xx2,yy2,zz2,b1,c1,f1,g1,h1,d1,b2,c2,f2,g2,h2,p2,q2,r2,d2,res)
    
    end program
    

    That is, just passing the parameters through. It is strongly encouraged to use modules, see Alexander McFarlane's answer, though it is not required. Alexander McFarlane shows how to pass f as an argument to the subroutine, such that you could use different functions in the subroutine, but your code does not seem to require this.

    Now, this is an awful long list of parameters, and you probably do not want to carry those around all the time. The usual approach to deal with this, is to put those parameters into a derived datatype and then just passing this around. Like this:

    !> A module implementing ellip related stuff.
    module ellip_module
    
      implicit none
    
      type ellip_type
        !whatever datatypes these need to be...
        integer :: b1,c1,f1,g1,h1,d1,b2,c2,f2,g2,h2,p2,q2,r2,d2
      end type
    end module ellip_module
    
    
    !> A module implementing condact related stuff.
    module condact_module
      use ellip_module ! Make use of the ellip module to have the type available
    
      implicit none
    
      type condact_type
        !whatever datatypes these need to be...
        integer :: iab11,iab22,xx2,yy2,zz2
      end type
    
      contains
    
      subroutine condact(i,j, con, ellip, res)
         integer :: i,j
         type(condact_type) :: con
         type(ellip_type) :: ellip
         real :: res
    
         real :: x
         res = f(x, con, ellip)
      end subroutine condact
    
      function f(x, con, ellip) result(res)
        real :: x
        real :: res
        type(condact_type) :: con
        type(ellip_type) :: ellip
    
        res = !whatever this should do
      end function f
    end module condact_module
    
    
    !> A program using the condact functionality.
    program test_condact
      use ellip_module
      use condact_module
    
      implicit none
    
      type(condact_type) :: mycon
      type(ellip_type) :: myellip
      integer :: i,j
      real :: res
    
      call condact(i,j, mycon, myellip, res)
    end program test_condact
    

    This is just a rough sketch, but I got the impression this is what you are looking for.

    0 讨论(0)
  • 2020-12-04 03:47

    What you care about here is association: you want to be able to associate entities in the function f with those in the subroutine condat. Storage association is one way to do this, which is what the common block is doing.

    There are other forms of association which can be useful. These are

    • use association
    • host association
    • argument association

    Argument association is described in haraldkl's answer.

    Use association comes through modules like

    module global_variables
      implicit none     ! I'm guessing on declarations, but that's not important
      public   ! Which is the default
      real b1,c1,f1,g1,h1,d1,b2,c2,f2,g2,h2,p2,q2,r2,d2,xx2,yy2,zz2
      integer iab11,iab22
    end module
    
    subroutine condat(i,j)
      use global_variables   ! Those public things are use associated
      ...
    end subroutine
    
    function f(x)
      use global_variables   ! And the same entities are accessible here
      ...
    end function
    

    Host association is having access to entities accessible to the host. A host here could usefully be a module or a program

    module everything
      integer iab11,...
      real ...
     contains
      subroutine condat(i,j)
        ! iab11 available from the host module
      end subroutine
    
      function f(x)
        ! iab11 available from the host module
      end function
    end module
    

    or even the subroutine itself

    subroutine condat(i,j)
      integer iab11,...
      real ...
     contains
      function f(x)
        ! Host condat's iab11 is accessible here
      end function
     end subroutine
    
    0 讨论(0)
  • 2020-12-04 04:01

    Below is an example of how you may achieve this...

    The code has been adapted from a BFGS method to show how you can pass functions and call other functions within a module...

    Here I use:

    • private functions nested within other subroutines
    • pass variables from a subroutine to a nested function
    • pass a function as an argument for a function that can be defined outside the module block

    Hopefully this will cover everything for you...

    Module Mod_Example
    
    Private :: private_func
    
       SUBROUTINE test_routine(res,start,fin,vector,func,dfunc)
          IMPLICIT NONE
          REAL, DIMENSION(:), INTENT(IN) :: res, start, fin
          REAL, DIMENSION(:), INTENT(INOUT) :: vector
    
          INTERFACE
             FUNCTION func(vector)                                      
                IMPLICIT NONE                                      
                REAL, DIMENSION(:), INTENT(IN) :: vector                
                REAL :: func                                       
             END FUNCTION func                                     
    
             FUNCTION dfunc(vector)                                     
                IMPLICIT NONE                                      
                REAL, DIMENSION(:), INTENT(IN) :: vector               
                REAL, DIMENSION(size(vector)) :: dfunc                  
             END FUNCTION dfunc                                    
          END INTERFACE
    
          ! do stuff with p
    
          private_func(res,start,fin,vector,func,dfunc) 
    
          ! do stuff
       END SUBROUTINE test_routine
    
       SUBROUTINE private_func(res,start,fin,vector,func,dfunc)
          IMPLICIT NONE
          REAL, DIMENSION(:), INTENT(IN) :: res, start, fin
          REAL, DIMENSION(:), INTENT(INOUT) :: vector
          INTERFACE
             FUNCTION func(vector)            
                REAL, DIMENSION(:), INTENT(IN) :: vector
                REAL :: func
             END FUNCTION func
             FUNCTION dfunc(vector)
                REAL, DIMENSION(:), INTENT(IN) :: vector
                REAL, DIMENSION(size(vector)) :: dfunc
             END FUNCTION dfunc     
          END INTERFACE   
    
          ! do stuff             
       END SUBROUTINE private_func
    
    END Mod_Example
    
    • func and dfunc would be declared within the program code that uses the MODULE Mod_Example with an interface block at the top.
    • the variables: res, start etc. can be declared with values in the main program block and passed to SUBROUTINE test_routine as arguments.
    • SUBROUTINE test_routine will call private_func with the variables that were passed to it.

    Your main program would then look something like this:

    Program Main_Program
       USE Mod_Example
       INTERFACE
          FUNCTION func(vector)            
             REAL, DIMENSION(:), INTENT(IN) :: vector
             REAL :: func
          END FUNCTION func
          FUNCTION dfunc(vector)
             REAL, DIMENSION(:), INTENT(IN) :: vector
             REAL, DIMENSION(size(vector)) :: dfunc
          END FUNCTION dfunc     
       END INTERFACE
    
       ! do stuff       
    
       ! calls test_routine form module
       ! uses dfunc and func defined below
       call test_routine(res,start,fin,vector,func,dfunc)
    
       ! do stuff
    END PROGRAM Main_Program
    
    ! define dfunc and nfunc for passing into the modular subroutine
    FUNCTION func(vector)
       IMPLICIT NONE
       REAL, DIMENSION(:), INTENT(IN) :: vector
       REAL :: func
    
       nfunc = vector
    END FUNCTION func
    
    FUNCTION dfunc(vector)
       IMPLICIT NONE
       REAL, DIMENSION(:), INTENT(IN) :: vector
       REAL, DIMENSION(size(vector)) :: dfunc   
    
       dfunc = vector
    END FUNCTION dfunc
    
    0 讨论(0)
提交回复
热议问题