Did you know ... Search Documentation:
Pack musicbrainz -- prolog/musicbrainz.pl
PublicShow source

This module provides client methods for the Musicbrainz XML service. The predicates it provides fall broadly into two categories: those for composing and querying the Musicbrainz web service, and those for decoding the resulting XML documents. Then there are a few higher level predicates that combine the two for common query patterns, insulating (mostly) the user from the idiosyncracies of XML. This module can also use the Lucene module (lucene.pl) to compose Lucene searches.

Quick start

A simple search returning a 'goodness of match' in Score, a Musicbrainz ID in ID, and an XML element in E, then extracting info from E with mb_facet/2:

?- mb_search(artist,'John Coltrane',Score,E), forall(mb_facet(E,F),writeln(F)).

Search for releases with 'trane' in the title, using general purpose mb_query/5 to get progress info:

?- mb_query(release,search(trane),[],Prog,E).

Search for artist then browse releases:

?- mb_search(artist,'John Coltrane',_,A),
   mb_browse(release,A,E),
   forall(mb_facet(E,F),(print(F),nl)).

Lucene search for male artist then direct lookup all releases (with debug on to report unrecognised fields):

?- debug(musicbrainz).
?- mb_search(artist,[coltrane, gender:male],_,A),
   mb_lookup(A,[inc([releases])],Item),
   forall(mb_facet(Item,F),(print(F),nl)).

Queries

The Musicbrainz XML web service is described at http://musicbrainz.org/doc/Development/XML_Web_Service/Version_2 . A query is logically composed of three parts:

  1. An entity type, which determines what kind of Musicbrainz entity is returned, for example, artist, release, work etc.
  2. A query type, which is a 'lookup', a 'browse', or a 'search'. Each of these has its associated parameters and is represented in this library as a Prolog term.
  3. Generic options, which control how much information is returned about each entity, and how many entities are returned.

Entity types

The core predicate mb_query/4 can deal with any entity type that the Musicbrainz services recognises. The name is simply represented as an atom of type mb_class. The core entity types are: artist, release, 'release-group', label, recording, work, area, url.

An entity can be referred to either as a pair Class-Id, or an element as returned by a previous query:

pair(mb_class,atom)       :< eref.
element(T) :- mb_class(T) :< eref.
uri                       :< eref.
uri :< atom.

Query types

The three query types are represented using three Prolog functors:

lookup(+ID:atom)
Looks up the Musicbrainz entity with the given ID. Returns an element.
browse(+Link:eref)
Returns a list of entities which are linked directly to the referenced entity. For example, the query browse(artist-ArtistID) applied to a core entity type release retrieves all the releases associated with the given artist. Returns a list of elements and a number giving the total number of matches.
search(+SeachTerm:text)
Full text search for the given text (an atom or string). Returns a list of elements and a number giving the total number of matches. If the search term is not atomic, loaded, then Term will be interpreted as a term describing a Lucene search as implemented in the module lucene.pl.

Options

The following options are recognised by mb_query/4 and mb_query/5:

limit(+N:integer)
For browse and search requests only - limits the number of returned entities.
offset(+N:integer)
For browse and search requests only - determines the offset of the returned list of entities relative to the full query results.
inc(+I:list(atom))
Contributes to the inc parameter of the query URL. See http://musicbrainz.org/doc/Development/XML_Web_Service/Version_2 for more information.
rels(+I:list(mb_class))
Contributes 'xxx-rels' components to the inc parameter of the query URL.
lrels(+I:list(mb_class))
Contributes 'xxx-level-rels' components to the inc parameter of the query URL.

If any inappropriate options are supplied for a given query, an exception is thrown.

XML Decoding

The system for decoding XML documents is based on the idea of 'facets': the main result document consists of a list of items of the requested entity type. Each entity has several facets, each of which can be thought of as a logical statement which is true relative to that item. Each facet is represented by a term with some functor and arguments of the appropriate types. For example, the facet name/1 applies to artists, countries, labels etc looks like name(Name), where Name is an atom. The name facet is extracted from the XML sub-element 'name', but other facets might result from more comlicated processing of the XML element representing the item. The predicate facet/4 determines which facets are recognised and how they are computed.

The predicate mb_facet/2 relates an XML element with its facets.

