GithubHelp home page GithubHelp logo

func's Introduction

Synopsis

:- use_module(library(func)).
main :-
    % create a Plus3 function by composing three others
    Plus3 = succ of _+1 of plus(1),
    call(Plus3, 1, 4),
    format('~s world~n', [atom_codes $ hello]).

Description

This module allows one to apply ($/2) and compose (of/2) terms as if they were functions. One often uses predicates as these functions, but one can define function behavior for arbitrary terms. See "What is a function" and "Defining functions" below.

Why? Prolog predicates are more powerful than functions, but sometimes the syntax is awkward or requires meaningless effort from the developer (generating and maintaining intermediate variable names and goals). Using library(func) often results in more succinct, clearer code. For example, the use of atom_codes/2 in the Synopsis above.

At compile time, library(func) converts function application and composition into standard predicate calls. There should be no performance penalty and one can still use nondeterminism.

What is a function?

For our purposes, a function is any term which can be converted into a predicate call that accepts input in a single variable and produces output by binding a single variable. The following sections describe terms which library(func) can natively treat as functions. See further below for instructions on defining function behavior for additional terms.

Predicates as functions

Any predicate whose final argument can be viewed as an "output" and whose penultimate argument can be viewed as "input" can be used, without modification, as a function.

For example, succ/2 can be seen as accepting an input as the first argument and producing an output, in the second argument, that's one greater. Similarly, the term plus(3) can be seen as a predicate which takes an integer input and generates an integer output that's three larger.

Because Prolog predicates often follow a convention of having "inputs" before "outputs", many predicates can be applied and composed as functions as is. This includes length/2, reverse/2, maplist/3, append/3, etc.

Dicts

An SWI-Prolog 7 dictionary is considered a function from its keys to its values. Applying the function to a non-existent key fails.

?- writeln(words{1:one, 2:two, 3:three} $ 2).
two
?- writeln(words{1:one, 2:two, 3:three} $ 4).
false.

This is similar to SWI Prolog's dot notation but doesn't throw an exception for missing keys. Dicts as functions can be composed and applied just like other functions.

Arithmetic expressions of one variable

Any arithmetic expression of a single variable can be applied and composed as a function. For example, 2*_+3 is the function which multiplies a number by two and then adds three. Similarly, sqrt(X)*X + X/2 is a function even though it uses the input in three different places.

format/2 templates

A format string acceptable as the first argument to format/2 can be used as a function. It generates an atom, list of codes or string as output. The template's type determines the output's type. This offers a powerful string interpolation syntax visually similar to Python's.

In this next example, X might hold any of the values codes, chars, number or length.

call('atom_~w' $ X, Atom, Term)

One might also use this interpolation syntax to build a file path:

Path = "/home/~w/src/~w/.git/config" $ [User, Project]

Tilde Terms

A compound term with a single ~ argument is considered a function which takes no input values and produces an output at the ~ position. For example,

atom(atom_string(~,"hello world")).

produces code that's equivalent to

atom_string(X,"hello world"),
atom(X).

This can be conveniently employed with arithmetic expressions.

length(List, ~ is X + Y).

Because tilde terms take no inputs, they can't be used with $/2 or of/2.

Defining functions

Any term can behave as a function by defining additional clauses for the multifile hook func:compile_function/4. See the full documentation for greater detail. In this example, we'll define a list term as a function from a 0-based index to the corresponding element of that list.

:- multifile func:compile_function/4.
func:compile_function(List, Index, Elem, nth0(Index, List, Elem)) :-
    is_list(List).

We might use it to convert small integers into English words:

N = 2,
format('The number word is ~w~n', [zero,one,two,three] $ N).

One might imagine similar definitions for assoc lists, binary trees, hash tables, etc.

Installation

Using SWI-Prolog 6.3 or later:

$ swipl
1 ?- pack_install(func).

Source code available and pull requests accepted on GitHub: https://github.com/mndrix/func

func's People

Contributors

edechter avatar mndrix avatar

Stargazers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

Watchers

 avatar  avatar  avatar

func's Issues

notation to mark function inputs?

Should there be syntax for describing the input to a function? Perhaps ^:

?- Q = queue_cons(^,item) $ queue_new.
Q = [item].

This suggests that length $ X is sugar for length(^,~) $ X. Is that the way to go?

Module qualified functions

Currently functions are expanded without module qualification.

:- use_module(library(func)).

foo :-
    length(mod:bar(~)).

:- initialization listing(foo/0). 
bash-3.2$ swipl -l test_func.pl
foo :-
    bar(A),
    length((mod):A).

support some of GRIPS function notation

GRIPS is another functional sugar for Prolog. Implement ideas from it, if they seem worthwhile:

  • <- functional definitions that automatically insert cuts to make the predicate deterministic
  • if guards for functional definitions

Perhaps these features should only be available by doing use_module(library(func), [grips/0]). Namely, explicitly enabling GRIPS support.

support some of Ciao's function notation

