Proposal for new types in library(error)

104 views
Skip to first unread message

Julio Di Egidio

unread,
Sep 17, 2016, 6:08:19 AM9/17/16
to swi-p...@googlegroups.com
Hello Jan, guys,

I'd propose the following types be added to library(error).

In the list, I am including some types that already exist because the
definition changes slightly, but the functionality stays the same (mainly
introducing some aliases).

I am also using a classification that I myself do not find satisfactory,
but if we could sort out a good classification, I think that might help the
readability of the docs (as the list of types becomes quite longer).

If overall you like the idea, please feel free to propose specific
amendments/deletions/additions. If we get to an agreement (a final list),
I'll be glad to do the coding (unless someone else wants to).

There are 3 columns below, Spec, Descr and Def. I am using a pseudo-DCG
not rigorous syntax for Def, but I hope you can decipher it:

Base types:
---
| none                  | No term (always fails)        | {fail}                                |
| not(Type)             | Not has type Type             | {\+ has_type(Type, Term)}             |
| var(Type)             | Variable or has type Type     | var; Type                             |
| part                  | Partially instantiated        | callable, not(ground)                 | #####
| attvar                | Attributed variable           | {attvar(Term)}                        |
| blob                  | Blob                          | {blob(Term, _)}                       | #####
| blob(BType)           | Blob of "type" BType          | {blob(Term, BType)}                   | #####
| engine                | Engine handle                 | {is_engine(Term)}                     |
| thread                | Thread handle                 | {is_thread(Term)}                     |
| stream                | Stream handle                 | {is_stream(Term)}                     |

Common types:
---
| mod(Type)             | Module-qualified              | atom':'Type                           | #####
| predind               | Predicate indicator           | atom'/'nonneg; atom'//'nonneg         |
| order                 | One of [, <, >]               | ground, {memberchk(Term, [, <, >])}   |
| char                  | 1-character atom              | atom, {atom_length(Term, 1)}          |
| chars                 | List of char                  | list(char)                            | **
| code                  | Unicode character code        | int(1, 0x10ffff)                      |
| codes                 | List of code                  | list(code)                            | **
| formatted             | Text or format-args.          | text'-'list; text                     |
| error                 | Formal error                  | 'error'(callable, any)                |
| fname                 | File name                     | text                                  |
| fpipe                 | File pipe(Cmd)                | 'pipe'(atom; string)                  |
| fspec                 | File name or pipe(Cmd)        | fname; fpipe                          | #####
| pair                  | Pair                          | pair(any, any)                        |
| pair(KType, VType)    | Pair of type KType, VType     | KType'-'VType                         |

Numeric types:
---
| num                   | Number                        | {number(Term)}                        |
| int                   | Integer                       | {integer(Term)}                       |
| float                 | Float                         | {float(Term)}                         |
| ratio                 | Rational                      | {rational(Term)}                      |
| nonneg                | Non-negative integer          | int, {Term >= 0}                       |
| nonpos                | Non-positive integer          | int, {Term =< 0}                       |
| posint                | Positive integer              | int, {Term > 0}                       |
| negint                | Negative integer              | int, {Term < 0}                       |
| num(L, H)             | Number in [L; H]              | num, {L =< Term, Term =< H}           |
| int(L, H)             | Integer in [L; H]             | int, {L =< Term, Term =< H}           |
| float(L, H)           | Float in [L; H]               | float, {L =< Term, Term =< H}         |
| ratio(L, H)           | Rational in [L; H]            | ratio, {L =< Term, Term =< H}         |

Type aliases:
---
| partial               | Partially instantiated        | part                                  |
| module(Type)          | Module-qualified              | mod(Type)                             |
| structure             | Structure (aka callable)      | callable                              |
| formal_error          | Formal error                  | error                                 |
| number                | Number                        | num                                   | **
| integer               | Integer                       | int                                   | **
| rational              | Rational                      | ratio                                 | **
| positive_integer      | Positive integer              | posint                                | **
| negative_integer      | Negative integer              | negint                                | **
| between(L, H)         | Number in [L; H]              | num(L, H)                             | **

** Already exists (the definition is different but functionally equivalent).

##### Please verify (in particular).

Thank you,

Julio

Paulo Moura

unread,
Sep 17, 2016, 9:32:45 AM9/17/16
to SWI-Prolog
Hi Julio,

> On 17/09/2016, at 11:08, Julio Di Egidio <ju...@diegidio.name> wrote:
>
> Hello Jan, guys,
>
> I'd propose the following types be added to library(error).
>
> In the list, I am including some types that already exist because the
> definition changes slightly, but the functionality stays the same (mainly
> introducing some aliases).
>
> I am also using a classification that I myself do not find satisfactory,
> but if we could sort out a good classification, I think that might help the
> readability of the docs (as the list of types becomes quite longer).
>
> If overall you like the idea, please feel free to propose specific
> amendments/deletions/additions. If we get to an agreement (a final list),
> I'll be glad to do the coding (unless someone else wants to).

I recently added a "type" object to the Logtalk library and, in doing so, I looked into the existing similar support across several Prolog systems. The documentation (includes a list of all types) and the code are available at:

http://logtalk.org/library/type_0.html

https://github.com/LogtalkDotOrg/logtalk3/blob/master/library/type.lgt

Part of designing a type library comes down to design choices (with portability being a main goal in the Logtalk case) but you may find something useful in the links above.

Cheers,
Paulo


> There are 3 columns below, Spec, Descr and Def. I am using a pseudo-DCG
> not rigorous syntax for Def, but I hope you can decipher it:
>
> Base types:
> ---
> | none | No term (always fails) | {fail} |
> | not(Type) | Not has type Type | {\+ has_type(Type, Term)} |
> | var(Type) | Variable or has type Type | var; Type |
> | part | Partially instantiated | callable, not(ground) | #####
> | attvar | Attributed variable | {attvar(Term)} |
> | blob | Blob | {blob(Term, _)} | #####
> | blob(BType) | Blob of "type" BType | {blob(Term, BType)} | #####
> | engine | Engine handle | {is_engine(Term)} |
> | thread | Thread handle | {is_thread(Term)} |
> | stream | Stream handle | {is_stream(Term)} |
>
> Common types:
> ---
> | mod(Type) | Module-qualified | atom':'Type |
> | predind | Predicate indicator | atom'/'nonneg; atom'//'nonneg |
> | order | One of [, <, >] | ground, {memberchk(Term, [, <, >])} |
> | char | 1-character atom | atom, {atom_length(Term, 1)} |
> | chars | List of char | list(char) | **
> | code | Unicode character code | int(1, 0x10ffff) |
> | codes | List of code | list(code) | **
> | formatted | Text or format-args. | text'-'list; text |
> | error | Formal error | 'error'(callable, any) |
> | fname | File name | text |
> | fpipe | File pipe(Cmd) | 'pipe'(atom; string) |
> | fspec | File name or pipe(Cmd) | fname; fpipe | #####
> | pair | Pair | pair(any, any) |
> | pair(KType, VType) | Pair of type KType, VType | KType'-'VType |
>
> Numeric types:
> ---
> | num | Number | {number(Term)} |
> | int | Integer | {integer(Term)} |
> | float | Float | {float(Term)} |
> | ratio | Rational | {rational(Term)} |
> | nonneg | Non-negative integer | int, {Term > 0} |
> | nonpos | Non-positive integer | int, {Term < 0} |
> | posint | Positive integer | int, {Term > 0} |
> | negint | Negative integer | int, {Term < 0} |
> | num(L, H) | Number in [L; H] | num, {L =< Term, Term =< H} |
> | int(L, H) | Integer in [L; H] | int, {L =< Term, Term =< H} |
> | float(L, H) | Float in [L; H] | float, {L =< Term, Term =< H} |
> | ratio(L, H) | Rational in [L; H] | ratio, {L =< Term, Term =< H} |
>
> Type aliases:
> ---
> | partial | Partially instantiated | part |
> | module(Type) | Module-qualified | mod(Type) |
> | structure | Structure (aka callable) | callable |
> | formal_error | Formal error | error |
> | number | Number | num | **
> | integer | Integer | int | **
> | rational | Rational | ratio | **
> | positive_integer | Positive integer | posint | **
> | negative_integer | Negative integer | negint | **
> | between(L, H) | Number in [L; H] | num(L, H) | **
>
> ** Already exists (the definition is different but functionally equivalent).
>
> ##### Please verify (in particular).
>
> Thank you,
>
> Julio
>
>
> --
> You received this message because you are subscribed to the Google Groups "SWI-Prolog" group.
> To unsubscribe from this group and stop receiving emails from it, send an email to swi-prolog+...@googlegroups.com.
> Visit this group at https://groups.google.com/group/swi-prolog.
> For more options, visit https://groups.google.com/d/optout.

