Skip to content

Instantly share code, notes, and snippets.

@mndrix
Created October 7, 2016 14:54
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save mndrix/2224422adc4913e715809245a6b02b3a to your computer and use it in GitHub Desktop.
Save mndrix/2224422adc4913e715809245a6b02b3a to your computer and use it in GitHub Desktop.
PriceCharting's Prolog library for currency amounts
:- module(currency, [ atom_currency/2
, codes_currency/2
, currency//1
]).
:- use_module(library(clpfd)).
:- use_module(library(dcg/basics), [integer//1]).
:- use_module(library(delay)).
:- use_module(library(error)).
% define currency type
:- multifile error:has_type/2.
error:has_type(currency, Pennies) :-
integer(Pennies),
Pennies >= 0.
%% atom_currency(+Atom:atom, -Currency:currency) is semidet.
%% atom_currency(-Atom:atom, +Currency:currency) is det.
%
% True if Atom represents a Currency amount. The atom is of the form
% `$12.34`
atom_currency(Atom, Currency) :-
delay(atom_codes(Atom, Codes)),
codes_currency(Codes, Currency).
codes_currency(Codes, Currency) :-
phrase(currency(Currency), Codes).
:- style_check(-no_effect).
% a currency amount like $12.34
currency(Currency) -->
{ Currency #= 100_000*Thousands + 100*Dollars + Pennies },
{ Thousands #>= 0 },
{ Dollars in 0..999 },
{ Pennies in 0..99 },
{ LargeDollars #= 1000*Thousands + Dollars },
"$",
( integer(Thousands), { Thousands #\= 0 }, "," ->
padded_dollars(Dollars)
; integer(LargeDollars), { LargeDollars > 999 }, peek(0'.) ->
{ Thousands #> 0 }
; % otherwise
{ Thousands = 0 },
integer(Dollars)
),
".",
pennies(Pennies).
:- style_check(+no_effect).
% declare next DCG character without consuming it
peek(Char, [Char|Rest], [Char|Rest]).
% the 0-padded dollars portion of a currency amount
padded_dollars(Dollars) -->
{ Dollars in 100..999 },
integer(Dollars),
!.
padded_dollars(Dollars) -->
{ Dollars in 10..99 },
"0",
integer(Dollars),
!.
padded_dollars(Dollars) -->
{ Dollars in 0..9 },
"00",
integer(Dollars).
% the pennies portion of a currency amount
pennies(Pennies) --> % try a big amount first
{ Pennies in 10..99 },
integer(Pennies),
!.
pennies(Pennies) -->
{ Pennies in 0..9 },
"0",
integer(Pennies).
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment