1/*   mails
    2     Author: Giménez, Christian.
    3
    4     Copyright (C) 2016 Giménez, Christian
    5
    6     This program is free software: you can redistribute it and/or modify
    7     it under the terms of the GNU General Public License as published by
    8     the Free Software Foundation, either version 3 of the License, or
    9     at your option) any later version.
   10
   11     This program is distributed in the hope that it will be useful,
   12     but WITHOUT ANY WARRANTY; without even the implied warranty of
   13     MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   14     GNU General Public License for more details.
   15
   16     You should have received a copy of the GNU General Public License
   17     along with this program.  If not, see <http://www.gnu.org/licenses/>.
   18
   19     25 nov 2016
   20*/
   21
   22
   23:- module(mails, [
   24	      search_to_substr/4, search_from_substr/4, search_unseen/3,
   25	      search_subject_substr/4, search_older_than/4
   26	  ]).

mails: Predicates for searching and reading mails

Maildir and IMF mixture for doing some easy managing on mails Maildir.

author
- Gimenez, Christian
license
- GPLv3 */
   35:- license(gplv3).   36
   37:- use_module(library(readutil)).   38
   39:- use_module(maildir).   40:- use_module(maildir/conditions).   41:- use_module(imf).
 search_to_substr(+Maildir:term, +Type:term, +Substr:codes, -LstMails:list)
True if LstMails are all the mails in the Maildir of type Type which in the "To" field has the given substring Substr.
Arguments:
Maildir- A path of the maildir (the main directory, not the cur, new, tmp, etc.).
Type- The type of maildir to search. See maildir_type/1.
Substr- The code string to search.
LstMails- A list terms. Each term is a mail path. */
   54search_to_substr(Maildir, Type, Substr, LstMails) :-
   55    search_mail(Maildir, Type, conditions:to_substr(Substr), LstMails).
 search_from_substr(+Maildir:term, +Type:term, +Substr:codes, -LstMails:list)
True if LstMails are all the mails in the Maildir of type Type which in the "To" field has the given substring Substr.
Arguments:
Maildir- A path of the maildir (the main directory, not the cur, new, tmp, etc.).
Type- The type of maildir to search. See maildir_type/1.
Substr- The code string to search.
LstMails- A list terms. Each term is a mail path. */
   67search_from_substr(Maildir, Type, Substr, LstMails) :-
   68    search_mail(Maildir, Type, conditions:from_substr(Substr), LstMails).
 search_subject_substr(+Maildir:term, +Type:term, +Substr:codes, -LstMails:list)
True if LstMails are all the mails in the Maildir of type Type which in the "Subject" field has the given substring Substr.
Arguments:
Maildir- A path of the maildir (the main directory, not the cur, new, tmp, etc.).
Type- The type of maildir to search. See maildir_type/1.
Substr- The code string to search.
LstMails- A list terms. Each term is a mail path. */
   80search_subject_substr(Maildir, Type, Substr, LstMails) :-
   81    search_mail(Maildir, Type, conditions:subject_substr(Substr), LstMails).
 search_unseen(+Maildir:term, +Type:term, -LstMails:list)
True iff LstMails is all the unseen Mails.
Arguments:
Maildir- A path of the maildir (the main directory, not the cur, new, tmp, etc.).
Type- The type of maildir to search. See maildir_type/1.
Substr- The code string to search.
LstMails- A list terms. Each term is a mail path.
See also
- is_seen/1. */
   96search_unseen(Maildir, Type, LstMails) :-
   97    search_mail(Maildir, Type, conditions:is_unseen, LstMails).
 search_older_than(+Maildir:term, +Type:term, +Date:pred, -LstMails:list)
True iff LstMails has all the mails dated before the provided Date.
Arguments:
Maildir- A path of the maildir (the main directory, not the cur, new, tmp, etc.).
Type- The type of maildir to search. See maildir_type/1.
Date- A date/9 predicate as defined in the date module.
LstMails- A list terms. Each term is a mail path.
See also
- date_time_stamp/2. */
  111search_older_than(Maildir, Type, Date, LstMails) :-
  112    search_mail(Maildir, Type, conditions:older_than(Date), LstMails)