-----------------------------------------------------------------
Paulo Moura
Logtalk developer

Email: <mailto:pmo...@logtalk.org>
Web: <http://logtalk.org/>
-----------------------------------------------------------------




Jan Burse

unread,
Sep 17, 2016, 2:34:16 PM9/17/16
to SWI-Prolog
The ISO standard defines a couple of types. For example
the following types I dont find in your list:

     byte    :  0..255      /* first occurence in glossary section 3.22 */
     byte_or_eof : union type of byte and integer -1
            /* callled in_byte in the standard, see section 8.13.1.1 */
     char_or_eof : union type of char and atom 'end_of_file'
            /* callled in_character in the standard, see section 8.12.1.1 */
     code_or_eof : union type of code and integer -1
            /* callled in_character_code in the standard, see section 8.12.1.5 */
     What else?

On a side note, I dont find type checking for:
     dicts??

Also it should be checked whether all the extra types of
SWI-Prolog, such as string, blob, dict, etc. satisfy the
clauses of 5.5.4 Types in the iso standard.

     a) new type must be disjoint
         (not satisified for the Jekejeke reference type,
          the type check for all clases along the inheritance
          chain succeeds)

     b) disjointness must carry over to compare
         (not satisified for the Jekejeke reference type,
          if it implements the comparable interface,
          it can compare across classes)
  
      c) type can be use in clausses
         (works for the reference type in Jekejeke,
          GC done by Java GC itself)

      d) tokenizer and parser
         (currently no support in Jekejeke reference
          type, SWI-Prolog situation slightly better,
          for example string and dict have their own syntax)

      e) evaluation
          (currently the reference data type in Jekejeke
          evaluates to itself)

      f) unparsing
        (currently the reference data type cannot really
         be written, since it can also not be read, only informative
         the hash code)
 
Or maybe some of the clauses of 5.5.4 Types must
be declared as not useful. In Logtalk I guess a) and b)
might be also violated by term objects?? Not sure what
Logtalk is doing with the rest of the clauses.

Bye

Jan Burse

unread,
Sep 17, 2016, 2:44:50 PM9/17/16
to SWI-Prolog
For FFIs (foreign function interfaces), it might be also useful to
have types such as int16, uint32, float32 and array types.

In ECLiPSe and untyped array is just a compound with functor
'[]'. But similar to homogenous lists, one might also define homogenous
arrays over some other type. Such an array of byte.

Here is for example a Sudoku with Arrays:
http://stackoverflow.com/a/20507755/502187

