37
38
39
42 USE python_funct_mod, ONLY : funct_python_nsamples
44
45
46
47#include "implicit_f.inc"
48
49
50
51 INTEGER NFUNCT, NTABLE, NPTS
52 TYPE(SUBMODEL_DATA), DIMENSION(NSUBMOD), INTENT(IN) :: LSUBMODEL
53
54
55
56
57
58
59 INTEGER I,ID,NPARAM,NPT,NFUNCT0,NTABLE0,NTABLE1
60 CHARACTER(LEN=NCHARTITLE) :: TITR
61 CHARACTER :: KEY*20,MESS*40
62 DATA mess/' FUNCTION COUNTING '/
63 INTEGER :: IFUN,N1
64 INTEGER :: IPYTHON
65 LOGICAL :: IS_AVAILABLE
66
67
68
69 nfunct0 = 0
71 npts = 0
72 ntable = 0
73 IF (nfunct0 > 0) THEN
75 DO ifun = 1, nfunct0
77 . keyword1 = key)
78 ipython = 0
79 IF(key(6:12) == '_PYTHON') ipython = 1
80 IF( ipython == 0 ) THEN
81 ntable = ntable + 1
82 CALL hm_get_intv(
'numberofpoints', npt, is_available, lsubmodel)
83 npts = npts + npt
84 ELSE
85 ntable = ntable + 1
86 npts = npts + funct_python_nsamples
87 ENDIF
88 ENDDO
89 ENDIF
90
91
92 nfunct = nfunct0
93
94
95
98
99
100
101
102 IF (ntable0 > 0) THEN
104 DO i = 1, ntable0
107 . option_titr = titr)
108 CALL hm_get_intv(
'ORDER', nparam, is_available, lsubmodel)
109 IF (nparam == 1) THEN
110 CALL hm_get_intv(
'N1', n1, is_available, lsubmodel)
111 npts = npts + n1
112 nfunct=nfunct+1
113 ENDIF
114 ENDDO
115 ENDIF
116
117
118 IF (ntable1 > 0) THEN
120 DO i = 1, ntable1
123 . option_titr = titr)
124 CALL hm_get_intv(
'ORDER', nparam, is_available, lsubmodel)
125 IF (nparam == 1) THEN
126 CALL hm_get_intv(
'curverows', n1, is_available, lsubmodel)
127 npts = npts + n1
128 nfunct=nfunct+1
129 ENDIF
130 ENDDO
131 ENDIF
132 ntable=ntable+ntable1 + ntable0
133
134
135
136
137
138
139
140 npts=2*npts
141
142 RETURN
143
subroutine hm_get_intv(name, ival, is_available, lsubmodel)
subroutine hm_option_count(entity_type, hm_option_number)
subroutine hm_option_start(entity_type)
integer, parameter nchartitle