File: mod_compute.f90

package info (click to toggle)
starpu-contrib 1.2.6%2Bdfsg-6
  • links: PTS, VCS
  • area: contrib
  • in suites: buster
  • size: 23,456 kB
  • sloc: ansic: 143,860; cpp: 23,732; sh: 13,444; makefile: 3,816; xml: 3,652; f90: 3,602; lisp: 877; yacc: 214; sed: 162; fortran: 25
file content (129 lines) | stat: -rw-r--r-- 4,255 bytes parent folder | download | duplicates (2)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
! StarPU --- Runtime system for heterogeneous multicore architectures.
!
! Copyright (C) 2015                                     CNRS
! Copyright (C) 2015                                     Inria
! Copyright (C) 2015                                     Université de Bordeaux
! Copyright (C) 2015                                     ONERA
!
! StarPU is free software; you can redistribute it and/or modify
! it under the terms of the GNU Lesser General Public License as published by
! the Free Software Foundation; either version 2.1 of the License, or (at
! your option) any later version.
!
! StarPU is distributed in the hope that it will be useful, but
! WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.
!
! See the GNU Lesser General Public License in COPYING.LGPL for more details.
!
! Computation kernels for the simulation

MODULE mod_compute

  USE mod_types
  USE starpu_mod
  USE mod_interface
  USE iso_c_binding

  IMPLICIT NONE

CONTAINS

  !--------------------------------------------------------------!
  SUBROUTINE init_element(ro,dro,basis,Neq_max,Np,Ng,i)
    INTEGER(KIND=C_INT),INTENT(IN)                           :: Neq_max,Np,Ng,i
    REAL(KIND=C_DOUBLE),DIMENSION(:,:),POINTER,INTENT(INOUT) :: ro,basis,dro
    !Local variables
    INTEGER(KIND=C_INT)                                      :: n,nb,neq

    DO nb=1,Np
       DO neq= 1,Neq_max
          ro(neq,nb)  = 0.01*(nb+neq)*i
       END DO
    END DO

    DO nb=1,Np
       DO neq= 1,Neq_max
          dro(neq,nb) = 0.05*(nb-neq)*i
       END DO
    END DO

    DO n=1,Ng
       DO nb=1,Np
          basis(nb,n) = 0.05*(n+nb)*i
       END DO
    END DO

  END SUBROUTINE init_element

  !--------------------------------------------------------------!
  RECURSIVE SUBROUTINE loop_element_cpu_fortran(coeff,Neq_max,Np,Ng, &
       &   ro_ptr,dro_ptr,basis_ptr) BIND(C)
    INTEGER(KIND=C_INT),VALUE                  :: Neq_max,Np,Ng
    REAL(KIND=C_DOUBLE),VALUE                  :: coeff
    TYPE(C_PTR)                                :: ro_ptr,dro_ptr,basis_ptr
    !Local variables
    REAL(KIND=C_DOUBLE),DIMENSION(:,:),POINTER :: ro,dro,basis

    CALL C_F_POINTER(ro_ptr,ro,[Neq_max,Np])
    CALL C_F_POINTER(dro_ptr,dro,[Neq_max,Np])
    CALL C_F_POINTER(basis_ptr,basis,[Np,Ng])

    CALL loop_element_cpu(ro,dro,basis,coeff,Neq_max,Ng,Np)

  END SUBROUTINE loop_element_cpu_fortran

  !--------------------------------------------------------------!
  RECURSIVE SUBROUTINE loop_element_cpu(ro,dro,basis,coeff,Neq_max,Ng,Np)
    REAL(KIND=C_DOUBLE),INTENT(IN)                           :: coeff
    INTEGER(KIND=C_INT),INTENT(IN)                           :: Neq_max,Ng,Np
    REAL(KIND=C_DOUBLE),DIMENSION(:,:),POINTER,INTENT(IN)    :: ro,basis
    REAL(KIND=C_DOUBLE),DIMENSION(:,:),POINTER,INTENT(INOUT) :: dro
    !Local variables
    REAL(KIND=C_DOUBLE)                                      :: coeff2,r
    INTEGER(KIND=C_INT)                                      :: n,nb,neq

    DO n=1,Ng
       r = 0.
       DO nb=1,Np
          DO neq= 1,Neq_max
             r = r + basis(nb,n) * ro(neq,nb)
          ENDDO
       ENDDO

       coeff2 = r + coeff

       DO nb=1,Np
          DO neq = 1,Neq_max
             dro(neq,nb) = coeff2 + dro(neq,nb)
          ENDDO
       ENDDO
    ENDDO

  END SUBROUTINE loop_element_cpu

  !--------------------------------------------------------------!
  RECURSIVE SUBROUTINE copy_element_cpu_fortran(Neq_max,Np, &
       &   ro_ptr,dro_ptr) BIND(C)
    INTEGER(KIND=C_INT),VALUE                  :: Neq_max,Np
    TYPE(C_PTR)                                :: ro_ptr,dro_ptr
    !Local variables
    REAL(KIND=C_DOUBLE),DIMENSION(:,:),POINTER :: ro,dro

    CALL C_F_POINTER(ro_ptr,ro,[Neq_max,Np])
    CALL C_F_POINTER(dro_ptr,dro,[Neq_max,Np])

    CALL copy_element_cpu(ro,dro)

  END SUBROUTINE copy_element_cpu_fortran

  !--------------------------------------------------------------!
  RECURSIVE SUBROUTINE copy_element_cpu(ro,dro)
    REAL(KIND=C_DOUBLE),DIMENSION(:,:),POINTER,INTENT(INOUT) :: ro
    REAL(KIND=C_DOUBLE),DIMENSION(:,:),POINTER,INTENT(IN)    :: dro

    ro = ro + dro

  END SUBROUTINE copy_element_cpu

END MODULE mod_compute