AS_Basic_CASL.der.hs revision 330b955a293fdc64e9145a159b2f2faec1f8011e
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
{- |
Module : $Header$
Copyright : (c) Klaus L�ttich, Christian Maeder, Uni Bremen 2002-2004
Licence : similar to LGPL, see HetCATS/LICENCE.txt or LIZENZ.txt
Maintainer : hets@tzi.de
Stability : provisional
Portability : portable
This is the Abstract Syntax tree of CASL Basic_specs, Symb_items and
Symb_map_items.
Follows Sect. II:2.2 of the CASL Reference Manual.
-}
module CASL.AS_Basic_CASL where
import Common.Id
import Common.AS_Annotation
import Data.List (nub)
-- DrIFT command
{-! global: UpPos !-}
data BASIC_SPEC b s f = Basic_spec [Annoted (BASIC_ITEMS b s f)]
deriving (Show,Eq)
data BASIC_ITEMS b s f = Sig_items (SIG_ITEMS b s f)
-- the Annotation following the keyword is dropped
-- but preceding the keyword is now an Annotation allowed
| Free_datatype [Annoted DATATYPE_DECL] [Pos]
-- pos: free, type, semi colons
| Sort_gen [Annoted (SIG_ITEMS b s f)] [Pos]
-- pos: generated, opt. braces
| Var_items [VAR_DECL] [Pos]
-- pos: var, semi colons
| Local_var_axioms [VAR_DECL] [Annoted (FORMULA f)] [Pos]
-- pos: forall, semi colons, dots
| Axiom_items [Annoted (FORMULA f)] [Pos]
-- pos: dots
| Ext_BASIC_ITEMS b
deriving (Show,Eq)
data SIG_ITEMS b s f = Sort_items [Annoted (SORT_ITEM f)] [Pos]
-- pos: sort, semi colons
| Op_items [Annoted (OP_ITEM f)] [Pos]
-- pos: op, semi colons
| Pred_items [Annoted (PRED_ITEM f)] [Pos]
-- pos: pred, semi colons
| Datatype_items [Annoted DATATYPE_DECL] [Pos]
-- type, semi colons
| Ext_SIG_ITEMS s
deriving (Show,Eq)
data SORT_ITEM f = Sort_decl [SORT] [Pos]
-- pos: commas
| Subsort_decl [SORT] SORT [Pos]
-- pos: commas, <
| Subsort_defn SORT VAR SORT (Annoted (FORMULA f)) [Pos]
-- pos: "=", "{", ":", ".", "}"
-- the left anno list stored in Annoted Formula is
-- parsed after the equal sign
| Iso_decl [SORT] [Pos]
-- pos: "="s
deriving (Show,Eq)
data OP_ITEM f = Op_decl [OP_NAME] OP_TYPE [OP_ATTR f] [Pos]
-- pos: commas, colon, OP_ATTR sep. by commas
| Op_defn OP_NAME OP_HEAD (Annoted (TERM f)) [Pos]
-- pos: "="
deriving (Show,Eq)
data OP_TYPE = Total_op_type [SORT] SORT [Pos]
-- pos: "*"s, "->" ; if null [SORT] then [Pos] = []
| Partial_op_type [SORT] SORT [Pos]
-- pos: "*"s, "->?"; if null [SORT] then pos: "?"
deriving (Show,Eq,Ord)
args_OP_TYPE :: OP_TYPE -> [SORT]
args_OP_TYPE (Total_op_type args _ _) = args
args_OP_TYPE (Partial_op_type args _ _) = args
res_OP_TYPE :: OP_TYPE -> SORT
res_OP_TYPE (Total_op_type _ res _) = res
res_OP_TYPE (Partial_op_type _ res _) = res
data OP_HEAD = Total_op_head [ARG_DECL] SORT [Pos]
-- pos: "(", semicolons, ")", colon
| Partial_op_head [ARG_DECL] SORT [Pos]
deriving (Show,Eq)
data ARG_DECL = Arg_decl [VAR] SORT [Pos]
-- pos: commas, colon
deriving (Show,Eq)
data OP_ATTR f = Assoc_op_attr | Comm_op_attr | Idem_op_attr
| Unit_op_attr (TERM f)
deriving (Show,Eq)
data PRED_ITEM f = Pred_decl [PRED_NAME] PRED_TYPE [Pos]
-- pos: commas, colon
| Pred_defn PRED_NAME PRED_HEAD (Annoted (FORMULA f)) [Pos]
-- pos: "<=>"
deriving (Show,Eq)
data PRED_TYPE = Pred_type [SORT] [Pos]
-- pos: if null [SORT] then "(",")" else "*"s
deriving (Show,Eq,Ord)
data PRED_HEAD = Pred_head [ARG_DECL] [Pos]
-- pos: "(",semi colons , ")"
deriving (Show,Eq)
data DATATYPE_DECL = Datatype_decl SORT [Annoted ALTERNATIVE] [Pos]
-- pos: "::=", "|"s
deriving (Show,Eq)
data ALTERNATIVE = Total_construct OP_NAME [COMPONENTS] [Pos]
-- pos: "(", semi colons, ")"
| Partial_construct OP_NAME [COMPONENTS] [Pos]
-- pos: "(", semi colons, ")", "?"
| Subsorts [SORT] [Pos]
-- pos: sort, commas
deriving (Show,Eq)
data COMPONENTS = Total_select [OP_NAME] SORT [Pos]
-- pos: commas, colon
| Partial_select [OP_NAME] SORT [Pos]
-- pos: commas, ":?"
| Sort SORT
deriving (Show,Eq)
data VAR_DECL = Var_decl [VAR] SORT [Pos]
-- pos: commas, colon
deriving (Show,Eq,Ord)
{- Position definition for FORMULA:
Information on parens are also encoded in [Pos]. If there
are more Pos than necessary there is a pair of Pos enclosing the
other Pos informations which encode the brackets of every kind
-}
data FORMULA f = Quantification QUANTIFIER [VAR_DECL] (FORMULA f) [Pos]
-- pos: QUANTIFIER, semi colons, dot
| Conjunction [FORMULA f] [Pos]
-- pos: "/\"s
| Disjunction [FORMULA f] [Pos]
-- pos: "\/"s
| Implication (FORMULA f) (FORMULA f) Bool [Pos]
-- pos: "=>" or "if" (True -> "=>")
| Equivalence (FORMULA f) (FORMULA f) [Pos]
-- pos: "<=>"
| Negation (FORMULA f) [Pos]
-- pos: not
| True_atom [Pos]
-- pos: true
| False_atom [Pos]
-- pos: false
| Predication PRED_SYMB [TERM f] [Pos]
-- pos: opt. "(",commas,")"
| Definedness (TERM f) [Pos]
-- pos: def
| Existl_equation (TERM f) (TERM f) [Pos]
-- pos: =e=
| Strong_equation (TERM f) (TERM f) [Pos]
-- pos: =
| Membership (TERM f) SORT [Pos]
-- pos: in
| Mixfix_formula (TERM f) -- Mixfix_ Term/Token/(..)/[..]/{..}
-- a formula left original for mixfix analysis
| Unparsed_formula String [Pos]
-- pos: first Char in String
| Sort_gen_ax [Constraint]
| ExtFORMULA f
-- needed for CASL extensions
deriving (Show,Eq,Ord)
{- In the CASL institution, sort generation constraints have an
additional signature morphism component (Sect. III:2.1.3, p.134 of the
CASL Reference Manual). The extra signature morphism component is
needed because the naive translation of sort generation constraints
along signature morphisms may violate the satisfaction condition,
namely when sorts are identified by the translation, with the effect
that new terms can be formed. We avoid this extra component here and
instead use natural numbers to decorate sorts, in this way retaining
their identity w.r.t. the original signature. The newSort in a
Constraint is implicitly decorated with its index in the list of
Constraints. The opSymbs component collects all the operation symbols
with newSort (with that index!) as a result sort. The argument sorts
of an operation symbol are decorated explicitly via a list [Int] of
integers. The origSort in a Constraint is the original sort
corresponding to the index. Note that this representation of sort
generation constraints is efficiently tailored towards both the use in
the proof calculus (Chap. IV:2, p. 282 of the CASL Reference Manual)
and the coding into second order logic (p. 429 of Theoret. Comp. Sci. 286).
-}
data Constraint = Constraint { newSort :: SORT,
opSymbs :: [(OP_SYMB,[Int])],
origSort :: SORT }
deriving (Show,Eq,Ord)
-- | from a Sort_gex_ax, recover:
-- | a traditional sort generation constraint plus a sort mapping
recover_Sort_gen_ax :: [Constraint] ->
([SORT],[OP_SYMB],[(SORT,SORT)])
recover_Sort_gen_ax constrs =
if length (nub sorts) == length sorts
-- no duplicate sorts, i.e. injective sort map? Then we can ignore indices
then (sorts,map fst (concat (map opSymbs constrs)),[])
-- otherwise, we have to introduce new sorts for the indices
-- and afterwards rename them into the sorts they denote
else (map indSort1 indices,map indOp indOps1,map sortMap indSorts)
where
sorts = map newSort constrs
indices = [0..length sorts-1]
indSorts = zip indices sorts
indSort (i,s) = if i<0 then s else indSort1 i
indSort1 i = origSort $ head (drop i constrs)
sortMap (i,s) = (indSort1 i,s)
indOps = zip indices (map opSymbs constrs)
indOps1 = concat (map (\(i,ops) -> map ((,) i) ops) indOps)
indOp (res,(Qual_op_name on (Total_op_type args1 res1 pos1) pos,args)) =
Qual_op_name on
(Total_op_type (map indSort (zip args args1))
(indSort (res,res1)) pos1) pos
indOp (res,(Qual_op_name on (Partial_op_type args1 res1 pos1) pos,args)) =
Qual_op_name on
(Partial_op_type (map indSort (zip args args1))
(indSort (res,res1)) pos1) pos
indOp _ = error
"CASL/AS_Basic_CASL: Internal error: Unqualified OP_SYMB in Sort_gen_ax"
data QUANTIFIER = Universal | Existential | Unique_existential
deriving (Show,Eq,Ord)
data PRED_SYMB = Pred_name PRED_NAME
| Qual_pred_name PRED_NAME PRED_TYPE [Pos]
-- pos: "(", pred, colon, ")"
deriving (Show,Eq,Ord)
data TERM f = Simple_id SIMPLE_ID -- "Var" might be a better constructor
| Qual_var VAR SORT [Pos]
-- pos: "(", var, colon, ")"
| Application OP_SYMB [TERM f] [Pos]
-- pos: parens around TERM f if any and seperating commas
| Sorted_term (TERM f) SORT [Pos]
-- pos: colon
| Cast (TERM f) SORT [Pos]
-- pos: "as"
| Conditional (TERM f) (FORMULA f) (TERM f) [Pos]
-- pos: "when", "else"
| Unparsed_term String [Pos] -- SML-CATS
-- A new intermediate state
| Mixfix_qual_pred PRED_SYMB -- as part of a mixfix formula
| Mixfix_term [TERM f] -- not starting with Mixfix_sorted_term/cast
| Mixfix_token Token -- NO-BRACKET-TOKEN, LITERAL, PLACE
| Mixfix_sorted_term SORT [Pos]
-- pos: colon
| Mixfix_cast SORT [Pos]
-- pos: "as"
| Mixfix_parenthesized [TERM f] [Pos] -- non-emtpy term list
-- pos: "(", commas, ")"
| Mixfix_bracketed [TERM f] [Pos]
-- pos: "[", commas, "]"
| Mixfix_braced [TERM f] [Pos] -- also for list-notation
-- pos: "{", "}"
deriving (Show,Eq,Ord)
data OP_SYMB = Op_name OP_NAME
| Qual_op_name OP_NAME OP_TYPE [Pos]
-- pos: "(", op, colon, ")"
deriving (Show,Eq,Ord)
type OP_NAME = Id
type PRED_NAME = Id
type SORT = Id
type VAR = SIMPLE_ID
-----
data SYMB_ITEMS = Symb_items SYMB_KIND [SYMB] [Pos]
-- pos: SYMB_KIND, commas
deriving (Show,Eq)
data SYMB_ITEMS_LIST = Symb_items_list [SYMB_ITEMS] [Pos]
-- pos: commas
deriving (Show,Eq)
data SYMB_MAP_ITEMS = Symb_map_items SYMB_KIND [SYMB_OR_MAP] [Pos]
-- pos: SYMB_KIND, commas
deriving (Show,Eq)
data SYMB_MAP_ITEMS_LIST = Symb_map_items_list [SYMB_MAP_ITEMS] [Pos]
-- pos: commas
deriving (Show,Eq)
data SYMB_KIND = Implicit | Sorts_kind
| Ops_kind | Preds_kind
deriving (Show,Eq)
data SYMB = Symb_id Id
| Qual_id Id TYPE [Pos]
-- pos: colon
deriving (Show,Eq)
data TYPE = O_type OP_TYPE
| P_type PRED_TYPE
| A_type SORT -- ambiguous pred or (constant total) op
deriving (Show,Eq)
data SYMB_OR_MAP = Symb SYMB
| Symb_map SYMB SYMB [Pos]
-- pos: "|->"
deriving (Show,Eq)