48
49
50
56
57
58
59#include "implicit_f.inc"
60#include "tablen_c.inc"
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77 TYPE (UNIT_TYPE_),INTENT(IN) ::UNITAB
78 INTEGER ,NUVAR,IUNIT
80 INTEGER ID, IGTYP
81 CHARACTER(LEN=NCHARTITLE) :: TITR
82 TYPE(PROP_TAG_) , DIMENSION(0:MAXPROP) :: PROP_TAG
83 TYPE(SUBMODEL_DATA),INTENT(IN)::LSUBMODEL(*)
84
85
86
87 INTEGER ITYP,SKFLAG
88 LOGICAL IS_AVAILABLE, IS_ENCRYPTED
89
90
91
93
94
95
96 CALL hm_get_intv(
'type',ityp,is_available,lsubmodel)
97 CALL hm_get_intv(
'SkewFlag',skflag,is_available,lsubmodel)
98
99
100 nuvar = 39
101
102 IF (ityp==1) THEN
105 ELSEIF (ityp==2) THEN
108 ELSEIF (ityp==3) THEN
111 ELSEIF (ityp==4) THEN
114 ELSEIF (ityp==5) THEN
117 ELSEIF (ityp==6) THEN
120 ELSEIF (ityp==7) THEN
123 ELSEIF (ityp==8) THEN
126 ELSEIF (ityp==9) THEN
129 ELSE
130
132 . msgtype=msgerror,
133 . anmode=aninfo_blind_2,
135 . c1=titr,
136 . i2=ityp)
137 END IF
138
139 prop_tag(igtyp)%G_EINT = 1
140 prop_tag(igtyp)%G_FOR = 3
141 prop_tag(igtyp)%G_MOM = 3
142 prop_tag(igtyp)%G_TOTDEPL = 3
143 prop_tag(igtyp)%G_TOTROT = 3
144 prop_tag(igtyp)%G_SKEW = 3
145 prop_tag(igtyp)%G_MASS = 1
146 prop_tag(igtyp)%G_NUVAR = nuvar
147 prop_tag(igtyp)%G_LENGTH_ERR = 3
148
149 RETURN
subroutine hm_get_intv(name, ival, is_available, lsubmodel)
subroutine hm_option_is_encrypted(is_encrypted)
subroutine hm_read_prop33_cyl_jnt(iout, ityp, skflag, pargeo, is_encrypted, unitab, iunit, id, titr, lsubmodel)
subroutine hm_read_prop33_fix_jnt(iout, ityp, skflag, pargeo, is_encrypted, unitab, iunit, id, titr, lsubmodel)
subroutine hm_read_prop33_free_jnt(iout, ityp, skflag, pargeo, is_encrypted, unitab, iunit, id, titr, lsubmodel)
subroutine hm_read_prop33_old_jnt(iout, ityp, skflag, pargeo, is_encrypted, unitab, iunit, id, titr, lsubmodel)
subroutine hm_read_prop33_plan_jnt(iout, ityp, skflag, pargeo, is_encrypted, unitab, iunit, id, titr, lsubmodel)
subroutine hm_read_prop33_rev_jnt(iout, ityp, skflag, pargeo, is_encrypted, unitab, iunit, id, titr, lsubmodel)
subroutine hm_read_prop33_sph_jnt(iout, ityp, skflag, pargeo, is_encrypted, unitab, iunit, id, titr, lsubmodel)
subroutine hm_read_prop33_trans_jnt(iout, ityp, skflag, pargeo, is_encrypted, unitab, iunit, id, titr, lsubmodel)
subroutine hm_read_prop33_univ_jnt(iout, ityp, pargeo, is_encrypted, unitab, iunit, id, titr, lsubmodel)
integer, parameter nchartitle
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)