PLASMA  2.4.5
PLASMA - Parallel Linear Algebra for Scalable Multi-core Architectures
 All Data Structures Namespaces Files Functions Variables Typedefs Enumerations Enumerator Macros Groups
example_sgesv_f.f
Go to the documentation of this file.
2 *
3 *********************************************************************
4 * plasma example routine(version 2.4.5)
5 * author: bilel hadri
6 * release date: november, 15th 2010
7 * plasma is a software package provided by univ. of tennessee,
8 * univ. of california berkeley and univ. of colorado denver.
9 * @generated s tue nov 22 14:35:54 2011
10 *********************************************************************
11 *
12  IMPLICIT NONE
13 *
14  include "plasmaf.h"
15 *
16 * purpose
17 * =======
18 *
19 * fortran example for plasma_sgesv
20 * example for solving a system of linear equations using lu
21 *
22 * =====================================================================
23 *
24 * .. parameters ..
25  INTEGER cores, n, nrhs
26  parameter( cores = 2 )
27  parameter( n = 10 )
28  parameter( nrhs = 5 )
29  COMPLEX*16 zone
30  parameter( zone = ( 1.0d+0, 0.0d+0 ) )
31 * ..
32 * .. local scalars ..
33  COMPLEX*16 a1( n, n ), b1( n, nrhs )
34  COMPLEX*16 a2( n, n ), b2( n, nrhs )
35  DOUBLE PRECISION rwork( n )
36  INTEGER*4 hl( 2 ), hpiv( 2 )
37  INTEGER i, info
38  INTEGER iseed( 4 )
39  DOUBLE PRECISION xnorm, anorm, bnorm, rnorm, eps
40  DOUBLE PRECISION dlamch, slange
41 * ..
42 * .. External subroutines ..
43  EXTERNAL zlarnv, dlamch, slange
46  EXTERNAL plasma_dealloc_handle
47  EXTERNAL sgemm
48 * ..
49 * .. executable statements ..
50 *
51  DO i = 1, 4
52  iseed( i ) = 1
53  ENDDO
54 *
55 * initialize plasma
56 *
57  CALL plasma_init( cores, info )
58  WRITE(*,*) "-- PLASMA is initialized on", cores, "cores."
59 *
60 * initialization of the matrix a1
61 *
62  CALL zlarnv( 1, iseed, n*n, a1 )
63  a2(:,:)=a1(:,:)
64 *
65 * initialization of the rhs
66 *
67  CALL zlarnv( 1, iseed, n*nrhs, b1 )
68  b2(:,:)=b1(:,:)
69 *
70 * Allocate l and ipiv
71 *
72  CALL plasma_alloc_workspace_sgesv_incpiv( n, hl, hpiv, info )
73 *
74 * plasma sgesv
75 *
76  CALL plasma_sgesv_incpiv( n, nrhs, a2, n, hl, hpiv,b2, n, info )
77 *
78 * check the solution
79 *
80  xnorm = slange('I',n, nrhs, b2, n, rwork)
81  anorm = slange('I',n, n, a1, n, rwork)
82  bnorm = slange('I',n, nrhs, b1, n, rwork)
83 
84  CALL sgemm('No transpose','No transpose', n, nrhs, n, zone,
85  $ a1, n, b2, n, -zone, b1, n)
86 
87  rnorm = slange('I',n, nrhs, b1, n, rwork)
88 
89  eps= dlamch('Epsilon')
90 
91  WRITE(*,*) '============'
92  WRITE(*,*) 'Checking the Residual of the solution '
93  WRITE(*,*) '-- ||Ax-B||_oo/((||A||_oo||x||_oo+||B||_oo).N.eps)=',
94  $ rnorm / ((anorm * xnorm + bnorm) * n * eps)
95 
96  IF ((rnorm > 60.0).AND.( info < 0 )) THEN
97  WRITE(*,*) "-- Error in SGESV example !"
98  ELSE
99  WRITE(*,*) "-- Run of SGESV example successful !"
100  ENDIF
101 
102 *
103 * Deallocate l and ipiv
104 *
105  CALL plasma_dealloc_handle( hl, info )
106  CALL plasma_dealloc_handle( hpiv, info )
107 *
108 * finalize plasma
109 *
110  CALL plasma_finalize( info )
111 *
112 * End of example_sgesv.
113 *
114  END PROGRAM example_sgesv_f