Ciao provides function notation which, like library(func), is just syntactic sugar on top of predicates. Support these features:

  • ~ prefix operator to evaluate any term using an appended final argument as the output
    • should also support all other function-like terms that we already support (equations, format strings, etc)
    • this is helpful since our $ operator requires an argument whereas ~ does not
  • fun_return declaration to support ~-prefix notation for an arbitrary output argument
  • fun_eval as a convenient shortcut around a library(function_expansion) clause definition
    • helpful for defining a decrement operator --N, for example
  • functional definitions using :=

Perhaps these features should only be available by doing use_module(library(func), [ciao/0]). Namely, explicitly enabling Ciao support.

support dicts as functions

SWI-Prolog 7 introduces dicts. Treat them as functions from a key to a value. SWI-Prolog already provides . syntactic sugar, but teaching func about them allows us to compose dicts with functions. It also makes func consistently support built in types.

We want to call get_dict/3 instead of get_dict_ex/3 which is the default for . notation.

function composition resolving predicates in the wrong module

Inside a module foo, I had imported a predicate bar_stuff/2 from the module bar. I composed the following function:

F = reverse of bar_stuff.

When applying F to a value, I got the error:

Undefined procedure: func:bar_stuff/2

The composed function was looking in the func module when it should have been looking in the foo module.

Make function composition look in the module in which the composed function was defined.

Reverse application operator

OCaml includes the reverse function operator (|>) which I've often found more readable than function composition + application. Have you consider adding such operator to func?

support records as functions

library(record) supports terms with named arguments. Allow one to use a record as a function mapping an argument name to its value. Like this

write(Person$name).

Which expands into something like this

person_name(Person, X),
write(X).

good cross-module behavior

library(func) should only expand macros in those modules which have requested it. Use the import sentinel trick to make sure that our macro doesn't apply to every module which has a $/2 operator.

If this is already implemented, create a test for it:

  • main defines $/2 predicate
  • main imports module alpha
  • module alpha imports module func
  • main's calls to $/2 should not be expanded as function macros

support format strings as functions

A format/2 template can be viewed as a function from a list of variables to another string. That makes string interpolation a simple function application.

This

X = 'Mary had a ~p lamb' $ little,
Y = "~w ~w Eater" $ ['Peter', 'Peter'].

should desugar to something equivalent to

format(atom(X), 'Mary had a ~p lamb', little),
format(codes(Y), "~w ~w Eater", ['Peter', 'Peter']).

The output data structure (atom or codes) is determined by template's string type. It also depends on how double quotes are being treated (see current_prolog_flag).

The syntax is similar to Python string interpolation which allows things like

"Mary had a %s lamb" % "little"

I've tried in vain to let this work:

Size = little,
X = 'Mary had a $Size lamb'.

Unfortunately, the reader discards variable names before macro expansion happens, so there's no way of mapping $Size to the variable formerly known as Size

Compile limited lambda syntax into predicates

Teach library(func) how to compile a predicate defined using lambda syntax and assigned to a variable. Like,

F = \X^Y^foo(stuff,Y,X),
...

% becomes

F = func:'5ecbc7c6883139e60b5db16550e8b5fc5da0244a',
...

func:'5ecbc7c6883139e60b5db16550e8b5fc5da0244a'(X,Y) :-
    foo(stuff,Y,X).

In certain circumstances, this technique can improve performance.

However, the main goal is to give users a convenient way to define predicates that are local to a clause. Without this feature, one must create a globally unique name for the predicate and risk it being called where it wasn't intended. This approach effectively keeps the auxiliary predicate definition local to the clause that uses it.

problems on SWI-Prolog V6

This issue collects all problems encountered when running on SWI-Prolog version 6. Unless V7 becomes the stable branch pretty soon, it would be good to fix this:

  • only call is_dict/1 if it exists (dict sugar doesn't make sense on V6)

support functional predicate definition syntax

Ciao (with :=) and GRIPS (with <-) and Mercury (with =) provide special syntax for defining predicates that behave like functions.

In both GRIPS and Mercury, function definition implies determinism. I think Ciao makes a mistake here by allowing nondeterministic predicates to be defined with functional notation.

Using functional definitions should imply determinism. Mercury's = should be enough syntax. I've never seen =/2 as a top level functor. So, assuming --/1 performs decrement, our definition should be

fact(0) = 1
fact(N) = N * fact(--N)

which desugars into

fact(0, F) :- 
    !,
    F = 1.
fact(N, F) :- 
    succ(Nminus, N),
    fact(Nminus, F0),
    F is F0*N.

There's no protection against fact(-1) looping forever, but most functional languages don't protect against that either.

support runtime $/2 and of/2

If I write

X = F $ foo.

I don't know what kind of function F is until runtime. Support this kind of code by expanding to something like this

func:compile_function(F, foo, Out, Goal),
Call(Goal),
X = Out.

factor out library(tap)

library(func) currently has library(tap) embedded inside it. That's because func was the first library to use the TAP infrastructure. Now that it's tested and working, it belongs in a separate pack so that other projects can use it too.

In the process, I should remove the dependency on library(list_util) because I want that library to eventually use library(tap) for itself. That can't happen with a circular dependency.

Also consider separating into library(tap/protocol) and library(tap/test). The former should handle TAP output generation. The latter should desugar a test file and generate main/0.

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    ๐Ÿ–– Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. ๐Ÿ“Š๐Ÿ“ˆ๐ŸŽ‰

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google โค๏ธ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.