Will not work in SWI-Prolog, since the SWI-Prolog CLP(FD) doesn't
support array access yet. Right?
| ratio(L, H)           | Rational in [<span styl

Jan Burse

unread,
Sep 17, 2016, 2:51:18 PM9/17/16
to SWI-Prolog
Anybody hears the arms race call? Could do array access in next
release of Jekejeke CLP(FD). To begin with, one would need to
support the array access syntax first (I guess SWI-Prolog can already
do it, but it is not enabled by default):

?- use_module(library(clpfd)).

true.

?- X #= Y.

X = Y,

Y in inf..sup.

?- X #= Y[1,2].

ERROR: Syntax error: Operator expected

ERROR: X #=

ERROR: ** here **

ERROR: Y[1,2] .


I did not yet do it, since I am still elaborating the arrays itself. Had
some strange ideas recently of embedding T[] java arrays somehow,

and they would also allow variable based terms access and modification,
but it is still tricky, but the analogy to compound helps in developing ideas further!

Bye

Julio Di Egidio

unread,
Sep 19, 2016, 11:39:53 AM9/19/16
to SWI-Prolog
On Saturday, September 17, 2016 at 3:32:45 PM UTC+2, Paulo Moura wrote:
Hi Julio,

> On 17/09/2016, at 11:08, Julio Di Egidio <ju...@diegidio.name> wrote:
>
> Hello Jan, guys,
>
> I'd propose the following types be added to library(error).
>
> In the list, I am including some types that already exist because the
> definition changes slightly, but the functionality stays the same (mainly
> introducing some aliases).
>
> I am also using a classification that I myself do not find satisfactory,
> but if we could sort out a good classification, I think that might help the
> readability of the docs (as the list of types becomes quite longer).
>
> If overall you like the idea, please feel free to propose specific
> amendments/deletions/additions. If we get to an agreement (a final list),
> I'll be glad to do the coding (unless someone else wants to).

I recently added a "type" object to the Logtalk library and, in doing so, I looked into the existing similar support across several Prolog systems. The documentation (includes a list of all types) and the code are available at:

http://logtalk.org/library/type_0.html

https://github.com/LogtalkDotOrg/logtalk3/blob/master/library/type.lgt

Part of designing a type library comes down to design choices (with portability being a main goal in the Logtalk case) but you may find something useful in the links above.

Hi Paulo, thanks for the feedback.

Except of course for the platform specific types, there is indeed a good match with the types in library(error), which is good.  I also like your classification, pretty clear.

I'd have a reservation on a types/1, as I think that already belongs to a "structured" type system (i.e. checking structures, then also disjunctions and conjunctions, as well as partial instantiations, etc.), not necessarily to a low level infrastructure.  But I have myself included few meta-types above (not/1 and var/1 in particular), so I guess where exactly to draw that line is debatable...

Possibly tougher, I'd have also some reservations on check/2 being multifile instead of valid/2: not because I don't see the point, but really because, contrary to what SWI itself does at the moment (regardless that has_type/2 is the extensible predicate, the logic for throwing exceptions on the pre-defined types is the same as yours), I'd expect a library(error) to only raise type errors...  E.g. if I declare N:between(1,10), I do mean a type, not a type plus a domain restriction.  Conversely, I'd rather propose a check_domain/3, aside an explicit check_type/2, kind of predicate where not only the type but also a domain is passed in as argument, essentially to keeping two notions, of type and domain, distinct.  It is also then possible to have valid/2 as basic, the idea of domain does not enter the library at all: just the idea of instantiation remains, but even on that I'd at least raise some caution...

Your thoughts?

Julio

Julio Di Egidio

unread,
Sep 19, 2016, 11:44:17 AM9/19/16
to SWI-Prolog
On Saturday, September 17, 2016 at 8:34:16 PM UTC+2, Jan Burse wrote:
The ISO standard defines a couple of types. For example
the following types I dont find in your list:

     byte    :  0..255      /* first occurence in glossary section 3.22 */
     byte_or_eof : union type of byte and integer -1
            /* callled in_byte in the standard, see section 8.13.1.1 */
     char_or_eof : union type of char and atom 'end_of_file'
            /* callled in_character in the standard, see section 8.12.1.1 */
     code_or_eof : union type of code and integer -1
            /* callled in_character_code in the standard, see section 8.12.1.5 */
     What else?

OK, I'll consider these.
 
On a side note, I dont find type checking for:
     dicts??

Dicts are a SWI-specific extension.

Also it should be checked whether all the extra types of
SWI-Prolog, such as string, blob, dict, etc. satisfy the
clauses of 5.5.4 Types in the iso standard.

Interesting question...

Julio
 <snip>

Julio Di Egidio

unread,
Sep 19, 2016, 11:54:44 AM9/19/16
to SWI-Prolog
On Saturday, September 17, 2016 at 8:44:50 PM UTC+2, Jan Burse wrote:
For FFIs (foreign function interfaces), it might be also useful to
have types such as int16, uint32, float32 and array types.

Yes, though in SWI there are three types of integers:
I suppose Jan could say a final word on which are the correct ones.

Not only for the native interface, e.g. flag/3 is said to be limited to 64 bit integers
(is that correct for 32 bit architectures as well?).

In ECLiPSe and untyped array is just a compound with functor
'[]'. But similar to homogenous lists, one might also define homogenous
arrays over some other type. Such an array of byte.

But arrays just do not exist in core Prolog, not even as a SWI-specific extension.

Julio


Paulo Moura

unread,
Sep 19, 2016, 12:20:25 PM9/19/16
to SWI-Prolog
Hi Julio,

> On 19/09/2016, at 16:39, Julio Di Egidio <ju...@diegidio.name> wrote:
>
> On Saturday, September 17, 2016 at 3:32:45 PM UTC+2, Paulo Moura wrote:
> Hi Julio,
>
> > On 17/09/2016, at 11:08, Julio Di Egidio <ju...@diegidio.name> wrote:
> >
> > Hello Jan, guys,
> >
> > I'd propose the following types be added to library(error).
> >
> > In the list, I am including some types that already exist because the
> > definition changes slightly, but the functionality stays the same (mainly
> > introducing some aliases).
> >
> > I am also using a classification that I myself do not find satisfactory,
> > but if we could sort out a good classification, I think that might help the
> > readability of the docs (as the list of types becomes quite longer).
> >
> > If overall you like the idea, please feel free to propose specific
> > amendments/deletions/additions. If we get to an agreement (a final list),
> > I'll be glad to do the coding (unless someone else wants to).
>
> I recently added a "type" object to the Logtalk library and, in doing so, I looked into the existing similar support across several Prolog systems. The documentation (includes a list of all types) and the code are available at:
>
> http://logtalk.org/library/type_0.html
>
> https://github.com/LogtalkDotOrg/logtalk3/blob/master/library/type.lgt
>
> Part of designing a type library comes down to design choices (with portability being a main goal in the Logtalk case) but you may find something useful in the links above.
>
> Hi Paulo, thanks for the feedback.
>
> Except of course for the platform specific types, there is indeed a good match with the types in library(error), which is good. I also like your classification, pretty clear.
>
> I'd have a reservation on a types/1, as I think that already belongs to a "structured" type system (i.e. checking structures, then also disjunctions and conjunctions, as well as partial instantiations, etc.), not necessarily to a low level infrastructure.

Possibly. But the cost of having it is low and is handy for some of the Logtalk built-in predicates (e.g. implements_protocol/2-3 can take either an object or a category identifier as the first argument).

> But I have myself included few meta-types above (not/1 and var/1 in particular), so I guess where exactly to draw that line is debatable...

I use var_or/1 as this name is already found in some systems (e.g. SICStus IIRC). It's quite useful for a good number of standard predicates (both in Prolog and Logtalk).

> Possibly tougher, I'd have also some reservations on check/2 being multifile instead of valid/2: not because I don't see the point, but really because, contrary to what SWI itself does at the moment (regardless that has_type/2 is the extensible predicate, the logic for throwing exceptions on the pre-defined types is the same as yours), I'd expect a library(error) to only raise type errors...

A minor point is that, in my case, is not library(error) but library(type) so the intended functionality is not exactly the same.

Besides portability issues, there are a couple of aspects that I don't like in the SWI-Prolog approach. One is the need for a is_not/2 predicate to "fix" the exceptions. This predicate is (currently) not declared multifile. Thus, it cannot be easily extended by the user. As you have noticed, this is the reason why check/2 is multifile instead of valid/2. Another aspect is the missing must_be/3 to allow passing the context of an error (i.e. the second argument of the error/2 exception term). This is "fixed" in my case by the check/3 predicate.

> E.g. if I declare N:between(1,10), I do mean a type, not a type plus a domain restriction.

The domain is quite useful. Take between(Type, Lower, Upper). Assuming that I'm checking number intervals, if we pass e.g. Type = integer or Type = float, we're forbidding mixed type arithmetic. But if we want it, we can simply do e.g. Type = number.

For collection types such as one_of(Type, Set), the Type argument allows us to distinguish some set membership cases that would not be possible without it. Another reason, of course, is that you want the domain errors.

> Conversely, I'd rather propose a check_domain/3, aside an explicit check_type/2, kind of predicate where not only the type but also a domain is passed in as argument, essentially to keeping two notions, of type and domain, distinct.

That's certainly possible. Although I prefer the combination of both domain and type errors being generated by the same predicate, the user can always add the check_domain/3 predicate to the library "type" object (using a complementing category). And, of course, nothing prevents adding e.g. between/2 or one_of/1.

> It is also then possible to have valid/2 as basic, the idea of domain does not enter the library at all: just the idea of instantiation remains, but even on that I'd at least raise some caution...
>
> Your thoughts?

For the type-checking usage scenarios I want, is simpler to have the check/2-3 predicates throw instantiation, domain, and type errors.

Cheers,
Paulo

Julio Di Egidio

unread,
Sep 20, 2016, 2:53:26 AM9/20/16
to SWI-Prolog
On Monday, September 19, 2016 at 6:20:25 PM UTC+2, Paulo Moura wrote:
On 19/09/2016, at 16:39, Julio Di Egidio <ju...@diegidio.name> wrote:
<snip> 
> I'd have a reservation on a types/1, as I think that already belongs to a "structured" type system (i.e. checking structures, then also disjunctions and conjunctions, as well as partial instantiations, etc.), not necessarily to a low level infrastructure.

Possibly. But the cost of having it is low and is handy for some of the Logtalk built-in predicates (e.g. implements_protocol/2-3 can take either an object or a category identifier as the first argument).

Eventually, I think I agree, and adding the "structured" types is easy enough: I suppose and/2 (possibly as ','/2), or/2 (as ';'/2) and not/1 (as ??) plus a partial/1 (as ??) should be enough, agreed?

>  E.g. if I declare N:between(1,10), I do mean a type, not a type plus a domain restriction.

The domain is quite useful. Take between(Type, Lower, Upper). Assuming that I'm checking number intervals, if we pass e.g. Type = integer or Type = float, we're forbidding mixed type arithmetic. But if we want it, we can simply do e.g. Type = number.

For collection types such as one_of(Type, Set), the Type argument allows us to distinguish some set membership cases that would not be possible without it. Another reason, of course, is that you want the domain errors.

Well, no, I really don't: unless you have specific reasons why I should...  (And I was not saying let's drop the type check: that between(1,10) was just an example of a type as offered by SWI that does a type check plus the domain check.)

