1

I have some trouble in Python calling fortran dll and really want some help and advice. My problem is passing a dynamic array to a function(provided by my Fortran DLL) .

For instance , I have a type with a dynamic array:

Module Class_Rotor 
    Implicit None 
    Type,Public ::Type_Rotor 
        Real(kind=8),Public::Mass 
        Real(kind=8),Allocatable,Public::Lamda(:,:) 
    End Type Type_Rotor 
End Module Class_Rotor 

Module Class_Trim 
    Implicit None 
    Type,Public::Type_Trim 
        Real(kind=8),Public::COLL 
        Real(kind=8),Public::LNGCYC 
    End Type Type_Trim 
End Module Class_Trim 

and I want to use the dynamic array in fortran subroutine

Subroutine CalculateRotor(Trim,Rotor)
!DEC$ ATTRIBUTES DLLEXPORT, STDCALL, REFERENCE, MIXED_STR_LEN_ARG, ALIAS:"CalculateRotor" :: CalculateRotor
    Use Class_Rotor
    Use Class_Trim
    TYPE(Type_Trim),Intent(in)::Trim
    TYPE(Type_Rotor),Intent(inout)::Rotor

    Rotor%Mass = Trim%COLL + Trim%LNGCYC
End Subroutine CalculateRotor

Subroutine CalculateTrim(Rotor,Trim)
!DEC$ ATTRIBUTES DLLEXPORT, STDCALL, REFERENCE, MIXED_STR_LEN_ARG, ALIAS:"CalculateTrim" :: CalculateTrim
    Use Class_Rotor
    Use Class_Trim
    TYPE(Type_Rotor),Intent(in)::Rotor
    TYPE(Type_Trim),Intent(inout)::Trim

    Trim%COLL = Rotor%Mass+Rotor%Lamda(2,2)

End Subroutine CalculateTrim

in addition,I define a sunroutine Alc to allocate the space of Rotor%Lamda,and pass value to it.

Subroutine Alc(Rotor,n,LamArray)
!DEC$ ATTRIBUTES DLLEXPORT, STDCALL, REFERENCE, MIXED_STR_LEN_ARG, ALIAS:"Alc" :: Alc
    Use Class_Rotor
    TYPE(Type_Rotor),intent(inout):: Rotor
    Integer(kind=4)::I,J
    Integer(kind=4),intent(in)::n
    Real(kind = 8),DIMENSION(n,n),intent(in)::LamArray

    IF(Allocated(Rotor%Lamda))Then
        DeAllocate(Rotor%Lamda)
    ENDIF

    Allocate(Rotor%Lamda(n,n))  
    Do I=1,n
        Do J=1,n
            Rotor%Lamda(I,J)=LamArray(I,J)  
        EndDo
    EndDo
End Subroutine Alc

I try like this: new a Fortran DLL project(vs2010+IVF), then I use this DLL in python:

from ctypes import *
import numpy as np
from numpy.ctypeslib import load_library,ndpointer

class Type_Rotor(Structure):
    _fields_ = [             
    ('Mass', c_double),
    ('Lamda', POINTER(c_double)),
    ]
    def __init__(self,cols):
        self.cols_count = cols 
        pc = (POINTER(c_double)*cols*cols)()
        self.Lamda = cast(pc,POINTER(c_double))

class Type_Trim(Structure):
    _fields_ = [             
    ('COLL', c_double),
    ('LNGCYC', c_double),
    ]  

def run():
    mydll = windll.LoadLibrary('Dll3.dll')
    CalculateRotor = mydll.CalculateRotor
    CalculateTrim = mydll.CalculateTrim
    Rotor = Type_Rotor(3)
    Trim = Type_Trim()

    Rotor.Mass = 1.0

    temp = (c_double *3*3) ((1,2,3),(4,5,6),(7,8,9))

    Trim.COLL = 11.0
    Trim.LNGCYC = -3.0

    mydll.Alc(byref(Rotor),byref(c_int(Rotor.cols_count)),byref(temp))
    for i in range(15):
        CalculateRotor(byref(Trim), byref(Rotor))
        print Trim.COLL,Trim.LNGCYC,Rotor.Mass
        CalculateTrim(byref(Rotor), byref(Trim))
    print Trim.COLL,Trim.LNGCYC,Rotor.Mass

if __name__=="__main__":
    run()    

under Win7,the first time run the python scripts with command line,return the answer that:A pointer passed to DeAllocate points to an object that cannot be deallocated, but the second time it gives the right answer

under Winxp,the first time run the python scripts with command line,return the answer that:A pointer passed to DeAllocate points to an object that cannot be deallocated, but the second time it gives the right answer,But,Then it crush!!!somtimes,it also return that :allocatable array is already allocated

I really don't know why? And How to use the dynamic array?

Mike
  • 11
  • 1
  • 4
    You opened a can of worms, enjoy reading this http://stackoverflow.com/questions/11934822/how-to-access-dynamically-allocated-fortran-arrays-in-c/11935949#11935949 . I advise to stay away from passing allocatable entities between different languages. Use C pointers wherever possible. Btw, kind=4 and kind=8 are not guaranteed to be 4 bytes and 8 bytes. – Vladimir F Героям слава Jul 17 '15 at 14:54
  • 1
    When I combine Fortran and Python I _always_ allocate memory in Python and pass a C pointer to Fortran. I just makes things easier. – bdforbes Jul 19 '15 at 02:38

0 Answers0