File 2440-Clean-up-comments.patch of Package erlang

From afd0690257ce11ca1e4b50fe70e8f731357dacd1 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Tue, 14 Mar 2017 10:48:57 +0100
Subject: [PATCH 09/10] Clean up comments

* Remove out-commented code
* Fix obvious typos and bad grammar
* Adhere to the conventions for when to use "%" and "%%".
---
 lib/asn1/src/asn1ct.erl                        | 116 +++++---------------
 lib/asn1/src/asn1ct_check.erl                  | 140 ++++++-------------------
 lib/asn1/src/asn1ct_constructed_ber_bin_v2.erl |  61 +++--------
 lib/asn1/src/asn1ct_constructed_per.erl        |  10 +-
 lib/asn1/src/asn1ct_gen.erl                    |  28 ++---
 lib/asn1/src/asn1ct_gen_ber_bin_v2.erl         |  70 +++----------
 lib/asn1/src/asn1ct_gen_per.erl                |  24 ++---
 lib/asn1/src/asn1ct_name.erl                   |   2 -
 lib/asn1/src/asn1ct_parser2.erl                |   2 +-
 lib/asn1/src/asn1ct_value.erl                  |  43 +-------
 lib/asn1/src/asn1rtt_ber.erl                   |  33 +++---
 11 files changed, 127 insertions(+), 402 deletions(-)

diff --git a/lib/asn1/src/asn1ct.erl b/lib/asn1/src/asn1ct.erl
index c9127266f..58cbc89db 100644
--- a/lib/asn1/src/asn1ct.erl
+++ b/lib/asn1/src/asn1ct.erl
@@ -23,10 +23,10 @@
 
 %% Compile Time functions for ASN.1 (e.g ASN.1 compiler).
 
-%%-compile(export_all).
 %% Public exports
 -export([compile/1, compile/2]).
 -export([test/1, test/2, test/3, value/2, value/3]).
+
 %% Application internal exports
 -export([compile_asn/3,compile_asn1/3,compile_py/3,compile/3,
 	 vsn/0,
@@ -75,12 +75,9 @@
 -define(ALTERNATIVE,alt).
 -define(ALTERNATIVE_UNDECODED,alt_undec).
 -define(ALTERNATIVE_PARTS,alt_parts).
-%-define(BINARY,bin).
 
 %% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 %% This is the interface to the compiler
-%% 
-%% 
 
 compile(File) ->
     compile(File,[]).
@@ -751,7 +748,6 @@ remove_import_doubles([]) ->
 remove_import_doubles(ImportList) ->
     MergedImportList = 
 	merge_symbols_from_module(ImportList,[]),
-%%    io:format("MergedImportList: ~p~n",[MergedImportList]),
     delete_double_of_symbol(MergedImportList,[]).
 
 merge_symbols_from_module([Imp|Imps],Acc) ->
@@ -769,7 +765,6 @@ merge_symbols_from_module([Imp|Imps],Acc) ->
 	  end,
 	  Imps),
     NewImps = lists:subtract(Imps,IfromModName),
-%%    io:format("Imp: ~p~nIfromModName: ~p~n",[Imp,IfromModName]),
     NewImp =
 	Imp#'SymbolsFromModule'{
 	  symbols = lists:append(
@@ -988,12 +983,8 @@ get_input_file(Module,[]) ->
 get_input_file(Module,[I|Includes]) ->
     case (catch input_file_type(filename:join([I,Module]))) of
 	{single_file,FileName} ->
-%% 	    case file:read_file_info(FileName) of
-%% 		{ok,_} ->
 		    {file,FileName};
-%% 		_ -> get_input_file(Module,Includes)
-%% 	    end;
-	_ -> 
+	_ ->
 	    get_input_file(Module,Includes)
     end.
 
@@ -1151,7 +1142,6 @@ is_asn1_flag(_) -> false.
 
 
 outfile(Base, Ext, Opts) ->
-%    io:format("Opts. ~p~n",[Opts]),
     Obase = case lists:keysearch(outdir, 1, Opts) of
 		{value, {outdir, Odir}} -> filename:join(Odir, Base);
 		_NotFound -> Base % Not found or bad format
@@ -1202,9 +1192,6 @@ compile_py(File,OutFile,Options) ->
 compile(File, _OutFile, Options) ->
     case compile(File, make_erl_options(Options)) of
 	{error,_Reason} ->
-	    %% case occurs due to error in asn1ct_parser2,asn1ct_check
-%%	    io:format("~p~n",[_Reason]),
-%%	    io:format("~p~n~s~n",[_Reason,"error"]),
 	    error;
 	ok -> 
 	    ok;
@@ -1499,7 +1486,8 @@ create_pdec_inc_command(_ModName,_,[],Acc) ->
 create_pdec_inc_command(ModName,{Comps1,Comps2},TNL,Acc) 
   when is_list(Comps1),is_list(Comps2) ->
     create_pdec_inc_command(ModName,Comps1 ++ Comps2,TNL,Acc);
-%% The following two functionclauses matches on the type after the top type. This one if the top type had no tag, i.e. a CHOICE
+%% The following two clauses match on the type after the top
+%% type. This one if the top type had no tag, i.e. a CHOICE.
 create_pdec_inc_command(ModN,Clist,[CL|_Rest],[[]]) when is_list(CL) ->
     create_pdec_inc_command(ModN,Clist,CL,[]);
 create_pdec_inc_command(ModN,Clist,[CL|_Rest],Acc) when is_list(CL) ->
@@ -1510,17 +1498,14 @@ create_pdec_inc_command(ModName,
 						prop=Prop}|Comps],
 			TNL=[C1|Cs],Acc)  ->
     case C1 of
