1%%
2%% %CopyrightBegin%
3%%
4%% Copyright Ericsson AB 1997-2016. All Rights Reserved.
5%%
6%% Licensed under the Apache License, Version 2.0 (the "License");
7%% you may not use this file except in compliance with the License.
8%% You may obtain a copy of the License at
9%%
10%%     http://www.apache.org/licenses/LICENSE-2.0
11%%
12%% Unless required by applicable law or agreed to in writing, software
13%% distributed under the License is distributed on an "AS IS" BASIS,
14%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
15%% See the License for the specific language governing permissions and
16%% limitations under the License.
17%%
18%% %CopyrightEnd%
19%%
20%%
21-module(iceval).
22
23-include("icforms.hrl").
24
25-export([eval_const/5, eval_e/5]).
26
27-export([check_tk/3, get_val/1, mk_val/1]).
28
29-define(get_max(__X, __Y), if __X > __Y -> __X; true -> __Y end).
30-define(get_min(__X, __Y), if __X > __Y -> __Y; true -> __X end).
31
32-define(BASE, 100000000000000000000000000000000).
33-define(FIXED_MAX, 9999999999999999999999999999999).
34
35%% Called fr: ictype 99, 522, 533
36%% Fixed constants can be declared as:
37%% (1)  const fixed pi = 3.14D; or
38%% (2)  typedef fixed<3,2> f32;
39%%      const f32 pi = 3.14D;
40%% Hence, if fixed is declared as (1) we must handle it especially.
41eval_const(G, S, N, tk_fixed, Expr) ->
42    case catch eval_e(G, S, N, tk_fixed, Expr) of
43	T when element(1, T) == error -> 0;
44	V when is_record(V, fixed) ->
45	    {ok, {tk_fixed, V#fixed.digits, V#fixed.scale}, V};
46	V ->
47	    ic_error:error(G, {bad_tk_match, Expr, tk_fixed, get_val(V)})
48    end;
49eval_const(G, S, N, TK, Expr) ->
50    case catch eval_e(G, S, N, TK, Expr) of
51	T when element(1, T) == error -> 0;
52	V ->
53	    case check_tk(G, TK, V) of
54		true -> ok;
55		false ->
56		    ic_error:error(G, {bad_tk_match, Expr, TK, get_val(V)})
57	    end,
58	    get_val(V)
59    end.
60
61
62check_op(G, S, N, Tk, Types, Op, E1, E2) ->
63    V1 = eval_e(G, S, N, Tk, E1),
64    V2 = eval_e(G, S, N, Tk, E2),
65    check_types(G, Op, E1, Types, V1),
66    check_types(G, Op, E2, Types, V2),
67    case check_comb(V1, V2) of
68	true ->
69	    {V1, V2};
70	false ->
71	    Err = {bad_type_combination, E1, get_val(V1), get_val(V2)},
72	    ic_error:error(G, Err),
73	    throw({error, Err})
74    end.
75
76check_op(G, S, N, Tk, Types, Op, E1) ->
77    V1 = eval_e(G, S, N, Tk, E1),
78    check_types(G, Op, E1, Types, V1),
79    V1.
80
81%% Match the declared type TK against the factual value of an constant
82%%
83check_tk(_G, _Any, default) -> true;		% Default case in union
84check_tk(_G, positive_int, V) when is_integer(V) andalso V >= 0 -> true;
85check_tk(_G, tk_long, V) when is_integer(V) -> true;
86check_tk(_G, tk_longlong, V) when is_integer(V) -> true;  %% LLON_G
87check_tk(_G, tk_short, V) when is_integer(V) -> true;
88check_tk(_G, tk_ushort, V) when is_integer(V) andalso V >= 0 -> true;
89check_tk(_G, tk_ulong, V) when is_integer(V) andalso V >= 0 -> true;
90check_tk(_G, tk_ulonglong, V) when is_integer(V) andalso V >= 0 -> true;  %% ULLON_G
91check_tk(_G, tk_float, V) when is_float(V) -> true;
92check_tk(_G, tk_double, V) when is_float(V) -> true;
93check_tk(_G, tk_boolean, V) -> is_bool(V);
94check_tk(_G, tk_char, {char, _V}) -> true;
95check_tk(_G, tk_wchar, {wchar, _V}) -> true; %% WCHAR
96check_tk(_G, {tk_string, _Len}, {string, _V}) -> true;
97check_tk(_G, {tk_wstring, _Len}, {wstring, _V}) -> true;  %% WSTRING
98check_tk(_G, {tk_fixed, Digits, Scale}, {fixed, Digits, Scale, _V}) -> true;
99check_tk(_G, tk_octet, V) when is_integer(V) -> true;
100%%check_tk(_G, tk_null, V) when integer(V) -> true;
101%%check_tk(_G, tk_void, V) when integer(V) -> true;
102%%check_tk(_G, tk_any, V) when integer(V) -> true;
103%%check_tk(_G, {tk_objref, "", "Object"}, V) when integer(V) -> true.
104check_tk(_G, {tk_enum, _, _, Body}, {enum_id, Id}) ->
105    until(fun(X) when X == Id -> true;
106	     (_X) ->
107		  false
108	  end, Body);
109check_tk(_G, _TK, _V) ->
110    false.
111
112get_val({string, X}) -> X;
113get_val({wstring, X}) -> X;  %% WCHAR
114get_val({char, X}) -> X;
115get_val({wchar, X}) -> X;  %% WSTRING
116get_val({enum_id, X}) -> X;
117get_val(X) -> X.
118
119check_types(G, Op, Expr, TypeList, V) ->
120    case until(fun(int) when is_integer(V) -> true;
121		  (float) when is_float(V) -> true;
122		  (bool) when V==true -> true;
123		  (bool) when V==false -> true;
124		  (fixed) when is_record(V, fixed) -> true;
125		  (_) -> false end,
126	       TypeList) of
127	true -> true;
128	false ->
129	    Err = {bad_type, Expr, Op, TypeList, V},
130	    ic_error:error(G, Err),
131	    throw({error, Err})
132    end.
133
134%%get_op(T) when tuple(T) -> element(1, T).
135
136%% Should be in lists
137until(F, [H|T]) ->
138    case F(H) of
139	true -> true;
140	false -> until(F, T)
141    end;
142until(_F, []) -> false.
143
144%% Section of all the boolean operators (because Erlang ops don't like
145%% boolean values.
146e_or(X, Y) when is_integer(X) andalso is_integer(Y) -> X bor Y;
147e_or(true, _) -> true;
148e_or(_, true) -> true;
149e_or(_, _) -> false.
150
151e_and(X, Y) when is_integer(X) andalso is_integer(Y) -> X band Y;
152e_and(true, true) -> true;
153e_and(_, _) -> false.
154
155e_xor(X, Y) when is_integer(X) andalso is_integer(Y) -> X bxor Y;
156e_xor(X, X) -> false;
157e_xor(_, _) -> true.
158
159%% Handling infix operators (+,-,*,/) for fixed type.
160%% Boundries determined as fixed<max(d1-s1,d2-s2) + max(s1,s2) + 1, max(s1,s2)>
161e_fixed_add(#fixed{digits = D1, scale = S1, value = V1},
162	    #fixed{digits = D2, scale = S2, value = V2}) ->
163    Scale = ?get_max(S1, S2),
164    Digits = ?get_max((D1-S1), (D2-S2)) + Scale +1,
165    %% We must normalize the values before adding. Why?
166    %% 4.23 and 5.2 are represented as 423 and 52. To be able to get the
167    %% correct result we must add 4230 and 5200 == 9430.
168    {PV1, PV2} = normalize(S1, V1, S2, V2),
169    check_fixed_overflow(#fixed{digits = Digits,
170				scale = Scale,
171				value = (PV1 + PV2)}).
172
173%% Boundries determined as fixed<max(d1-s1,d2-s2) + max(s1,s2) + 1, max(s1,s2)>
174e_fixed_sub(#fixed{digits = D1, scale = S1, value = V1},
175	    #fixed{digits = D2, scale = S2, value = V2}) ->
176    Scale = ?get_max(S1, S2),
177    Digits = ?get_max((D1-S1), (D2-S2)) + Scale +1,
178    {PV1, PV2} = normalize(S1, V1, S2, V2),
179    check_fixed_overflow(#fixed{digits = Digits,
180				scale = Scale,
181				value = (PV1 - PV2)}).
182
183%% Boundries determined as fixed<d1+d2, s1+s2>
184e_fixed_mul(#fixed{digits = D1, scale = S1, value = V1},
185	    #fixed{digits = D2, scale = S2, value = V2}) ->
186    check_fixed_overflow(#fixed{digits = (D1+D2),
187				scale = (S1+S2),
188				value = V1*V2}).
189
190%% Boundries determined as fixed<(d1-s1+s2) + s inf ,s inf>
191e_fixed_div(#fixed{digits = D1, scale = S1, value = V1},
192	    #fixed{digits = _D2, scale = S2, value = V2}) ->
193    {PV1, PV2} = normalize(S1, V1, S2, V2),
194    DigitsMin = (D1-S1+S2),
195    R1 = (PV1 div PV2),
196    R2 = (R1*?BASE + (PV1 rem PV2) * (?BASE div PV2)),
197    {Result2, Sinf} = delete_zeros_value(R2, 0, R1),
198    check_fixed_overflow(#fixed{digits = DigitsMin + Sinf, scale = Sinf,
199				value = Result2}).
200
201
202%% Checks combination of argument types, basically floats and ints are
203%% interchangeable, and all types are allowed with themselves. No
204%% other combinations are allowed
205%%
206check_comb(X, Y) when is_integer(X) andalso is_integer(Y) -> true;
207check_comb(X, Y) when is_float(X) andalso is_integer(Y) -> true;
208check_comb(X, Y) when is_integer(X) andalso is_float(Y) -> true;
209check_comb(X, Y) when is_float(X) andalso is_float(Y) -> true;
210check_comb({X, _}, {X, _}) -> true;		% Strings and chars are tuples
211check_comb({fixed, _, _, _}, {fixed, _, _, _}) -> true;
212check_comb(X, Y) ->
213    case {is_bool(X), is_bool(Y)} of
214	{true, true} ->
215	    true;
216	_ ->
217	    false
218    end.
219
220is_bool(true) -> true;
221is_bool(false) -> true;
222is_bool(_) -> false.
223
224
225%%%% (15)
226eval_e(G, S, N, Tk, {'or', T1, T2}) ->
227    {E1, E2} = check_op(G, S, N, Tk, [int, bool], 'or', T1, T2),
228    e_or(E1, E2);
229
230%%%% (16)
231eval_e(G, S, N, Tk, {'xor', T1, T2}) ->
232    {E1, E2} = check_op(G, S, N, Tk, [int, bool], 'xor', T1, T2),
233    e_xor(E1, E2);
234
235%%%% (17)
236eval_e(G, S, N, Tk, {'and', T1, T2}) ->
237    {E1, E2} = check_op(G, S, N, Tk, [int, bool], 'and', T1, T2),
238    e_and(E1, E2);
239
240%%%% (18)
241eval_e(G, S, N, Tk, {'rshift', T1, T2}) ->
242    {E1, E2} = check_op(G, S, N, Tk,  [int], 'rshift', T1, T2),
243    E1 bsr E2;
244eval_e(G, S, N, Tk, {'lshift', T1, T2}) ->
245    {E1, E2} = check_op(G, S, N, Tk, [int], 'lshift', T1, T2),
246    E1 bsl E2;
247
248%%%% (19)
249eval_e(G, S, N, Tk, {'+', T1, T2}) ->
250    case check_op(G, S, N, Tk, [int, float, fixed], '+', T1, T2) of
251	{F1, F2} when is_record(F1,fixed) andalso is_record(F2,fixed) ->
252	    e_fixed_add(F1, F2);
253	{E1, E2} ->
254	    E1 + E2
255    end;
256eval_e(G, S, N, Tk, {'-', T1, T2}) ->
257    case check_op(G, S, N, Tk, [int, float, fixed], '-', T1, T2) of
258	{F1, F2} when is_record(F1,fixed) andalso is_record(F2,fixed) ->
259	    e_fixed_sub(F1, F2);
260	{E1, E2} ->
261	    E1 - E2
262    end;
263
264%%%% (20)
265eval_e(G, S, N, Tk, {'*', T1, T2}) ->
266    case check_op(G, S, N, Tk, [int, float, fixed], '*', T1, T2) of
267	{F1, F2} when is_record(F1,fixed) andalso is_record(F2,fixed) ->
268	    e_fixed_mul(F1, F2);
269	{E1, E2} ->
270	    E1 * E2
271    end;
272eval_e(G, S, N, Tk, {'/', T1, T2}) ->
273    case check_op(G, S, N, Tk, [int, float, fixed], '/', T1, T2) of
274	{F1, F2} when is_record(F1,fixed) andalso is_record(F2,fixed) ->
275	    e_fixed_div(F1, F2);
276	{E1, E2} ->
277	    E1 / E2
278    end;
279eval_e(G, S, N, Tk, {'%', T1, T2}) ->
280    {E1, E2} = check_op(G, S, N, Tk, [int], '%', T1, T2),
281    E1 rem E2;
282
283%%%% (21)
284eval_e(G, S, N, Tk, {{'-', _Line}, T}) ->
285    case check_op(G, S, N, Tk, [int, float, fixed], '-', T) of
286	F when is_record(F,fixed) ->
287	    F#fixed{value = -(F#fixed.value)};
288	Number ->
289	    -Number
290    end;
291eval_e(G, S, N, Tk, {{'+', _Line}, T}) ->
292    check_op(G, S, N, Tk, [int, float, fixed], '+', T);
293eval_e(G, S, N, Tk, {{'~', Line}, T}) ->
294    ic_error:error(G, {unsupported_op, {'~', Line}}),
295    eval_e(G, S, N, Tk, T);
296
297
298%% Ints are repr. by an Erlang integer val, floats and doubles by
299%% Erlang floats, chars and strings must be tuplerized for type
300%% checking. These tuples are removed just before returning from top
301%% function.
302%%
303eval_e(_G, _S, _N, tk_fixed, {'<fixed_pt_literal>', _Line, X}) ->
304    create_fixed(X);
305eval_e(G, _S, _N, {tk_fixed, Digits, Scale}, {'<fixed_pt_literal>', Line, X})
306  when Digits < 32, Digits >= Scale ->
307    case convert_fixed(X, [], Digits, Digits-Scale) of
308	{error, Format, Args} ->
309	    ic_error:error(G, {bad_fixed, Format, Args, Line});
310	FixedData ->
311	    {fixed, Digits, Scale, FixedData}
312    end;
313eval_e(_G, _S, _N, _Tk, {'<integer_literal>', _Line, X}) -> list_to_integer(X);
314eval_e(_G, _S, _N, {tk_string,_}, {'<string_literal>', _Line, X}) -> {string, X};
315eval_e(_G, _S, _N, {tk_wstring,_}, {'<wstring_literal>', _Line, X}) -> {wstring, X}; %% WSTRING
316eval_e(_G, _S, _N, tk_char, {'<character_literal>', _Line, X}) -> {char, hd(X)};
317eval_e(_G, _S, _N, tk_wchar, {'<wcharacter_literal>', _Line, X}) -> {wchar, hd(X)}; %% WCHAR
318eval_e(_G, _S, _N, _Tk, {'TRUE', _Line}) -> true;
319eval_e(_G, _S, _N, _Tk, {'FALSE', _Line}) -> false;
320eval_e(_G, _S, _N, _Tk, {'<floating_pt_literal>', _Line, X}) -> to_float(X);
321%% Some possible error conditions
322eval_e(_G, _S, _N, _Tk, {'<character_literal>', _Line, X}) -> {char, hd(X)}; %% ERROR?
323%%
324eval_e(G, S, N, _Tk, X) when element(1, X) == scoped_id ->
325    mk_val(ictype:scoped_lookup(G, S, N, X));
326eval_e(_G, _S, _N, _Tk, {default, _}) -> default;	% Default case in union
327eval_e(G, _S, _N, Tk, Val) ->
328    ic_error:error(G, {plain_error_string, Val,
329		       io_lib:format("value and declared type ~p differ", [Tk])}).
330
331%% A fixed type can be 123.45 or 123 but we represent it as integers (i.e. 12345 or 123).
332convert_fixed([], Acc, 0, _) ->
333    list_to_integer(lists:reverse(Acc));
334convert_fixed([], _Acc, _, _) ->
335    {error, "Fixed type do not match the digits field", []};
336convert_fixed([$.|Rest], Acc, Digits, 0) ->
337    convert_fixed(Rest, Acc, Digits, -1);
338convert_fixed([$.|_Rest], _Acc, _, _) ->
339    {error, "Fixed decimal point placed incorrectly", []};
340convert_fixed([X|Rest], Acc, Digits, Position) ->
341    convert_fixed(Rest, [X|Acc], Digits-1, Position-1).
342
343
344create_fixed([$0|Rest]) ->
345    %% Leading zeros shall be ignored.
346    create_fixed(Rest);
347create_fixed(Fixed) ->
348    create_fixed(Fixed, [], 0, 0, false).
349
350create_fixed([], Acc, Total, Frac, true) ->
351    {Fixed, N} = remove_trailing_zeros(Acc, 0),
352    Digits = Total-N,
353    Scale = Frac-N,
354    #fixed{digits = Digits, scale = Scale, value = list_to_integer(Fixed)};
355create_fixed([], Acc, Total, _Frac, false) ->
356    %% A '.' never found. Hence, must be 2000D
357    #fixed{digits = Total, scale = 0, value = list_to_integer(lists:reverse(Acc))};
358create_fixed([$.|Rest], Acc, Total, _, _) ->
359    create_fixed(Rest, Acc, Total, 0, true);
360create_fixed([X|Rest], Acc, Total, Frac, FoundDot) ->
361    create_fixed(Rest, [X|Acc], Total+1, Frac+1, FoundDot).
362
363remove_trailing_zeros([$0|Rest], N) ->
364    remove_trailing_zeros(Rest, N+1);
365remove_trailing_zeros(Fixed, N) ->
366    {lists:reverse(Fixed), N}.
367
368%% Make the newly looked up value a value that can be type checked.
369mk_val({_, _, {tk_string, _}, V}) -> {string, V};
370mk_val({_, _, {tk_wstring, _}, V}) -> {wstring, V};  %% WSTRING
371mk_val({_, _, tk_char, V}) -> {char, V};
372mk_val({_, _, tk_wchar, V}) -> {wchar, V}; %% WCHAR
373mk_val({_, _, enum_val, V}) ->
374    {enum_id, ic_forms:get_id2(V)};
375mk_val(X) when element(1, X) == error -> X;
376mk_val({_, _, _TK, V}) ->
377    V;
378mk_val(V) -> V.
379
380
381
382%% Floating point numbers
383%%
384%%	Conversion to Erlang floating points is neccessary because
385%%	list_to_float BIF differs from IDL floats. "1e2" ".4e2" is
386%%	allowed in IDL and must be translated to "1.0e2" and "0.4e2"
387
388to_float(X) ->
389    list_to_float(erlangify(X)).
390
391erlangify([$. | R]) ->
392    [$0, $. | R];
393erlangify(R) ->
394    look_for_dot(R).
395
396look_for_dot([$. | R]) -> [$. | dot_pending(R)];
397look_for_dot([$e | R]) -> [$., $0, $e | R];
398look_for_dot([$E | R]) -> [$., $0, $E | R];
399look_for_dot([X | R]) -> [X | look_for_dot(R)].
400
401dot_pending([$e | R]) -> [$0, $e | R];
402dot_pending([$E | R]) -> [$0, $E | R];
403dot_pending([]) -> [$0];
404dot_pending(R) -> R.
405
406
407%%------------------------------------------------------------------
408%%--------------- Fixed Datatype Helper Functions ------------------
409%%------------------------------------------------------------------
410%% Pretty?! No, but since we now the upper-limit this is the fastest way
411%% to calculate 10^x
412power(0) ->  1;
413power(1) ->  10;
414power(2) ->  100;
415power(3) ->  1000;
416power(4) ->  10000;
417power(5) ->  100000;
418power(6) ->  1000000;
419power(7) ->  10000000;
420power(8) ->  100000000;
421power(9) ->  1000000000;
422power(10) -> 10000000000;
423power(11) -> 100000000000;
424power(12) -> 1000000000000;
425power(13) -> 10000000000000;
426power(14) -> 100000000000000;
427power(15) -> 1000000000000000;
428power(16) -> 10000000000000000;
429power(17) -> 100000000000000000;
430power(18) -> 1000000000000000000;
431power(19) -> 10000000000000000000;
432power(20) -> 100000000000000000000;
433power(21) -> 1000000000000000000000;
434power(22) -> 10000000000000000000000;
435power(23) -> 100000000000000000000000;
436power(24) -> 1000000000000000000000000;
437power(25) -> 10000000000000000000000000;
438power(26) -> 100000000000000000000000000;
439power(27) -> 1000000000000000000000000000;
440power(28) -> 10000000000000000000000000000;
441power(29) -> 100000000000000000000000000000;
442power(30) -> 1000000000000000000000000000000;
443power(31) -> 10000000000000000000000000000000;
444power(_) ->  10000000000000000000000000000000.
445
446
447
448%% If the result of an operation (+, -, * or /) causes overflow we use this
449%% operation. However, since these calculations are performed during compiletime,
450%% shouldn't the IDL-specification be changed to not cause overflow?! But, since
451%% the OMG standard allows this we must support it.
452check_fixed_overflow(#fixed{digits = Digits, scale = Scale, value = Value}) ->
453    case count_digits(abs(Value)) of
454	overflow ->
455	    {N, NewVal} = cut_overflow(0, Value),
456%	    NewDigits = Digits - N,
457	    if
458		N > Scale ->
459		    #fixed{digits = 31, scale = 0, value = NewVal};
460		true ->
461		    NewScale = Scale - N,
462		    {NewVal2, Removed} = delete_zeros(NewVal, NewScale),
463		    #fixed{digits = 31, scale = NewScale-Removed, value = NewVal2}
464	    end;
465	Count when Count > Digits ->
466	    Diff = Count-Digits,
467	    if
468		Diff > Scale ->
469		    #fixed{digits = Digits, scale = 0,
470			   value = (Value div power(Diff))};
471		true ->
472		    NewScale = Scale-Diff,
473		    {NewVal, Removed} = delete_zeros((Value div power(Diff)), NewScale),
474		    #fixed{digits = Digits-Removed,
475			   scale = NewScale-Removed,
476			   value = NewVal}
477	    end;
478	Count ->
479	    {NewVal, Removed} = delete_zeros(Value, Scale),
480	    #fixed{digits = Count-Removed, scale = Scale-Removed, value = NewVal}
481    end.
482
483%% This function see to that the values are of the same baase.
484normalize(S, V1, S, V2) ->
485    {V1, V2};
486normalize(S1, V1, S2, V2) when S1 > S2 ->
487    {V1, V2*power(S1-S2)};
488normalize(S1, V1, S2, V2) ->
489    {V1*power(S2-S1), V2}.
490
491%% If we have access to the integer part of the fixed type we use this
492%% operation to remove all trailing zeros. If we know the scale, length of
493%% fraction part, we can use delete_zeros as well. But, after a division
494%% it's hard to know the scale and we don't need to calcluate the integer part.
495delete_zeros_value(0, N, _) ->
496    {0, 32-N};
497delete_zeros_value(X, N, M) when X > M, (X rem 10) == 0 ->
498    delete_zeros_value((X div 10), N+1, M);
499delete_zeros_value(X, N, _) ->
500    {X, 32-N}.
501
502%% If we know the exact scale of a fixed type we can use this operation to
503%% remove all trailing zeros.
504delete_zeros(0, _) ->
505    {0,0};
506delete_zeros(X, Max) ->
507    delete_zeros(X, 0, Max).
508delete_zeros(X, Max, Max) ->
509    {X, Max};
510delete_zeros(X, N, Max) when (X rem 10) == 0 ->
511    delete_zeros((X div 10), N+1, Max);
512delete_zeros(X, N, _) ->
513    {X, N}.
514
515cut_overflow(N, X) when X > ?FIXED_MAX ->
516    cut_overflow(N+1, (X div 10));
517cut_overflow(N, X) ->
518    {N, X}.
519
520%% A fast way to check the size of a fixed data type.
521count_digits(X) when X >  ?FIXED_MAX -> overflow;
522count_digits(X) when X >= 1000000000000000000000000000000 -> 31;
523count_digits(X) when X >= 100000000000000000000000000000 -> 30;
524count_digits(X) when X >= 10000000000000000000000000000 -> 29;
525count_digits(X) when X >= 1000000000000000000000000000 -> 28;
526count_digits(X) when X >= 100000000000000000000000000 -> 27;
527count_digits(X) when X >= 10000000000000000000000000 -> 26;
528count_digits(X) when X >= 1000000000000000000000000 -> 25;
529count_digits(X) when X >= 100000000000000000000000 -> 24;
530count_digits(X) when X >= 10000000000000000000000 -> 23;
531count_digits(X) when X >= 1000000000000000000000 -> 22;
532count_digits(X) when X >= 100000000000000000000 -> 21;
533count_digits(X) when X >= 10000000000000000000 -> 20;
534count_digits(X) when X >= 1000000000000000000 -> 19;
535count_digits(X) when X >= 100000000000000000 -> 18;
536count_digits(X) when X >= 10000000000000000 -> 17;
537count_digits(X) when X >= 1000000000000000 -> 16;
538count_digits(X) when X >= 100000000000000 -> 15;
539count_digits(X) when X >= 10000000000000 -> 14;
540count_digits(X) when X >= 1000000000000 -> 13;
541count_digits(X) when X >= 100000000000 -> 12;
542count_digits(X) when X >= 10000000000 -> 11;
543count_digits(X) when X >= 1000000000 -> 10;
544count_digits(X) when X >= 100000000 -> 9;
545count_digits(X) when X >= 10000000 -> 8;
546count_digits(X) when X >= 1000000 -> 7;
547count_digits(X) when X >= 100000 -> 6;
548count_digits(X) when X >= 10000 -> 5;
549count_digits(X) when X >= 1000 -> 4;
550count_digits(X) when X >= 100 -> 3;
551count_digits(X) when X >= 10 -> 2;
552count_digits(_X) -> 1.
553
554%%------------------------------------------------------------------
555%%--------------- END Fixed Datatype Helper Functions --------------
556%%------------------------------------------------------------------
557