44 . NOM_OPT ,FUNCRYPT ,UNITAB ,LSUBMODEL)
57#include
"implicit_f.inc"
66 INTEGER NFUNCT, NPTS_ALLOC
67 INTEGER NPC(*),FUNCRYPT(*)
70 INTEGER NOM_OPT(LNOPT1,*)
71 TYPE(
submodel_data),
DIMENSION(NSUBMOD),
INTENT(IN) :: LSUBMODEL
76 INTEGER I,,L,FUNC_ID,NPTS,STAT,N,II,ISMOOTH
79 my_real xscale,yscale,xshift,yshift
80 CHARACTER(LEN=NCHARTITLE) :: TITR
81 CHARACTER MESS*40,KEY*20
82 DATA mess/
' FUNCTION & TABLES DEFINITION '/
83 LOGICAL :: IS_ENCRYPTED, IS_AVAILABLE
84 INTEGER :: NB_FUNCT, NB_FUNCT_SMOOTH, IPT, NPT
88 IF (nfunct == 0)
RETURN
92 WRITE (iout,2000) nfunct
95 is_encrypted = .false.
96 is_available = .false.
105 IF (nb_funct > 0)
THEN
110 . option_titr = titr,
111 . option_id = func_id,
116 IF(key(6:12) ==
'_SMOOTH') ismooth = 1
117 IF(key(6:12) ==
'_PYTHON') ipython = 1
119 IF(ismooth == 0 .AND. ipython == 0 )
THEN
122 CALL fretitl(titr,nom_opt(lnopt1-ltitr+1,l),ltitr)
123 nom_opt(1, l) = func_id
124 npc(nfunct + l + 1) = func_id
125 npc(2 * nfunct + l + 1) = ismooth
128 WRITE(iout, 2100) func_id
130 CALL hm_get_intv(
'numberofpoints', npt, is_available, lsubmodel)
135 IF (.NOT. is_encrypted)
THEN
136 WRITE(iout,
'(3X,1PG20.13,2X,1G20.13)') time,funct
139 pld(npc(l + 1)) = time
141 IF (pld(npc(l+1)) <= pld(npc(l+1)-2))
THEN
143 CALL ancmsg(msgid = 156, msgtype = msgerror, anmode = aninfo_blind_1,
144 . i1 = func_id, c1 = titr, i2 = npts, i3 = npts-1)
147 npc(l + 1) = npc(l + 1) + 1
148 pld(npc(l + 1)) = funct
149 npc(l + 1) = npc(l + 1) + 1
153 CALL ancmsg(msgid=1874, msgtype=msgwarning, anmode=aninfo_blind_1,
159 table(l)%NOTABLE=func_id
162 ALLOCATE(table(l)%X(1),stat=stat)
163 IF (stat /= 0)
CALL ancmsg(msgid=268,anmode=aninfo,
166 ALLOCATE(table(l)%X(1)%VALUES(npts),stat=stat)
167 IF (stat /= 0)
CALL ancmsg(msgid=268,anmode=aninfo,
170 ALLOCATE(table(l)%Y,stat=stat)
171 IF (stat /= 0)
CALL ancmsg(msgid=268,anmode=aninfo,
174 ALLOCATE(table(l)%Y%VALUES(npts),stat=stat)
175 IF (stat /= 0)
CALL ancmsg(msgid=268,anmode=aninfo,
180 table(l)%X(1)%VALUES(n)=pld(npc(l)+2*n-2)
181 table(l)%Y%VALUES(n) =pld(npc(l)+2*n-1)
183 IF (is_encrypted)
THEN
184 WRITE(iout,
'(A)')
'CONFIDENTIAL DATA'
193 IF (nb_funct_smooth > 0)
THEN
195 DO i = 1, nb_funct_smooth
198 . option_titr = titr,
199 . option_id = func_id,
205 CALL fretitl(titr,nom_opt(lnopt1-ltitr
206 nom_opt(1, l) = func_id
207 npc(nfunct + l + 1) = func_id
208 npc(2 * nfunct + l + 1) = ismooth
211 WRITE(iout, 2200) func_id
213 CALL hm_get_floatv(
'A_SCALE_X' ,xscale ,is_available ,lsubmodel ,unitab)
214 CALL hm_get_floatv(
'F_SCALE_Y' ,yscale ,is_available ,lsubmodel ,unitab)
215 CALL hm_get_floatv(
'A_SHIFT_X' ,xshift ,is_available ,lsubmodel ,unitab)
216 CALL hm_get_floatv(
'F_SHIFT_Y' ,yshift ,is_available ,lsubmodel ,unitab)
217 IF (xscale == zero) xscale = one
218 IF (yscale == zero) yscale = one
221 IF (.NOT. is_encrypted)
222 .
WRITE(iout,
'(3X,1PG20.13,3(2X,1G20.13))') xscale,yscale,xshift,yshift
226 CALL hm_get_intv(
'numberofpoints', npt, is_available, lsubmodel)
232 time = time * xscale + xshift
233 funct = funct * yscale + yshift
235 IF (.NOT. is_encrypted)
THEN
236 WRITE(iout,
'(3X,1PG20.13,2X,1G20.13)') time,funct
239 pld(npc(l + 1)) = time
241 IF (pld(npc(l+1)) <= pld(npc(l+1)-2))
THEN
243 CALL ancmsg(msgid = 156, msgtype = msgerror, anmode = aninfo_blind_1,
244 . i1 = func_id, c1 = titr, i2 = npts, i3 = npts-1)
247 npc(l + 1) = npc(l + 1) + 1
249 npc(l + 1) = npc(l + 1) + 1
253 CALL ancmsg(msgid=1874, msgtype
259 table(l)%NOTABLE=func_id
262 ALLOCATE(table(l)%X(1),stat=stat)
263 IF (stat /= 0)
CALL ancmsg(msgid=268,anmode=aninfo,
266 ALLOCATE(table(l)%X(1)%VALUES(npts),stat=stat)
267 IF (stat /= 0)
CALL ancmsg(msgid=268,anmode=aninfo,
270 ALLOCATE(table(l)%Y,stat=stat)
271 IF (stat /= 0)
CALL ancmsg(msgid=268,anmode=aninfo,
274 ALLOCATE(table(l)%Y%VALUES(npts),stat=stat)
275 IF (stat /= 0)
CALL ancmsg(msgid=268,anmode=aninfo,
280 table(l)%X(1)%VALUES(n)=pld(npc(l)+2*n-2)
281 table(l)%Y%VALUES(n) =pld(npc(l)+2*n-1)
283 IF (is_encrypted)
THEN
284 WRITE(iout,
'(A)')
'CONFIDENTIAL DATA'
296 .
' NUMBER OF LOAD CURVES. . . . . . . . =',i10/)
2972100
FORMAT(/
' LOAD CURVE ID . . . . . . . . . . . =',i10//
2992200
FORMAT(/
' LOAD SMOOTH CURVE ID . . . . . . . =',i10)
3002300
FORMAT(/
' XSCALE YSCALE XSHIFT
subroutine ancmsg(msgid, msgtype, anmode, i1, i2, i3, i4, i5, i6, i7, i8, i9, i10, i11, i12, i13, i14, i15, i16, i17, i18, i19, i20, r1, r2, r3, r4, r5, r6, r7, r8, r9, c1, c2, c3, c4, c5, c6, c7, c8, c9, prmode)