1 | % (c) 2009-2015 Lehrstuhl fuer Softwaretechnik und Programmiersprachen, | |
2 | % Heinrich Heine Universitaet Duesseldorf | |
3 | % This software is licenced under EPL 1.0 (http://www.eclipse.org/org/documents/epl-v10.html) | |
4 | ||
5 | :- module(unit_parser, [ | |
6 | unit_args_to_list/2 | |
7 | ]). | |
8 | ||
9 | :- use_module(library(lists)). | |
10 | ||
11 | :- use_module(probsrc(self_check), [assert_must_succeed/1]). | |
12 | :- use_module(probsrc(parsercall), [parse_formula/2]). | |
13 | :- use_module(probsrc(error_manager), [add_error/3]). | |
14 | ||
15 | :- use_module(units_alias). | |
16 | :- use_module(units_domain, [units_domain_division/3,power_of_multiply_units/3]). | |
17 | ||
18 | :- use_module(probsrc(module_information), [module_info/2]). | |
19 | :- module_info(group,plugin_units). | |
20 | :- module_info(description,'Units Plugin: Parsing unit expressions inside pragmas to internal representation of units.'). | |
21 | ||
22 | %unit_args_to_list(X,_) :- format('Input unit argument: ~w~n', [X]), nl, fail. | |
23 | :- assert_must_succeed(unit_args_to_list("m",[[0,m,1]])). | |
24 | :- assert_must_succeed(unit_args_to_list("degC",[[0,degC,1]])). | |
25 | :- assert_must_succeed(unit_args_to_list("cm",[[-2,m,1]])). | |
26 | :- assert_must_succeed(unit_args_to_list("10*m**1",[[1,m,1]])). | |
27 | :- assert_must_succeed(unit_args_to_list("10**-1 * m**1",[[-1,m,1]])). | |
28 | :- assert_must_succeed(unit_args_to_list("10 * m",[[1,m,1]])). | |
29 | :- assert_must_succeed(unit_args_to_list("m * 10",[[1,m,1]])). | |
30 | :- assert_must_succeed(unit_args_to_list("km/h",[[3,m,1],[0,h,-1]])). | |
31 | unit_args_to_list(Arg,O) :- | |
32 | catch(parse_formula(Arg,Expression),_Exception, fail), | |
33 | expression_to_unit(Expression,O), correct_unit(O), !. | |
34 | unit_args_to_list(Arg,_) :- | |
35 | atom_codes(ArgAtom,Arg), | |
36 | add_error(incorrect_unit_definition, 'Incorrect unit definition: ', ArgAtom). | |
37 | ||
38 | %expression_to_unit(Expr,_) :- format('Input unit expression: ~w~n', [Expr]), nl, fail. | |
39 | :- assert_must_succeed(expression_to_unit(identifier(pos(9,1,4,1,4,1),m),[[0,m,1]])). | |
40 | :- assert_must_succeed(expression_to_unit(mult_or_cart(pos,power_of(pos,integer(pos,10),unary_minus(pos,integer(pos,1))),power_of(pos,identifier(pos,m),integer(pos,1))),[[-1,m,1]])). | |
41 | expression_to_unit(identifier(_Pos,Name),Out) :- | |
42 | unit_alias(Name,AliasDef) | |
43 | -> Out = AliasDef | |
44 | ; valid_unit_symbol(Name), | |
45 | Out = [[0,Name,1]]. | |
46 | expression_to_unit(power_of(_Pos,identifier(Pos,Name),Exponent),Unit) :- !, | |
47 | expression_to_unit(identifier(Pos,Name),UnitOfIdentifier), | |
48 | unary_minus_exponent(Exponent,NumericExponent), | |
49 | power_of_multiply_units(NumericExponent,UnitOfIdentifier,Unit). | |
50 | expression_to_unit(power_of(_Pos,integer(_Pos2,10),Exponent),Unit) :- !, | |
51 | unary_minus_exponent(Exponent,NumericExponent), | |
52 | Unit = [[NumericExponent,na,na]]. | |
53 | expression_to_unit(mult_or_cart(_Pos,Arg1,Arg2),Unit) :- !, | |
54 | expression_to_unit(Arg1,Unit1), expression_to_unit(Arg2,Unit2), | |
55 | multiply_units(Unit1,Unit2,Unit). | |
56 | expression_to_unit(div(_Pos,Arg1,Arg2),Unit) :- !, | |
57 | expression_to_unit(Arg1,Unit1), expression_to_unit(Arg2,Unit2), | |
58 | units_domain_division(Unit1,Unit2,Unit). | |
59 | expression_to_unit(integer(_Pos,10),[[1,na,na]]) :- !. | |
60 | ||
61 | unary_minus_exponent(unary_minus(_Pos,integer(_Pos2,X)), MX) :- !, MX is -X. | |
62 | unary_minus_exponent(integer(_Pos,X), X) :- !. | |
63 | ||
64 | multiply_units([[X,na,na]],[[0,Unit,X2]],[[X,Unit,X2]]) :- !, Unit \= na, X2 \= na. | |
65 | multiply_units([[0,Unit,X2]],[[X,na,na]],[[X,Unit,X2]]) :- !, Unit \= na, X2 \= na. | |
66 | multiply_units(U1,U2,U) :- !, append(U1,U2,U). | |
67 | ||
68 | correct_unit(ListOfUnits) :- | |
69 | maplist(nafree,ListOfUnits). | |
70 | ||
71 | nafree([A,B,C]) :- A \= na, B \= na, C \= na. | |
72 | ||
73 | valid_unit_symbol(m). | |
74 | valid_unit_symbol(kg). | |
75 | valid_unit_symbol(s). | |
76 | valid_unit_symbol('A'). | |
77 | valid_unit_symbol('K'). | |
78 | valid_unit_symbol(mol). | |
79 | valid_unit_symbol(cd). |