Skip to content

Commit

Permalink
Merge remote-tracking branch 'origin/master' into sequence-invertibility
Browse files Browse the repository at this point in the history
Conflicts:
	BackendAst/DAstACN.fs
  • Loading branch information
mario-bucev committed Sep 8, 2024
2 parents af4ddef + 792d1f1 commit 5405d7f
Show file tree
Hide file tree
Showing 7 changed files with 142 additions and 88 deletions.
139 changes: 74 additions & 65 deletions BackendAst/DAstACN.fs

Large diffs are not rendered by default.

65 changes: 48 additions & 17 deletions BackendAst/GenerateAcnIcd.fs
Original file line number Diff line number Diff line change
Expand Up @@ -64,14 +64,15 @@ let PrintAcnAsHTML stgFileName (r:AstRoot) =
icd_acn.EmitFilePart2 stgFileName (Path.GetFileName fName) (content |> Seq.StrJoin "")
)

let PrintAcnAsHTML2 stgFileName (r:AstRoot) =
let PrintAcnAsHTML2 stgFileName (r:AstRoot) (icdHashesToPrint:string list) =
let icdHashesToPrintSet = icdHashesToPrint |> Set.ofList
let fileTypeAssignments =
r.icdHashes.Values |>
Seq.collect id |>
Seq.choose(fun z ->
match z.tasInfo with
| None -> None
| Some ts -> Some (ts.tasName, z.hash)) |>
| Some ts when icdHashesToPrintSet.Contains z.hash -> Some (ts.tasName, z.hash)
| _ -> None) |>
Map.ofSeq

let colorize (t: IToken) =
Expand All @@ -81,7 +82,7 @@ let PrintAcnAsHTML2 stgFileName (r:AstRoot) =
let safeText = t.Text.Replace("<",lt).Replace(">",gt)
let uid =
match fileTypeAssignments.TryFind t.Text with
|Some hash -> icd_acn.TasName stgFileName safeText hash
|Some hash (*when icdHashesToPrintSet.Contains hash*) -> icd_acn.TasName stgFileName safeText hash
|None -> safeText
let colored =
match t.Type with
Expand Down Expand Up @@ -627,7 +628,8 @@ let emitTas2 stgFileName (r:AstRoot) myParams (icdTas:IcdTypeAss) =
let sCommentLine = icdTas.hash::icdTas.comments |> Seq.StrJoin (icd_uper.NewLine stgFileName ())
let arRows =
icdTas.rows |> List.mapi (fun i rw -> emitIcdRow stgFileName r (i+1) rw)
icd_acn.EmitSequenceOrChoice stgFileName false icdTas.name icdTas.hash false (icdTas.kind) (icdTas.minLengthInBytes.ToString()) (icdTas.maxLengthInBytes.ToString()) "sMaxBitsExplained" sCommentLine arRows (myParams 4I) (sCommentLine.Split [|'\n'|])
let bHasAcnDef = icdTas.hasAcnDefinition
icd_acn.EmitSequenceOrChoice stgFileName false icdTas.name icdTas.hash bHasAcnDef (icdTas.kind) (icdTas.minLengthInBytes.ToString()) (icdTas.maxLengthInBytes.ToString()) "sMaxBitsExplained" sCommentLine arRows (myParams 4I) (sCommentLine.Split [|'\n'|])

(*
let rec PrintType2 stgFileName (r:AstRoot) acnParams (icdTas:IcdTypeAss): string list =
Expand Down Expand Up @@ -690,20 +692,42 @@ let PrintTasses2 stgFileName (r:AstRoot) : string list =
| None -> None) |>
Seq.toList



let PrintAsn1FileInColorizedHtml (stgFileName:string) (r:AstRoot) (f:Asn1File) =
let printTasses3 stgFileName (r:DAst.AstRoot) : (string list)*(string list) =
let pdus = r.args.icdPdus |> Option.map Set.ofList
let icdHashesToPrint =
seq {
for f in r.Files do
for m in f.Modules do
for tas in m.TypeAssignments do
match pdus.IsNone || pdus.Value.Contains tas.Name.Value with
| true ->
match tas.Type.icdTas with
| Some icdTas ->
let icdTassesHash = getMySelfAndChildren r icdTas
yield! icdTassesHash
| None -> ()
| false -> ()
} |> Seq.distinct |> Seq.toList
let files =
icdHashesToPrint
|> Seq.choose(fun hash ->
match r.icdHashes.TryFind hash with
| Some chIcdTas -> Some (emitTas2 stgFileName r (fun _ -> []) (selectTypeWithSameHash chIcdTas))
| None -> None) |> Seq.toList
(files, icdHashesToPrint)

