Skip to content

Commit 3a77cc1

Browse files
feat(IntVector): add Copy and Copy_ interfaces
Add new interfaces for copying integer vectors: - Public interfaces `Copy` and `Copy_` - Implementation for different integer types (INT8, INT16, INT32, INT64) - Support for full vector copy and partial copy with specified ranges - Fix case inconsistency in `intVec_getTotalDimension` function name - Fix capitalization of `PUBLIC` keyword in QuadraturePoint_Method.F90 - Add optional parameter `isUpper` to QuadraturePoint conversion functions
1 parent 3079918 commit 3a77cc1

File tree

3 files changed

+208
-7
lines changed

3 files changed

+208
-7
lines changed

src/modules/IntVector/src/IntVector_ConstructorMethod.F90

Lines changed: 121 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -31,6 +31,8 @@ MODULE IntVector_ConstructorMethod
3131
PUBLIC :: IntVector
3232
PUBLIC :: IntVector_Pointer
3333
PUBLIC :: Convert
34+
PUBLIC :: Copy
35+
PUBLIC :: Copy_
3436

3537
!----------------------------------------------------------------------------
3638
! Shape@Constructor
@@ -76,10 +78,10 @@ END FUNCTION intVec_Size
7678
! This function returns the total dimension (or rank) of an array,
7779

7880
INTERFACE GetTotalDimension
79-
MODULE PURE FUNCTION IntVec_getTotalDimension(obj) RESULT(Ans)
81+
MODULE PURE FUNCTION intVec_getTotalDimension(obj) RESULT(Ans)
8082
TYPE(IntVector_), INTENT(IN) :: obj
8183
INTEGER(I4B) :: ans
82-
END FUNCTION IntVec_getTotalDimension
84+
END FUNCTION intVec_getTotalDimension
8385
END INTERFACE GetTotalDimension
8486

8587
!----------------------------------------------------------------------------
@@ -371,4 +373,121 @@ MODULE PURE SUBROUTINE obj_convert_int(From, To)
371373
END SUBROUTINE obj_convert_int
372374
END INTERFACE Convert
373375

