TABLE OF CONTENTS


ABINIT/m_stream_string [ Modules ]

[ Top ] [ Modules ]

NAME

  m_stream_string

FUNCTION

  This module define a type representing a variable size
  string. It can be used in a file-like way by writing to it or reading it.
  Memory is automatically allocated on writing and freed on reading.

COPYRIGHT

 Copyright (C) 2009-2024 ABINIT group (TC, MG)
 This file is distributed under the terms of the
 GNU General Public License, see ~abinit/COPYING
 or http://www.gnu.org/copyleft/gpl.txt .

NOTES

 Provide tools to manipulate variable size strings in an incremental FIFO way
 Use `stream%push` to incrementally fill the string. The required memory space will be allocated
 automatically when needed.
 To avoid memory leaks you have to use stream_free on the stream to free the memory space unless
 you already flushed it using stream%flush, stream%transfer, stream%to_string or stream%to_file.
 Unlike the last four methods, stream_copy and stream_debug do not modify the source stream

SOURCE

26 #if defined HAVE_CONFIG_H
27 #include "config.h"
28 #endif
29 
30 #include "abi_common.h"
31 
32 module m_stream_string
33 
34   use defs_basis
35   use m_profiling_abi
36 
37   use m_fstrings, only : prep_char !, replace
38 
39   implicit none
40 
41   private
42 
43   integer,public,parameter :: chunk_size = 248
44 
45   type,private :: stream_chunk
46     type(stream_chunk), pointer :: next => null()
47     character(len=chunk_size) :: chunk = repeat(' ', chunk_size)
48   end type stream_chunk
49 
50   type,public :: stream_string
51     integer :: length = 0
52     type(stream_chunk), pointer :: head => null()
53     contains
54       procedure :: flush => stream_flush_unit
55       procedure :: flush_units => stream_flush_units
56       procedure :: free => stream_free
57       procedure :: copy => stream_copy
58       procedure :: push => stream_push
59       procedure :: pop_chunk => stream_pop_chunk
60       procedure :: to_string => stream_to_string
61       procedure :: to_file => stream_to_file
62       procedure :: transfer => stream_transfer
63       procedure :: debug => stream_debug
64 
65   end type stream_string
66 
67 contains

m_stream_string/stream_copy [ Functions ]

[ Top ] [ m_stream_string ] [ Functions ]

NAME

 stream_copy

FUNCTION

  copy src content to dest without altering src

SOURCE

180 subroutine stream_copy(src, dest)
181   class(stream_string),intent(inout) :: src, dest
182   type(stream_chunk), pointer :: cursor
183   cursor => src%head
184   do while (associated(cursor))
185     call dest%push(cursor%chunk)
186     cursor => cursor%next
187   end do
188 end subroutine stream_copy

m_stream_string/stream_debug [ Functions ]

[ Top ] [ m_stream_string ] [ Functions ]

NAME

 stream_debug

FUNCTION

  Show the content of the chunks on stdout

SOURCE

367 subroutine stream_debug(src)
368   class(stream_string),intent(inout) :: src
369   type(stream_chunk), pointer :: cursor
370   integer :: c
371   cursor => src%head
372   c = 1
373   do while (associated(cursor))
374     write(std_out,*) "Chunk no", c
375     write(std_out,'(A)') cursor%chunk
376     cursor => cursor%next
377     c = c + 1
378   end do
379 end subroutine stream_debug

m_stream_string/stream_free [ Functions ]

[ Top ] [ m_stream_string ] [ Functions ]

NAME

 stream_free

FUNCTION

  free stream. Most of the time this is not needed since
  routines to access the content free the stream

SOURCE

155 subroutine stream_free(stream)
156 
157   class(stream_string),intent(inout) :: stream
158   type(stream_chunk), pointer :: cursor, prev
159   cursor => stream%head
160   do while (associated(cursor))
161     prev => cursor
162     cursor => cursor%next
163     ABI_FREE_SCALAR(prev)
164   end do
165   stream%head => NULL()
166   stream%length = 0
167 
168 end subroutine stream_free

m_stream_string/stream_pop_chunk [ Functions ]

[ Top ] [ m_stream_string ] [ Functions ]

NAME

 stream_pop_chunk

FUNCTION

  Remove the last chunk of stream an put its content in string

SOURCE