let PrintAsn1FileInColorizedHtml (stgFileName:string) (r:AstRoot) (icdHashesToPrint:string list) (f:Asn1File) =
//let tryCreateRefType = CreateAsn1AstFromAntlrTree.CreateRefTypeContent
let icdHashesToPrintSet = icdHashesToPrint |> Set.ofList
let fileModules = f.Modules |> List.map(fun m -> m.Name.Value) |> Set.ofList
let fileTypeAssignments =
r.icdHashes.Values |>
Seq.collect id |>
Seq.choose(fun z ->
match z.tasInfo with
| None -> None
| Some ts when fileModules.Contains ts.modName -> Some (ts.tasName, z.hash)
| Some _ -> None ) |>
Map.ofSeq
| Some ts when icdHashesToPrintSet.Contains z.hash && fileModules.Contains ts.modName -> Some (ts.tasName, z.hash)
| Some _ -> None ) |> Seq.toList


//let blueTasses = f.Modules |> Seq.collect(fun m -> getModuleBlueTasses m)
Expand Down Expand Up @@ -744,13 +768,20 @@ let PrintAsn1FileInColorizedHtml (stgFileName:string) (r:AstRoot) (f:Asn1File) =
|Some(tok) -> tok
|None -> if idx = 0 then t else f.Tokens.[idx-1]
let uid =
match fileTypeAssignments.TryFind t.Text with
|Some tasHash ->
//match fileTypeAssignments.TryFind t.Text with
match fileTypeAssignments |> List.filter(fun (tasName,_) -> tasName = t.Text) with
| [] -> safeText
//|Some tasHash ->
| (_,tasHash)::[] ->
if nextToken.Type = asn1Lexer.ASSIG_OP && prevToken.Type <> asn1Lexer.LID then
icd_uper.TasName stgFileName safeText tasHash
else
icd_uper.TasName2 stgFileName safeText tasHash
|None -> safeText
| _ ->
//printfn "Warning: %s is not unique" t.Text
//printfn "Warning: %A" (fileTypeAssignments |> List.filter(fun (tasName,_) -> tasName = t.Text))
safeText
//|None -> safeText
let colored =
match t.Type with
|asn1Lexer.StringLiteral
Expand All @@ -769,14 +800,14 @@ let PrintAsn1FileInColorizedHtml (stgFileName:string) (r:AstRoot) (f:Asn1File) =

let DoWork (r:AstRoot) (deps:Asn1AcnAst.AcnInsertedFieldDependencies) (stgFileName:string) (asn1HtmlStgFileMacros:string option) outFileName =
let files1 = r.Files |> Seq.map (fun f -> PrintTasses stgFileName f r )
let files1b = PrintTasses2 stgFileName r
let (files1b, icdHashesToPrint) = printTasses3 stgFileName r
let bAcnParamsMustBeExplained = true
let asn1HtmlMacros =
match asn1HtmlStgFileMacros with
| None -> stgFileName
| Some x -> x
let files2 = r.Files |> Seq.map (PrintAsn1FileInColorizedHtml asn1HtmlMacros r)
let files3 = PrintAcnAsHTML2 stgFileName r
let files2 = r.Files |> Seq.map (PrintAsn1FileInColorizedHtml asn1HtmlMacros r icdHashesToPrint)
let files3 = PrintAcnAsHTML2 stgFileName r icdHashesToPrint
let cssFileName = Path.ChangeExtension(outFileName, ".css")
let htmlContent = icd_acn.RootHtml stgFileName files1 files2 bAcnParamsMustBeExplained files3 (Path.GetFileName(cssFileName))
let htmlContentb = icd_acn.RootHtml stgFileName files1b files2 bAcnParamsMustBeExplained files3 (Path.GetFileName(cssFileName))
Expand Down
2 changes: 1 addition & 1 deletion Docs/examples/calculate_crc/Makefile
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@ $(info ${PATH})
all: cTest adaTest

cTest:
asn1scc -mfm postEncoding -c -ACN -atc -o c_out/ a.a* && (cd c_out/ ; make coverage; cd ..)
asn1scc -if Acn_Dec_Int_PositiveInteger_ConstSize -if Acn_Enc_Int_PositiveInteger_ConstSize -mfm postEncoding -c -ACN -atc -o c_out/ a.a* && (cd c_out/ ; make coverage; cd ..)

adaTest:
asn1scc -mfm postEncoding -Ada -ACN -atc -o a_out/ a.a* && (cd a_out/ ; make coverage; cd ..)
Expand Down
2 changes: 1 addition & 1 deletion Docs/examples/calculate_crc2/Makefile
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@ $(info ${PATH})
all: cTest adaTest

cTest:
asn1scc -c -ACN -atc -o c_out/ a.a* && (cd c_out/ ; make coverage; cd ..)
asn1scc -if Acn_Dec_Int_PositiveInteger_ConstSize -if Acn_Enc_Int_PositiveInteger_ConstSize -c -ACN -atc -o c_out/ a.a* && (cd c_out/ ; make coverage; cd ..)

