notmuch-0.3.1.1: Haskell binding to Notmuch, the mail indexer
Safe HaskellSafe-Inferred
LanguageHaskell2010

Notmuch

Description

High-level interface to the notmuch mail indexer.

Example program to add/remove a tag on all messages matching a query:

main :: IO ()
main = getArgs >>= \args -> case args of
  [path, expr, '+':tag] -> go path expr tag messageAddTag
  [path, expr, '-':tag] -> go path expr tag messageRemoveTag
  _ -> die "usage: hs-notmuch-tag-set DB-DIR SEARCH-TERM +TAG|-TAG"
  where
    go path expr tag f =
      runExceptT (do
        db <- databaseOpen path
        query db (Bare expr) >>= messages >>= traverse_ (f (fromString tag))
      ) >>= either (die . (show :: Status -> String)) pure

File descriptor exhaustion

Some Message operations cause the message file to be opened (and remain open until the object gets garbage collected):

  • messageHeader will open the file to read the headers, except for the From, Subject and Message-Id headers which are indexed.

If the RTS is using a multi-generation collector (the default), and if you are working with lots of messages, you may hit max open files limits. The best way to avoid this is to avoid the scenarios outlined above. Alternative approaches that could help include:

  • Use a single-generation collector (build with -rtsopts and run with +RTS -G1). This incurs the cost of scanning the entire heap on every GC run.
  • In an interactive program, build with -threaded to enable parallel GC. By default, major GC will be triggered when the program is idle for a certain time.
  • Manually execute performMajorGC at relevant times to ensure that older generations get cleaned up.
Synopsis

Opening a database

databaseOpen :: (Mode a, AsNotmuchError e, MonadError e m, MonadIO m) => FilePath -> m (Database a) Source #

Open a database. The database will be closed and associated resources freed upon garbage collection.

The mode is determined by usage. Because read-only functions also work on read-write databases, databaseOpenReadOnly is also provided for convenience.

databaseOpenReadOnly :: (AsNotmuchError e, MonadError e m, MonadIO m) => FilePath -> m (Database RO) Source #

Convenience function for opening a database read-only

databasePath :: Database a -> FilePath Source #

Get the path of the database

databaseVersion :: MonadIO m => Database a -> m Int Source #

Database format version of the given database.

data Database (a :: DatabaseMode) Source #

A database handle. The database will be closed and freed when it is garbage collected.

Use query to perform a search or findMessage to search for a particular message.

The Database type carries a phantom for the database mode, which is propgated to derived Query, Thread and Message objects. This is used to prevent write operations being performed against a read-only database.

Instances

Instances details
HasTags (Database a) Source #

Get all tags used in the database

Instance details

Defined in Notmuch

Methods

tags :: MonadIO m => Database a -> m [Tag] Source #

Database modes

class Mode a Source #

This is an internal class whose instances are the promoted DatabaseMode constructors.

Minimal complete definition

getMode, upgrade

Instances

Instances details
Mode 'DatabaseModeReadOnly Source # 
Instance details

Defined in Notmuch.Binding

Mode 'DatabaseModeReadWrite Source # 
Instance details

Defined in Notmuch.Binding

type RO = 'DatabaseModeReadOnly Source #

Convenience synonym for the promoted DatabaseModeReadOnly constructor.

type RW = 'DatabaseModeReadWrite Source #

Convenience synonym for the promoted DatabaseModeReadWrite constructor.

Querying the database

data Query (a :: DatabaseMode) Source #

Query object. Cleaned up when garbage collected.

Use messages or threads to get the results.

The Query type carries a phantom for the database mode, so that write operations on messages derived from it are restricted to read/write database sessions.

Instances

Instances details
HasMessages Query Source #

Retrieve all messages matching a Query

Instance details

Defined in Notmuch

Methods

messages :: forall e m (mode :: DatabaseMode). (AsNotmuchError e, MonadError e m, MonadIO m) => Query mode -> m [Message 0 mode] Source #