-% 	Name ->
-% 	    %% In this case C1 is an atom
-% 	    TagCommand = get_tag_command(TS,?MANDATORY,Prop),
-% 	    create_pdec_inc_command(ModName,get_components(TS#type.def),Cs,[TagCommand|Acc]);
 	{Name,undecoded} ->
 	    TagCommand = get_tag_command(TS,?UNDECODED,Prop),
 	    create_pdec_inc_command(ModName,Comps,Cs,concat_sequential(TagCommand,Acc));
 	{Name,parts} ->
 	    TagCommand = get_tag_command(TS,?PARTS,Prop),
 	    create_pdec_inc_command(ModName,Comps,Cs,concat_sequential(TagCommand,Acc));
-	L when is_list(L) -> % I guess this never happens due to previous function clause
+	L when is_list(L) ->
+            %% I guess this never happens due to previous clause.
 	    %% This case is only possible as the first element after
 	    %% the top type element, when top type is SEGUENCE or SET.
 	    %% Follow each element in L. Must note every tag on the
@@ -1542,8 +1527,6 @@ create_pdec_inc_command(ModName,
 						RestPartsList,[]),
 		    create_pdec_inc_command(ModName,Comps,Cs,
 					    [[?MANDATORY,InnerDirectives]|Acc]);
-%		    create_pdec_inc_command(ModName,Comps,Cs,
-%					    [InnerDirectives,?MANDATORY|Acc]);
 		[Opt,EncTag] ->
 		    InnerDirectives = 
 			create_pdec_inc_command(ModName,TS#type.def,
@@ -1551,9 +1534,8 @@ create_pdec_inc_command(ModName,
 		    create_pdec_inc_command(ModName,Comps,Cs,
 					    [[Opt,EncTag,InnerDirectives]|Acc])
 	    end;
-%	    create_pdec_inc_command(ModName,CList,RestPartsList,Acc);
-%%	    create_pdec_inc_command(ModName,TS#type.def,RestPartsList,Acc);
-	_ -> %% this component may not be in the config list
+	_ ->
+            %% this component may not be in the config list
 	    TagCommand = get_tag_command(TS,?MANDATORY,Prop),
 	    create_pdec_inc_command(ModName,Comps,TNL,concat_sequential(TagCommand,Acc))
     end;
@@ -1564,7 +1546,6 @@ create_pdec_inc_command(ModName,
 			[{C1,Directive}|Rest],Acc) ->
     case Directive of
 	List when is_list(List) ->
-%	    [Command,Tag] = get_tag_command(TS,?ALTERNATIVE,Prop),
 	    TagCommand = get_tag_command(TS,?ALTERNATIVE,Prop),
 	    CompAcc = 
 		create_pdec_inc_command(ModName,
@@ -1573,9 +1554,6 @@ create_pdec_inc_command(ModName,
 			 [Command,Tag] when is_atom(Command) ->
 			     [[Command,Tag,CompAcc]|Acc];
 			 [L1,_L2|Rest] when is_list(L1) ->
-% 			     [LastComm|Comms] = lists:reverse(TagCommand),
-% 			     [concat_sequential(lists:reverse(Comms),
-% 					       [LastComm,CompAcc])|Acc]
 			     case lists:reverse(TagCommand) of
 				 [Atom|Comms] when is_atom(Atom) ->
 				     [concat_sequential(lists:reverse(Comms),
@@ -1584,12 +1562,8 @@ create_pdec_inc_command(ModName,
 				     [concat_sequential(lists:reverse(Comms),
 							[[Command2,Tag2,CompAcc]])|Acc]
 			     end
-% 			     [concat_sequential(lists:reverse(Comms),
-% 						InnerCommand)|Acc]
-		     
 		     end,
 	    create_pdec_inc_command(ModName,{'CHOICE',Comps},Rest,
-%				    [[Command,Tag,CompAcc]|Acc]);
 				    NewAcc);
 	undecoded ->
 	    TagCommand = get_tag_command(TS,?ALTERNATIVE_UNDECODED,Prop),
@@ -1645,7 +1619,6 @@ create_partial_decode_gen_info(_M1,{M2,_}) ->
     throw({error,{"wrong module name in asn1 config file",
 		  M2}}).
 
-%create_partial_decode_gen_info1(ModName,{ModName,TypeList}) ->
 create_partial_decode_gen_info1(ModName,{FuncName,TypeList}) ->
     case TypeList of
 	[TopType|Rest] ->
@@ -1665,11 +1638,6 @@ create_partial_decode_gen_info1(ModName,{FuncName,TypeList}) ->
     end;
 create_partial_decode_gen_info1(_,_) ->
     ok.
-% create_partial_decode_gen_info1(_,[]) ->
-%     [];
-% create_partial_decode_gen_info1(_M1,{M2,_}) ->
-%     throw({error,{"wrong module name in asn1 config file",
-% 				  M2}}).
 
 %% create_pdec_command/4 for each name (type or component) in the
 %% third argument, TypeNameList, a command is created. The command has
@@ -1685,7 +1653,6 @@ create_pdec_command(_ModName,_,[],Acc) ->
 		Fun(L,[H|Res],Fun)
 	end,
     Remove_empty_lists(Acc,[],Remove_empty_lists);
-%    lists:reverse(Acc);
 create_pdec_command(ModName,[#'ComponentType'{name=C1,typespec=TS}|_Comps],
 		    [C1|Cs],Acc) ->
     %% this component is a constructed type or the last in the
@@ -1734,9 +1701,7 @@ create_pdec_command(ModName,TS=#type{def=Def},[C1|Cs],Acc) ->
 create_pdec_command(_,_,TNL,_) ->
     throw({error,{"unexpected error when creating partial "
 		  "decode command",TNL}}).
-	    
-% get_components({'CHOICE',Components}) ->
-%     Components;
+
 get_components(#'SEQUENCE'{components={C1,C2}}) when is_list(C1),is_list(C2) ->
     C1++C2;
 get_components(#'SEQUENCE'{components=Components}) ->
@@ -1807,8 +1772,6 @@ get_tag_command(#type{tag=[Tag]},Command) ->
     [Command,encode_tag_val(decode_class(Tag#tag.class),Tag#tag.form, 
 			    Tag#tag.number)];
 get_tag_command(T=#type{tag=[Tag|Tags]},Command) ->
-%     [get_tag_command(T#type{tag=[Tag]},Command)|
-%      [get_tag_command(T#type{tag=Tags},Command)]].
     TC = get_tag_command(T#type{tag=[Tag]},Command),
     TCs = get_tag_command(T#type{tag=Tags},Command),
     case many_tags(TCs) of
@@ -1836,7 +1799,6 @@ get_tag_command(#type{tag=Tag},Command,Prop) when is_record(Tag,tag) ->
     get_tag_command(#type{tag=[Tag]},Command,Prop);
 get_tag_command(T=#type{tag=[Tag|Tags]},Command,Prop) ->
     [get_tag_command(T#type{tag=[Tag]},Command,Prop)|[
-%     get_tag_command(T#type{tag=Tags},?MANDATORY,Prop)]].
      get_tag_command(T#type{tag=Tags},Command,Prop)]].
 
 anonymous_dec_command(?UNDECODED,'OPTIONAL') ->
@@ -1951,8 +1913,8 @@ read_config_data(Key) ->
 	true ->
 	    case asn1ct_table:lookup(asn1_general,{asn1_config,Key}) of
 		[{_,Data}] -> Data;
-		Err -> % Err is [] when nothing was saved in the ets table
-%%		    io:format("strange data from config file ~w~n",[Err]),
+		Err ->
+                    %% Err is [] when nothing was saved in the ets table
 		    Err
 	    end
     end.
@@ -1965,7 +1927,6 @@ read_config_data(Key) ->
 
 %% saves input data in a new gen_state record
 save_gen_state(exclusive_decode,{_,ConfList},PartIncTlvTagList) ->
-    %ConfList=[{FunctionName,PatternList}|Rest]
     State =
 	case get_gen_state() of
 	    S when is_record(S,gen_state) -> S;
@@ -1975,14 +1936,12 @@ save_gen_state(exclusive_decode,{_,ConfList},PartIncTlvTagList) ->
 			       inc_type_pattern=ConfList},
     save_config(gen_state,StateRec);
 save_gen_state(_,_,_) ->
-%%    ok.
     case get_gen_state() of
 	S when is_record(S,gen_state) -> ok;
 	_ -> save_config(gen_state,#gen_state{})
     end.
 
 save_gen_state(selective_decode,{_,Type_component_name_list}) ->
-%%    io:format("Selective_decode: ~p~n",[Type_component_name_list]),
     State =
 	case get_gen_state() of
 	    S when is_record(S,gen_state) -> S;
@@ -2064,11 +2023,6 @@ update_gen_state(type_pattern,State,Data) ->
 update_gen_state(func_name,State,Data) ->
     save_gen_state(State#gen_state{func_name=Data});
 update_gen_state(namelist,State,Data) ->
-%     SData =
-% 	case Data of
-% 	    [D] when is_list(D) -> D;
-% 	    _ -> Data
-% 	end,
     save_gen_state(State#gen_state{namelist=Data});
 update_gen_state(tobe_refed_funcs,State,Data) ->
     save_gen_state(State#gen_state{tobe_refed_funcs=Data});
@@ -2123,7 +2077,6 @@ get_tobe_refed_func(Name) ->
 %% tuple.  Do not save if it exists in generated_functions, because
 %% then it will be or already is generated.
 add_tobe_refed_func(Data) ->
-    %% 
     {Name,SI,Pattern} = 
 	fun({N,Si,P,_}) -> {N,Si,P};
 	    (D) -> D end (Data),
@@ -2131,8 +2084,6 @@ add_tobe_refed_func(Data) ->
 	case SI of
 	    I when is_integer(I) ->
 		fun(D) -> D end(Data);
-% 		fun({N,Ix,P}) -> {N,Ix+1,P};
-% 		   ({N,Ix,P,T}) -> {N,Ix+1,P,T} end (Data);
 	    _ ->
 		fun({N,_,P}) -> {N,0,P};
 		   ({N,_,P,T}) -> {N,0,P,T} end (Data)
@@ -2140,12 +2091,13 @@ add_tobe_refed_func(Data) ->
     
     L = get_gen_state_field(generated_functions),
     case generated_functions_member(get(currmod),Name,L,Pattern) of
-	true -> % it exists in generated_functions, it has already
-                % been generated or saved in tobe_refed_func
+	true ->
+            %% it exists in generated_functions, it has already
+            %% been generated or saved in tobe_refed_func
 	    ok;
 	_ ->
 	    add_once_tobe_refed_func(NewData),
-	    %%only to get it saved in generated_functions
+	    %% only to get it saved in generated_functions
 	    maybe_rename_function(tobe_refed,Name,Pattern)
     end.
 
@@ -2160,16 +2112,13 @@ add_once_tobe_refed_func(Data) ->
 			 ({N,I,_,_}) when N==Name,I==Index -> true;
 			 (_) -> false end,TRFL) of
 	[] ->
-%%    case lists:keysearch(element(1,Data),1,TRFL) of
-%%	false ->
 	    update_gen_state(tobe_refed_funcs,[Data|TRFL]);
 	_ ->
 	    ok
     end.
 
 
-    
-%% moves Name from the to be list to the generated list.
+%% Moves Name from the to be list to the generated list.
 generated_refed_func(Name) ->
     L = get_gen_state_field(tobe_refed_funcs),
     NewL = lists:keydelete(Name,1,L),
@@ -2177,7 +2126,7 @@ generated_refed_func(Name) ->
     L2 = get_gen_state_field(gen_refed_funcs),
     update_gen_state(gen_refed_funcs,[Name|L2]).
 
-%% adds Data to gen_refed_funcs field in gen_state.
+%% Adds Data to gen_refed_funcs field in gen_state.
 add_generated_refed_func(Data) ->
     case is_function_generated(Data) of
 	true ->
@@ -2199,7 +2148,7 @@ next_refed_func() ->
 reset_gen_state() ->
     save_gen_state(#gen_state{}).
 
-%% adds Data to generated_functions field in gen_state.
+%% Adds Data to generated_functions field in gen_state.
 add_generated_function(Data) ->
     L = get_gen_state_field(generated_functions),
     update_gen_state(generated_functions,[Data|L]).
@@ -2218,16 +2167,18 @@ maybe_rename_function(Mode,Name,Pattern) ->
 		{_,true} ->
 		    L2 = generated_functions_filter(get(currmod),Name,L),
 		    case lists:keysearch(Pattern,3,L2) of
-			false -> %name existed, but not pattern
+			false ->
+                            %% name existed, but not pattern
 			    NextIndex = length(L2),
-			    %%rename function
+			    %% rename function
 			    Suffix = lists:concat(["_",NextIndex]),
 			    NewName = 
 				maybe_rename_function2(type_check(Name),Name,
 						       Suffix),
 			    add_generated_function({Name,NextIndex,Pattern}),
 			    NewName;
-			Value -> % name and pattern existed
+			Value ->
+                            %% name and pattern existed
 			    %% do not save any new index
 			    Suffix = make_suffix(Value),
 			    Name2 =
@@ -2237,9 +2188,9 @@ maybe_rename_function(Mode,Name,Pattern) ->
 				end,
 			    lists:concat([Name2,Suffix])
 		    end;
-		{inc_disp,_} -> %% this is when
-                                %% decode_partial_inc_disp/2 is
-                                %% generated
+		{inc_disp,_} ->
+                    %% this is when decode_partial_inc_disp/2 is
+                    %% generated
 		    add_generated_function({Name,0,Pattern}),
 		    Name;
 		_ -> % this if call from add_tobe_refed_func
@@ -2285,23 +2236,12 @@ generated_functions_member(M,Name,[_|T]) ->
 generated_functions_member(_,_,[]) ->
     false.
 
-% generated_functions_member(M,Name,L) ->
-%     case lists:keymember(Name,1,L) of
-% 	true ->
-% 	    true;
-% 	_ ->
-% 	    generated_functions_member1(M,Name,L)
-%     end.
-% generated_functions_member1(M,#'Externaltypereference'{module=M,type=Name},L) ->
-%     lists:keymember(Name,1,L);
-% generated_functions_member1(_,_,_) -> false.
-
 generated_functions_filter(_,Name,L) when is_atom(Name);is_list(Name) ->
     lists:filter(fun({N,_,_}) when N==Name -> true;
 		    (_) -> false
 		 end, L);
 generated_functions_filter(M,#'Externaltypereference'{module=M,type=Name},L)->
-    % remove toptypename from patterns
+    %% remove top typename from patterns
     RemoveTType = 
 	fun({N,I,[N,P]}) when N == Name ->
 		{N,I,P};
@@ -2338,8 +2278,6 @@ set_current_sindex(Index) ->
 
 type_check(A) when is_atom(A) ->
     atom;
-%% type_check(I) when is_integer(I) ->
-%%     integer;
 type_check(L) when is_list(L) ->
     Pred = fun(X) when X=<255 ->
 		   false;
diff --git a/lib/asn1/src/asn1ct_check.erl b/lib/asn1/src/asn1ct_check.erl
index 4f04b7824..e867b9606 100644
--- a/lib/asn1/src/asn1ct_check.erl
+++ b/lib/asn1/src/asn1ct_check.erl
@@ -23,10 +23,9 @@
 
 %% Main Module for ASN.1 compile time functions
 
-%-compile(export_all).
 -export([check/2,storeindb/2,format_error/1]).
-%-define(debug,1).
 -include("asn1_records.hrl").
+
 %%% The tag-number for universal types
 -define(N_BOOLEAN, 1). 
 -define(N_INTEGER, 2). 
@@ -63,7 +62,8 @@
 -define(TAG_CONSTRUCTED(Num),
 	#tag{class='UNIVERSAL',number=Num,type='IMPLICIT',form=32}).
 
--record(newt,{type=unchanged,tag=unchanged,constraint=unchanged,inlined=no}). % used in check_type to update type and tag
+%% used in check_type to update type and tag
+-record(newt,{type=unchanged,tag=unchanged,constraint=unchanged,inlined=no}).
  
 check(S,{Types,Values,ParameterizedTypes,Classes,Objects,ObjectSets}) ->
     %%Predicates used to filter errors
@@ -561,7 +561,6 @@ check_class_fields(S,[F|Fields],Acc) ->
 			    D;
 			{undefined,user} -> 
 			    %% neither of {primitive,bif} or {constructed,bif}
-				    
 			    {_,D} = get_referenced_type(S,#'Externaltypereference'{module=S#state.mname,type=Type#type.def}),
 			    D;
 			_ ->
@@ -623,7 +622,6 @@ if_current_checked_type(S,#type{def=Def}) ->
     CurrentModule = S#state.mname,
     CurrentCheckedName = S#state.tname,
     MergedModules = S#state.inputmodules,
- %   CurrentCheckedModule = S#state.mname,
     case Def of
 	#'Externaltypereference'{module=CurrentModule,
 				 type=CurrentCheckedName} ->
@@ -656,7 +654,6 @@ check_pobjectset(S,PObjSet) ->
 	    ClassName = #'Externaltypereference'{module=Mod,
 						 type=get_datastr_name(Def)},
 	    {valueset,Set} = ValueSet,
-%	    ObjectSet = #'ObjectSet'{class={objectclassname,ClassName},
 	    ObjectSet = #'ObjectSet'{class=ClassName,
 				     set=Set},
 	    #pobjectsetdef{pos=Pos,name=Name,args=Args,class=Type#type.def,
@@ -1696,7 +1693,7 @@ check_value(OldS,V) when is_record(V,typedef) ->
 		    %% reference to class
 		    check_value(OldS,V#typedef{typespec=TS#'ObjectSet'{class=Eref}});
 		#typedef{typespec=HostType} ->
-		    % an ordinary value set with a type in #typedef.typespec
+		    %% an ordinary value set with a type in #typedef.typespec
 		    ValueSet0 = TS#'ObjectSet'.set,
 		    Constr = check_constraints(OldS, HostType, [ValueSet0]),
 		    Type = check_type(OldS,TSDef,TSDef#typedef.typespec),
@@ -2381,15 +2378,6 @@ normalize_s_of(SorS,S,Value,Type,NameList)
 
 
 %% normalize_restrictedstring handles all format of restricted strings.
-%% tuple case
-% normalize_restrictedstring(_S,[Int1,Int2],_) when is_integer(Int1),is_integer(Int2) ->
-%     {Int1,Int2};
-% %% quadruple case
-% normalize_restrictedstring(_S,[Int1,Int2,Int3,Int4],_) when is_integer(Int1),
-% 							   is_integer(Int2),
-% 							   is_integer(Int3),
-% 							   is_integer(Int4) ->
-%     {Int1,Int2,Int3,Int4};
 %% character string list case
 normalize_restrictedstring(S,[H|T],CType) when is_list(H);is_tuple(H) ->
     [normalize_restrictedstring(S,H,CType)|normalize_restrictedstring(S,T,CType)];
@@ -2491,7 +2479,7 @@ check_ptype(S,Type,Ts) when is_record(Ts,type) ->
 		  Ts#type{def=TDef}
 	  end,
     Ts2;
-%parameterized class
+%% parameterized class
 check_ptype(_S,_PTDef,Ts) when is_record(Ts,objectclass) ->
     throw({asn1_param_class,Ts}).
 
@@ -2506,8 +2494,6 @@ check_formal_parameter(_, #'Externaltypereference'{}) ->
 check_formal_parameter(S, #'Externalvaluereference'{value=Name}) ->
     asn1_error(S, {illegal_typereference,Name}).
 
-% check_type(S,Type,ObjSpec={{objectclassname,_},_}) ->
- %     check_class(S,ObjSpec);
 check_type(_S,Type,Ts) when is_record(Type,typedef),
 			   (Type#typedef.checked==true) ->
     Ts;
@@ -2606,7 +2592,6 @@ check_type(S=#state{recordtopname=TopName},Type,Ts) when is_record(Ts,type) ->
 			  constraint = NewC};
 		    _ ->
 			%% Here we only expand the tags and keep the ext ref.
-			    
 			NewExt = ExtRef#'Externaltypereference'{module=merged_mod(S,RefMod,Ext)},
 			TempNewDef#newt{
 			  type = check_externaltypereference(S,NewExt),
@@ -2749,7 +2734,6 @@ check_type(S=#state{recordtopname=TopName},Type,Ts) when is_record(Ts,type) ->
 		    case TopName of
 			[] ->
 			    [get_datastr_name(Type)];
-%			    [Type#typedef.name];
 			_ -> 
 			    TopName
 		    end,
@@ -2773,7 +2757,6 @@ check_type(S=#state{recordtopname=TopName},Type,Ts) when is_record(Ts,type) ->
 		    case TopName of
 			[] ->
 			    [get_datastr_name(Type)];
-%			    [Type#typedef.name];
 			_ -> 
 			    TopName
 		    end,
@@ -2898,8 +2881,6 @@ tablecinf_choose(#'SEQUENCE'{tablecinf=TCI}) ->
 
 get_innertag(_S,#'ObjectClassFieldType'{type=Type}) ->
     case Type of
-%	#type{tag=Tag} -> Tag;
-%	{fixedtypevaluefield,_,#type{tag=[]}=T} -> get_taglist(S,T);
 	{fixedtypevaluefield,_,#type{tag=Tag}} -> Tag;
 	{TypeFieldName,_} when is_atom(TypeFieldName) -> [];
 	_ -> []
@@ -3754,14 +3735,8 @@ check_reference(S,#'Externaltypereference'{pos=Pos,module=Emod,type=Name}) ->
 		{ok,Imodule} ->
 		    check_imported(S,Imodule,Name),
 		    #'Externaltypereference'{module=Imodule,type=Name};
-%% 		    case check_imported(S,Imodule,Name) of
-%% 			ok ->
-%% 			    #'Externaltypereference'{module=Imodule,type=Name};
-%% 			Err ->
-%% 			    Err
-%% 		    end;
 		_ ->
-		    %may be a renamed type in multi file compiling!
+		    %% may be a renamed type in multi file compiling!
 		    {M,T}=get_renamed_reference(S,Name,Emod),
 		    NewName = asn1ct:get_name_of_def(T),
 		    NewPos = asn1ct:get_pos_of_def(T),
@@ -4170,7 +4145,6 @@ iof_associated_type(S,[]) ->
 					    def=AssociateSeq}},
 	    asn1_db:dbput(S#state.mname,'INSTANCE OF',TypeDef),
 	    instance_of_decl(S#state.mname);
-%%	    put(instance_of,{generate,S#state.mname});
 	_ ->
 	    instance_of_decl(S#state.mname),
 	    ok
@@ -4199,14 +4173,12 @@ iof_associated_type1(S,C) ->
     ObjectIdentifier =
 	#'ObjectClassFieldType'{classname=TypeIdentifierRef,
 				class=[],
-%%				fieldname=[{valuefieldreference,id}],
 				fieldname={id,[]},
 				type={fixedtypevaluefield,id,
 				      #type{def='OBJECT IDENTIFIER'}}},
     Typefield =
 	#'ObjectClassFieldType'{classname=TypeIdentifierRef,
 				class=[],
-%%				fieldname=[{typefieldreference,'Type'}],
 				fieldname={'Type',[]},
 				type=Typefield_type},
     IOFComponents0 =
@@ -4360,11 +4332,11 @@ check_boolean(_S,_Constr) ->
 check_octetstring(_S,_Constr) ->
     ok.
 
-% check all aspects of a SEQUENCE
-% - that all component names are unique
-% - that all TAGS are ok (when TAG default is applied)
-% - that each component is of a valid type
-% - that the extension marks are valid
+%% check all aspects of a SEQUENCE
+%% - that all component names are unique
+%% - that all TAGS are ok (when TAG default is applied)
+%% - that each component is of a valid type
+%% - that the extension marks are valid
 
 check_sequence(S,Type,Comps)  ->
     Components = expand_components(S,Comps),    
@@ -4705,11 +4677,11 @@ check_objectidentifier(_S,_Constr) ->
 
 check_relative_oid(_S,_Constr) ->
     ok.
-% check all aspects of a CHOICE
-% - that all alternative names are unique
-% - that all TAGS are ok (when TAG default is applied)
-% - that each alternative is of a valid type
-% - that the extension marks are valid
+%% check all aspects of a CHOICE
+%% - that all alternative names are unique
+%% - that all TAGS are ok (when TAG default is applied)
+%% - that each alternative is of a valid type
+%% - that the extension marks are valid
 check_choice(S,Type,Components) when is_list(Components) ->
     Components1 = [C||C = #'ComponentType'{} <- Components],
     case check_unique(Components1,#'ComponentType'.name) of
@@ -5063,12 +5035,12 @@ remove_doubles1(El,L) ->
 %% referred to in the ObjectClassFieldType, and the name of the unique
 %% field of the class of the ObjectClassFieldType. 
 %%
-% %% The level information outermost/innermost must be kept. There are
-% %% at least two possibilities to cover here for an outermost case: 1)
-% %% Both the simple table and the component relation have a common path
-% %% at least one step below the outermost level, i.e. the leading
-% %% information shall be on a sub level. 2) They don't have any common
-% %% path.
+%% The level information outermost/innermost must be kept. There are
+%% at least two possibilities to cover here for an outermost case: 1)
+%% Both the simple table and the component relation have a common path
+%% at least one step below the outermost level, i.e. the leading
+%% information shall be on a sub level. 2) They don't have any common
+%% path.
 get_simple_table_info(S, Cs, AtLists) ->
     [get_simple_table_info1(S, Cs, AtList, []) || AtList <- AtLists].
 
@@ -5109,10 +5081,10 @@ simple_table_info(S,#'ObjectClassFieldType'{classname=ClRef,
 	    {_FirstFieldName,FieldNames} ->
 		lists:last(FieldNames)
 	end,
-    %%ObjectClassFieldName is the last element in the dotted
-    %%list of the ObjectClassFieldType. The last element may
-    %%be of another class, that is referenced from the class
-    %%of the ObjectClassFieldType
+    %% ObjectClassFieldName is the last element in the dotted list of
+    %% the ObjectClassFieldType. The last element may be of another
+    %% class, that is referenced from the class of the
+    %% ObjectClassFieldType
     ClassDef =
 	case ObjectClass of
 	    [] ->
@@ -5128,7 +5100,7 @@ simple_table_info(S,#'ObjectClassFieldType'{classname=ClRef,
 %% the "name path" in the at-list to the component relation constraint
 %% that must refer to a simple table constraint. The list is empty if
 %% no component relation constraints were found.
-%% 
+%%
 %% NamePath has the names of all components that are followed from the
 %% beginning of the search. CNames holds the names of all components
 %% of the start level, this info is used if an outermost at-notation
@@ -5141,6 +5113,7 @@ any_component_relation(S,[#'ComponentType'{name=CName,typespec=Type}|Cs],CNames,
 		%% whether this constraint is relevant for the level
 		%% where the search started
 		AtNot = extract_at_notation(AtNotation),
+
 		%% evaluate_atpath returns the relative path to the
 		%% simple table constraint from where the component
 		%% relation is found.
@@ -5246,12 +5219,10 @@ get_components(_,#'SET'{components=Cs}) ->
     tuple2complist(Cs);
 get_components(_,{'CHOICE',Cs}) ->
     tuple2complist(Cs);
-%do not step in inlined structures
+%%do not step in inlined structures
 get_components(any,{'SEQUENCE OF',T = #type{def=_Def,inlined=no}}) ->
-%    get_components(any,Def);
     T;
 get_components(any,{'SET OF',T = #type{def=_Def,inlined=no}}) ->
-%    get_components(any,Def);
     T;
 get_components(_,_) ->
     [].
@@ -5281,15 +5252,12 @@ extract_at_notation([{Level,ValueRefs}]) ->
 componentrelation1(S,C = #type{def=Def,constraint=Constraint,tablecinf=TCI},
 		   Path) ->
     Ret =
-%	case Constraint of
-%	    [{componentrelation,{_,_,ObjectSet},AtList}|_Rest] ->
 	case lists:keyfind(componentrelation, 1, Constraint) of
 	    {_,{_,_,ObjectSet},AtList} ->
 		[{_,AL=[#'Externalvaluereference'{}|_R1]}|_R2] = AtList,
 		%% Note: if Path is longer than one,i.e. it is within
 		%% an inner type of the actual level, then the only
 		%% relevant at-list is of "outermost" type.
-%%		#'ObjectClassFieldType'{class=ClassDef} = Def,
 		ClassDef = get_ObjectClassFieldType_classdef(S,Def),
 		AtPath = 
 		    lists:map(fun(#'Externalvaluereference'{value=V})->V end,
@@ -5375,7 +5343,6 @@ innertype_comprel1(S,T = #type{def=Def,constraint=Cons,tablecinf=TCI},Path) ->
 		%% relevant here.
 		[{_,AL=[#'Externalvaluereference'{value=_Attr}|_R1]}|_R2] 
 		    = AtList,
-%%		#'ObjectClassFieldType'{class=ClassDef} = Def,
 		ClassDef = get_ObjectClassFieldType_classdef(S,Def),
 		AtPath = 
 		    lists:map(fun(#'Externalvaluereference'{value=V})->V end,
@@ -5444,7 +5411,7 @@ leading_attr_index1(S,[C|Cs],Arg={ObjectSet,_,CDef,P},
 value_match(S,C,Name,SubAttr) ->
     value_match(S,C,Name,SubAttr,[]). % C has name Name
 value_match(_S,#'ComponentType'{},_Name,[],Acc) ->
-    Acc;% do not reverse, indexes in reverse order
+    Acc;                    % do not reverse, indexes in reverse order
 value_match(S,#'ComponentType'{typespec=Type},Name,[At|Ats],Acc) ->
     InnerType = asn1ct_gen:get_inner(Type#type.def),
     Components =
@@ -5514,8 +5481,6 @@ get_tableconstraint_info(S,Type,[C=#'ComponentType'{typespec=CheckedTs}|Cs],Acc)
 				  CheckedTs#type{
 				    def=NewOCFT
 				    }};
-%				    constraint=[{tableconstraint_info,
-%						 FieldRef}]}};
 	    {'SEQUENCE OF',SOType} when is_record(SOType,type),
 					(element(1,SOType#type.def)=='CHOICE') ->
 		CTypeList = element(2,SOType#type.def),
@@ -5618,51 +5583,6 @@ get_taglist1(S,[_H|Rest]) -> % skip EXTENSIONMARK
 get_taglist1(_S,[]) ->
     [].
 
-%% def_to_tag(S,Def) ->
-%%     case asn1ct_gen:def_to_tag(Def) of
-%% 	{'UNIVERSAL',T} ->
-%% 	    case asn1ct_gen:prim_bif(T) of
-%% 		true ->
-%% 		    ?TAG_PRIMITIVE(tag_number(T));
-%% 		_ ->
-%% 		    ?TAG_CONSTRUCTED(tag_number(T))
-%% 	    end;
-%% 	_ -> []
-%%     end.
-%% tag_number('BOOLEAN') -> 1;
-%% tag_number('INTEGER') -> 2;
-%% tag_number('BIT STRING') -> 3;
-%% tag_number('OCTET STRING') -> 4;
-%% tag_number('NULL') -> 5;
-%% tag_number('OBJECT IDENTIFIER') -> 6;
-%% tag_number('ObjectDescriptor') -> 7;
-%% tag_number('EXTERNAL') -> 8;
-%% tag_number('INSTANCE OF') -> 8;
-%% tag_number('REAL') -> 9;
-%% tag_number('ENUMERATED') -> 10;
-%% tag_number('EMBEDDED PDV') -> 11;
-%% tag_number('UTF8String') -> 12;
-%% %%tag_number('RELATIVE-OID') -> 13;
-%% tag_number('SEQUENCE') -> 16;
-%% tag_number('SEQUENCE OF') -> 16;
-%% tag_number('SET') -> 17;
-%% tag_number('SET OF') -> 17;
-%% tag_number('NumericString') -> 18;
-%% tag_number('PrintableString') -> 19;
-%% tag_number('TeletexString') -> 20;
-%% %%tag_number('T61String') -> 20;
-%% tag_number('VideotexString') -> 21;
-%% tag_number('IA5String') -> 22;
-%% tag_number('UTCTime') -> 23;
-%% tag_number('GeneralizedTime') -> 24;
-%% tag_number('GraphicString') -> 25;
-%% tag_number('VisibleString') -> 26;
-%% %%tag_number('ISO646String') -> 26;
-%% tag_number('GeneralString') -> 27;
-%% tag_number('UniversalString') -> 28;
-%% tag_number('CHARACTER STRING') -> 29;
-%% tag_number('BMPString') -> 30.
-
 merge_tags(T1, T2) when is_list(T2) ->
     merge_tags2(T1 ++ T2, []);
 merge_tags(T1, T2) ->
diff --git a/lib/asn1/src/asn1ct_constructed_ber_bin_v2.erl b/lib/asn1/src/asn1ct_constructed_ber_bin_v2.erl
index e94f25af5..976296a27 100644
--- a/lib/asn1/src/asn1ct_constructed_ber_bin_v2.erl
+++ b/lib/asn1/src/asn1ct_constructed_ber_bin_v2.erl
@@ -36,13 +36,13 @@
 
 -define(ASN1CT_GEN_BER,asn1ct_gen_ber_bin_v2).
 
-% the encoding of class of tag bits 8 and 7
+%% the encoding of class of tag bits 8 and 7
 -define(UNIVERSAL,   0).
 -define(APPLICATION, 16#40).
 -define(CONTEXT,     16#80).
 -define(PRIVATE,     16#C0).
 
-% primitive or constructed encoding % bit 6
+%% primitive or constructed encoding % bit 6
 -define(PRIMITIVE,   0).
 -define(CONSTRUCTED, 2#00100000).
 
@@ -103,7 +103,6 @@ gen_encode_sequence(Gen, Typename, #type{}=D) ->
 				   uniqueclassfield=Unique} when Used /= Unique ->
 		false;
 	    %% ObjectSet, name of the object set in constraints
-	    %% 
 	    #simpletableattributes{objectsetname=ObjectSetRef,
 				   c_name=AttrN,
 				   c_index=N,
@@ -230,7 +229,6 @@ gen_decode_sequence(Gen, Typename, #type{}=D) ->
 				   usedclassfield=UniqueFieldName,
 				   uniqueclassfield=UniqueFieldName,
 				   valueindex=ValIndex} ->
-%	    {ObjectSetRef,AttrN,_N,UniqueFieldName} ->%% N is index of attribute that determines constraint
 		F = fun(#'ComponentType'{typespec=CT})->
 			    case {asn1ct_gen:get_constraint(CT#type.constraint,componentrelation),CT#type.tablecinf} of
 				{no,[{objfun,_}|_]} -> true;
@@ -283,7 +281,8 @@ gen_decode_sequence(Gen, Typename, #type{}=D) ->
 	    case Ext of
 		{ext,_,_} -> 
 		    emit(["case ",{prev,tlv}," of [] -> true; _ -> true end, % ... extra fields skipped",nl]);
-		_ -> % noext | extensible 
+		_ ->
+                    %% noext | extensible
 		    emit(["case ",{prev,tlv}," of",nl,
 			  "[] -> true;",
 			  "_ -> exit({error,{asn1, {unexpected,",{prev,tlv},
@@ -430,7 +429,6 @@ gen_decode_set(Gen, Typename, #type{}=D) ->
 
     {DecObjInf,ValueIndex} =
 	case TableConsInfo of
-%%	    {ObjectSetRef,AttrN,_N,UniqueFieldName} ->%% N is index of attribute that determines constraint
 	    #simpletableattributes{objectsetname=ObjectSetRef,
 				   c_name=AttrN,
 				   usedclassfield=UniqueFieldName,
@@ -445,7 +443,8 @@ gen_decode_set(Gen, Typename, #type{}=D) ->
 			    end
 		    end,
 		case lists:any(F,CompList) of
-		    true -> % when component relation constraint establish
+		    true ->
+                        %% when component relation constraint establish
 			%% relation from a component to another components
 			%% subtype component
 			{{AttrN,{deep,ObjectSetRef,UniqueFieldName,ValIndex}},
@@ -720,7 +719,7 @@ gen_dec_sequence_call2(Erules,TopType,{Root1,EList,Root2},_Ext,DecObjInf) ->
 			   length(Root1)+length(EList),noext,
 			   DecObjInf,LA,ArgsAcc).
 
-%% returns a list of tags of the elements in the component (second
+%% Returns a list of tags of the elements in the component (second
 %% root) list up to and including the first mandatory tag. See 24.6 in
 %% X.680 (7/2002)
 get_root2_taglist([],Acc) ->
@@ -809,8 +808,6 @@ gen_dec_set_cases(Erules,TopType,[Comp|RestComps],Pos) ->
                [FirstTag|_] ->
 		   [(?ASN1CT_GEN_BER:decode_class(FirstTag#tag.class) bsl 10) + FirstTag#tag.number]
 	   end,
-%    emit([indent(6),"%Tags: ",Tags,nl]),
-%    emit([indent(6),"%Type#type.tag: ",Type#type.tag,nl]),
     CaseFun = fun(TagList=[H|T],Fun,N) ->
 		      Semicolon = case TagList of
 				      [_Tag1,_|_] -> [";",nl];
@@ -825,7 +822,6 @@ gen_dec_set_cases(Erules,TopType,[Comp|RestComps],Pos) ->
 		      emit([";",nl])
 	      end,
     CaseFun(Tags,CaseFun,0),
-%%    emit([";",nl]),
     gen_dec_set_cases(Erules,TopType,RestComps,Pos+1).
 
 
@@ -1005,14 +1001,6 @@ gen_enc_line(Erules,TopType,Cname,
 			 ["{",{curr,encBytes},",",{curr,encLen},"} = "],
 			 EncObj)
     end;
-% gen_enc_line(Erules,TopType,Cname,
-% 	     Type=#type{constraint=[{componentrelation,_,_}],
-% 			def=#'ObjectClassFieldType'{type={typefield,_}}},
-% 	     Element,Indent,OptOrMand=mandatory,EncObj) 
-%   when is_list(Element) ->
-%     asn1ct_name:new(tmpBytes),
-%     gen_enc_line(Erules,TopType,Cname,Type,Element,Indent,OptOrMand,
-% 		 ["{",{curr,tmpBytes},",_} = "],EncObj);
 gen_enc_line(Erules,TopType,Cname,Type,Element,Indent,OptOrMand,EncObj) 
   when is_list(Element) ->
     gen_enc_line(Erules,TopType,Cname,Type,Element,Indent,OptOrMand,
@@ -1033,8 +1021,6 @@ gen_enc_line(Erules,TopType,Cname,Type,Element,Indent,OptOrMand,Assign,EncObj)
     gen_optormand_case(OptOrMand, Erules, TopType, Cname, Type, Element),
     case {Type,asn1ct_gen:get_constraint(Type#type.constraint,
 					 componentrelation)} of
-% 	#type{constraint=[{tableconstraint_info,RefedFieldName}],
-% 	      def={typefield,_}} ->
 	{#type{def=#'ObjectClassFieldType'{type={typefield,_},
 					   fieldname=RefedFieldName}},
 	 {componentrelation,_,_}} ->
@@ -1044,9 +1030,7 @@ gen_enc_line(Erules,TopType,Cname,Type,Element,Indent,OptOrMand,Assign,EncObj)
 		    case OptOrMand of
 			mandatory -> ok;
 			_ ->
-%			    emit(["{",{curr,tmpBytes},",",{curr,tmpLen},
 			    emit(["{",{curr,tmpBytes},",_ } = "])
-%				  "} = "])
 		    end,
 		    emit([Fun,"(",{asis,Name},", ",Element,", ",
 			  {asis,RestFieldNames},"),",nl]),
@@ -1164,7 +1148,9 @@ gen_dec_line(Erules,TopType,Cname,CTags,Type,OptOrMand,DecObjInf)  ->
 		gen_dec_call(InnerType,Erules,TopType,Cname,Type,
 			     BytesVar,Tag,
 			     mandatory,", mandatory, ",DecObjInf,OptOrMand);
-	    _ -> %optional or default or a mandatory component after an extensionmark
+	    _ ->
+                %% optional or default, or a mandatory component after
+                %% an extension marker
 		{FirstTag,RestTag} = 
 		    case Tag of 
 			[] -> 
@@ -1239,9 +1225,9 @@ gen_dec_line(Erules,TopType,Cname,CTags,Type,OptOrMand,DecObjInf)  ->
 		PostponedDec
 	end,
     case DecObjInf of
-	{Cname,ObjSet} -> % this must be the component were an object is 
-	    %% choosen from the object set according to the table 
-	    %% constraint.
+	{Cname,ObjSet} ->
+            %% This must be the component were an object is chosen
+	    %% from the object set according to the table constraint.
 	    ObjSetName = case ObjSet of
 			     {deep,OSName,_,_} ->
 				 OSName;
@@ -1278,10 +1264,7 @@ gen_dec_call({typefield,_},_,_,_Cname,Type,BytesVar,Tag,_,_,false,_) ->
     [];
 gen_dec_call({typefield,_},_,_,Cname,Type,BytesVar,Tag,_,_,_DecObjInf,OptOrMandComp) ->
     call(decode_open_type, [BytesVar,{asis,Tag}]),
-    RefedFieldName = 
-% 	asn1ct_gen:get_constraint(Type#type.constraint,
-% 				  tableconstraint_info),
-	(Type#type.def)#'ObjectClassFieldType'.fieldname,
+    RefedFieldName = (Type#type.def)#'ObjectClassFieldType'.fieldname,
     [{Cname,RefedFieldName,asn1ct_gen:mk_var(asn1ct_name:curr(term)),
       asn1ct_gen:mk_var(asn1ct_name:curr(tmpterm)),Tag,OptOrMandComp}];
 gen_dec_call(InnerType, Gen, TopType, Cname, Type, BytesVar,
@@ -1337,8 +1320,6 @@ gen_dec_call1(WhatKind, _, TopType, Cname, Type, BytesVar, Tag) ->
 	    emit(["{'",asn1ct_gen:list2name([Cname|TopType]),"',",
 		  BytesVar,"}"]);
 	_ ->
-%	    {DecFunName, _DecMod, _DecFun} = 
-%		case {asn1ct:get_gen_state_field(namelist),WhatKind} of
 	    EmitDecFunCall = 
 		fun(FuncName) ->
 			case {WhatKind,Type#type.tablecinf} of
@@ -1354,14 +1335,11 @@ gen_dec_call1(WhatKind, _, TopType, Cname, Type, BytesVar, Tag) ->
 		    Sindex =
 			case WhatKind of
 			    #'Externaltypereference'{} ->
-%				asn1ct:maybe_rename_function(WhatKind,List),
 				SI = asn1ct:maybe_saved_sindex(WhatKind,List),
 				Saves = {WhatKind,SI,List},
 				asn1ct:add_tobe_refed_func(Saves),
 				SI;
 			    _ ->
-%				asn1ct:maybe_rename_function([Cname|TopType],
-%							     List),
 				SI = asn1ct:maybe_saved_sindex([Cname|TopType],List),
 				Saves = {[Cname|TopType],SI,List,Type},
 				asn1ct:add_tobe_refed_func(Saves),
@@ -1369,8 +1347,6 @@ gen_dec_call1(WhatKind, _, TopType, Cname, Type, BytesVar, Tag) ->
 			end,
 		    asn1ct:update_gen_state(namelist,Rest),
 		    Prefix=asn1ct:get_gen_state_field(prefix),
-%		    Suffix =
-%			lists:concat(["_",asn1ct:latest_sindex()]),
 		    Suffix =
 			case Sindex of
 			    I when is_integer(I),I>0 -> lists:concat(["_",I]);
@@ -1378,8 +1354,6 @@ gen_dec_call1(WhatKind, _, TopType, Cname, Type, BytesVar, Tag) ->
 			end,
 		    {DecFunName,_,_}=
 			mkfuncname(TopType,Cname,WhatKind,Prefix,Suffix),
-%		    SuffixedName = 
-%			lists:concat([DecFunName,asn1ct:latest_sindex()]),
 		    EmitDecFunCall(DecFunName);
 		[{Cname,parts}|Rest] ->
 		    asn1ct:update_gen_state(namelist,Rest),
@@ -1399,13 +1373,6 @@ gen_dec_call1(WhatKind, _, TopType, Cname, Type, BytesVar, Tag) ->
 			mkfuncname(TopType,Cname,WhatKind,"dec_",""),
 		    EmitDecFunCall(DecFunName)
 	    end
-% 	    case {WhatKind,Type#type.tablecinf} of
-% 		{{constructed,bif},[{objfun,_}|_Rest]} ->
-% 		    emit([DecFunName,"(",BytesVar,", ",{asis,Tag},
-% 			  ", ObjFun)"]);
-% 		_ ->
-% 		    emit([DecFunName,"(",BytesVar,", ",{asis,Tag},")"])
-% 	    end
     end.
 
 
diff --git a/lib/asn1/src/asn1ct_constructed_per.erl b/lib/asn1/src/asn1ct_constructed_per.erl
index c3d1dae90..986d88b67 100644
--- a/lib/asn1/src/asn1ct_constructed_per.erl
+++ b/lib/asn1/src/asn1ct_constructed_per.erl
@@ -30,7 +30,6 @@
 -export([gen_decode_choice/3]).
 
 -include("asn1_records.hrl").
-%-compile(export_all).
 
 -import(asn1ct_gen, [emit/1,get_record_name_prefix/1]).
 
@@ -357,7 +356,6 @@ gen_dec_constructed_imm(Erule, Typename, #type{}=D) ->
 	    #'SEQUENCE'{tablecinf=TCI,components=CL} ->
 		{add_textual_order(CL),TCI};
 	    #'SET'{tablecinf=TCI,components=CL} ->
-%%		{add_textual_order(CL),TCI}
 		{CL,TCI} % the textual order is already taken care of
 	end,
     Ext = extensible_dec(CompList),
@@ -375,13 +373,11 @@ gen_dec_constructed_imm(Erule, Typename, #type{}=D) ->
 	      end,
     ObjSetInfo =
 	case TableConsInfo of
-%%	    {ObjectSet,AttrN,N,UniqueFieldName} ->%% N is index of attribute that determines constraint
 	    #simpletableattributes{objectsetname=ObjectSet,
 				   c_name=AttrN,
 				   usedclassfield=UniqueFieldName,
 				   uniqueclassfield=UniqueFieldName,
 				   valueindex=ValIndex} ->
-%%		{AttrN,ObjectSet};
 		F = fun(#'ComponentType'{typespec=CT})->
 			    case {asn1ct_gen:get_constraint(CT#type.constraint,componentrelation),CT#type.tablecinf} of
 				{no,[{objfun,_}|_R]} -> true;
@@ -689,7 +685,7 @@ gen_decode_choice(Erules,Typename,D) when is_record(D,type) ->
     emit([".",nl]).
 
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-% Encode generator for SEQUENCE OF type
+%% Encode generator for SEQUENCE OF type
 
 gen_encode_sof(Erule, Typename, SeqOrSetOf, D) ->
     asn1ct_name:start(),
@@ -934,9 +930,7 @@ add_textual_order({R1,Ext,R2}) ->
     {NewExt,Num2} = add_textual_order1(Ext,Num1),
     {NewR2,_} = add_textual_order1(R2,Num2),
     {NewR1,NewExt,NewR2}.
-%%add_textual_order1(Cs=[#'ComponentType'{textual_order=Int}|_],I)
-%%  when is_integer(Int) ->
-%%    {Cs,I};
+
 add_textual_order1(Cs,NumIn) ->
     lists:mapfoldl(fun(C=#'ComponentType'{},Num) ->
 			   {C#'ComponentType'{textual_order=Num},
diff --git a/lib/asn1/src/asn1ct_gen.erl b/lib/asn1/src/asn1ct_gen.erl
index 2e9dbd78d..4a51bcf8e 100644
--- a/lib/asn1/src/asn1ct_gen.erl
+++ b/lib/asn1/src/asn1ct_gen.erl
@@ -190,13 +190,9 @@ pgen_partial_decode(_, _, _) ->
     ok.
 
 pgen_partial_inc_dec(Rtmod,Erules,Module) ->
-%    io:format("Start partial incomplete decode gen?~n"),
     case asn1ct:get_gen_state_field(inc_type_pattern) of
 	undefined ->
-%	    io:format("Partial incomplete decode gen not started: ~w~n",[asn1ct:get_gen_state_field(active)]),
 	    ok;
-%	[] ->
-%	    ok;
 	ConfList -> 
 	    PatternLists=lists:map(fun({_,P}) -> P end,ConfList),
 	    pgen_partial_inc_dec1(Rtmod,Erules,Module,PatternLists),
@@ -214,11 +210,9 @@ pgen_partial_inc_dec1(Rtmod,Erules,Module,[P|Ps]) ->
     asn1ct:update_gen_state(prefix,"dec-inc-"),
     case asn1ct:maybe_saved_sindex(TopTypeName,P) of
 	I when is_integer(I),I > 0 ->
-%	    io:format("Index:~p~n",[I]),
 	    asn1ct:set_current_sindex(I);
 	_I ->
 	    asn1ct:set_current_sindex(0),
-%	    io:format("Index=~p~n",[_I]),
 	    ok
     end,
     Rtmod:gen_decode(Erules,TypeDef),
@@ -249,8 +243,8 @@ gen_partial_inc_dec_refed_funcs(Rtmod, #gen{erule=ber}=Gen) ->
 
 pgen_partial_dec(_Rtmod,Erules,_Module) ->
     Type_pattern = asn1ct:get_gen_state_field(type_pattern),
-%    io:format("Type_pattern: ~w~n",[Type_pattern]),
-    %% Get the typedef of the top type and follow into the chosen components until the last type/component.
+    %% Get the typedef of the top type and follow into the chosen
+    %% components until the last type/component.
     pgen_partial_types(Erules,Type_pattern),
     ok.
 
@@ -265,7 +259,6 @@ pgen_partial_types(#gen{options=Options}=Gen, TypePattern)  ->
 
 
 pgen_partial_types1(Erules,[{FuncName,[TopType|RestTypes]}|Rest]) ->
-%    emit([FuncName,"(Bytes) ->",nl]),
     CurrMod = get(currmod),
     TypeDef = asn1_db:dbget(CurrMod,TopType),
     traverse_type_structure(Erules,TypeDef,RestTypes,FuncName,
@@ -290,8 +283,9 @@ traverse_type_structure(Erules,Type,[],FuncName,TopTypeName) ->
 	end,
     Ctmod:gen_decode_selected(Erules,TypeDef,FuncName); % what if Type is #type{}
 traverse_type_structure(Erules,#type{def=Def},[[N]],FuncName,TopTypeName) 
-  when is_integer(N) -> % this case a decode of one of the elements in
-                     % the SEQUENCE OF is required.
+  when is_integer(N) ->
+    %% In this case a decode of one of the elements in the SEQUENCE OF is
+    %% required.
     InnerType = asn1ct_gen:get_inner(Def),
     case InnerType of
 	'SEQUENCE OF' ->
@@ -367,8 +361,9 @@ traverse_type_structure(Erules,#typedef{typespec=Def},[T|Ts],FuncName,
 	    TypeDef = asn1_db:dbget(M,TName),
 	    traverse_type_structure(Erules,TypeDef,[T|Ts],FuncName,
 				    [TypeDef#typedef.name]);
-	_ -> %this may be a referenced type that shall be traversed or
-             %the selected type
+	_ ->
+            %% This may be a referenced type that shall be traversed
+            %% or the selected type
 	    traverse_type_structure(Erules,Def,Ts,FuncName,[T|TopTypeName])
     end.
 	    
@@ -450,7 +445,6 @@ pgen_partial_incomplete_decode1(#gen{erule=ber}) ->
 	    lists:foreach(fun emit_partial_incomplete_decode/1,Data)
     end,
     GeneratedFs= asn1ct:get_gen_state_field(gen_refed_funcs),
-%    io:format("GeneratedFs :~n~p~n",[GeneratedFs]),
     gen_part_decode_funcs(GeneratedFs,0);
 pgen_partial_incomplete_decode1(#gen{}) -> ok.
 
@@ -878,7 +872,6 @@ gen_partial_inc_dispatcher(#gen{erule=ber}) ->
 	{_,undefined} ->
 	    ok;
 	{Data1,Data2} ->
-%	    io:format("partial_incomplete_decode: ~p~ninc_type_pattern: ~p~n",[Data,Data2]),
 	    gen_partial_inc_dispatcher(Data1, Data2, "")
     end;
 gen_partial_inc_dispatcher(#gen{}) ->
@@ -1091,8 +1084,6 @@ gen_record(Gen, TorPtype, Name, #type{}=Type, Num) ->
 		  case Seq#'SEQUENCE'.pname of
 		      false ->
 			  {record,Seq#'SEQUENCE'.components};
-%% 		      _Pname when TorPtype == type ->
-%% 			  false;
 		      _ ->
 			  {record,Seq#'SEQUENCE'.components}
 		  end;
@@ -1105,8 +1096,6 @@ gen_record(Gen, TorPtype, Name, #type{}=Type, Num) ->
 		      _ ->
 			  {record,to_textual_order(Set#'SET'.components)}
 		  end;
-%	      {'SET',{_,_CompList}} -> 
-%		  {record,_CompList}; 
 	      {'CHOICE',_CompList} -> {inner,Def};
 	      {'SEQUENCE OF',_CompList} -> {['SEQOF'|Name],Def};
 	      {'SET OF',_CompList} -> {['SETOF'|Name],Def};
@@ -1312,7 +1301,6 @@ get_inner({fixedtypevaluefield,_,Type}) ->
 get_inner({typefield,TypeName}) ->
     TypeName;
 get_inner(#'ObjectClassFieldType'{type=Type}) ->
-%    get_inner(Type);
     Type;
 get_inner(T) when is_tuple(T) -> 
     case element(1,T) of
diff --git a/lib/asn1/src/asn1ct_gen_ber_bin_v2.erl b/lib/asn1/src/asn1ct_gen_ber_bin_v2.erl
index 429b14f8b..948566a6f 100644
--- a/lib/asn1/src/asn1ct_gen_ber_bin_v2.erl
+++ b/lib/asn1/src/asn1ct_gen_ber_bin_v2.erl
@@ -37,19 +37,19 @@
 
 -import(asn1ct_gen, [emit/1]).
 
-						% the encoding of class of tag bits 8 and 7
+%% The encoding of class of tag bits 8 and 7
 -define(UNIVERSAL,   0).
 -define(APPLICATION, 16#40).
 -define(CONTEXT,     16#80).
 -define(PRIVATE,     16#C0).
 
-						% primitive or constructed encoding % bit 6
+%% Primitive or constructed encoding % bit 6
 -define(PRIMITIVE,   0).
 -define(CONSTRUCTED, 2#00100000).
 
 
 -define(T_ObjectDescriptor, ?UNIVERSAL bor ?PRIMITIVE bor 7).
-						% restricted character string types
+%% Restricted character string types
 -define(T_NumericString,    ?UNIVERSAL bor ?PRIMITIVE bor 18). %can be constructed
 -define(T_PrintableString,  ?UNIVERSAL bor ?PRIMITIVE bor 19). %can be constructed
 -define(T_TeletexString,    ?UNIVERSAL bor ?PRIMITIVE bor 20). %can be constructed
@@ -352,7 +352,6 @@ gen_inc_decode(Erules,Type) when is_record(Type,typedef) ->
 %% gen_decode_selected exported function for selected decode
 gen_decode_selected(Erules,Type,FuncName) ->
     emit([FuncName,"(Bin) ->",nl]),
-%    Pattern = asn1ct:get_gen_state_field(tag_pattern),
     Patterns = asn1ct:read_config_data(partial_decode),
     Pattern = 
 	case lists:keysearch(FuncName,1,Patterns) of
@@ -391,12 +390,10 @@ gen_decode_selected_type(_Erules,TypeDef) ->
 				       asn1ct_gen:list2name(TopType),"'"]),
 	    emit([DecFunName,"(",BytesVar,
 		  ", ",{asis,Tag},")"]);
-%	    emit([";",nl]);
 	TheType ->
 	    DecFunName = mkfuncname(TheType,dec),
 	    emit([DecFunName,"(",BytesVar,
 		  ", ",{asis,Tag},")"])
-%	    emit([";",nl])
     end.
 
 %%===============================================================================
@@ -411,7 +408,6 @@ gen_decode(Erules,Typename,Type) when is_record(Type,type) ->
     FunctionName =
 	case asn1ct:get_gen_state_field(active) of
 	    true -> 
-%		Suffix = asn1ct_gen:index2suffix(SIndex),
 		Pattern = asn1ct:get_gen_state_field(namelist),
 		Suffix = 
 		    case asn1ct:maybe_saved_sindex(Typename,Pattern) of
@@ -424,8 +420,6 @@ gen_decode(Erules,Typename,Type) when is_record(Type,type) ->
 	    _ -> 
 		lists:concat(["'dec_",asn1ct_gen:list2name(Typename)])
 	end,
-%    io:format("Typename: ~p,~n",[Typename]),
-%    io:format("FunctionName: ~p~n",[FunctionName]),
     case asn1ct_gen:type(InnerType) of
 	{constructed,bif} ->
 	    ObjFun =
@@ -435,7 +429,6 @@ gen_decode(Erules,Typename,Type) when is_record(Type,type) ->
 		    _ ->
 			""
 		end,
-%	    emit([Prefix,asn1ct_gen:list2name(Typename),"'(Tlv, TagIn",ObjFun,") ->",nl]),
 	    emit([FunctionName,"'(Tlv, TagIn",ObjFun,") ->",nl]),
 	    asn1ct_gen:gen_decode_constructed(Erules,Typename,InnerType,Type);
 	Rec when is_record(Rec,'Externaltypereference') ->
@@ -468,10 +461,10 @@ gen_decode(Erules,Typename,Type) when is_record(Type,type) ->
 
 gen_decode(Erules,Tname,#'ComponentType'{name=Cname,typespec=Type}) ->
     NewTname = [Cname|Tname],
-    %% The tag is set to [] to avoid that it is
-    %% taken into account twice, both as a component/alternative (passed as
-    %% argument to the encode decode function and within the encode decode
-    %% function it self.
+    %% The tag is set to [] to avoid that it is taken into account
+    %% twice, both as a component/alternative (passed as argument to
+    %% the encode/decode function), and within the encode decode
+    %% function itself.
     NewType = Type#type{tag=[]},
     case {asn1ct:get_gen_state_field(active),
 	  asn1ct:get_tobe_refed_func(NewTname)} of
@@ -859,11 +852,7 @@ gen_encode_field_call(ObjName,FieldName,Type) ->
 			  X#tag.form,X#tag.number)||
 	      X <- OTag],
     case Type#typedef.name of
-	{primitive,bif} -> %%tag should be the primitive tag
-% 	    OTag = Def#type.tag,
-% 	    Tag = [encode_tag_val(decode_class(X#tag.class),
-% 				  X#tag.form,X#tag.number)||
-% 		      X <- OTag],
+	{primitive,bif} ->            %tag should be the primitive tag
 	    gen_encode_prim(ber,Def,{asis,lists:reverse(Tag)},
 			    "Val"),
 	    [];
@@ -901,12 +890,6 @@ gen_encode_default_call(ClassName,FieldName,Type) ->
 	#'Externaltypereference'{module=Emod,type=Etype} ->
 	    emit(["   '",Emod,"':'enc_",Etype,"'(Val, ",{asis,Tag},")",nl]),
 	    []
-% 	'ASN1_OPEN_TYPE' ->
-% 	    emit(["%% OPEN TYPE",nl]),
-% 	    gen_encode_prim(ber,
-% 			    Type#type{def='ASN1_OPEN_TYPE'},
-% 			    "TagIn","Val"),
-% 	    emit([".",nl])
     end.
     
 %%%%%%%%%%%%%%%%
@@ -987,24 +970,20 @@ emit_tlv_format(Bytes) ->
 
 notice_tlv_format_gen() ->
     Module = get(currmod),
-%    io:format("Noticed: ~p~n",[Module]),
     case get(tlv_format) of
 	{done,Module} ->
 	    ok;
-	_ -> % true or undefined
+	_ ->                                    % true or undefined
 	    put(tlv_format,true)
     end.
 
 emit_tlv_format_function() ->
     Module = get(currmod),
-%    io:format("Tlv formated: ~p",[Module]),
     case get(tlv_format) of
 	true ->
-%	    io:format(" YES!~n"),
 	    emit_tlv_format_function1(),
 	    put(tlv_format,{done,Module});
 	_ ->
-%	    io:format(" NO!~n"),
 	    ok
     end.
 emit_tlv_format_function1() ->
@@ -1093,12 +1072,6 @@ gen_decode_default_call(ClassName,FieldName,Bytes,Type) ->
 	    emit(["   '",Emod,"':'dec_",Etype,"'(",Bytes,", ",
 		  {asis,Tag},")",nl]),
 	    []
-% 	'ASN1_OPEN_TYPE' ->
-% 	    emit(["%% OPEN TYPE",nl]),
-% 	    gen_encode_prim(ber,
-% 			    Type#type{def='ASN1_OPEN_TYPE'},
-% 			    "TagIn","Val"),
-% 	    emit([".",nl])
     end.
 %%%%%%%%%%%
 
@@ -1137,7 +1110,6 @@ more_genfields([Field|Fields]) ->
 gen_objectset_code(Erules,ObjSet) ->
     ObjSetName = ObjSet#typedef.name,
     Def = ObjSet#typedef.typespec,
-%    {ClassName,ClassDef} = Def#'ObjectSet'.class,
     #'Externaltypereference'{module=ClassModule,
 			     type=ClassName} = Def#'ObjectSet'.class,
     ClassDef = asn1_db:dbget(ClassModule,ClassName),
@@ -1261,8 +1233,8 @@ gen_inlined_enc_funs1(Fields, [{typefield,Name,_}|Rest], ObjSetName,
 		end,
 		{Acc0,0};
 	    false ->
-		%% This field was not present in the object thus there
-		%% were no type in the table and we therefore generate
+		%% This field was not present in the object; thus, there
+		%% was no type in the table and we therefore generate
 		%% code that returns the input for application
 		%% treatment.
 		emit([indent(9),{asis,Name}," ->",nl]),
@@ -1300,7 +1272,6 @@ emit_inner_of_fun(TDef=#typedef{name={ExtMod,Name},typespec=Type},
 		  InternalDefFunName) ->
     OTag = Type#type.tag,
     Tag = [encode_tag_val(decode_class(X#tag.class),X#tag.form,X#tag.number)|| X <- OTag],
-% remove    Tag = [X#tag{class=decode_class(X#tag.class)}|| X <- OTag],
     case {ExtMod,Name} of
 	{primitive,bif} ->
 	    emit(indent(12)),
@@ -1315,16 +1286,10 @@ emit_inner_of_fun(TDef=#typedef{name={ExtMod,Name},typespec=Type},
 	    {[],0}
     end;
 emit_inner_of_fun(#typedef{name=Name},_) ->
-%    OTag = Type#type.tag,
-% remove    Tag = [X#tag{class=decode_class(X#tag.class)}|| X <- OTag],
-%    Tag = [encode_tag_val(decode_class(X#tag.class),X#tag.form,X#tag.number)|| X <- OTag],
     emit([indent(12),"'enc_",Name,"'(Val)"]),
     {[],0};
 emit_inner_of_fun(Type,_) when is_record(Type,type) ->
     CurrMod = get(currmod),
-%    OTag = Type#type.tag,
-% remove    Tag = [X#tag{class=decode_class(X#tag.class)}|| X <- OTag],
-%    Tag = [encode_tag_val(decode_class(X#tag.class),X#tag.form,X#tag.number)|| X <- OTag],
     case Type#type.def of
 	Def when is_atom(Def) ->
 	    OTag = Type#type.tag,
@@ -1474,7 +1439,6 @@ emit_dec_open_type(I) ->
 emit_inner_of_decfun(#typedef{name={ExtName,Name},typespec=Type}, _Prop,
 		     InternalDefFunName) ->
     OTag = Type#type.tag,
-%%    Tag = [X#tag{class=decode_class(X#tag.class)}|| X <- OTag],
     Tag = [(decode_class(X#tag.class) bsl 10) + X#tag.number || X <- OTag],
     case {ExtName,Name} of
 	{primitive,bif} ->
@@ -1483,8 +1447,6 @@ emit_inner_of_decfun(#typedef{name={ExtName,Name},typespec=Type}, _Prop,
 	    0;
 	{constructed,bif} ->
 	    emit([indent(12),"'dec_",
-% 		  asn1ct_gen:list2name(InternalDefFunName),"'(Bytes, ",Prop,
-% 		  ", ",{asis,Tag},")"]),
  		  asn1ct_gen:list2name(InternalDefFunName),"'(Bytes, ",
 		  {asis,Tag},")"]),
 	    1;
@@ -1498,7 +1460,6 @@ emit_inner_of_decfun(#typedef{name=Name},_Prop,_) ->
     0;
 emit_inner_of_decfun(#type{}=Type, _Prop, _) ->
     OTag = Type#type.tag,
-%%    Tag = [X#tag{class=decode_class(X#tag.class)}|| X <- OTag],
     Tag = [(decode_class(X#tag.class) bsl 10) + X#tag.number || X <- OTag],
     CurrMod = get(currmod),
     Def = Type#type.def,
@@ -1510,11 +1471,9 @@ emit_inner_of_decfun(#type{}=Type, _Prop, _) ->
 	    gen_dec_prim(Type, "Bytes", Tag);
 	#'Externaltypereference'{module=CurrMod,type=T} ->
 	    emit([indent(9),T," ->",nl,indent(12),"'dec_",T,
-%		  "'(Bytes, ",Prop,")"]);
 		  "'(Bytes)"]);
 	#'Externaltypereference'{module=ExtMod,type=T} ->
 	    emit([indent(9),T," ->",nl,indent(12),ExtMod,":'dec_",
-%		  T,"'(Bytes, ",Prop,")"])
 		  T,"'(Bytes, ",{asis,Tag},")"])
     end,
     0.
@@ -1580,7 +1539,7 @@ encode_tag_val(Class, Form, TagNo) ->
 
 %%%%%%%%%%% 
 %% mk_object_val(Value) -> {OctetList, Len} 
-%% returns a Val as a list of octets, the 8 bit is allways set to one except 
+%% returns a Val as a list of octets, the 8 bit is always set to one except
 %% for the last octet, where its 0 
 %% 
 
@@ -1594,8 +1553,9 @@ mk_object_val(0, Ack, Len) ->
 mk_object_val(Val, Ack, Len) -> 
     mk_object_val(Val bsr 7, [((Val band 127) bor 128) | Ack], Len + 1). 
 
-%% For BER the ExtensionAdditionGroup notation has no impact on the encoding/decoding
-%% and therefore we only filter away the ExtensionAdditionGroup start and end markers
+%% For BER the ExtensionAdditionGroup notation has no impact on the
+%% encoding/decoding. Therefore we can filter away the
+%% ExtensionAdditionGroup start and end markers.
 extaddgroup2sequence(ExtList) when is_list(ExtList) ->
     lists:filter(fun(#'ExtensionAdditionGroup'{}) ->
 			 false;
diff --git a/lib/asn1/src/asn1ct_gen_per.erl b/lib/asn1/src/asn1ct_gen_per.erl
index 79e58395c..645e0e3ae 100644
--- a/lib/asn1/src/asn1ct_gen_per.erl
+++ b/lib/asn1/src/asn1ct_gen_per.erl
@@ -24,7 +24,6 @@
 %% all types in an ASN.1 module
 
 -include("asn1_records.hrl").
-%-compile(export_all).
 
 -export([gen_dec_imm/2]).
 -export([gen_dec_prim/3,gen_encode_prim_imm/3]).
@@ -39,8 +38,9 @@
 -import(asn1ct_func, [call/3]).
 
 
-%% Generate ENCODING ******************************
-%%****************************************x
+%%****************************************
+%% Generate ENCODING
+%%****************************************
 
 dialyzer_suppressions(#gen{erule=per,aligned=Aligned}) ->
     Mod = case Aligned of
@@ -58,14 +58,6 @@ dialyzer_suppressions(#gen{erule=per,aligned=Aligned}) ->
 
 gen_encode(Erules,Type) when is_record(Type,typedef) ->
     gen_encode_user(Erules,Type).
-%%    case Type#typedef.typespec of
-%%	Def when is_record(Def,type) ->	    
-%%	    gen_encode_user(Erules,Type);
-%%	Def when is_tuple(Def),(element(1,Def) == 'Object') ->
-%%	    gen_encode_object(Erules,Type);
-%%	Other ->
-%%	    exit({error,{asn1,{unknown,Other}}})
-%%    end.
 
 gen_encode(Erules,Typename,#'ComponentType'{name=Cname,typespec=Type}) ->
     NewTypename = [Cname|Typename],
@@ -76,7 +68,6 @@ gen_encode(Erules,Typename,Type) when is_record(Type,type) ->
     ObjFun =
 	case lists:keysearch(objfun,1,Type#type.tablecinf) of
 	    {value,{_,_Name}} ->
-%%		lists:concat([", ObjFun",Name]);
 		", ObjFun";
 	    false ->
 		""
@@ -396,10 +387,11 @@ gen_dec_prim(Erule, Type, BytesVar) ->
     asn1ct_imm:dec_code_gen(Imm, BytesVar).
 
 
-%% For PER the ExtensionAdditionGroup notation has significance for the encoding and decoding
-%% the components within the ExtensionAdditionGroup is treated in a similar way as if they
-%% have been specified within a SEQUENCE, therefore we construct a fake sequence type here
-%% so that we can generate code for it
+%% For PER the ExtensionAdditionGroup notation has significance for
+%% the encoding and decoding. The components within the
+%% ExtensionAdditionGroup is treated in a similar way as if they have
+%% been specified within a SEQUENCE. Therefore we construct a fake
+%% sequence type here so that we can generate code for it.
 extaddgroup2sequence(ExtList) ->
     extaddgroup2sequence(ExtList,0,[]).
 
diff --git a/lib/asn1/src/asn1ct_name.erl b/lib/asn1/src/asn1ct_name.erl
index 72d541cbb..06f6604a2 100644
--- a/lib/asn1/src/asn1ct_name.erl
+++ b/lib/asn1/src/asn1ct_name.erl
@@ -20,7 +20,6 @@
 %%
 -module(asn1ct_name).
 
-%%-compile(export_all).
 -export([start/0,
 	 curr/1,
 	 clear/0,
@@ -44,7 +43,6 @@ start() ->
     end.
 
 name_server_loop({Ref, Parent} = Monitor,Vars) ->
-%%    io:format("name -- ~w~n",[Vars]),
     receive
 	{_From,clear} ->
 	    name_server_loop(Monitor, []);
diff --git a/lib/asn1/src/asn1ct_parser2.erl b/lib/asn1/src/asn1ct_parser2.erl
index 2de9b0e2f..3f1819b66 100644
--- a/lib/asn1/src/asn1ct_parser2.erl
+++ b/lib/asn1/src/asn1ct_parser2.erl
@@ -1496,7 +1496,7 @@ parse_ContentsConstraint([{'ENCODED',_},{'BY',_}|Rest]) ->
 parse_ContentsConstraint(Tokens) ->
     parse_error(Tokens).
 
-% X.683 Parameterization of ASN.1 specifications
+%% X.683 Parameterization of ASN.1 specifications
 
 parse_Governor(Tokens) ->
     Flist = [fun parse_Type/1,
diff --git a/lib/asn1/src/asn1ct_value.erl b/lib/asn1/src/asn1ct_value.erl
index 8bd99d995..d1f5ce5c9 100644
--- a/lib/asn1/src/asn1ct_value.erl
+++ b/lib/asn1/src/asn1ct_value.erl
@@ -24,12 +24,12 @@
 %%  The value is randomized within it's constraints
 
 -include("asn1_records.hrl").
-%-compile(export_all).
 
 -export([from_type/2]).
 
-%% Generate examples of values ******************************
-%%****************************************x
+%%****************************************
+%% Generate examples of values
+%%****************************************
 
 
 from_type(M,Typename) ->
@@ -92,9 +92,6 @@ get_inner(T) when is_tuple(T) ->
 	Other ->
 	    Other
     end.
-%%get_inner(T) when is_tuple(T) -> element(1,T).
-
-
 
 from_type_constructed(M,Typename,InnerType,D) when is_record(D,type) ->
     case InnerType of
@@ -147,7 +144,8 @@ get_choice(M,Typename,Type) ->
     case TCompList of
 	[] -> 
 	    {asn1_EMPTY,asn1_EMPTY};
-	{CompList,ExtList} -> % Should be enhanced to handle extensions too
+	{CompList,ExtList} ->
+            %% should be enhanced to handle extensions too.
 	    CList = CompList ++ ExtList,
 	    C = lists:nth(random(length(CList)),CList),
 	    {C#'ComponentType'.name,from_type(M,Typename,C)};
@@ -247,14 +245,6 @@ from_type_prim(M, D) ->
 			_ ->
 			    {2#11111111,2,2}
 		    end;
-%% 		    Sign1 = random_sign(integer),
-%% 		    Sign2 = random_sign(integer),
-%% 		    {Sign1*random(10000),2,Sign2*random(1028)};
-%% 		2 ->
-%% 		    %% base 10 tuple format
-%% 		    Sign1 = random_sign(integer),
-%% 		    Sign2 = random_sign(integer),
-%% 		    {Sign1*random(10000),10,Sign2*random(1028)};
 		_ ->
 		    %% base 10 string format, NR3 format
 		    case random(2) of
@@ -343,22 +333,6 @@ random_unnamed_bit_string(M, C) ->
 	    {PadLen,<<BitString/bitstring,0:PadLen>>}
     end.
 
-%% FIXME:
-%% random_sign(integer) ->
-%%     case random(2) of
-%% 	2 ->
-%% 	    -1;
-%% 	_ ->
-%% 	    1
-%%     end;
-%% random_sign(string) ->
-%%     case random(2) of
-%% 	2 ->
-%% 	    "-";
-%% 	_ ->
-%% 	    ""
-%%     end.
-
 random(Upper) ->
     rand:uniform(Upper).
 
@@ -409,13 +383,6 @@ c_random(VRange,Single) ->
 	    S;
 	{_,S} when is_list(S) ->
 	    lists:nth(random(length(S)),S)
-%%	{S1,S2} ->
-%%	    io:format("asn1ct_value: hejsan hoppsan~n");
-%%	_ ->
-%%	    io:format("asn1ct_value: hejsan hoppsan 2~n")
-%%	    io:format("asn1ct_value: c_random/2: S1 = ~w~n"
-%%		      "S2 = ~w,~n",[S1,S2])
-%%	    exit(self(),goodbye)
     end.
 
 adjust_list(Len,Orig) ->
diff --git a/lib/asn1/src/asn1rtt_ber.erl b/lib/asn1/src/asn1rtt_ber.erl
index fdb9b9061..882a25c33 100644
--- a/lib/asn1/src/asn1rtt_ber.erl
+++ b/lib/asn1/src/asn1rtt_ber.erl
@@ -92,7 +92,7 @@
 -define(N_BMPString, 30).
 
 
-% the complete tag-word of built-in types
+%% The complete tag-word of built-in types
 -define(T_BOOLEAN,          ?UNIVERSAL bor ?PRIMITIVE bor 1).
 -define(T_INTEGER,          ?UNIVERSAL bor ?PRIMITIVE bor 2).
 -define(T_BIT_STRING,       ?UNIVERSAL bor ?PRIMITIVE bor 3). % can be CONSTRUCTED
@@ -137,11 +137,11 @@ ber_decode_erlang(Tlv) ->
 decode_primitive(Bin) ->
     {Form,TagNo,V,Rest} = decode_tag_and_length(Bin),
     case Form of
-	1 -> % constructed
+	1 ->                                    % constructed
 	    {{TagNo,decode_constructed(V)},Rest};
-	0 -> % primitive
+	0 ->                                    % primitive
 	    {{TagNo,V},Rest};
-	2 -> % constructed indefinite
+	2 ->                                  % constructed indefinite
 	    {Vlist,Rest2} = decode_constructed_indefinite(V,[]),
 	    {{TagNo,Vlist},Rest2}
     end.
@@ -165,31 +165,30 @@ decode_primitive_incomplete([[default,TagNo]],Bin) -> %default
 	{Form,TagNo,V,Rest} ->
 	    decode_incomplete2(Form,TagNo,V,[],Rest);
 	_ ->
-	    %{asn1_DEFAULT,Bin}
 	    asn1_NOVALUE
     end;
-decode_primitive_incomplete([[default,TagNo,Directives]],Bin) -> %default, constructed type, Directives points into this type
+decode_primitive_incomplete([[default,TagNo,Directives]],Bin) ->
+    %% default, constructed type, Directives points into this type
     case decode_tag_and_length(Bin) of
 	{Form,TagNo,V,Rest} ->
 	    decode_incomplete2(Form,TagNo,V,Directives,Rest);
 	_ ->
-	    %{asn1_DEFAULT,Bin}
 	    asn1_NOVALUE
     end;
-decode_primitive_incomplete([[opt,TagNo]],Bin) -> %optional
+decode_primitive_incomplete([[opt,TagNo]],Bin) ->
+    %% optional
     case decode_tag_and_length(Bin) of
 	{Form,TagNo,V,Rest} ->
 	    decode_incomplete2(Form,TagNo,V,[],Rest);
 	_ ->
-	    %{{TagNo,asn1_NOVALUE},Bin}
 	    asn1_NOVALUE
     end;
-decode_primitive_incomplete([[opt,TagNo,Directives]],Bin) -> %optional
+decode_primitive_incomplete([[opt,TagNo,Directives]],Bin) ->
+    %% optional
     case decode_tag_and_length(Bin) of
 	{Form,TagNo,V,Rest} ->
 	    decode_incomplete2(Form,TagNo,V,Directives,Rest);
 	_ ->
-	    %{{TagNo,asn1_NOVALUE},Bin}
 	    asn1_NOVALUE
     end;
 %% An optional that shall be undecoded
@@ -236,7 +235,8 @@ decode_primitive_incomplete([[alt_parts,TagNo]|RestAlts],Bin) ->
 	_ ->
 	    decode_primitive_incomplete(RestAlts,Bin)
     end;
-decode_primitive_incomplete([[undec,_TagNo]|_RestTag],Bin) -> %incomlete decode
+decode_primitive_incomplete([[undec,_TagNo]|_RestTag],Bin) ->
+    %% incomlete decode
     decode_incomplete_bin(Bin);
 decode_primitive_incomplete([[parts,TagNo]|_RestTag],Bin) ->
     case decode_tag_and_length(Bin) of
@@ -301,7 +301,8 @@ decode_constructed_incomplete(Directives=[[Alt,_]|_],Bin)
 	    {TagNo,Tlv};
 	{alt_parts,_} ->
 	    [{TagNo,decode_parts_incomplete(V)}];
-	no_match -> %% if a choice alternative was encoded that
+	no_match ->
+            %% if a choice alternative was encoded that
 	    %% was not specified in the config file,
 	    %% thus decode component anonomous.
 	    {Tlv,_}=decode_primitive(Bin),
@@ -546,7 +547,7 @@ decode_tag_and_length(<<Class:2, Form:1, 31:5, Buffer/binary>>) ->
 decode_tag(<<0:1,PartialTag:7, Buffer/binary>>, TagAck) ->
     TagNo = (TagAck bsl 7) bor PartialTag,
     {TagNo, Buffer};
-% more tags
+%% more tags
 decode_tag(<<_:1,PartialTag:7, Buffer/binary>>, TagAck) ->
     TagAck1 = (TagAck bsl 7) bor PartialTag,
     decode_tag(Buffer, TagAck1).
@@ -941,12 +942,12 @@ encode_bit_string_bits(C, BitListVal, _NamedBitList, TagIn) when is_list(BitList
 	    case length(BitListVal) of
 		BitSize when BitSize == Size ->
 		    {Len, Unused, OctetList} = encode_bitstring(BitListVal),
-		    %%add unused byte to the Len
+		    %% add unused byte to the Len
 		    encode_tags(TagIn, [Unused | OctetList], Len+1);
 		BitSize when BitSize < Size ->
 		    PaddedList = pad_bit_list(Size-BitSize,BitListVal),
 		    {Len, Unused, OctetList} = encode_bitstring(PaddedList),
-		    %%add unused byte to the Len
+		    %% add unused byte to the Len
 		    encode_tags(TagIn, [Unused | OctetList], Len+1);
 		BitSize ->
 		    exit({error,{asn1,
-- 
2.12.0

openSUSE Build Service is sponsored by