source: CPL/oasis3/trunk/src/mod/oasis3/src/blasold.f @ 1677

Last change on this file since 1677 was 1677, checked in by aclsce, 12 years ago

Imported oasis3 (tag ipslcm5a) from cvs server to svn server (igcmg project).

File size: 4.3 KB
Line 
1      SUBROUTINE blasold (pfild ,kmsize, kfield, pmcoeff, kaux, kaddr,
2     $                    kasize, pacoeff, ksiztot, paux)
3C****
4C               *****************************
5C               * OASIS ROUTINE  -  LEVEL 3 *
6C               * -------------     ------- *
7C               *****************************
8C
9C**** *blasold* - Stupid blas routine
10C
11C     Purpose:
12C     -------
13C     Do linear combination of fields with given coefficients
14C     before interpolation
15C
16C**   Interface:
17C     ---------
18C       *CALL*  *blasold (pfild ,kmsize, kfield, pmcoeff, kaux, kaddr,
19C                         kasize, pacoeff, ksiztot, paux)*
20C
21C     Input:
22C     -----
23C                pfild   : field array to be modified (real 1D)
24C                kmsize  : size of the field array (integer)
25C                kfield  : field identificator number (integer)
26C                pmcoeff : field multiplicative coefficient (real)
27C                kaux    : number of combined auxilary fields (integer)
28C                kaddr   : pointer for auxilary fields (integer 1D)
29C                kasize  : size of auxilary fields (integer 1D)
30C                pacoeff : auxilary field multiplicative coefficient (real 1D)
31C                ksiztot : total size of work memory used (integer)
32C                paux    : global work array (real 1D)
33C
34C     Output:
35C     ------
36C                pfild   : new field array (real 1D)
37C
38C     Workspace:
39C     ---------
40C     None
41C
42C     Externals:
43C     ---------
44C     None
45C
46C     Reference:
47C     ---------
48C     See OASIS manual (1995)
49C
50C     History:
51C     -------
52C       Version   Programmer     Date      Description
53C       -------   ----------     ----      ----------- 
54C       2.0       L. Terray      95/10/01  created
55C       2.3       S. Valcke      99/04/30  added: printing levels
56C
57C %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
58C
59C* ---------------------------- Include files ---------------------------
60C
61      USE mod_kinds_oasis
62      USE mod_unit
63      USE mod_printing
64C
65C* ---------------------------- Argument declarations -------------------
66C
67      REAL (kind=ip_realwp_p) pfild(kmsize)
68      REAL (kind=ip_realwp_p) paux(ksiztot), pacoeff(kaux)
69      INTEGER (kind=ip_intwp_p) kaddr(kaux), kasize(kaux)
70C
71C* ---------------------------- Local declarations ----------------------
72C
73      INTEGER (kind=ip_intwp_p) istop
74      LOGICAL llchk
75C
76C* ---------------------------- Poema verses ----------------------------
77C
78C %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
79C
80C*    1. Initialization
81C        --------------
82C
83      IF (nlogprt .GE. 2) THEN
84          WRITE (UNIT = nulou,FMT = *) ' '
85          WRITE (UNIT = nulou,FMT = *) ' '
86          WRITE (UNIT = nulou,FMT = *) 
87     $    '           ROUTINE blasold  -  Level 3'
88          WRITE (UNIT = nulou,FMT = *) 
89     $    '           ***************     *******'
90          WRITE (UNIT = nulou,FMT = *) ' '
91          WRITE (UNIT = nulou,FMT = *) 
92     $    ' Do linear combination of fields'
93          WRITE (UNIT = nulou,FMT = *) ' '
94          WRITE (UNIT = nulou,FMT = *) ' '
95      ENDIF
96      istop = 0
97C
98C* Check all fields have same dimensions as current field
99C
100      DO 110 jc = 1, kaux
101        llchk = (kasize(jc) - kmsize) .EQ. 0
102        IF (.NOT. llchk) THEN
103            CALL prtout ('WARNING!!!
104     $          Pb in combining field number =', kfield, 2)
105            CALL prtout ('Different size for auxilary field number =',
106     $          jc, 2)
107            istop = istop + 1
108        ENDIF
109 110  CONTINUE
110      IF (istop .GT. 0) CALL HALTE('STOP in blasold')
111C
112C
113C*    2. Linear combination
114C        ------------------
115C
116C* Multiply current field by main coefficient
117C
118      DO 210 ja = 1, kmsize
119        pfild(ja) = pmcoeff * pfild(ja)
120 210  CONTINUE
121C
122C* Combine with other fields if required
123C
124      IF (kaux .GE. 1) THEN
125          DO 220 jc = 1, kaux
126            DO 230 ja = 1, kmsize
127              pfild(ja) = pfild(ja) + pacoeff(jc) *
128     $                    paux(kaddr(jc)+ja-1)
129 230        CONTINUE
130 220      CONTINUE
131      ENDIF
132C
133C
134C*    3. End of routine
135C        --------------
136C
137      IF (nlogprt .GE. 2) THEN
138          WRITE (UNIT = nulou,FMT = *) ' '
139          WRITE (UNIT = nulou,FMT = *) 
140     $    '--------- End of routine blasold ---------'
141          CALL FLUSH (nulou)
142      ENDIF
143      RETURN
144      END
Note: See TracBrowser for help on using the repository browser.