adaTest:
asn1scc -Ada -ACN -atc -o a_out/ a.a* && (cd a_out/ ; make coverage; cd ..)
Expand Down
9 changes: 8 additions & 1 deletion FrontEndAst/CheckAsn1.fs
Original file line number Diff line number Diff line change
Expand Up @@ -687,7 +687,14 @@ let CheckFiles( ast:AstRoot) (pass :int) =
modules |> Seq.map(fun m-> m.Name) |> CheckForDuplicates
// check each file
modules |> Seq.iter (fun x -> CheckModule x ast pass)

//check that the icdPdus list provided in the command line is valid
match ast.args.icdPdus with
| None -> ()
| Some pdus ->
let allPdus = modules |> Seq.collect(fun m -> m.TypeAssignments |> Seq.map(fun tas -> tas.Name.Value)) |> Seq.toList
pdus |> List.iter(fun pdu ->
if not (allPdus |> Seq.exists(fun x -> x = pdu)) then
raise (SemanticError(emptyLocation, sprintf "The PDU '%s' which was specified in the command line does not exist in the ASN.1 files" pdu)))



1 change: 1 addition & 0 deletions FrontEndAst/DAst.fs
Original file line number Diff line number Diff line change
Expand Up @@ -81,6 +81,7 @@ and IcdTypeAss = {
maxLengthInBytes : BigInteger
hash : string
canBeEmbedded : bool
hasAcnDefinition : bool
createRowsFunc : IcdInnerTableFunc
}

Expand Down
12 changes: 9 additions & 3 deletions asn1scc/Program.fs
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,7 @@ type CliArguments =
| [<Unique; AltCommandLine("-customIcdUper")>] CustomIcdUper of custom_stg_colon_out_filename:string
| [<Unique; AltCommandLine("-icdAcn")>] IcdAcn of acn_icd_output_file:string
| [<Unique; AltCommandLine("-customIcdAcn")>] CustomIcdAcn of custom_stg_colon_out_filename:string
| [<Unique; AltCommandLine("-icdPdus")>] IcdPdus of asn1_type_assignments_list:string list
| [<Unique; AltCommandLine("-icdPdus")>] IcdPdus of asn1_type_assignments_list:string

| [<Unique; AltCommandLine("-AdaUses")>] AdaUses
| [<Unique; AltCommandLine("-ACND")>] ACND
Expand Down Expand Up @@ -101,7 +101,7 @@ E.g., -eee 50 will enable this mode for enumerated types with 50 or more enumera
| CustomIcdUper _ -> "Invokes the custom stg file 'stgFile.stg' using the icdUper backend and produces the output file 'outputFile'"
| IcdAcn _ -> "Produces an Interface Control Document for the input ASN.1 and ACN grammars for ACN encoding"
| CustomIcdAcn _ -> "Invokes the custom stg file 'stgFile.stg' using the icdAcn backend and produces the output file 'outputFile'"
| IcdPdus _ -> "A list of type assignments to be included in the generated ICD."
| IcdPdus _ -> "A list of type assignments to be included in the generated ICD. If there are multiple type assignments, please separate them with commas and enclose them in double quotes."
| AdaUses -> "Prints in the console all type Assignments of the input ASN.1 grammar"
| ACND -> "creates ACN grammars for the input ASN.1 grammars using the default encoding properties"
| Debug_Asn1 _ -> "Prints all input ASN.1 grammars in a single module/single file and with parameterized types removed. Used for debugging purposes"
Expand Down Expand Up @@ -318,7 +318,13 @@ let constructCommandLineSettings args (parserResults: ParseResults<CliArguments>
IcdAcnHtmlFileName = ""
generateConstInitGlobals = parserResults.Contains(<@Init_Globals@>)
custom_Stg_Ast_Version = parserResults.GetResult(<@ Custom_Stg_Ast_Version @>, defaultValue = 1)
icdPdus = parserResults.TryGetResult(<@ IcdPdus @>)
icdPdus =
match parserResults.TryGetResult(<@ IcdPdus @>) with
| None -> None
| Some pdus ->
// remove double quotes and split by comma
let actualPdus = pdus.Replace("\"", "")
Some ((actualPdus.Split(',')) |> Seq.map(fun (z:string) -> z.Trim()) |> Seq.filter(fun z -> not (String.IsNullOrEmpty z)) |> Seq.toList)
mappingFunctionsModule = parserResults.TryGetResult(<@ Mapping_Functions_Module @>)
integerSizeInBytes =
let ws = parserResults.GetResult(<@Word_Size@>, defaultValue = 8)
Expand Down

0 comments on commit 5405d7f

Please sign in to comment.