246 subroutine stream_pop_chunk(stream, string)
247   class(stream_string),intent(inout) :: stream
248   character(len=chunk_size),intent(out) :: string
249   type(stream_chunk),pointer :: cursor
250 
251   string = stream%head%chunk
252   if (stream%length > chunk_size) then
253     ! copy the next pointer
254     cursor => stream%head%next
255     ! have next pointing to nothing
256     stream%head%next => NULL()
257     ! free head
258     ABI_FREE_SCALAR(stream%head)
259     stream%head => cursor
260     stream%length = stream%length - chunk_size
261   else
262     ABI_FREE_SCALAR(stream%head)
263     stream%length = 0
264   end if
265 
266 end subroutine stream_pop_chunk

m_stream_string/stream_push [ Functions ]

[ Top ] [ m_stream_string ] [ Functions ]

NAME

 stream_push

FUNCTION

  Write string to stream, allocating memory if needed

SOURCE

200 subroutine stream_push(stream, string)
201   class(stream_string),intent(inout) :: stream
202   character(len=*),intent(in) :: string
203   integer :: offset, room_left, soffset
204   type(stream_chunk), pointer :: cursor
205 
206   offset = stream%length
207 
208   if (.not.associated(stream%head)) then
209     ABI_MALLOC_SCALAR(stream%head)
210   end if
211   cursor => stream%head
212 
213   do while(offset > chunk_size)
214     cursor => cursor%next
215     offset = offset - chunk_size
216   end do
217 
218   room_left = chunk_size - offset
219   if (room_left < len(string)) then
220     cursor%chunk(offset+1:chunk_size) = string(1:room_left)
221     soffset = room_left
222     do while (soffset < len(string))
223       ABI_MALLOC_SCALAR(cursor%next)
224       cursor%next%chunk(1:min(chunk_size, len(string)-soffset)) = &
225         string(soffset+1:min(soffset+chunk_size,len(string)))
226       cursor => cursor%next
227       soffset = soffset + chunk_size
228     end do
229   else
230     cursor%chunk(offset+1:offset+len(string)) = string
231   end if
232   stream%length = stream%length + len(string)
233 
234 end subroutine stream_push

m_stream_string/stream_to_file [ Functions ]

[ Top ] [ m_stream_string ] [ Functions ]

NAME

 stream_to_file

FUNCTION

  Write the content of stream to the file, freeing stream

SOURCE

306 subroutine stream_to_file(stream, file_d)
307   class(stream_string),intent(inout) :: stream
308   integer,intent(in) :: file_d
309   character(len=chunk_size) :: stmp
310   integer :: offset, length
311   offset = 0
312 
313   do while (stream%length > 0)
314     length = stream%length
315     call stream%pop_chunk(stmp)
316     write(file_d, '(A)', advance='no') stmp(1:min(length, chunk_size))
317     offset = offset + chunk_size
318   end do
319 
320 end subroutine stream_to_file

m_stream_string/stream_to_string [ Functions ]

[ Top ] [ m_stream_string ] [ Functions ]

NAME

 stream_to_string

FUNCTION

  Copy the content of stream to string, freeing stream. String must be large enough

SOURCE

278 subroutine stream_to_string(stream, string)
279 
280   class(stream_string),intent(inout) :: stream
281   character(len=*),intent(out) :: string
282   character(len=chunk_size) :: stmp
283   integer :: offset, length
284   offset = 0
285 
286   string = repeat(' ', len(string))
287   do while (stream%length > 0)
288     length = stream%length
289     call stream%pop_chunk(stmp)
290     string(offset+1:offset+min(length, chunk_size)) = stmp(1:min(length, chunk_size))
291     offset = offset + chunk_size
292   end do
293 
294 end subroutine stream_to_string

m_stream_string/stream_transfer [ Functions ]

[ Top ] [ m_stream_string ] [ Functions ]

NAME

 stream_transfer

FUNCTION

  Copy the content of src to dest, freeing src
  If possible does not reallocate memory and just have
  dest point to src content

SOURCE

334 subroutine stream_transfer(src, dest)
335   class(stream_string),intent(inout) :: src, dest
336   character(len=chunk_size) :: chunk
337   integer :: length
338   if(.not.associated(dest%head)) then
339     ! if possible just transfer the pointer
340     dest%head => src%head
341     dest%length = src%length
342     src%head => NULL()
343   else
344     do while (src%length > 0)
345       length = src%length
346       call src%pop_chunk(chunk)
347       if(length > chunk_size) then
348         call dest%push(chunk)
349       else
350         call dest%push(chunk(1:length))
351       end if
352     end do
353   end if
354 
355 end subroutine stream_transfer