1:- encoding(utf8).
    2:- module(
    3  media_type,
    4  [
    5    media_type//1,          % ?MediaType
    6    media_type/1,           % ?MediaType
    7    media_type_encoding/2,  % ?MediaType, ?Encoding
    8    media_type_extension/2, % ?MediaType, ?Extension
    9    media_type_family/2,    % ?MediaType, ?Family
   10    media_type_label/2,     % ?MediaType, ?Label
   11    media_type_parameter/2, % +MediaType, ?Parameter
   12    media_type_program/3,   % ?MediaType, -Program, -Args
   13    must_be_media_type/2    % +MediaTypes, +MediaType
   14  ]
   15).

Media Types library

Library of Media Types, based on the official Media Types as maintained by IANA, and de facto Media Types as they are used in the wild.

Media Types are a common way of denoting binary and textual content. As such, this library is useful to base sensible defaults for processing input files on, and can be used to simplify HTTP requests and aspects of serving content over HTTP.

Also tries to maintain a one-to-one mapping between Media Types and the most commonly used file name extension for files containing content in that Media Type.

*/

   34:- use_module(library(apply)).   35:- use_module(library(error)).   36:- use_module(library(lists)).   37:- use_module(library(pair_ext), []).   38:- use_module(library(settings)).   39
   40:- use_module(library(call_ext)).   41:- use_module(library(dcg)).   42:- use_module(library(stream_ext)).   43
   44:- discontiguous
   45    encoding_/2,
   46    extension_/2,
   47    family_/2,
   48    label_/2,
   49    media_type_/2,
   50    program_/2.   51
   52:- multifile
   53    error:has_type/2.   54
   55error:has_type(media_type, MediaType) :-
   56  MediaType = media(Super/Sub,Params),
   57  error:has_type(atom, Super),
   58  error:has_type(atom, Sub),
   59  error:has_type(list(pair(atom)), Params).
   60
   61:- setting(default_text_editor, atom, emacs,
   62           "The default program that is used for opening text files.").
 media_type(+MediaType:media_type)// is det
media_type(-MediaType:media_type)// is det
   69media_type(MediaType) -->
   70  {ground(MediaType)}, !,
   71  media_type_generate(MediaType).
   72media_type(MediaType) -->
   73  media_type_parse(MediaType).
   74
   75media_type_generate(media(Super/Sub,Params)) -->
   76  atom(Super),
   77  "/",
   78  atom(Sub),
   79  params_generate(Params).
   80
   81params_generate([]) --> !, "".
   82params_generate([H|T]) -->
   83  ";",
   84  param_generate(H),
   85  params_generate(T).
   86
   87param_generate(Key-Value) -->
   88  atom(Key),
   89  "=",
   90  atom(Value).
   91
   92media_type_parse(media(Super/Sub,Params)) -->
   93  ...(SuperCodes),
   94  "/",
   95  ...(SubCodes),
   96  (";" -> whites, params_parse(Params) ; eos, {Params = []}), !,
   97  {maplist(atom_codes, [Super,Sub], [SuperCodes,SubCodes])}.
   98
   99params_parse([H|T]) -->
  100  param_parse(H), !,
  101  params_parse(T).
  102params_parse([]) --> "".
  103
  104param_parse(Key-Value) -->
  105  ...(KeyCodes),
  106  "=",
  107  ...(ValueCodes),
  108  (";" -> whites ; eos),
  109  {maplist(atom_codes, [Key,Value], [KeyCodes,ValueCodes])}.
 media_type(+MediaType:media_type) is semidet
media_type(-MediaType:media_type) is multi
  116media_type(MediaType) :-
  117  media_type_(_, MediaType).
 media_type_encoding(+MediaType:media_type, +Encoding:atom) is semidet