HasThreads Query Source #

Retrieve the threads matching a Query

Instance details

Defined in Notmuch

Methods

threads :: forall e m (mode :: DatabaseMode). (AsNotmuchError e, MonadError e m, MonadIO m) => Query mode -> m [Thread mode] Source #

query :: MonadIO m => Database a -> SearchTerm -> m (Query a) Source #

Query the database. To retrieve results from a Query, use threads or messages.

queryCountMessages :: (AsNotmuchError e, MonadError e m, MonadIO m) => Query a -> m Int Source #

Count the number of messages matching a query.

Complexity: same as the underlying Xapian search…

queryCountThreads :: (AsNotmuchError e, MonadError e m, MonadIO m) => Query a -> m Int Source #

Count the number of threads matching a query.

Θ(n) in the number of messages!

Search expressions

data SearchTerm Source #

Search expression. Use Bare if you want to use a query string as-is (see also notmuch-search-terms(7)).

Use show to stringify a SearchTerm.

Constructors

FreeForm String 
From String 
To String 
Subject String 
Attachment String 
Tag Tag 
Id MessageId 
Thread ThreadId 
Folder String 
Path String 
Date String String 
Asterisk 
And SearchTerm SearchTerm 
Or SearchTerm SearchTerm 
Xor SearchTerm SearchTerm 
Not SearchTerm 
Bare String 

Instances

Instances details
Generic SearchTerm Source # 
Instance details

Defined in Notmuch.Search

Associated Types

type Rep SearchTerm :: Type -> Type

Methods

from :: SearchTerm -> Rep SearchTerm x

to :: Rep SearchTerm x -> SearchTerm

Show SearchTerm Source #

Stringify a query expression.

Instance details

Defined in Notmuch.Search

Methods

showsPrec :: Int -> SearchTerm -> ShowS

show :: SearchTerm -> String

showList :: [SearchTerm] -> ShowS

NFData SearchTerm Source # 
Instance details

Defined in Notmuch.Search

Methods

rnf :: SearchTerm -> ()

type Rep SearchTerm Source # 
Instance details

Defined in Notmuch.Search