>  Conversely, I'd rather propose a check_domain/3, aside an explicit check_type/2, kind of predicate where not only the type but also a domain is passed in as argument, essentially to keeping two notions, of type and domain, distinct.

That's certainly possible. Although I prefer the combination of both domain and type errors being generated by the same predicate, the user can always add the check_domain/3 predicate to the library "type" object (using a complementing category). And, of course, nothing prevents adding e.g. between/2 or one_of/1.

Hmm, it's just not the same: with your (and SWI's implied) approach, if we want -say- between(int,1 10) to be properly a type, we rather have to define a new type.  "We can add more salt to a plate, we cannot take it off if it is too much."  With the approach I am delineating, everything instead is properly "stratified", logically and semantically, not to mention, properly modular.  For another example, var/0 and var_or/1 (var/1 in SWI) make little sense in the context of a library that throws instantiation errors *otherwise*: meaning that I too want them there, just, to reiterate, throwing errors other than type errors I think is improper.  Not to mention, which too I'd think is indicative, fixing library(error) with check/2 (must_be/2 in SWI) the extensible predicate would be a dramatic breaking change, while clearly separating the notion of type from that of domain would even simplify and straighten up SWI's code at a much lower cost in terms of breaking changes.  --  Anyway, while I find that a very interesting and possibly useful discussion, it's also good that it is not blocking re the immediate issue of adding types to the existing library(error).

Julio

Jan Wielemaker

unread,
Sep 20, 2016, 2:58:58 AM9/20/16
to Julio Di Egidio, SWI-Prolog
On 09/19/2016 05:54 PM, Julio Di Egidio wrote:
> On Saturday, September 17, 2016 at 8:44:50 PM UTC+2, Jan Burse wrote:
>
> For FFIs (foreign function interfaces), it might be also useful to
> have types such as int16, uint32, float32 and array types.
>
>
> Yes, though in SWI there are three types of integers:
> http://www.swi-prolog.org/pldoc/man?section=artypes
> I suppose Jan could say a final word on which are the correct ones.

The internal integer representations are not important. They cannot
be distinguished at the Prolog level. The C interface has a number of
PL_get_<some int type>[_ex](term_t t, <some int type>*ip); The _ex
versions raise a domain error if the Prolog type is integer, but the
value is outside the range of the requested integer type.

The description of these types in the docs is mainly there to make
you aware that

- small integers are cheap
- 64-bit integers are more expensive and always present
- large integers are even more expensive and only there when
linked with libgmp.

I'm not sure there is much value in having these types in library(error).
Surely I never felt the need to use them myself.

Cheers --- Jan

>
> Not only for the native interface, e.g. flag/3 is said to be limited to
> 64 bit integers
> (is that correct for 32 bit architectures as well?).
>
> In ECLiPSe and untyped array is just a compound with functor
> '[]'. But similar to homogenous lists, one might also define homogenous
> arrays over some other type. Such an array of byte.
>
>
> But arrays just do not exist in core Prolog, not even as a SWI-specific
> extension.
>
> Julio
> |
>
>
> |
>
> --
> You received this message because you are subscribed to the Google
> Groups "SWI-Prolog" group.
> To unsubscribe from this group and stop receiving emails from it, send
> an email to swi-prolog+...@googlegroups.com
> <mailto:swi-prolog+...@googlegroups.com>.

Paulo Moura

unread,
Sep 20, 2016, 7:09:54 AM9/20/16
to SWI-Prolog
Hi Julio,

> On 20/09/2016, at 07:53, Julio Di Egidio <ju...@diegidio.name> wrote:
>
> On Monday, September 19, 2016 at 6:20:25 PM UTC+2, Paulo Moura wrote:
> On 19/09/2016, at 16:39, Julio Di Egidio <ju...@diegidio.name> wrote:
> <snip>
> > I'd have a reservation on a types/1, as I think that already belongs to a "structured" type system (i.e. checking structures, then also disjunctions and conjunctions, as well as partial instantiations, etc.), not necessarily to a low level infrastructure.
>
> Possibly. But the cost of having it is low and is handy for some of the Logtalk built-in predicates (e.g. implements_protocol/2-3 can take either an object or a category identifier as the first argument).
>
> Eventually, I think I agree, and adding the "structured" types is easy enough: I suppose and/2 (possibly as ','/2), or/2 (as ';'/2) and not/1 (as ??) plus a partial/1 (as ??) should be enough, agreed?

Possibly. But the reality is that, no matter which structured types you use, specs can become quite verbose easily. e.g. types([var,object_identifier,category_identifier]) or or(var,or(...,...)) or any other variation. If a spec is common, I suspect most users would simply prefer to define a new type with a nice shorter name than use these structured types heavily.

> > E.g. if I declare N:between(1,10), I do mean a type, not a type plus a domain restriction.
>
> The domain is quite useful. Take between(Type, Lower, Upper). Assuming that I'm checking number intervals, if we pass e.g. Type = integer or Type = float, we're forbidding mixed type arithmetic. But if we want it, we can simply do e.g. Type = number.
>
> For collection types such as one_of(Type, Set), the Type argument allows us to distinguish some set membership cases that would not be possible without it. Another reason, of course, is that you want the domain errors.
>
> Well, no, I really don't: unless you have specific reasons why I should...

In my case, I do want/need the domain (also the instantiation) errors. A main reason is a future type-checker that would signal errors following the predicate specs (which specify instantiation, type, and domain errors).

> (And I was not saying let's drop the type check: that between(1,10) was just an example of a type as offered by SWI that does a type check plus the domain check.)

1 =< 1.5 =< 10. It could be fine in some cases and an error in others. The Type argument in between(Type, 1, 10) disambiguates and *allows* for the two cases.

> > Conversely, I'd rather propose a check_domain/3, aside an explicit check_type/2, kind of predicate where not only the type but also a domain is passed in as argument, essentially to keeping two notions, of type and domain, distinct.

I guess my point here is that, even if you regard them as distinct, there are many cases where they are used together in predicate specs.

> That's certainly possible. Although I prefer the combination of both domain and type errors being generated by the same predicate, the user can always add the check_domain/3 predicate to the library "type" object (using a complementing category). And, of course, nothing prevents adding e.g. between/2 or one_of/1.
>
> Hmm, it's just not the same: with your (and SWI's implied) approach, if we want -say- between(int,1 10) to be properly a type, we rather have to define a new type.

We can interpret between(integer, 1, 10) as either specifying a new type or as specifying a domain (or interval) over integers. Personally, I'm not concern is this bit of fuzziness.