376+
!----------------------------------------------------------------------------
377+
! Copy@Constructor
378+
!----------------------------------------------------------------------------
379+
380+
!> author: Vikas Sharma, Ph. D.
381+
! date: 2025-06-22
382+
! summary: Copy y into x, x will be reallocated
383+
!
384+
!# Introduction
385+
!
386+
! Get the size of y and reallocate x to the same size.
387+
! If x is already allocated, it will be reallocated to the size of y.
388+
389+
INTERFACE Copy
390+
MODULE PURE SUBROUTINE obj_Copy_Int8(x, y)
391+
INTEGER(INT8), INTENT(INOUT), ALLOCATABLE :: x(:)
392+
INTEGER(INT8), INTENT(IN) :: y(:)
393+
END SUBROUTINE obj_Copy_Int8
394+
END INTERFACE Copy
395+
396+
!----------------------------------------------------------------------------
397+
! Copy@Constructor
398+
!----------------------------------------------------------------------------
399+
400+
!> author: Vikas Sharma, Ph. D.
401+
! date: 2025-06-22
402+
! summary: Copy y into x, x will be reallocated
403+
!
404+
!# Introduction
405+
!
406+
! Get the size of y and reallocate x to the same size.
407+
! If x is already allocated, it will be reallocated to the size of y.
408+
409+
INTERFACE Copy
410+
MODULE PURE SUBROUTINE obj_Copy_Int16(x, y)
411+
INTEGER(INT16), INTENT(INOUT), ALLOCATABLE :: x(:)
412+
INTEGER(INT16), INTENT(IN) :: y(:)
413+
END SUBROUTINE obj_Copy_Int16
414+
END INTERFACE Copy
415+
416+
!----------------------------------------------------------------------------
417+
! Copy@Constructor
418+
!----------------------------------------------------------------------------
419+
420+
!> author: Vikas Sharma, Ph. D.
421+
! date: 2025-06-22
422+
! summary: Copy y into x, x will be reallocated
423+
!
424+
! Introduction
425+
!
426+
! Get the size of y and reallocate x to the same size.
427+
! If x is already allocated, it will be reallocated to the size of y.
428+
429+
INTERFACE Copy
430+
MODULE PURE SUBROUTINE obj_Copy_Int32(x, y)
431+
INTEGER(INT32), INTENT(INOUT), ALLOCATABLE :: x(:)
432+
INTEGER(INT32), INTENT(IN) :: y(:)
433+
END SUBROUTINE obj_Copy_Int32
434+
END INTERFACE Copy
435+
436+
!----------------------------------------------------------------------------
437+
! Copy@Constructor
438+
!----------------------------------------------------------------------------
439+
440+
!> author: Vikas Sharma, Ph. D.
441+
! date: 2025-06-22
442+
! summary: Copy y into x, x will be reallocated
443+
!
444+
!# Introduction
445+
!
446+
! Get the size of y and reallocate x to the same size.
447+
! If x is already allocated, it will be reallocated to the size of y.
448+
449+
INTERFACE Copy
450+
MODULE PURE SUBROUTINE obj_Copy_Int64(x, y)
451+
INTEGER(INT64), INTENT(INOUT), ALLOCATABLE :: x(:)
452+
INTEGER(INT64), INTENT(IN) :: y(:)
453+
END SUBROUTINE obj_Copy_Int64
454+
END INTERFACE Copy
455+
456+
!----------------------------------------------------------------------------
457+
! Copy@Constructor
458+
!----------------------------------------------------------------------------
459+
460+
!> author: Vikas Sharma, Ph. D.
461+
! date: 2025-06-22
462+
! summary: Copy portion of y into x
463+
464+
INTERFACE Copy_
465+
MODULE PURE SUBROUTINE obj_Copy1_(x, x_start, y, y_start, y_end)
466+
INTEGER(I4B), INTENT(INOUT) :: x(:)
467+
!! x vector should be allocated
468+
INTEGER(I4B), INTENT(IN) :: y(:)
469+
INTEGER(I4B), INTENT(IN) :: x_start
470+
INTEGER(I4B), INTENT(IN) :: y_start, y_end
471+
END SUBROUTINE obj_Copy1_
472+
END INTERFACE Copy_
473+
474+
!----------------------------------------------------------------------------
475+
! Copy@Constructor
476+
!----------------------------------------------------------------------------
477+
478+
!> author: Vikas Sharma, Ph. D.
479+
! date: 2025-06-22
480+
! summary: Copy y into x
481+
482+
INTERFACE Copy_
483+
MODULE PURE SUBROUTINE obj_Copy2_(x, y)
484+
INTEGER(I4B), INTENT(INOUT) :: x(:)
485+
INTEGER(I4B), INTENT(IN) :: y(:)
486+
END SUBROUTINE obj_Copy2_
487+
END INTERFACE Copy_
488+
489+
!----------------------------------------------------------------------------
490+
!
491+
!----------------------------------------------------------------------------
492+
374493
END MODULE IntVector_ConstructorMethod

src/modules/QuadraturePoint/src/QuadraturePoint_Method.F90

Lines changed: 11 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -29,7 +29,7 @@ MODULE QuadraturePoint_Method
2929

3030
PUBLIC :: Initiate
3131
PUBLIC :: Copy
32-
public :: ASSIGNMENT(=)
32+
PUBLIC :: ASSIGNMENT(=)
3333
PUBLIC :: QuadraturePoint
3434
PUBLIC :: QuadraturePoint_Pointer
3535
PUBLIC :: DEALLOCATE
@@ -69,23 +69,29 @@ END FUNCTION QuadraturePointNameToId
6969

7070
!> author: Vikas Sharma, Ph. D.
7171
! date: 2023-08-06
72-
! summary: Quadrature point name to quadrature point id
72+
! summary: Convert Quadrature point from int id to string name
7373

7474
INTERFACE
75-
MODULE FUNCTION QuadraturePointIdToName(name) RESULT(ans)
75+
MODULE FUNCTION QuadraturePointIdToName(name, isUpper) RESULT(ans)
7676
INTEGER(I4B), INTENT(IN) :: name
7777
TYPE(String) :: ans
78+
LOGICAL, INTENT(IN), OPTIONAL :: isUpper
7879
END FUNCTION QuadraturePointIdToName
7980
END INTERFACE
8081