media_type_encoding(+MediaType:media_type, -Encoding:atom) is semidet
  124% A parameter `charset'.
  125media_type_encoding(MediaType, Encoding) :-
  126  media_type_parameter(MediaType, charset-Encoding0), !,
  127  stream_ext:clean_encoding_(Encoding0, Encoding).
  128media_type_encoding(MediaType, Encoding) :-
  129  media_type_encoding_(MediaType, Encoding), !.
  130
  131media_type_encoding_(media(text/turtle,_), utf8).
 media_type_extension(+MediaType:media_type, +Extension:atom) is semidet
media_type_extension(+MediaType:media_type, -Extension:atom) is det
media_type_extension(-MediaType:media_type, +Extension:atom) is det
media_type_extension(-MediaType:media_type, -Extension:atom) is multi
  140media_type_extension(MediaType, Ext) :-
  141  call_det_when(
  142    (ground(MediaType) ; ground(Ext)),
  143    (extension_(Key, Ext),
  144     media_type_(Key, MediaType))).
 media_type_family(+MediaType:media_type, +Family:term) is semidet
media_type_family(+MediaType:media_type, -Family:term) is semidet
media_type_family(-MediaType:media_type, +Family:term) is nondet
media_type_family(-MediaType:media_type, -Family:term) is multi
  153media_type_family(MediaType, Family) :-
  154  ground(Family), !,
  155  family_(Key, Family),
  156  media_type_(Key, MediaType).
  157media_type_family(MediaType, Family) :-
  158  media_type_(Key, MediaType),
  159  family_(Key, Family).
 media_type_label(+MediaType:media_type, -Label:string) is det
media_type_label(-MediaType:media_type, -Label:string) is multi
  165media_type_label(MediaType, Label) :-
  166  call_det_when_ground(
  167    MediaType,
  168    (media_type_(Key, MediaType),
  169     label_(Key, Label))).
 media_type_parameter(+MediaType:media_type, +Parameter:pair(atom)) is semidet
media_type_parameter(+MediaType:media_type, -Parameter:pair(atom)) is nondet
  176media_type_parameter(media(_/_,Params), Param) :-
  177  member(Param, Params).
 media_type_program(+MediaType:media_type, -Program:atom, -Args:list) is nondet
media_type_program(-MediaType:media_type, -Program:atom, -Args:list) is multi
  184media_type_program(MediaType, Program, Args) :-
  185  media_type_(Key, MediaType),
  186  program_(Key, Program0),
  187  media_type_program_(Program0, Program, Args).
  188
  189media_type_program_(program(Program,Args), Program, Args) :- !.
  190media_type_program_(text_editor, Program, []) :- !,
  191  setting(default_text_editor, Program).
  192media_type_program_(Program, Program, []).
 must_be_media_type(+MediaTypes:list(media_type), +MediaType:media_type) is det
  198must_be_media_type(MediaTypes, media(Super/Sub,_)) :-
  199  memberchk(media(Super/Sub,_), MediaTypes), !.
  200must_be_media_type(MediaTypes, MediaType) :-
  201  must_be(oneof(MediaTypes), MediaType).
  202
  203
  204
  205% MEDIA TYPE REGISTRATIONS %
 media_type_(?Extension:atom, ?MediaType:media_type, ?Programs:list(or([atom,compound])), ?Label:string) is nondet
  209extension_('7z_1', '7z').
  210label_('7z_1', "7z").
  211media_type_('7z_1', media(application/'x-7z-compressed',[])).
  212
  213extension_(atom_1, atom).
  214label_(atom_1, "Atom XML").
  215media_type_(atom_1, media(application/'atom+x',[])).
  216program_(atom_1, text_editor).
  217
  218extension_(bmp_1, bmp).
  219label_(bmp_1, "Windows Bitmap (BMP)").
  220media_type_(bmp_1, media(image/bmp,[])).
  221program_(bmp_1, eog).
  222
  223extension_(bz2_1, bz2).
  224label_(bz2_1, "bzip2").
  225media_type_(bz2_1, media(application/'x-bzip2',[])).
  226program_(bz2_1, program(bzip2,['-d'])).
  227
  228extension_(cab_1, cab).
  229label_(cab_1, "Microsoft Cabinet").
  230media_type_(cab_1, media(application/'vnd.ms-cab-compressed',[])).
  231
  232extension_(cdx_1, cdx).
  233label_(cdx_1, "CambridgeSoft ChemDraw").
  234media_type_(cdx_1, media(chemical/'x-cdx',[])).
  235
  236extension_(cpio_1, cpio).
  237label_(cpio_1, "cpio").
  238media_type_(cpio_1, media(application/'x-cpio',[])).
  239
  240extension_(csv_1, csv).
  241family_(csv_1, sparql(ask)).
  242family_(csv_1, sparql(select)).
  243label_(csv_1, "Comma-separated values (CSV)").
  244media_type_(csv_1, media(text/csv,[])).
  245program_(csv_1, text_editor).
  246
  247extension_(doc_1, doc).
  248label_(doc_1, "Microsoft Word Document").
  249media_type_(doc_1, media(application/msword,[])).
  250program_(doc_1, [program(libreoffice,'--writer')]).
  251
  252extension_(docm_1, docm).
  253label_(docm_1, "Microsoft Word Document").
  254media_type_(docm_1, media(application/'vnd.ms-word.document.macroenabled.12',[])).
  255program_(docm_1, program(libreoffice,'--writer')).
  256
  257extension_(docx_1, docx).
  258label_(docx_1, "OpenOffice Wordprocessing Document").
  259media_type_(docx_1, media(application/'vnd.openxmlformats-officedocument.wordprocessingml.document',[])).
  260program_(docx_1, program(libreoffice,'--writer')).
  261
  262extension_(dot_1, dot).
  263label_(dot_1, "GraphViz DOT").
  264media_type_(dot_1, media(text/'vnd.graphviz',[])).
  265program_(dot_1, text_editor).
  266
  267extension_(dotm_1, dotm).
  268label_(dotm_1, "Microsoft Word Template").
  269media_type_(dotm_1, media(application/'vnd.ms-word.template.macroenabled.12',[])).
  270program_(dotm_1, program(libreoffice,'--writer')).
  271
  272extension_(dotx_1, dotx).
  273label_(dotx_1, "OpenOffice Wordprocessing Template").
  274media_type_(dotx_1, media(application/'vnd.openxmlformats-officedocument.wordprocessingml.template',[])).
  275program_(dotx_1, program(libreoffice,'--writer')).
  276
  277extension_(dwg_1, dwg).
  278label_(dwg_1, "Drawing (DWG) proprietary format used by CAD software").
  279media_type_(dwg_1, media(application/dwg,[])).
  280
  281extension_(dxf_1, dxf).
  282label_(dxf_1, "AutoCAD Drawing Exchange Format (DXF)").
  283media_type_(dxf_1, media(image/'vnd.dxf',[])).
  284
  285extension_(eps_1, eps).
  286label_(eps_1, "Encapsulated PostScript (EPS)").
  287media_type_(eps_1, media(image/eps,[])).
  288program_(eps_1, xfig).
  289
  290extension_(epub_1, epub).
  291label_(epub_1, "ePub").
  292media_type_(epub_1, media(application/'epub+zip',[])).
  293
  294extension_(exr_1, exr).
  295label_(exr_1, "OpenEXR is a high dynamic-range (HDR) image file format developed by Industrial Light & Magic for use in computer imaging applications").
  296
  297extension_(fig_1, fig).
  298label_(fig_1, "FIG graphics language (Xfig)").
  299program_(fig_1, xfig).
  300
  301extension_(fits_1, fits).
  302label_(fits_1, "Flexible Image Transport System (FITS)").
  303media_type_(fits_1, media(application/fits,[])).
  304
  305extension_(flv_1, flv).
  306label_(flv_1, "Flash video (FLV)").
  307media_type_(flv_1, media(video/'x-flv',[])).
  308
  309extension_(geojson_1, geojson).
  310label_(geojson_1, "GeoJSON").
  311media_type_(geojson_1, media(application/'vnd.geo+json',[])).
  312program_(geojson_1, text_editor).
  313
  314extension_(gif_1, gif).
  315label_(gif_1, "Graphics Interchange Format (GIF)").
  316media_type_(gif_1, media(image/gif,[])).
  317program_(gif_1, eog).
  318program_(gif_1, xfig).
  319
  320extension_(gml_1, gml).
  321label_(gml_1, "Geography Markup Language (GML)").
  322media_type_(gml_1, media(application/'gml+xml',[])).
  323program_(gml_1, text_editor).
  324
  325extension_(gml_2, gml).
  326label_(gml_2, "Graph Markup Language (GML)").
  327media_type_(gml_2, media(text/'x-gml',[])).
  328program_(gml_2, gephi).
  329
  330extension_(gpx_1, gpx).
  331label_(gpx_1, "GPS Exchange Format (GPX)").
  332media_type_(gpx_1, media(application/'gpx+xml',[])).
  333
  334extension_(gz_1, gz).
  335label_(gz_1, "GNU Zip").
  336media_type_(gz_1, media(application/gzip,[])).
  337
  338extension_(hdt_1, hdt).
  339label_(hdt_1, "Header Dictionary Triples (HDT)").
  340media_type_(hdt_1, media(application/'vnd.hdt',[])).
  341
  342extension_(html_1, html).
  343family_(html_1, rdf).
  344family_(html_1, rdfa).
  345label_(html_1, "Hyper Text Markup Language (HTML)").
  346media_type_(html_1, media(text/html,[])).
  347program_(html_1, firefox).
  348
  349extension_(ico_1, ico).
  350label_(ico_1, "Windows Icon (Microsoft uses Media Type `image/x-icon')").
  351media_type_(ico_1, media(image/'vnd.microsoft.icon',[])).
  352program_(ico_1, eog).
  353
  354extension_(jgf_1, jgf).
  355label_(jgf_1, "JSON Graph Format (JGF)").
  356media_type_(jgf_1, media(application/'vnd.jgf+json',[])).
  357program_(jgf_1, text_editor).
  358
  359extension_(jp2_1, jp2).
  360label_(jp2_1, "JPEG 2000").
  361media_type_(jp2_1, media(image/jp2,[])).
  362
  363encoding_(jpg_1, octet).
  364extension_(jpg_1, jpg).
  365label_(jpg_1, "Joint Photographic Experts Group (JPEG)").
  366media_type_(jpg_1, media(image/jpeg,[])).
  367program_(jpg_1, eog).
  368program_(jpg_1, xfig).
  369
  370extension_(js_1, js).
  371label_(js_1, "JavaScript (JS)").
  372media_type_(js_1, media(application/javascript,[])).
  373program_(js_1, text_editor).
  374
  375encoding_(json_1, utf8).
  376extension_(json_1, json).
  377label_(json_1, "JavaScript Object Notation (JSON)").
  378media_type_(json_1, media(application/json,[])).
  379program_(json_1, text_editor).
  380
  381extension_(jsonld_1, jsonld).
  382family_(jsonld_1, rdf).
  383label_(jsonld_1, "JSON-LD 1.0").
  384media_type_(jsonld_1, media(application/'ld+json',[])).
  385program_(jsonld_1, text_editor).
  386
  387extension_(jsp_1, jsp).
  388label_(jsp_1, "Java Server Pages (JSP)").
  389media_type_(jsp_1, media(application/jsp,[])).
  390
  391extension_(kml_1, kml).
  392label_(kml_1, "KML").
  393media_type_(kml_1, media(application/'vnd.google-earth.kml+xml',[])).
  394
  395extension_(kmz_1, kmz).
  396label_(kmz_1, "KMZ").
  397media_type_(kmz_1, media(application/'vnd.google-earth.kmz',[])).
  398
  399extension_(lha_1, lha).
  400label_(lha_1, "LHA").
  401media_type_(lha_1, media(application/'x-lzh-compressed',[])).
  402
  403extension_(mdb_1, mdb).
  404label_(mdb_1, "Microsoft Access Database").
  405media_type_(mdb_1, media(application/'vnd.ms-access',[])).
  406program_(mdb_1, program(libreoffice,['--base'])).
  407
  408extension_(mobi_1, mobi).
  409label_(mobi_1, "Mobi").
  410media_type_(mobi_1, media(application/'vnd.amazon.mobi8-ebook',[])).
  411
  412extension_(mol_1, mol).
  413label_(mol_1, "MDL Information Systems (MDL) Molfile").
  414media_type_(mol_1, media(chemical/'x-mdl-molfile',[])).
  415
  416extension_(mp4_1, mp4).
  417label_(mp4_1, "MPEG-4 Part 14").
  418media_type_(mp4_1, media(video/mp4,[])).
  419program_(mp4_1, vlc).
  420
  421extension_(n3_1, n3).
  422label_(n3_1, "Notation 3 (N3)").
  423media_type_(n3_1, media(text/n3,[])).
  424program_(n3_1, text_editor).
  425
  426extension_(nc_1, nc).
  427label_(nc_1, "Network Common Data Form (NetCDF)").
  428media_type_(nc_1, media(application/netcdf,[])).
  429
  430encoding_(nq_1, utf8).
  431extension_(nq_1, nq).
  432family_(nq_1, rdf).
  433label_(nq_1, "N-Quads 1.1").
  434media_type_(nq_1, media(application/'n-quads',[])).
  435program_(nq_1, text_editor).
  436
  437encoding_(nt_1, utf8).
  438extension_(nt_1, nt).
  439family_(nt_1, rdf).
  440label_(nt_1, "N-Triples 1.1").
  441media_type_(nt_1, media(application/'n-triples',[])).
  442program_(nt_1, text_editor).
  443
  444extension_(odp_1, odp).
  445label_(odp_1, "OpenDocument presenatation").
  446media_type_(odp_1, media(application/'vnd.oasis.opendocument.presentation',[])).
  447program_(odp_1, program(libreoffice)).
  448
  449extension_(ods_1, ods).
  450label_(ods_1, "OpenDocument Spreadsheet").
  451media_type_(ods_1, media(application/'vnd.oasis.opendocument.spreadsheet',[])).
  452program_(ods_1, program(libreoffice,['--calc'])).
  453
  454extension_(odt_1, odt).
  455label_(odt_1, "OpenDocument Text").
  456media_type_(odt_1, media(application/'vnd.oasis.opendocument.text',[])).
  457program_(odt_1, program(libreoffice,['--writer'])).
  458
  459extension_(pbm_1, pbm).
  460label_(pbm_1, "Portable Bitmap Format (PBM)").
  461media_type_(pbm_1, media(image/'x-portable-bitmap',[])).
  462
  463extension_(pct_1, pct).
  464label_(pct_1, "PICT is a graphics file format introduced on the original Apple Macintosh computer as its standard metafile format.").
  465media_type_(pct_1, media(image/'x-pict',[])).
  466
  467extension_(pcx_1, pcx).
  468label_(pcx_1, "PiCture EXchange (PC Paintbrush)").
  469media_type_(pcx_1, media(image/'vnd.zbrush.pcx',[])).
  470program_(pcx_1, eog).
  471program_(pcx_1, xfig).
  472
  473extension_(pdf_1, pdf).
  474label_(pdf_1, "Portable Document Format (PDF)").
  475media_type_(pdf_1, media(application/pdf,[])).
  476program_(pdf_1, evince).
  477program_(pdf_1, xpdf).
  478
  479extension_(pgm_1, pgm).
  480label_(pgm_1, "Portable Graymap Format (PGM)").
  481media_type_(pgm_1, media(image/'x-portable-graymap',[])).
  482
  483extension_(pic_1, pic).
  484label_(pic_1, "PIC language").
  485
  486encoding_(pl_1, utf8).
  487extension_(pl_1, pl).
  488label_(pl_1, "Prolog").
  489media_type_(pl_1, media(application/'x-prolog',[])).
  490program_(pl_1, text_editor).
  491
  492encoding_(png_1, octet).
  493extension_(png_1, png).
  494label_(png_1, "Portable Network Graphics (PNG)").
  495media_type_(png_1, media(image/png,[])).
  496program_(png_1, eog).
  497program_(png_1, xfig).
  498
  499extension_(pnm_1, pnm).
  500label_(pnm_1, "Portable Anymap Format (PNM)").
  501media_type_(pnm_1, media(image/'x-portable-anymap',[])).
  502program_(pnm_1, eog).
  503
  504extension_(pot_1, pot).
  505label_(pot_1, "Microsoft PowerPoint").
  506media_type_(pot_1, media(application/'vnd.ms-powerpoint',[])).
  507program_(pot_1, program(libreoffice,['--impress'])).
  508
  509extension_(potm_1, potm).
  510label_(potm_1, "Microsoft PowerPoint Template").
  511media_type_(potm_1, media(application/'vnd.ms-powerpoint.template.macroenabled.12',[])).
  512program_(potm_1, program(libreoffice,['--impress'])).
  513
  514extension_(potx_1, potx).
  515label_(potx_1, "OpenOffice Presentation Template").
  516media_type_(potx_1, media(application/'vnd.openxmlformats-officedocument.presentationml.template',[])).
  517program_(potx_1, program(libreoffice,['--impress'])).
  518
  519extension_(pov_1, pov).
  520label_(pov_1, "Scene-description language for 3D modelling for the Persistence of Vision Raytracer.").
  521
  522extension_(ppa_1, ppa).
  523label_(ppa_1, "Microsoft PowerPoint").
  524media_type_(ppa_1, media(application/'vnd.ms-powerpoint',[])).
  525program_(ppa_1, program(libreoffice,['--impress'])).
  526
  527extension_(ppam_1, ppam).
  528label_(ppam_1, "Microsoft PowerPoint Add-in").
  529media_type_(ppam_1, media(application/'vnd.ms-powerpoint.addin.macroenabled.12',[])).
  530program_(ppam_1, program(libreoffice,['--impress'])).
  531
  532extension_(ppm_1, ppm).
  533label_(ppm_1, "Portable Pixmap Format (PPM)").
  534media_type_(ppm_1, media(image/'x-portable-pixmap',[])).
  535program_(ppm_1, xfig).
  536
  537extension_(pps_1, pps).
  538label_(pps_1, "Microsoft PowerPoint").
  539media_type_(pps_1, media(application/'vnd.ms-powerpoint',[])).
  540program_(pps_1, program(libreoffice,['--impress'])).
  541
  542extension_(ppsm_1, ppsm).
  543label_(ppsm_1, "Microsoft PowerPoint Slideshow").
  544media_type_(ppsm_1, media(application/'vnd.ms-powerpoint.slideshow.macroenabled.12',[])).
  545program_(ppsm_1, program(libreoffice,['--impress'])).
  546
  547extension_(ppsx_1, ppsx).
  548label_(ppsx_1, "OpenOffice Presentation Slideshow").
  549media_type_(ppsx_1, media(application/'vnd.openxmlformats-officedocument.presentationml.slideshow',[])).
  550program_(ppsx_1, program(libreoffice,['--impress'])).
  551
  552extension_(ppt_1, ppt).
  553label_(ppt_1, "Microsoft PowerPoint").
  554media_type_(ppt_1, media(application/'vnd.ms-powerpoint',[])).
  555program_(ppt_1, program(libreoffice,['--impress'])).
  556
  557extension_(pptm_1, pptm).
  558label_(pptm_1, "Microsoft PowerPoint Presentation").
  559media_type_(pptm_1, media(application/'vnd.ms-powerpoint.presentation.macroenabled.12',[])).
  560program_(pptm_1, program(libreoffice,['--impress'])).
  561
  562extension_(pptx_1, pptx).
  563label_(pptx_1, "OpenOffice Presentation").
  564media_type_(pptx_1, media(application/'vnd.openxmlformats-officedocument.presentationml.presentation',[])).
  565program_(pptx_1, program(libreoffice,['--impress'])).
  566
  567extension_(ps_1, ps).
  568label_(ps_1, "PostScript (PS)").
  569media_type_(ps_1, media(application/postscript,[])).
  570program_(ps_1, evince).
  571program_(ps_1, xfig).
  572program_(ps_1, xpdf).
  573
  574extension_(psd_1, psd).
  575label_(psd_1, "Adobe Photoshop Document (PSD)").
  576media_type_(psd_1, media(image/'image/vnd.adobe.photoshop',[])).
  577
  578extension_(rar_1, rar).
  579label_(rar_1, "Roshal Archive (RAR)").
  580media_type_(rar_1, media(application/'vnd.rar',[])).
  581
  582extension_(ras_1, ras).
  583label_(ras_1, "Sun Raster").
  584program_(ras_1, eog).
  585
  586extension_(rdf_1, rdf).
  587family_(rdf_1, rdf).
  588label_(rdf_1, "RDF/XML 1.1").
  589media_type_(rdf_1, media(application/'rdf+xml',[])).
  590program_(rdf_1, text_editor).
  591
  592encoding_(rq_1, utf8).
  593extension_(rq_1, rq).
  594label_(rq_1, "SPARQL 1.1 Query").
  595media_type_(rq_1, media(application/'sparql-query',[])).
  596program_(rq_1, text_editor).
  597
  598extension_(rss_1, rss).
  599label_(rss_1, "Rich Site Summary (RSS)").
  600media_type_(rss_1, media(application/'rss+xml',[])).
  601program_(rss_1, text_editor).
  602
  603extension_(rtf_1, rtf).
  604label_(rtf_1, "Rich Text Format (RTF)").
  605media_type_(rtf_1, media(application/rtf,[])).
  606
  607extension_(ru_1, ru).
  608label_(ru_1, "SPARQL 1.1 Update").
  609media_type_(ru_1, media(application/'sparql-update',[])).
  610program_(ru_1, text_editor).
  611
  612extension_(sgi_1, sgi).
  613label_(sgi_1, "Silicon Graphics Image (SGI)").
  614media_type_(sgi_1, media(image/sgi,[])).
  615
  616encoding_(srj_1, utf8).
  617extension_(srj_1, srj).
  618family_(srj_1, sparql(ask)).
  619family_(srj_1, sparql(select)).
  620label_(srj_1, "SPARQL 1.1 Query Results JSON Format").
  621media_type_(srj_1, media(application/'sparql-results+json',[])).
  622program_(srj_1, text_editor).
  623
  624extension_(srx_1, srx).
  625family_(srx_1, sparql(ask)).
  626family_(srx_1, sparql(select)).
  627label_(srx_1, "SPARQL Query Results XML Format").
  628media_type_(srx_1, media(application/'sparql-results+xml',[])).
  629program_(srx_1, text_editor).
  630
  631extension_(svg_1, svg).
  632label_(svg_1, "Scalable Vector Graphics (SVG)").
  633media_type_(svg_1, media(image/'svg+xml',[])).
  634program_(svg_1, eog).
  635program_(svg_1, firefox).
  636
  637extension_(tar_1, tar).
  638media_type_(tar_1, media(application/'x-tar',[])).
  639label_(tar_1, "TAR").
  640
  641extension_(tga_1, tga).
  642label_(tga_1, "Truevision Advanced Raster Graphics Adapter (TARGA)").
  643media_type_(tga_1, media(image/'x-targa',[])).
  644program_(tga_1, eog).
  645
  646extension_(tiff_1, tiff).
  647label_(tiff_1, "Tagged Image File Format (TIFF)").
  648media_type_(tiff_1, media(image/tiff,[])).
  649program_(tiff_1, eog).
  650program_(tiff_1, xfig).
  651
  652extension_(torrent_1, torrent).
  653label_(torrent_1, "BitTorrent").
  654media_type_(torrent_1, media(application/'x-bittorrent',[])).
  655program_(torrent_1, 'transmission-gtk').
  656
  657encoding_(trig_1, utf8).
  658extension_(trig_1, trig).
  659family_(trig_1, rdf).
  660label_(trig_1, "TriG 1.1").
  661media_type_(trig_1, media(application/trig,[])).
  662program_(trig_1, text_editor).
  663
  664extension_(trix_1, trix).
  665label_(trix_1, "Triples in XML (TriX)").
  666program_(trix_1, text_editor).
  667
  668extension_(tsv_1, tsv).
  669family_(tsv_1, sparql(ask)).
  670family_(tsv_1, sparql(select)).
  671label_(tsv_1, "Tag-separated values (TSV)").
  672media_type_(tsv_1, media(text/'tab-separated-values',[])).
  673program_(tsv_1, text_editor).
  674
  675encoding_(ttl_1, utf8).
  676extension_(ttl_1, ttl).
  677label_(ttl_1, "Turtle 1.1").
  678media_type_(ttl_1, media(text/turtle,[])).
  679program_(ttl_1, text_editor).
  680
  681extension_(wbmp_1, wbmp).
  682label_(wbmp_1, "Wireless Application Protocol Bitmap Format (Wireless Bitmap)").
  683media_type_(wbmp_1, media(image/'vnd.wap.bmp',[])).
  684program_(wbmp_1, eog).
  685
  686extension_(xbm_1, xbm).
  687label_(xbm_1, "X BitMap (XBM)").
  688media_type_(xbm_1, media(image/'x-bitmap',[])).
  689program_(xbm_1, eog).
  690program_(xbm_1, xfig).
  691
  692extension_(xhtml_1, xhtml).
  693family_(xhtml_1, rdf).
  694family_(xhtml_1, rdfa).
  695label_(xhtml_1, "XHTML").
  696media_type_(xhtml_1, media(application/'xhtml+xml',[])).
  697program_(xhtml_1, text_editor).
  698
  699extension_(xla_1, xla).
  700label_(xla_1, "Microsoft Excel").
  701media_type_(xla_1, media(application/'vnd.ms-excel',[])).
  702program_(xla_1, program(libreoffice,['--calc'])).
  703
  704extension_(xlam_1, xlam).
  705label_(xlam_1, "Microsoft Excel Add-in").
  706media_type_(xlam_1, media(application/'vnd.ms-excel.addin.macroenabled.12',[])).
  707program_(xlam_1, program(libreoffice,['--calc'])).
  708
  709extension_(xls_1, xls).
  710label_(xls_1, "Microsoft Excel").
  711media_type_(xls_1, media(application/'vnd.ms-excel',[])).
  712program_(xls_1, program(libreoffice,['--calc'])).
  713
  714extension_(xlsb_1, xlsb).
  715label_(xlsb_1, "Microsoft Excel Spreadsheet").
  716media_type_(xlsb_1, media(application/'vnd.ms-excel.sheet.binary.macroenabled.12',[])).
  717program_(xlsb_1, program(libreoffice,['--calc'])).
  718
  719extension_(xlsm_1, xlsm).
  720label_(xlsm_1, "Microsoft Excel Spreadsheet").
  721media_type_(xlsm_1, media(application/'vnd.ms-excel.sheet.macroenabled.12',[])).
  722program_(xlsm_1, program(libreoffice,['--calc'])).
  723
  724extension_(xlsx_1, xlsx).
  725label_(xlsx_1, "OpenOffice Spreadsheet").
  726media_type_(xlsx_1, media(application/'vnd.openxmlformats-officedocument.spreadsheetml.sheet',[])).
  727program_(xlsx_1, program(libreoffice,['--calc'])).
  728
  729extension_(xlt_1, xlt).
  730label_(xlt_1, "Microsoft Excel").
  731media_type_(xlt_1, media(application/'vnd.ms-excel',[])).
  732program_(xlt_1, program(libreoffice,['--calc'])).
  733
  734extension_(xltm_1, xltm).
  735label_(xltm_1, "Microsoft Excel Template").
  736media_type_(xltm_1, media(application/'vnd.ms-excel.template.macroenabled.12',[])).
  737program_(xltm_1, program(libreoffice,['--calc'])).
  738
  739extension_(xltx_1, xltx).
  740label_(xltx_1, "OpenOffice Spreadsheet Template").
  741media_type_(xltx_1, media(application/'vnd.openxmlformats-officedocument.spreadsheetml.template',[])).
  742program_(xltx_1, program(libreoffice,['--calc'])).
  743
  744extension_(xml_1, xml).
  745label_(xml_1, "Extended Markup Language (XML)").
  746media_type_(xml_1, media(text/xml,[])).
  747program_(xml_1, text_editor).
  748
  749extension_(xpm_1, xpm).
  750label_(xpm_1, "X PixMap (XPM)").
  751media_type_(xpm_1, media(image/'x-xpixmap',[])).
  752program_(xpm_1, eog).
  753program_(xpm_1, xfig).
  754
  755extension_(xz_1, xz).
  756label_(xz_1, "xz").
  757media_type_(xz_1, media(application/'x-xz',[])).
  758
  759extension_(yml_1, yml).
  760label_(yml_1, "YAML Ain't Markup Language (YAML)").
  761media_type_(yml_1, media(application/'x-yaml',[])).
  762program_(yml_1, text_editor).
  763
  764extension_(vdx_1, vdx).
  765label_(vdx_1, "Microsoft Visio XML drawing").
  766
  767extension_(vml_1, vml).
  768label_(vml_1, "Vector Markup Language (VML), part of Microsoft Open Office XML").
  769media_type_(vml_1, media(application/'vnd.openxmlformats-officedocument.vmlDrawing',[])).
  770
  771extension_(vmlz_1, vmlz).
  772label_(vmlz_1, "GNU zipped VML").
  773media_type_(vmlz_1, media(application/'vnd.openxmlformats-officedocument.vmlDrawing',[])).
  774
  775extension_(warc_1, warc).
  776label_(warc_1, "Web ARChive (WARC) archive format").
  777media_type_(warc_1, media(application/warc,[])).
  778
  779extension_(wbmp_1, wbmp).
  780label_(wbmp_1, "Wireless Application Protocol Bitmap Format (WBMP)").
  781media_type_(wbmp_1, media(image/'vnd.wap.wbmp',[])).
  782
  783extension_(webp_1, webp).
  784media_type_(webp_1, media(image/webp,[])).
  785label_(webp_1, "Google image format for the web (WebP)").
  786
  787extension_(wmv_1, wmv).
  788label_(wmv_1, "Windows Media Video (WMV)").
  789media_type_(wmv_1, media(video/'x-ms-wmv',[])).
  790program_(wmv_1, vlc).
  791
  792extension_(wrl_1, wrl).
  793media_type_(wrl_1, media(model/vrml,[])).
  794label_(wrl_1, "Virtual Reality Modeling Language (VRML)").
  795
  796extension_(wrz_1, wrz).
  797label_(wrz_1, "GNU zipped VRML").
  798media_type_(wrz_1, media(model/vrml,[])).
  799
  800extension_(zip_1, zip).
  801label_(zip_1, "ZIP").
  802media_type_(zip_1, media(application/zip,[]))