> "We can add more salt to a plate, we cannot take it off if it is too much." With the approach I am delineating, everything instead is properly "stratified", logically and semantically, not to mention, properly modular.

I don't see anything wrong in your approach. The only "truth way" that matters is the one that solves the problem at hand. We're discussing libraries and there's certainly room for users to propose and use alternative libraries. E.g. in SWI-Prolog we have to lambda libraries, one bundled and another provided as a pack. They use different names and thus do not conflict.

> For another example, var/0 and var_or/1 (var/1 in SWI) make little sense in the context of a library that throws instantiation errors *otherwise*: meaning that I too want them there,

Yes, was I mentioned above, I also want the instantiation errors.

> just, to reiterate, throwing errors other than type errors I think is improper. Not to mention, which too I'd think is indicative, fixing library(error) with check/2 (must_be/2 in SWI)

(btw, Logtalk uses check/2 and valid/2 instead of must_be/2 and friends for the simple reason that check/1 and valid/1 were already in use in its library before library(error) was added to SWI-Prolog)

> the extensible predicate would be a dramatic breaking change, while clearly separating the notion of type from that of domain would even simplify and straighten up SWI's code at a much lower cost in terms of breaking changes. -- Anyway, while I find that a very interesting and possibly useful discussion, it's also good that it is not blocking re the immediate issue of adding types to the existing library(error).

Cheers,
Paulo

Julio Di Egidio

unread,
Sep 21, 2016, 7:55:56 PM9/21/16
to SWI-Prolog
On Tuesday, September 20, 2016 at 1:09:54 PM UTC+2, Paulo Moura wrote:
> On 20/09/2016, at 07:53, Julio Di Egidio <ju...@diegidio.name> wrote:
> On Monday, September 19, 2016 at 6:20:25 PM UTC+2, Paulo Moura wrote:
> > On 19/09/2016, at 16:39, Julio Di Egidio <ju...@diegidio.name> wrote:
> <snip>
> > > I'd have a reservation on a types/1, as I think that already belongs to a "structured" type system (i.e. checking structures, then also disjunctions and conjunctions, as well as partial instantiations, etc.), not necessarily to a low level infrastructure.
>
> > Possibly. But the cost of having it is low and is handy for some of the Logtalk built-in predicates (e.g. implements_protocol/2-3 can take either an object or a category identifier as the first argument).
>
> Eventually, I think I agree, and adding the "structured" types is easy enough: I suppose and/2 (possibly as ','/2), or/2 (as ';'/2) and not/1 (as ??) plus a partial/1 (as ??) should be enough, agreed?

Possibly. But the reality is that, no matter which structured types you use, specs can become quite verbose easily. e.g. types([var,object_identifier,category_identifier]) or or(var,or(...,...)) or any other variation. If a spec is common, I suspect most users would simply prefer to define a new type with a nice shorter name than use these structured types heavily.

Yes, of course, but then we are back to square one...  I rather like your "cost of having it is low and is handy", so I'd just add those.

> >  E.g. if I declare N:between(1,10), I do mean a type, not a type plus a domain restriction.
>
> The domain is quite useful. Take between(Type, Lower, Upper). Assuming that I'm checking number intervals, if we pass e.g. Type = integer or Type = float, we're forbidding mixed type arithmetic. But if we want it, we can simply do e.g. Type = number.
>
> For collection types such as one_of(Type, Set), the Type argument allows us to distinguish some set membership cases that would not be possible without it. Another reason, of course, is that you want the domain errors.
>
> Well, no, I really don't: unless you have specific reasons why I should...

In my case, I do want/need the domain (also the instantiation) errors. A main reason is a future type-checker that would signal errors following the predicate specs (which specify instantiation, type, and domain errors).

I don't think that is a good argument: as said, with that approach, we cannot have just the pure type errors, while by keeping the two notions, of type and domain, distinct, everything can be done (including what you want, at the cost of few extra-lines of code and not even for the user) and consistently, while with your way or SWI's consistency is simply lost and unrecoverable...  And now that is a serious issue, because it rather makes library(error) fundamentally broken.  OTOH, it's true that the same logic is all over the place already, including the C interface as Jan notices above, and while this to me, as said, makes the whole thing fundamentally broken, I am not sure we can reasonably do anything at all about it...  other than, indeed, just forgetting about it and roll out our own: and I mean, both library(error) and the native checked interface...  Hmm....

Julio

Julio Di Egidio

unread,
Sep 21, 2016, 8:33:08 PM9/21/16
to SWI-Prolog
On Thursday, September 22, 2016 at 1:55:56 AM UTC+2, Julio Di Egidio wrote:
On Tuesday, September 20, 2016 at 1:09:54 PM UTC+2, Paulo Moura wrote:
> On 20/09/2016, at 07:53, Julio Di Egidio <ju...@diegidio.name> wrote:
> > On Monday, September 19, 2016 at 6:20:25 PM UTC+2, Paulo Moura wrote:
> > > On 19/09/2016, at 16:39, Julio Di Egidio <ju...@diegidio.name> wrote:
<snip>
> >  E.g. if I declare N:between(1,10), I do mean a type, not a type plus a domain restriction.
>
> The domain is quite useful. Take between(Type, Lower, Upper). Assuming that I'm checking number intervals, if we pass e.g. Type = integer or Type = float, we're forbidding mixed type arithmetic. But if we want it, we can simply do e.g. Type = number.
>
> For collection types such as one_of(Type, Set), the Type argument allows us to distinguish some set membership cases that would not be possible without it. Another reason, of course, is that you want the domain errors.
>
> Well, no, I really don't: unless you have specific reasons why I should...

In my case, I do want/need the domain (also the instantiation) errors. A main reason is a future type-checker that would signal errors following the predicate specs (which specify instantiation, type, and domain errors).

I don't think that is a good argument: as said, with that approach, we cannot have just the pure type errors, while by keeping the two notions, of type and domain, distinct, everything can be done (including what you want, at the cost of few extra-lines of code and not even for the user) and consistently, while with your way or SWI's consistency is simply lost and unrecoverable...  And now that is a serious issue, because it rather makes library(error) fundamentally broken.  OTOH, it's true that the same logic is all over the place already, including the C interface as Jan notices above, and while this to me, as said, makes the whole thing fundamentally broken, I am not sure we can reasonably do anything at all about it...  other than, indeed, just forgetting about it and roll out our own: and I mean, both library(error) and the native checked interface...  Hmm....

Anyway, never mind: while I think that is a legitimate discussion/objection on its own, it is indeed not reasonable to rewrite the whole system, while, on the other hand, it is a little bit unfortunate but doable having to define new error types that do not throw domain or even instantiation errors when needed.  So, at least for the immediate purpose of completing library(error), and hoping the "inconsistency" does not creep up again later at some point, I'd just say OK, let it be.

At this point, I'll just come up with a revised proposal that takes into account all the feedback so far... (some of it is in a private conversation I had with Jan, but it only adds about aliases: I'll include those in the revised proposal).  Please bear with me...

Julio

Jan Wielemaker

