@@ -40134,6 +40134,199 @@ else if ("*".equals(suf))
4013440134 return alternatives;
4013540135 }
4013640136
40137+ public Vector cobolDataDefinitions(java.util.Map context)
40138+ { // Each non-filler item at level > 01 becomes an attribute
40139+ // of a relevant container. If composite (no picture),
40140+ // it also becomes a class & container in turn.
40141+
40142+ Vector res = new Vector();
40143+
40144+ if ("compilationUnit".equals(tag))
40145+ { for (int i = 0; i < terms.size(); i++)
40146+ { ASTTerm tt = (ASTTerm) terms.get(i);
40147+ Vector ttres = tt.cobolDataDefinitions(context);
40148+ res.addAll(ttres);
40149+ }
40150+ return res;
40151+ }
40152+
40153+ if ("programUnit".equals(tag))
40154+ { for (int i = 0; i < terms.size(); i++)
40155+ { ASTTerm tt = (ASTTerm) terms.get(i);
40156+ Vector ttres = tt.cobolDataDefinitions(context);
40157+ res.addAll(ttres);
40158+ }
40159+ return res;
40160+ }
40161+
40162+ if ("dataDivision".equals(tag))
40163+ { // DATA DIVISION . dataDivisionSection*
40164+
40165+ for (int i = 3; i < terms.size(); i++)
40166+ { ASTTerm tt = (ASTTerm) terms.get(i);
40167+ Vector ttres = tt.cobolDataDefinitions(context);
40168+ res.addAll(ttres);
40169+ }
40170+ return res;
40171+ }
40172+
40173+ if ("dataDivisionSection".equals(tag))
40174+ { // fileSection | dataBaseSection |
40175+ // workingStorageSection | linkageSection | ...
40176+
40177+ ASTTerm tt = (ASTTerm) terms.get(0);
40178+ Vector ttres = tt.cobolDataDefinitions(context);
40179+ return ttres;
40180+ }
40181+
40182+ if ("workingStorageSection".equals(tag))
40183+ { // WORKING-STORAGE SECTION . dataDescriptionEntry*
40184+
40185+ for (int i = 3; i < terms.size(); i++)
40186+ { ASTTerm tt = (ASTTerm) terms.get(i);
40187+ Vector ttres = tt.cobolDataDefinitions(context);
40188+ res.addAll(ttres);
40189+ }
40190+ return res;
40191+ }
40192+
40193+ if ("dataDescriptionEntry".equals(tag))
40194+ { // dataDescriptionEntryFormat1 |
40195+ // dataDescriptionEntryFormat2 |
40196+ // dataDescriptionEntryFormat3 |
40197+ // dataDescriptionEntryExecSql
40198+
40199+ ASTTerm tt = (ASTTerm) terms.get(0);
40200+ Vector ttres = tt.cobolDataDefinitions(context);
40201+ return ttres;
40202+ }
40203+
40204+ if ("dataDescriptionEntryFormat1".equals(tag))
40205+ { // Level (FILLER | dataName)? dataClause* .
40206+
40207+ // If preceding item at lower or same levelnumber,
40208+ // container != null and this is attribute of
40209+ // container or padding (FILLER).
40210+ // If preceding item at higher levelnumber, or no
40211+ // preceding item (container = null), this is
40212+ // a new container class.
40213+
40214+ ASTTerm tt = (ASTTerm) terms.get(0);
40215+ String level = tt.literalForm();
40216+ int levelNumber = 0;
40217+ String fieldName = "";
40218+
40219+ if ("77".equals(level))
40220+ { context.put("container", null);
40221+ return res;
40222+ }
40223+
40224+ try
40225+ { levelNumber = Integer.parseInt(level); }
40226+ catch (Exception ex) { return res; }
40227+
40228+ if (terms.size() == 1)
40229+ { return res; }
40230+
40231+ ASTTerm t2 = (ASTTerm) terms.get(1);
40232+ if ("FILLER".equals(t2 + "") ||
40233+ t2.getTag().equals("dataName"))
40234+ { fieldName = t2.literalForm(); }
40235+ else
40236+ { fieldName = "FILLER"; }
40237+
40238+ Entity container = (Entity) context.get("container");
40239+
40240+ if (ASTTerm.hasTag(terms,"dataPictureClause"))
40241+ { // It is a basic item, not an entity
40242+ if (container == null) // no container, so top-level attribute
40243+ { if ("FILLER".equals(fieldName)) { }
40244+ else
40245+ { Attribute att =
40246+ new Attribute(fieldName, new Type("String", null),
40247+ ModelElement.INTERNAL);
40248+ res.add(att);
40249+
40250+ context.put("previousLevel", new Integer(levelNumber));
40251+ }
40252+ }
40253+ else // basic attribute of some container
40254+ { int contLevel = container.levelNumber;
40255+
40256+ Integer previousLevel = (Integer) context.get("previousLevel");
40257+
40258+ int prevLevel = previousLevel.intValue();
40259+
40260+ if (levelNumber >= prevLevel)
40261+ { // attribute of container
40262+ if ("FILLER".equals(fieldName)) {}
40263+ else
40264+ { Attribute att =
40265+ new Attribute(fieldName, new Type("String", null),
40266+ ModelElement.INTERNAL);
40267+ container.addAttribute(att);
40268+ } // could itself be composite
40269+ context.put("previousLevel",
40270+ new Integer(levelNumber));
40271+ }
40272+ else if (levelNumber < prevLevel)
40273+ { // attribute of another container
40274+ if ("FILLER".equals(fieldName)) {}
40275+ else
40276+ { Attribute att =
40277+ new Attribute(fieldName, new Type("String", null),
40278+ ModelElement.INTERNAL);
40279+ Entity actualContainer =
40280+ container.findContainer(levelNumber);
40281+ if (actualContainer != null)
40282+ { actualContainer.addAttribute(att);
40283+ context.put("container", actualContainer);
40284+ }
40285+ } // could itself be composite
40286+ context.put("previousLevel",
40287+ new Integer(levelNumber));
40288+ }
40289+ }
40290+ }
40291+ else // No PICTURE => new entity
40292+ { if ("FILLER".equals(fieldName)) {}
40293+ else
40294+ { Entity newent = new Entity(fieldName + "_Class");
40295+ newent.levelNumber = levelNumber;
40296+ Attribute att =
40297+ new Attribute(fieldName, new Type(newent),
40298+ ModelElement.INTERNAL);
40299+
40300+ Integer previousLevel = (Integer) context.get("previousLevel");
40301+
40302+ int prevLevel = -1;
40303+ if (previousLevel != null)
40304+ { prevLevel = previousLevel.intValue(); }
40305+
40306+ res.add(newent);
40307+ if (container == null) // top-level
40308+ { res.add(att); }
40309+ else if (levelNumber >= prevLevel)
40310+ { newent.container = container;
40311+ container.addAttribute(att);
40312+ }
40313+ else
40314+ { Entity actualContainer =
40315+ container.findContainer(levelNumber);
40316+ if (actualContainer != null)
40317+ { newent.container = actualContainer;
40318+ actualContainer.addAttribute(att);
40319+ }
40320+ }
40321+
40322+ context.put("container", newent);
40323+ context.put("previousLevel", new Integer(levelNumber));
40324+ }
40325+ }
40326+ }
40327+
40328+ return res;
40329+ }
4013740330
4013840331 public static void convertAntlr2CSTL()
4013940332 { // Testing of JS to KM3
0 commit comments