8182
!----------------------------------------------------------------------------
8283
! QuadraturePoint_ToChar@ConstructorMethods
8384
!----------------------------------------------------------------------------
8485

86+
!> author: Vikas Sharma, Ph. D.
87+
! date: 2025-06-18
88+
! summary: Convert Quadrature poitn from int id to char name
89+
8590
INTERFACE
86-
MODULE FUNCTION QuadraturePoint_ToChar(name) RESULT(ans)
91+
MODULE FUNCTION QuadraturePoint_ToChar(name, isUpper) RESULT(ans)
8792
INTEGER(I4B), INTENT(IN) :: name
88-
TYPE(String) :: ans
93+
LOGICAL(LGT), OPTIONAL, INTENT(IN) :: isUpper
94+
CHARACTER(:), ALLOCATABLE :: ans
8995
END FUNCTION QuadraturePoint_ToChar
9096
END INTERFACE
9197

src/submodules/IntVector/src/[email protected]

Lines changed: 76 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -241,4 +241,80 @@
241241
END IF
242242
END PROCEDURE obj_convert_int
243243

244+
!----------------------------------------------------------------------------
245+
! Copy
246+
!----------------------------------------------------------------------------
247+
248+
MODULE PROCEDURE obj_Copy_Int8
249+
INTEGER(I4B) :: tsize, ii
250+
tsize = SIZE(y)
251+
CALL Reallocate(x, tsize)
252+
DO ii = 1, tsize
253+
x(ii) = y(ii)
254+
END DO
255+
256+
END PROCEDURE obj_Copy_Int8
257+
258+
!----------------------------------------------------------------------------
259+
! Copy
260+
!----------------------------------------------------------------------------
261+
262+
MODULE PROCEDURE obj_Copy_Int16
263+
INTEGER(I4B) :: tsize, ii
264+
tsize = SIZE(y)
265+
CALL Reallocate(x, tsize)
266+
DO ii = 1, tsize
267+
x(ii) = y(ii)
268+
END DO
269+
END PROCEDURE obj_Copy_Int16
270+
271+
!----------------------------------------------------------------------------
272+
! Copy
273+
!----------------------------------------------------------------------------
274+
275+
MODULE PROCEDURE obj_Copy_Int32
276+
INTEGER(I4B) :: tsize, ii
277+
tsize = SIZE(y)
278+
CALL Reallocate(x, tsize)
279+
DO ii = 1, tsize
280+
x(ii) = y(ii)
281+
END DO
282+
END PROCEDURE obj_Copy_Int32
283+
284+
!----------------------------------------------------------------------------
285+
! Copy
286+
!----------------------------------------------------------------------------
287+
288+
MODULE PROCEDURE obj_Copy_Int64
289+
INTEGER(I4B) :: tsize, ii
290+
tsize = SIZE(y)
291+
CALL Reallocate(x, tsize)
292+
DO ii = 1, tsize
293+
x(ii) = y(ii)
294+
END DO
295+
END PROCEDURE obj_Copy_Int64
296+
297+
!----------------------------------------------------------------------------
298+
! Copy
299+
!----------------------------------------------------------------------------
300+
301+
MODULE PROCEDURE obj_Copy1_
302+
INTEGER(I4B) :: xx, yy
303+
304+
DO yy = y_start, y_end
305+
xx = x_start + yy - y_start
306+
x(xx) = y(yy)
307+
END DO
308+
END PROCEDURE obj_Copy1_
309+
310+
!----------------------------------------------------------------------------
311+
! Copy
312+
!----------------------------------------------------------------------------
313+
314+
MODULE PROCEDURE obj_Copy2_
315+
INTEGER(I4B) :: tsize
316+
tsize = SIZE(y)
317+
CALL obj_Copy1_(x=x, y=y, x_start=1, y_start=1, y_end=tsize)
318+
END PROCEDURE obj_Copy2_
319+
244320
END SUBMODULE Methods

0 commit comments

Comments
 (0)