type Rep SearchTerm = D1 ('MetaData "SearchTerm" "Notmuch.Search" "notmuch-0.3.1.1-inplace" 'False) ((((C1 ('MetaCons "FreeForm" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "From" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: (C1 ('MetaCons "To" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "Subject" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))) :+: ((C1 ('MetaCons "Attachment" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "Tag" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Tag))) :+: (C1 ('MetaCons "Id" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MessageId)) :+: C1 ('MetaCons "Thread" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ThreadId))))) :+: (((C1 ('MetaCons "Folder" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "Path" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: (C1 ('MetaCons "Date" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "Asterisk" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "And" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SearchTerm) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SearchTerm)) :+: C1 ('MetaCons "Or" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SearchTerm) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SearchTerm))) :+: (C1 ('MetaCons "Xor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SearchTerm) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SearchTerm)) :+: (C1 ('MetaCons "Not" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SearchTerm)) :+: C1 ('MetaCons "Bare" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))))))

Working with threads

class HasThread a where Source #

Objects with an associated ThreadId

Methods

threadId :: MonadIO m => a -> m ThreadId Source #

Instances

Instances details
HasThread (Thread a) Source #

Get the ThreadId of a SearchTerm

Instance details

Defined in Notmuch

Methods

threadId :: MonadIO m => Thread a -> m ThreadId Source #

HasThread (Message n a) Source #

Get the ThreadId of a Message

Instance details

Defined in Notmuch

Methods

threadId :: MonadIO m => Message n a -> m ThreadId Source #

data Thread (a :: DatabaseMode) Source #

Thread object. Cleaned up when garbage collected.

Use messages to get the messages of a thread.

The Thread type carries a phantom for the database mode, so that write operations on messages derived from it are restricted to read/write database sessions.

Instances

Instances details
HasMessages Thread Source #

Retrieve the messages in a SearchTerm

Instance details

Defined in Notmuch

Methods

messages :: forall e m (mode :: DatabaseMode). (AsNotmuchError e, MonadError e m, MonadIO m) => Thread mode -> m [Message 0 mode] Source #

HasTags (Thread a) Source #

Get all tags used in a thread

Instance details

Defined in Notmuch

Methods

tags :: MonadIO m => Thread a -> m [Tag] Source #

HasThread (Thread a) Source #

Get the ThreadId of a SearchTerm

Instance details

Defined in Notmuch

Methods

threadId :: MonadIO m => Thread a -> m ThreadId Source #

threadToplevelMessages :: (AsNotmuchError e, MonadError e m, MonadIO m) => Thread a -> m [Message 0 a] Source #

Returns only messages in a thread which are not replies to other messages in the thread.

threadNewestDate :: MonadIO m => Thread a -> m UTCTime Source #

O(1) Date of the newest message in a SearchTerm.

threadSubject :: MonadIO m => Thread a -> m ByteString Source #

Returns the subject of the first message in the query results that belongs to this thread.

threadAuthors :: MonadIO m => Thread a -> m ThreadAuthors Source #

Return authors of a thread. These are split into:

threadTotalMessages :: MonadIO m => Thread a -> m Int Source #

O(1) count of messages in the thread.

Thread ID

type ThreadId = ByteString Source #

Thread identifier generated and used by libnotmuch.

class HasThreads a where Source #

Objects with associated threads

Methods

threads :: (AsNotmuchError e, MonadError e m, MonadIO m) => a mode -> m [Thread mode] Source #

Instances

Instances details
HasThreads Query Source #

Retrieve the threads matching a Query

Instance details

Defined in Notmuch

Methods

threads :: forall e m (mode :: DatabaseMode). (AsNotmuchError e, MonadError e m, MonadIO m) => Query mode -> m [Thread mode] Source #

Thread authors

data ThreadAuthors Source #

Authors belonging to messages in a query result of a thread ordered by date.

Instances

Instances details
Generic ThreadAuthors Source # 
Instance details

Defined in Notmuch

Associated Types

type Rep ThreadAuthors :: Type -> Type

Show ThreadAuthors Source # 
Instance details

Defined in Notmuch

Methods

showsPrec :: Int -> ThreadAuthors -> ShowS

show :: ThreadAuthors -> String

showList :: [ThreadAuthors] -> ShowS

NFData ThreadAuthors Source # 
Instance details

Defined in Notmuch

Methods

rnf :: ThreadAuthors -> ()

type Rep ThreadAuthors Source # 
Instance details

Defined in Notmuch

type Rep ThreadAuthors = D1 ('MetaData "ThreadAuthors" "Notmuch" "notmuch-0.3.1.1-inplace" 'False) (C1 ('MetaCons "ThreadAuthors" 'PrefixI 'True) (S1 ('MetaSel ('Just "_matchedAuthors") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Author]) :*: S1 ('MetaSel ('Just "_unmatchedAuthors") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Author])))

type Author = Text Source #

Author of a message.

matchedAuthors :: Lens' ThreadAuthors [Author] Source #

Lens to matched authors. See also threadAuthors.

unmatchedAuthors :: Lens' ThreadAuthors [Author] Source #

Lens to unmatched authors. See also threadAuthors.

Working with messages

findMessage :: (AsNotmuchError e, MonadError e m, MonadIO m) => Database a -> MessageId -> m (Maybe (Message 0 a)) Source #

Look for a particular message in the database.

class HasMessages a where Source #

Objects with associated messages.

Methods

messages :: (AsNotmuchError e, MonadError e m, MonadIO m) => a mode -> m [Message 0 mode] Source #

Instances

Instances details
HasMessages Query Source #

Retrieve all messages matching a Query

Instance details

Defined in Notmuch

Methods

messages :: forall e m (mode :: DatabaseMode). (AsNotmuchError e, MonadError e m, MonadIO m) => Query mode -> m [Message 0 mode] Source #

HasMessages Thread Source #

Retrieve the messages in a SearchTerm

Instance details

Defined in Notmuch

Methods

messages :: forall e m (mode :: DatabaseMode). (AsNotmuchError e, MonadError e m, MonadIO m) => Thread mode -> m [Message 0 mode] Source #

HasMessages (Message n) Source #

Retrieve the replies to a Message

Instance details

Defined in Notmuch

Methods

messages :: forall e m (mode :: DatabaseMode). (AsNotmuchError e, MonadError e m, MonadIO m) => Message n mode -> m [Message 0 mode] Source #

data Message (n :: Nat) (a :: DatabaseMode) Source #

Message object. Cleaned up when garbage collected.

The Message type carries a phantom for the database mode, so that write operations are restricted to read/write database sessions.

There is also a phantom type parameter for the degree of frozenness of the message. Tag operations on a frozen message are atomic, only becoming visible to other threads/processes after the thaw. The freeze/thaw behaviour is available via withFrozenMessage.

Instances

Instances details
HasMessages (Message n) Source #

Retrieve the replies to a Message

Instance details

Defined in Notmuch

Methods

messages :: forall e m (mode :: DatabaseMode). (AsNotmuchError e, MonadError e m, MonadIO m) => Message n mode -> m [Message 0 mode] Source #

HasTags (Message n a) Source #

Get the tags of a single message

Instance details

Defined in Notmuch

Methods

tags :: MonadIO m => Message n a -> m [Tag] Source #

HasThread (Message n a) Source #

Get the ThreadId of a Message

Instance details

Defined in Notmuch

Methods

threadId :: MonadIO m => Message n a -> m ThreadId Source #

Headers

type MessageId = ByteString Source #

Message-Id header value.

messageId :: MonadIO m => Message n a -> m MessageId Source #

Get the message ID.

messageDate :: MonadIO m => Message n a -> m UTCTime Source #

Get the date the message was sent.

messageHeader :: MonadIO m => ByteString -> Message n a -> m (Maybe ByteString) Source #

Get the named header as a UTF-8 encoded string. Empty string if header is missing or Nothing on error.

May open a file descriptor that will not be closed until the message gets garbage collected.

Tags

messageSetTags :: (MonadIO m, Foldable t) => t Tag -> Message 0 RW -> m () Source #

Set tags for the message. Atomic.

messageAddTag :: MonadIO m => Tag -> Message n RW -> m () Source #

Add the tag to a message. If adding/removing multiple tags, use messageSetTags to set the whole tag list atomically, or use withFrozenMessage to avoid inconsistent states when adding/removing tags.

messageRemoveTag :: MonadIO m => Tag -> Message n RW -> m () Source #

Remove the tag from a message. If adding/removing multiple tags, use messageSetTags to set the whole tag list atomically, or use withFrozenMessage to avoid inconsistent states when adding/removing tags.

withFrozenMessage :: (forall n. Message n RW -> IO a) -> Message 0 RW -> IO a Source #

Freeze the message, run the given computation and return the result. The message is always thawed at the end.

Have to start with Message 0 RW due to GHC type system limitation (type-level Nat is not inductive).

Files

messageFilename :: MonadIO m => Message n a -> m FilePath Source #

Get the filename of the message.

indexFile :: (AsNotmuchError e, MonadError e m, MonadIO m) => Database RW -> FilePath -> m (Message 0 RW) Source #

Index a file with the default indexing options. (This binding does not yet provide a way to change the indexing options.) Returns the indexed message.

If message has same message ID as another message in the database, the new filename will be added to the message and the existing message is returned.

Possible errors include:

  • StatusPathError if file path is not absolute or is not an extension of the database path. This check is performed in this binding, not in the foreign libnotmuch code.
  • StatusFileError when file does not exist or cannot be opened
  • StatusFileNotEmail when file does not look like an email

removeFile :: (AsNotmuchError e, MonadError e m, MonadIO m) => Database RW -> FilePath -> m RemoveResult Source #

Remove a message filename. If the message has no more filenames return MessageRemoved, otherwise MessagePersists.

The underlying routine (as of notmuch v0.28) returns NOTMUCH_STATUS_SUCCESS even when the given path does not exist, is not an internet message, or is not recorded in the database. Therefore removeFile also returns MessageRemoved in this scenario. This is particularly confusing when the Message-Id of the given file is known, but the the file itself is unknown.

data RemoveResult Source #

Result of a removeFile operation.

Instances

Instances details
Show RemoveResult Source # 
Instance details

Defined in Notmuch.Binding

Methods

showsPrec :: Int -> RemoveResult -> ShowS

show :: RemoveResult -> String

showList :: [RemoveResult] -> ShowS

Eq RemoveResult Source # 
Instance details

Defined in Notmuch.Binding

Methods

(==) :: RemoveResult -> RemoveResult -> Bool

(/=) :: RemoveResult -> RemoveResult -> Bool

Tags

class HasTags a where Source #

Objects with tags

Methods

tags :: MonadIO m => a -> m [Tag] Source #

Instances

Instances details
HasTags (Database a) Source #

Get all tags used in the database

Instance details

Defined in Notmuch

Methods

tags :: MonadIO m => Database a -> m [Tag] Source #

HasTags (Thread a) Source #

Get all tags used in a thread

Instance details

Defined in Notmuch

Methods

tags :: MonadIO m => Thread a -> m [Tag] Source #

HasTags (Message n a) Source #

Get the tags of a single message

Instance details

Defined in Notmuch

Methods

tags :: MonadIO m => Message n a -> m [Tag] Source #

data Tag Source #

Message tag. Use mkTag to construct a tag. Or use -XOverloadedStrings, but beware that the IsString instance is non-total.

This data type avoid copying when passing tags to libnotmuch. But copies do occur when reading tags from a database.

A previous experiment with interning showed no benefit. Tags are typically very short so the overhead erodes any advantage.

Instances

Instances details
IsString Tag Source #

Throws exception if the tag is empty or too long.

Instance details

Defined in Notmuch.Tag

Methods

fromString :: String -> Tag

Show Tag Source # 
Instance details

Defined in Notmuch.Tag

Methods

showsPrec :: Int -> Tag -> ShowS

show :: Tag -> String

showList :: [Tag] -> ShowS

NFData Tag Source # 
Instance details

Defined in Notmuch.Tag

Methods

rnf :: Tag -> ()

Eq Tag Source # 
Instance details

Defined in Notmuch.Tag

Methods

(==) :: Tag -> Tag -> Bool

(/=) :: Tag -> Tag -> Bool

Ord Tag Source # 
Instance details

Defined in Notmuch.Tag

Methods

compare :: Tag -> Tag -> Ordering

(<) :: Tag -> Tag -> Bool

(<=) :: Tag -> Tag -> Bool

(>) :: Tag -> Tag -> Bool

(>=) :: Tag -> Tag -> Bool

max :: Tag -> Tag -> Tag

min :: Tag -> Tag -> Tag

mkTag :: ByteString -> Maybe Tag Source #

O(n) Just a tag, or Nothing if the string is too long

Use UTF-8 encoding to include non-ASCII characters in a tag.

getTag :: Tag -> ByteString Source #

O(1)

tagMaxLen :: Int Source #

The maximum tag length. Defined as NOTMUCH_TAG_MAX in notmuch.h.

Errors

class AsNotmuchError s where Source #

Classy prism for injecting a libnotmuch status code.

Instances

Instances details
AsNotmuchError Status Source # 
Instance details

Defined in Notmuch.Binding

Library information

libnotmuchVersion :: Version Source #

The version of libnotmuch that hs-notmuch was built against. (The program could be running against a different version.)