unread,
Sep 22, 2016, 3:43:54 AM9/22/16
to Julio Di Egidio, SWI-Prolog
Personally I think the whole domain/type argument is rather
artificial. Prolog is an untyped language where everything is a term.
Variables are a little odd in this discussion. Both types and domains
however just tell you that a subset of all terms is admissible. While
raising errors in the core and libraries I quite often have a hard
time to define whether something is a type or domain error. Roughly I
think the types are integer, float, number, atom, string, compound and
a few more. By a character code? A one-char atom (char)? Does each
functor (name/arity) define a subtype of compound?

Library error is mostly about practicalities. It makes it fairly easy
to check terms at runtime and throw the appropriate error.

I think my ideal is a principled description of types, type aliases
and instantiation (partial terms) that can be inspected and reasoned
about and automatically generated code that is close to the current
API of library(error).

Cheers --- Jan

>
> Anyway, never mind: while I think that is a legitimate
> discussion/objection on its own, it is indeed not reasonable to rewrite
> the whole system, while, on the other hand, it is a little bit
> unfortunate but doable having to define new error types that do not
> throw domain or even instantiation errors when needed. So, at least for
> the immediate purpose of completing library(error), and hoping the
> "inconsistency" does not creep up again later at some point, I'd just
> say OK, let it be.
>
> At this point, I'll just come up with a revised proposal that takes into
> account all the feedback so far... (some of it is in a private
> conversation I had with Jan, but it only adds about aliases: I'll
> include those in the revised proposal). Please bear with me...
>
> Julio
>
> --
> You received this message because you are subscribed to the Google
> Groups "SWI-Prolog" group.
> To unsubscribe from this group and stop receiving emails from it, send
> an email to swi-prolog+...@googlegroups.com
> <mailto:swi-prolog+...@googlegroups.com>.

Jan Burse

unread,
Sep 22, 2016, 4:36:17 AM9/22/16
to SWI-Prolog
Hi,

Turbo Prolog had a type system, now Visual Prolog, still has.
https://en.wikipedia.org/wiki/Visual_Prolog

The best thing about Prolog is in my option, that it doesn't have
untagged unions. You cannot fool around with memory layout.

So if you do a union:

     nat = n
           | s(nat)

Its automatically tagged by n/0 and s/1. Markus Triska has observed
that nevertheless users sometimes use data structures that are not
fully tagged. Such as:

       tree = node(tree, tree)
               | integer

So tree leaves in the above are just integers, no functor around.
But from WAM implementation we know that there are anyway
two levels of tagging.

The first tag is the basic type, i.e. callable, integer, float or variable.
And for callables the second is the functor. But Markus Triska is
right, declarative programming ith the first level tag is a little complicated.

Bye

Jan Burse

unread,
Sep 22, 2016, 4:44:31 AM9/22/16
to SWI-Prolog
Further examples of Prolog systems if some type system are
Mercury and Ciao I guess. In Ciao they have an assertion language, right?

Possibly Mercury is maybe now defunct (? not sure ?), one of the main
developers is now working on a new language called Plasma.

In Plasma I guess some ideas from Haskell are replicated, for example
through monads one can also type Program behaviour.

For example we could have transaction monads and everything that is
done with transaction monads can then be commit or rolled back (just a picture).

And the type system assures what code can be mixed and what not.
If I remember well mercury already pioneered this by distinguishing
pure and impure predicates etc..

Program behaviour types cannot be assured by a must/2 predicate,
or can they? At least I don't see how at the moment.

Jan Burse

unread,
Sep 22, 2016, 4:48:44 AM9/22/16
to SWI-Prolog
Further non-Prolog languages that include Program behaviour types
is Scala I guess. At least in the older versions of Scala I guess one
could express such things via the Unit type.

But Scala is pretty dead now, right?

I dunno. The most pratical approach to model Program behaviour types
seems to me still OOP. To some extend you can at least define base
classes of participants in certain collarboration patterns, which is already
pretty good! Not extremly safe, but it expresses something!

So Logtalk could offer a lot!

Jan Burse

unread,
Sep 22, 2016, 5:19:10 AM9/22/16
to SWI-Prolog

Paul Bone - Plasma Programming Language

https://www.youtube.com/watch?v=sIVzfYelaS4

(There are also some attempts to automatically parallelize
code, althought didn't watch the full video yet, cant say
anyting about it)

Martin

unread,
Sep 22, 2016, 10:52:16 AM9/22/16
to swi-p...@googlegroups.com
I wouldn't call Scala dead - I've found a small blog post about the
topic [1] which argues via OpenHub's monthly contributions and the
number of job offers. In the logic community, I know of Isabelle's Scala
Code generation, the Leon project which verifies a subset of Scala[2],
the Leo III higher-order prover[3] and the GAPT framework for proof
theory [4] but I'm pretty sure I've missed something important. Still, I
would not agree with the claim in Denis' blog that Scala isn't a niche
language anymore. Rust might also go into a direction you imagine, by
the way.

cheers, Martin


[1] http://appliedscala.com/blog/2016/scala-popularity/
[2] http://lara.epfl.ch/w/leon
[3] http://page.mi.fu-berlin.de/lex/leo3/
[4] https://logic.at/gapt/
> <https://en.wikipedia.org/wiki/Visual_Prolog>
>
> --
> You received this message because you are subscribed to the Google
> Groups "SWI-Prolog" group.
> To unsubscribe from this group and stop receiving emails from it, send
> an email to swi-prolog+...@googlegroups.com
> <mailto:swi-prolog+...@googlegroups.com>.

Jan Burse

unread,
Sep 22, 2016, 1:23:25 PM9/22/16
to SWI-Prolog
Even DOS is dead (and PowerShell), long live bash:
http://www.howtogeek.com/249966/how-to-install-and-use-the-linux-bash-shell-on-windows-10/

Maybe there is a scheme behind it:
1) Phase 1 Explosion of Diversity
2) Phase 2 Survival of a Few, because its simpler and cheaper

Bye

Jan Burse

unread,
Sep 22, 2016, 1:26:31 PM9/22/16
to SWI-Prolog
Some driving force to adopt bash could be the cloud...

Diversity is good if you have Niches. If the
Niches break away, diversity can go away.

Jan Burse

unread,
Sep 22, 2016, 1:44:20 PM9/22/16
to SWI-Prolog
Sorry for hitchhiking this thread, which should be about types....

Last rant, the Go Programming Language looks also fishy to me:
https://www.oreilly.com/learning/run-strikingly-fast-parallel-file-searches-in-go-with-sync-errgroup

Some embarassingly parallel stuff should be also embarassingly simple
to code. Looks rather complecated to me what Go is doing here.

Maybe its easier in Plasma. Or even easier in Prolog?!

Julio Di Egidio

unread,
Sep 26, 2016, 8:56:45 AM9/26/16
to SWI-Prolog
On Thursday, September 22, 2016 at 9:43:54 AM UTC+2, Jan Wielemaker wrote:

Personally I think the whole domain/type argument is rather
artificial.

Eventually, I agree, but also because I was wrong: between/2 does not give
domain errors, at the moment only cyclic/0 and acyclic/0 do, and that is the
only thing I'd fix, that is, I'd make these two also throw type errors: then,
IMO, it'd be all clean and clear!  --  Can we do it?