This module defines a portray/2 clause for terms like element(Type,_,_) where type is one of the core Musicbrainz entity types. It extracts the facets id(_) and either name(_) or title(_) (whichever is present, and displays the element in the form

<mb:Type/Id|NameOrTitle>

Multi-page Queries

Browse and search queries produce a list of answers, a subset of which is returned depending on the limit and offset options. A higher level predicate mb_query/5 gives a general way of accessing the elements of the result set, returning each item one by one on backtracking, along with a progress indicator, which is a term that looks like N/T, which means 'N th out of T'. The option auto_page(boolean) controls how large result sets are handled. If false, only one HTTP request is fired off, yielding a window into the full result set determined by the options limit(integer) and offset(integer). If true (the default), multiple queries are executed transparently, yielding the full result set in chunks determined by the limit option. This defaults to the value of the setting limit.

author
- Samer Abdallah, UCL (2014)
 mb_search(+T:mb_class, +Term:text, -Score:between(0,100), -Item:element(T)) is nondet
Searches for entities of type T using arbitrary text. Multiple matches are yielded on backtracking, with Score giving a goodness of fit between 0 and 100 and Item containing all the information returned about the item, which can be examined using mb_facet/2. Executes multiple queries to page through an arbitrary number of results.
 mb_browse(+T:mb_class, +Link:eref, -Item:element(T)) is nondet
Finds entities of type T which are directly linked with the entity Link. Multiple items are returned one by one on backtracking. Executes multiple queries to page through an arbitrary number of results.
 mb_lookup(+E:eref, +Opts:options, -Item:element(T)) is semidet
 mb_lookup(+E:eref, -Item:element(T)) is semidet
Lookup a Musicbrainz entity. The entity E can be specified either as a pair Type-Id or a previously returned XML element.
 mb_query(+T:mb_class, +Req:request(T,items(T)), +Opts:options, -P:progress, -E:element(T)) is nondet
Executes a query that produces multiple results and binds E to each of the items in turn on backtracking. This predicate accepts the option auto_page(boolean). If true (the default), any offset(N) option is ignored, and the the full result set is returned one by one, on backtracking, executing multiple queries if necessary. Otherwise, the results for a single query with the given offset (default 0) is produced.

Progress through the whole result set is given in P, which is a term I/N, where N is the total number of items in the result set and I is the index of the current item. If I is bound on input, that single item is fetched directly. The elements returned can be examined using mb_facet/2.

 mb_query(+T:mb_class, +Req:request(T,A), +Opts:options, -Result:A) is det
Execute a query against the Musicbrainz server, requesting entities of class T. The request term Req is a ground term specifying a lookup, browse, or search query. Supplied options must be appropriate for the given query type. Each request is associated with a return type, which is the type of Result. All queries eventually come through this predicate. The address of the Musicbrainz web service is hard coded here.

The request terms and their types are:

lookup(atom) :: request(A,element(A)).
browse(eref) :: request(A,items(A)).
search(text) :: request(A,items(A)).

items(A) == pair(natural,list(element(A))).
pair(X,Y) ---> X-Y.

element(A) is the type of XML element terms like element(A,_,_).

throws
- mb_error(E:element(error)) If the Musicbrainz server returns an error term. E is an XML element containing supplementary information returned by the server.
 mb_facet(+E:element, ?Facet:facet) is nondet
This predicate implements a scheme for extracting information from an XML element. The idea is that attributes and sub-elements of an element represent 'facets', which can be thought of modal predicates which a true relative to this element. Each facet is therefore like a Prolog predicate, with a name, arity, and typed arguments.

If Facet is unbound on entry, then all facets which true relative to element E are produced on backtracking.

If Facet is nonvar on entry, then the element is scanned to test/bind any variables in the facet.

 mb_id(+E:element(_), -Id:atom) is semidet
Short accessor for entity Id.
 mb_class(+E:element(_), -T:mb_class) is semidet
Short accessor for entity class.
 mb_id_uri(+T:mb_class, +ID:atom, -URI:uri) is det
mb_id_uri(-T:mb_class, -ID:atom, +URI:uri) is semidet
Gets the Musicbrainz URI for the given entity type and ID. It can also work in reverse: given a URI, it can return the entity type and ID.
 mb_uri(+E:element(_), -URI:uri) is det
Get Musicbrainz URI for a given element. This can be used, for example, to query the linkedbrainz.org SPARQL endpoint.

Undocumented predicates

The following predicates are exported, but not or incorrectly documented.

 mb_lookup(Arg1, Arg2)
 mb_relation(Arg1, Arg2, Arg3, Arg4, Arg5)
 mb_lazy_query(Arg1, Arg2, Arg3, Arg4)