Kenny
There are undocumented routines that you could use for 64 bits but you would have to provide your own interfaces.
Given time we could provide new routines that work constistently for both 32 and 64 bits.
Welcome to our forums
Kenny
There are undocumented routines that you could use for 64 bits but you would have to provide your own interfaces.
Given time we could provide new routines that work constistently for both 32 and 64 bits.
ok, if they're going to available by, say, end of Jan, that's OK.
if not, what are the C_External calls i would need to point to?
K
Kenny
Here is a sample but you will need a new clearwin64.dll because __open_heap and __close_heap are not currently exported.
c_external open_heap '__open_heap' ():INTEGER*8
c_external close_heap '__close_heap' (VAL4)
c_external heap_malloc '__heap_malloc'(VAL4,VAL4):INTEGER*8
c_external heap_free '__heap_free' (VAL4,VAL4)
integer*8 han,addr(10)
han = open_heap()
do i =1, 10
addr(i) = heap_malloc(han, 1000000)
write(*, '(Z8)') addr(i)
end do
do i =1,10
call heap_free(han,addr(i))
end do
call close_heap(han)
end
I will see if new DLLs can be made generally available.
hmm, i spoke too soon!
i'm getting an 'out of heap space' error under quite specific circumstances.
as far as i can tell there's plenty of memory available (committed figure is ~800Mb) and the failing request is only for 208 bytes.
if i send you the application installer and the datafiles that cause the issue, will you be able to take a look?
K
following up...
the actual crash happens on a 'write' statement, which, IIRC, means it's actually happened somewhere else and the write statement is the first time windows gets an opportunity to report the error...
K
Kenny
Please see my personal message to you.
Quoted from PaulLaidler Kenny
Here is a sample but you will need a new clearwin64.dll because __open_heap and __close_heap are not currently exported.
I am interested in aligning ALLOCATE on a page boundary, so I am wondering what the modified code might show. c_external open_heap '__open_heap' ():INTEGER8 c_external close_heap '__close_heap' (VAL4) c_external heap_malloc '__heap_malloc'(VAL4,VAL4):INTEGER8 c_external heap_free '__heap_free' (VAL4,VAL4) integer*8 han,addr(10), page, offset integer i
han = open_heap()
do i =1, 10
addr(i) = heap_malloc(han, 1000000)
page = addr(i)/4096
offset = addr(i) - page*4096
write(*, '(Z8,2i8)') addr(i), page, offset
end do
do i =10,1,-1
call heap_free(han,addr(i))
end do
call close_heap(han)
end
John
heap_malloc calls HeapAlloc and from the Microsoft documentation 'The alignment of memory returned by HeapAlloc is MEMORY_ALLOCATION_ALIGNMENT'.
This is 16 for 64 bit systems.
heap_malloc returns an address for allocated memory of user-given size which is unlike ALLOCATE which provides runtime memory for an object whose size is known to the compiler.
GET_GSTORAGE@ calls VirtualAlloc. Google 'VirtualAlloc MSDN'.
I have encountered a problem which means that I will not be able to provide access to the new routines described above.
At the moment the general advice is to move to 64 bits as soon as possible and if an address for memory (off the heap) is required then call ALLOCATE for a CHARACTER array and then get its LOC.
p.s. Just to clarify. There are existing functions in the library (mentioned above) that currently require a user interface. These will continue to be available. Plans to provide direct access to these functions (without the need for a user interface) have been put on hold.
Here is some code that illustrates how to get the address of a block of memory from the global heap using a call to ALLOCATE and FTN95.
subroutine alloc(addr, size)
integer(7)::addr,size
character,pointer::arr(:)
ALLOCATE(arr(size))
if(ALLOCATED(arr))then
addr = loc(arr)
else
addr = 0
print*, 'Allocate failed'
end if
end subroutine
subroutine dealloc(addr)
integer(7)::addr
character,pointer::arr(:)
ALLOCATE(arr(1), ABSOLUTE_ADDRESS=addr)
DEALLOCATE(arr) !Note: DEALLOCATE raises an exception on failure.
addr = 0
end subroutine
program main
integer(7) addr
call alloc(addr, 100000_7)
write(*,'(Z8)') addr
call dealloc(addr)
end program
p.s. It is better to use ASSOCIATED rather than ALLOCATED.
hi, could you email me that text block? when I copy/paste it, it won't compile (it's got some sort of illegal character (hex'A0') embedded in it)
K
Hmmm, i don't think that works?
do you get different values returned by alloc if you call it more than once without dealloc-ing?
i'm experimenting with a 'hybrid' solution that seems fairly solid but it depends on keeping a record of the start and end addresses allocated in a table.
basically, if the buffer size (to the nearest multiple of 16bytes) is large then i use GET_GSTORAGE@ if it's medium then i use GET_STORAGE@ if it's tiny then i use localalloc (via a STDCALL)
nbuf = 16
nb7 = (nb-1)/nbuf*nbuf+nbuf
if( mod(nb7,4096).gt.2048) then
CALL GET_GSTORAGE@ (IA, NB7)
else if( nb7.gt.128) then
CALL GET_STORAGE@ (IA, NB7)
else
ia = localalloc(0,nb7)
endif
then when freeing the memory, i use the recorded start/end addresses to get the size of the block and free the memory in the appropriate manner:
ja = ia
isiz=-1
call A_VMmem(ja, isiz) ! returns the size of the block
if( mod(isiz,4096).gt.2048) then
CALL return_GSTORAGE@ (IA)
call GIVEBACK_ALLOCATION_BLOCKS@(kval)
ia = 0
else if( isiz.gt.128) then
CALL return_STORAGE@ (IA)
call GIVEBACK_ALLOCATION_BLOCKS@(kval)
ia = 0
elseif( isiz.gt.0) then
ia = localfree(ia)
if( ia.ne.0) then
write(*,*)'failed to free', ia
endif
endif
K
That is strange, and may be related to the exact details of your copy-paste procedure. I used Firefox on Windows to copy, and pasted by redirection to a file in a command window, and did not find any characters with the high bit set.
I may note that it is not quite correct to use an argument to ALLOCATED that has not been declared to be allocatable. You should probably use ASSOCIATED instead. Similarly, NULLIFY instead of DEALLOCATE? The choice between pointers versus allocatables depends on what you want to do in your application.
Quoted from Robert It is worth remembering that VirtualAlloc allocates (or uses memory) at page size granularity. So an alloc of a few bytes takes a full 4K page
Robert, Your earlier statement that you provided interests me, as I am wanting to allocate arrays on the heap, starting on a new memory page. How do I get access to 'VirtualAlloc' ?
Quoted from mecej4 That is strange, and may be related to the exact details of your copy-paste procedure. I used Firefox on Windows to copy, and pasted by redirection to a file in a command window, and did not find any characters with the high bit set.
i also use FF and if i swipe the code block and paste into notepad then i look at it in a hex window:
4C4C204745545F53544F524147454020 2849412C204E4237290D0A202020202020656C7365C2A00D0A20202020202020206961202020203D20206C6F63616C616C6C6F6328302C6E6237290D0A202020 202020656E646966202000
k
Quoted from JohnCampbell
Quoted from Robert It is worth remembering that VirtualAlloc allocates (or uses memory) at page size granularity. So an alloc of a few bytes takes a full 4K page
Robert, Your earlier statement that you provided interests me, as I am wanting to allocate arrays on the heap, starting on a new memory page. How do I get access to 'VirtualAlloc' ?
there may be a STDCALL? there is for LocalAlloc for example.
K
PS if you look in WIN32API.INS:
STDCALL VIRTUALFREE 'VirtualFree' (REF,VAL,VAL):LOGICAL*4 STDCALL VIRTUALALLOC 'VirtualAlloc' (REF,VAL,VAL,VAL):INTEGER(7)
but you'll have to google MSDN to find out what the arguments are...
K
Kenny: If you send me a personal message with your email address then I will email you a copy of the code.
mecej4: Yes ASSOCIATED is better and avoids the warning message. I will edit the post.
John: For 64 bit applications you can access VirtualAlloc via GET_GSTORAGE@ or GET_GSTORAGE64@ but VirtualAlloc does not get heap memory. For further information Google 'VirtualAlloc MSDN'.
Quoted from PaulLaidler Here is some code that illustrates how to get the address of a block of memory from the global heap using a call to ALLOCATE and FTN95.
subroutine alloc(addr, size) integer(7)::addr,size character,pointer::arr(:) ALLOCATE(arr(size)) if(ALLOCATED(arr))then addr = loc(arr) else addr = 0 print*, 'Allocate failed' end if end subroutine subroutine dealloc(addr) integer(7)::addr character,pointer::arr(:) ALLOCATE(arr(1), ABSOLUTE_ADDRESS=addr) DEALLOCATE(arr) !Note: DEALLOCATE raises an exception on failure. addr = 0 end subroutine program main integer(7) addr call alloc(addr, 100000_7) write(*,'(Z8)') addr call dealloc(addr) end programp.s. It is better to use ASSOCIATED rather than ALLOCATED.
Paul, if you change the main routine:
program main
integer(7) addr(10)
do i=1,10
call alloc(addr(i), 100000_7)
write(*,'(Z8)') addr(i)
enddo
do i=1,10
call dealloc(addr(i))
ENDDO
end program
you see that the call to alloc always returns the same address...
20202000
K
I should have also tested the code for a 32 bit application. It works for 64 bits.
There is something wrong with addr = loc(arr). addr = loc(arr(1)) is better but still not right.
I will have to think again for 32 bits.
This is my contribution to understanding memory allocation
module ELEM_DATA_BASE ! (minimal example)
integer*4 :: MXELEM = 0 ! maximum element number expected
integer*4, allocatable :: INDEXE(:) ! (max_elements)
!
TYPE elem_array_record ! set in elcomp
integer*4 :: sd_size
real*8, allocatable :: sd(:) ! S(nd,nd) !symmetric stiffness matrix sd( nt )
END TYPE elem_array_record
!
type (elem_array_record), allocatable :: elem_array_records(:) ! (max_elem_records)
!
end module ELEM_DATA_BASE
Program Report_memory_positions
use ELEM_DATA_BASE
integer :: i, is, stat
is = 1024*1024-8
write (*,fmt='(a,i0,a)') 'allocating arrays of size = ',is*8/4096+1,' pages'
mxelem = 10
allocate ( indexe(mxelem), STAT=stat )
write (*,*) ' indexe(mxelem) allocated : STAT =',stat
call report_location ( LOC(indexe) )
allocate ( elem_array_records(mxelem), STAT=stat )
write (*,*) ' elem_array_records(mxelem) allocated : STAT =',stat
call report_location ( LOC(elem_array_records) )
write (*,fmt='(/a/)') ' now allocating arrays'
do i = 1,mxelem
elem_array_records(i)%sd_size = is
allocate ( elem_array_records(i)%sd(is), STAT=stat )
call report_location ( LOC(elem_array_records(i)%sd(1)) )
end do
end Program Report_memory_positions
subroutine report_location ( addr )
integer*8 :: addr, page, offs, page_size = 4096, last_addr = 0, dpage
page = addr / page_size
offs = addr - page*page_size
dpage = (addr-last_addr)/page_size
write ( *,11) addr, page, offs, addr-last_addr, dpage
11 format (' array allocated at mem= ',i0,' : page ',i0,' offs ',i0,' spacing ',i0,' bytes ',i0,' pages')
last_addr = addr
end subroutine report_location
My problem is I don't understand the page spacing of the 'sd' arrays, but they all start on a new memory page, which is something I am trying to manage. (but with a 64 byte offset?)