I'd also propose that for now we only focus on adding missing type definitions
in library(error) with the only and specific goal of *completing coverage of the
argument types that appear in built-in predicates* (with few exceptions maybe,
e.g. I'd like an interval numeric type).  --  I'll list these in a separate post.

As for a more proper type system, which would include meta-types, a fully
formalised definition syntax, as well as directives and aliases, I'd propose
this be left as a candidate for a next iteration.  For one thing, I'd still build
this on top of library(error), not in place of it.  And, for another thing, there
are packs already that implement type systems (and I am writing one myself),
and it might be worth using these as experiments to pick from/reason with,
at least to narrow down the discussion a little bit.

Julio

Jan Wielemaker

unread,
Sep 26, 2016, 9:30:59 AM9/26/16
to Julio Di Egidio, SWI-Prolog
On 09/26/2016 02:56 PM, Julio Di Egidio wrote:
> On Thursday, September 22, 2016 at 9:43:54 AM UTC+2, Jan Wielemaker
> wrote:
>
>> Personally I think the whole domain/type argument is rather
>> artificial.
>
> Eventually, I agree, but also because I was wrong: between/2 does not
> give domain errors, at the moment only cyclic/0 and acyclic/0 do, and
> that is the only thing I'd fix, that is, I'd make these two also
> throw type errors: then, IMO, it'd be all clean and clear! -- Can
> we do it?

Well, I consider this a bug:

6 ?- must_be(between(1, 10), 13).
ERROR: Type error: `between(1,10)' expected, found `13' (an integer)
ERROR: In:
ERROR: [10] throw(error(...,_414))

If there is a case for a domain error, this should be the one. I
wouldn't be against dropping domain_error altogether if we had to start
from scratch, but they exist in the standard.

I really have no clue whether violating (a)cyclic constraints is a type
or a domain error ... Maybe someone has a well motivated argument ...

> I'd also propose that for now we only focus on adding missing type
> definitions in library(error) with the only and specific goal of
> *completing coverage of the argument types that appear in built-in
> predicates* (with few exceptions maybe, e.g. I'd like an interval
> numeric type). -- I'll list these in a separate post.

Agree.

> As for a more proper type system, which would include meta-types, a
> fully formalised definition syntax, as well as directives and
> aliases, I'd propose this be left as a candidate for a next
> iteration. For one thing, I'd still build this on top of
> library(error), not in place of it. And, for another thing, there
> are packs already that implement type systems (and I am writing one
> myself), and it might be worth using these as experiments to pick
> from/reason with, at least to narrow down the discussion a little
> bit.

Yes. Once we know the types we want to support we can restructure the
library. As long as we don't touch the interface that should be fine.

Cheers --- Jan

Julio Di Egidio

unread,
Sep 26, 2016, 12:25:47 PM9/26/16
to SWI-Prolog
On Monday, September 26, 2016 at 3:30:59 PM UTC+2, Jan Wielemaker wrote:
On 09/26/2016 02:56 PM, Julio Di Egidio wrote:
> On Thursday, September 22, 2016 at 9:43:54 AM UTC+2, Jan Wielemaker
> wrote:
>
>> Personally I think the whole domain/type argument is rather
>> artificial.
>
> Eventually, I agree, but also because I was wrong: between/2 does not
> give domain errors, at the moment only cyclic/0 and acyclic/0 do, and
> that is the only thing I'd fix, that is, I'd make these two also
> throw type errors: then, IMO, it'd be all clean and clear!  --  Can
> we do it?

Well, I consider this a bug:

6 ?- must_be(between(1, 10), 13).
ERROR: Type error: `between(1,10)' expected, found `13' (an integer)
ERROR: In:
ERROR: [10] throw(error(...,_414))

If there is a case for a domain error, this should be the one. I
wouldn't be against dropping domain_error altogether if we had to start
from scratch, but they exist in the standard.

I really have no clue whether violating (a)cyclic constraints is a type
or a domain error ... Maybe someone has a well motivated argument ...

Yet, as a legitimate use case for the contrary, consider defining a decimal digit.
The line is just not clear cut, not even in the ISO standard if I recall correctly.

Additionally, just having domain errors for some of the pre-defined
types, with not even an extensibility mechanism for it (adding to has_type/2
just cannot do it), is simply inconsistent...

So, indeed, I am proposing that we drop the idea of checking domains and
throwing domain errors from must_be/2 completely.

We can then implement domain checking and errors *on top* of that: after all,

  1) even logically, a domain check follows the type check;

  2) OTOH, if we allow for domains, why not other constraints and corresponding
    ISO errors?

Along that line, consider what an extended system might look like:

I) has_type/2 as the extensibility hook remains at it is;

II) must_be/2 must throw type_error errors only;

III) domain checking and errors are implemented "aside", as (for example):

  must_be_dom(Type, GDom, Term)

where, after checking Type and throwing type_error if that fails, invokes
call(GDom, Term) and throws domain_error if that fails;

IV) maybe even other kinds of ISO as well as custom errors should be handled, via something like:

  must_be_err(Err, GTest, Term)

that invokes call(GTest, Term) and throws Err if that fails;

Then coverage is complete as far as argument checking and throwing
ISO conformant errors goes.

V) finally, signatures should be extended as well, to allow for those constraints
to be expressed, hence few special types would be needed, e.g.:

  dom(Type, GDom) % argument of type Type with a domain constraint;
  err(Err, GTest) % argument with a custom constraint;

Now, that is just a quick idea, to show the kind of consequences that I find along that
path, but the main point I am trying to forward is that domains come after (error) types,
logically as well as in terms of code design.  So, I am not really advocating against
handling domains in library(error), but I'd insist for a self-consistent (error) type system
beneath: which, as said, can be achieved by simply fixing the cyclic/acyclic types.

Julio

Julio Di Egidio

unread,
Sep 27, 2016, 12:33:04 AM9/27/16
to swi-p...@googlegroups.com
On Monday, September 26, 2016 at 3:30:59 PM UTC+2, Jan Wielemaker wrote:
On 09/26/2016 02:56 PM, Julio Di Egidio wrote: 
<snip> 
> I'd also propose that for now we only focus on adding missing type
> definitions in library(error) with the only and specific goal of
> *completing coverage of the argument types that appear in built-in
> predicates* (with few exceptions maybe, e.g. I'd like an interval
> numeric type).  --  I'll list these in a separate post.

Agree.

OK, to reiterate, this is for a first iteration, that is:
only adding missing type definitions in library(error) with the specific

goal of *completing coverage of the argument types that appear in built-in
predicates* (with few exceptions maybe).

A couple of comments:

- I have left a not/1: I'd think this is needed, e.g. to define a
varnonatt/0 or a partial/0 (and I mean these as use cases, i.e. whether
they do or do not end up in library(error)).

- I have also left a bunch of aliases: this would warrant a discussion in
itself, some of these are not even aliases proper, rather they are
derived types (specialisations), then I have come to the conclusion that
aliases proper make no sense in library(error), instead I find useful
having the category in the meta-data (still not implemented in
library(error), only documented).

The following markers are used:
* marks new types
* ### marks new types to review in particular

Base types:
---
| any          | Any term (always true)       | {[]>>true}            |
| none         | No term (always fail)        | {[]>>fail}            | * ###
| var          | Variable (may be attributed) | {var}                 |
| nonvar       | Not a variable               | {nonvar}              |
| ground       | Ground                       | {ground}              |
| atom         | Atom                         | {atom}                |
| atomic       | Atomic                       | {atomic}              |
| compound     | Compound                     | {compound}            |
| callable     | Callable                     | {callable}            |
| cyclic       | Cyclic                       | {cyclic_term}         |
| acyclic      | Acyclic                      | {acyclic_term}        |
| partial      | Partial callable             | callable, not(ground) | * ###
| not(T)       | Not has type T               | {\+ has_type(T)}      | * ###
| var(T)       | Variable or has type T       | var; T                | * ###

System types:
---
| blob      | Blob                      | {[]>>blob(Term, _)}    | * ###
| blob(BT)  | Blob of "type" BT         | {[BT]>>blob(Term, BT)} | * ###
| attvar    | Attributed variable       | {attvar}               | *
| varnonatt | Variable not attributed   | var, not(attvar)       | * ###
| string    | String                    | {string}               |
| dict      | Dictionary                | {is_dict}              |
| engine    | Engine handle             | {is_engine}            | *
| thread    | Thread handle             | {is_thread}            | *
| stream    | Stream handle             | {is_stream}            |
| encoding  | A supported encodings (*) | {current_encoding}     |

(*) Currently supported encodings are ...

Common types:
---
| mod(T)       | Optionally module-qualified | s(atom:T); T                      | * ###
| predind      | Predicate indicator         | s(atom/nonneg); s(atom//nonneg)   | *
| boolean      | One of true, false          | oneof([true, false])              | *
| boolish      | One of true, false, yes, no | oneof([true, false, yes, no])     | * ###
| order        | One of , <, >               | oneof([, <, >])                   | *
| error        | Formal error                | s(error(callable, any))           | *
| fname        | File name                   | text                              | *
| fpipe        | File pipe(Cmd)              | s(pipe(atom; string))             | *
| fspec        | File name or pipe(Cmd)      | fname; fpipe                      | * ###
| pair         | Pair                        | pair(any, any)                    | *
| pair(TK, TV) | Pair of type TK, TV         | s(TK-TV)                          | *
| oneof(L)     | Ground element of list L    | ground, {[L]>>memberchk(Term, L)} |

Text types:
---
| char      | 1-character atom       | atom, {[]>>atom_length(Term, 1)} | *

| chars     | List of char           | list(char)                       |
| code      | Unicode character code | int(1, 0x10ffff)                 | *

| codes     | List of code           | list(code)                       |
| text      | Text                   | atom; string; chars; codes       |
| formatted | Text or format-args.   | s(text-list); text               | *

List types:
---
| list         | List                      | {is_list}              |
| open_list    | Open (aka partial) list   | {is_open_list}         | * ###
| diff_list    | Difference list           | {is_diff_list}         | * ###
| list(T)      | List of type T            | {is_list_type(T)}      |
| open_list(T) | Open list of type T       | {is_open_list_type(T)} | * ###
| diff_list(T) | Difference list of type T | {is_diff_list_type(T)} | * ###

Numeric types:
---
| num                   | Number                         | {number}                             | * ###
| int                   | Integer                        | {integer}                            | * ###
| float                 | Float                          | {float}                              |
| ratio                 | Rational                       | {rational}                           | * ###
| ivl_btype             | Interval bound "type"          | oneof([closed, open, c, o])          | * ###
| ivl_bound(NT)         | Interval bound of type NT      | oneof([inf, -inf, +inf]); NT         | * ###
| ivl_gt(NT, L, LT)     | Number of type NT in ?L..+inf] | (*1)                                 | * ###
| ivl_lt(NT, H, HT)     | Number of type NT in [-inf..H? | (*2)                                 | * ###
| ivl(NT, L, H, LT, HT) | Number of type NT in ?L..H?    | ivl_gt(NT, L, LT), ivl_lt(NT, H, HT) | * ###
| between(NT, L, H)     | Number of type NT in [L; H]    | ivl(NT, L, H, c, c)                  | * ###
| between(L, H)         | Number in [L; H]               | (*3)                                 | * ###
| arith(NT, V)          | Evaluated is V of type NT (*)  | (*4)                                 | * ###
| arith(NT)             | Evaluated has type NT (*)      | arith(NT, _)                         | * ###

(*) Evaluates a copy of Term with is/2.  Unifies the result with V in arith/2.

(*1) ivl_gt(NT, L, LT) --->
    NT, {[L, LT]>>
    ((  memberchk(LT, [closed, c])              % Term in [L..+inf]
    ->  (   memberchk(L, [-inf])                % if Term in [-inf..+inf]
        ->  true                                % -> true
        ;   memberchk(L, [inf, +inf])           % else if Term in [+inf..+inf]
        ->  memberchk(Term, [inf, +inf])        % -> Term == inf (or +inf)
        ;   Term >= L                           % else Term >= L
        )
    ;   memberchk(LT, [open, o])                % Term in (L..+inf]
    ->  (   memberchk(L, [-inf])                % if Term in (-inf..+inf]
        ->  \+ memberchk(Term, [-inf])          % -> Term =\= -inf
        ;   \+ memberchk(L, [inf, +inf])        % else if Term in (L..+inf]
        ->  (   memberchk(Term, [inf, +inf])    % -> if Term == inf (or +inf)
            ->  true                            %    -> true
            ;   Term > L                        %    else Term > L
            )
        )
    ))}

(*2) ivl_lt(NT, H, HT) --->
    ... symmetric to (*1) ...

(*3) between(L, H) --->
    {[L, H]>>
    ((  has_type(int, L),
        has_type(int, H)
    ))} -> between(int, L, H); between(num, L, H)

(*4) arith(NT, V) --->
    {[NT, V]>>
    ((  catch(V is Term, _, fail),
        has_type(NT, V)
    ))}

Type aliases:
---
| module(T)                 | Optionally module-qualified | mod(T)            | * ###
| modcall                   | Opt. mod-qualif. callable   | mod(callable)     | * ###
| predicate_indicator       | Predicate indicator         | predind           | * ###
| structure                 | Structure (aka callable)    | callable          | * ###
| formal_error              | Formal error                | error             | * ###
| list_or_partial_list      | List or open list           | list; open_list   | * ###
| number                    | Number                      | num               | * ###
| integer                   | Integer                     | int               | * ###
| rational                  | Rational                    | ratio             | * ###
| positive_integer          | Positive integer            | posint            | * ###
| negative_integer          | Negative integer            | negint            | * ###
| nonneg                    | Non-negative integer        | ivl_gt(int, 0, c) | * ###
| nonpos                    | Non-positive integer        | ivl_lt(int, 0, c) | * ###
| posint                    | Positive integer            | ivl_gt(int, 0, o) | * ###
| negint                    | Negative integer            | ivl_lt(int, 0, o) | * ###

Please review.

Thank you,

Julio

Julio Di Egidio

unread,
Sep 28, 2016, 9:30:47 AM9/28/16
to SWI-Prolog
So, after spending again weeks trying to fix something that is inconsistent and incomplete, not
to mention how basic at least for real production, and trying to do it so that also backward and
forward compatibility and extensibility are preserved while coping with the mistakes made in the
past, and sensibly so, and diplomatically so, etc. etc. etc., and make everybody happy and what not,
we are still just stuck at square one and I am told that we are waiting for reasoned arguments....

Fuck it, I am done with this bullshit and bullshitters once and for all.

Julio

P.S.  I have already had to endure personal libel in this forum: if the reply to the above message
is just some more of that, this time I'll report whomever it is to the authorities.
Reply all
Reply to author
Forward
0 new messages