exiftool-0.1.1.0: Haskell bindings to ExifTool
Copyright(c) Martin Hoppenheit 2021
LicenseMIT
Maintainermartin@hoppenheit.info
Safe HaskellNone
LanguageHaskell2010

ExifTool

Description

This module contains bindings to the ExifTool command-line application that enable reading, writing and deleting metadata in various file formats. Here's a short code example, the details are explained below.

{-# LANGUAGE OverloadedLists #-}
{-# LANGUAGE OverloadedStrings #-}

import Data.HashMap.Strict ((!?))
import ExifTool

example :: IO ()
example =
  withExifTool $ \et -> do
    -- Read metadata, with exact (!?) and fuzzy (~~) tag lookup.
    m <- getMeta et "a.jpg"
    print $ m !? Tag "EXIF" "ExifIFD" "DateTimeOriginal"
    print $ m ~~ Tag "EXIF" "" "XResolution"
    print $ m ~~ Tag "XMP" "" ""
    -- Write and delete metadata.
    setMeta et [(Tag "XMP" "XMP-dc" "Description", String "...")] "a.jpg"
    deleteMeta et [Tag "XMP" "XMP-dc" "Description"] "a.jpg"

Note that this module expects the exiftool binary to be in your PATH.

Synopsis

Running an ExifTool instance

Most functions in this module interact with an ExifTool instance i.e., a running ExifTool process represented by the ExifTool data type. The easiest way to obtain an instance is the withExifTool function that takes care of starting and stopping the process.

data ExifTool Source #

An ExifTool instance, initialized with startExifTool and terminated with stopExifTool.

startExifTool :: IO ExifTool Source #

Start an ExifTool instance. Use stopExifTool when done, or withExifTool to combine both steps.

stopExifTool :: ExifTool -> IO () Source #

Stop a running ExifTool instance.

withExifTool :: (ExifTool -> IO a) -> IO a Source #

Start an ExifTool instance, do something with it, then stop it.

Reading and writing metadata

The ExifTool instance can then be used to read, write or delete metadata in a file with the respective functions. These come in two variants, one that throws runtime errors when the ExifTool process returns error messages and one that instead produces Either values. Choose those that best fit your use case.

getMeta Source #

Arguments

:: ExifTool

ExifTool instance

-> Text

file name

-> IO Metadata

tag/value Map

Read all metadata from a file, with ExifTool errors leading to runtime errors. (Use getMetaEither instead if you would rather intercept them.)

setMeta Source #

Arguments

:: ExifTool

ExifTool instance

-> Metadata

tag/value Map

-> Text

file name

-> IO () 

Write metadata to a file, with ExifTool errors leading to runtime errors. (Use setMetaEither instead if you would rather intercept them.) The file is modified in place. Make sure you have the necessary backups!

deleteMeta Source #

Arguments

:: ExifTool

ExifTool instance

-> [Tag]

tags to be deleted

-> Text

file name

-> IO () 

Delete metadata from a file, with ExifTool errors leading to runtime errors. (Use deleteMetaEither instead if you would rather intercept them.) The file is modified in place. Make sure you have the necessary backups!

getMetaEither Source #

Arguments

:: ExifTool

ExifTool instance

-> Text

file name

-> IO (Either Text Metadata)

tag/value Map

Read all metadata from a file, with ExifTool errors returned as Left values.

setMetaEither Source #

Arguments

:: ExifTool

ExifTool instance

-> Metadata

tag/value Map

-> Text

file name

-> IO (Either Text ()) 

Write metadata to a file, with ExifTool errors returned as Left values. The file is modified in place. Make sure you have the necessary backups!

deleteMetaEither Source #

Arguments

:: ExifTool

ExifTool instance

-> [Tag]

tags to be deleted

-> Text

file name

-> IO (Either Text ()) 

Delete metadata from a file, with ExifTool errors returned as Left values. The file is modified in place. Make sure you have the necessary backups!

Data types and utility functions

Metadata is represented by a HashMap of Tag/Value pairs (with alias Metadata), so it is advisable to import some functions like lookup or !? from the Data.HashMap.Strict module. The ExifTool module defines additional utility functions that make working with Metadata easier.

type Metadata = HashMap Tag Value Source #

A set of ExifTool tag/value pairs.

data Tag Source #

An ExifTool tag name, consisting of three components:

  1. The family 0 tag group (information type) e.g., EXIF or XMP.
  2. The family 1 tag group (specific location) e.g., IFD0 or XMP-dc.
  3. The actual tag name e.g., XResolution or Description.

Example: Tag "EXIF" "IFD0" "XResolution" corresponds to the ExifTool tag name EXIF:IFD0:XResolution.

During development, there are several ways to find the exact name of a tag:

Constructors

Tag 

Fields

Instances

Instances details
Eq Tag Source # 
Instance details

Defined in ExifTool

Methods

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

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

Show Tag Source # 
Instance details

Defined in ExifTool

Methods

showsPrec :: Int -> Tag -> ShowS #

show :: Tag -> String #

showList :: [Tag] -> ShowS #

Generic Tag Source # 
Instance details

Defined in ExifTool

Associated Types

type Rep Tag :: Type -> Type #

Methods

from :: Tag -> Rep Tag x #

to :: Rep Tag x -> Tag #

Hashable Tag Source # 
Instance details

Defined in ExifTool

Methods

hashWithSalt :: Int -> Tag -> Int #

hash :: Tag -> Int #

ToJSON Tag Source # 
Instance details

Defined in ExifTool

ToJSONKey Tag Source # 
Instance details

Defined in ExifTool

FromJSON Tag Source # 
Instance details

Defined in ExifTool

FromJSONKey Tag Source # 
Instance details

Defined in ExifTool

type Rep Tag Source # 
Instance details

Defined in ExifTool

type Rep Tag = D1 ('MetaData "Tag" "ExifTool" "exiftool-0.1.1.0-Av1VQQnxU7rDJ3iCQVkvb7" 'False) (C1 ('MetaCons "Tag" 'PrefixI 'True) (S1 ('MetaSel ('Just "tagFamily0") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "tagFamily1") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "tagName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))))

data Value Source #

An ExifTool tag value, enclosed in a type wrapper.

Instances

Instances details
Eq Value Source # 
Instance details

Defined in ExifTool

Methods

(==) :: Value -> Value -> Bool #

(/=) :: Value -> Value -> Bool #

Show Value Source # 
Instance details

Defined in ExifTool

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

ToJSON Value Source # 
Instance details

Defined in ExifTool

FromJSON Value Source # 
Instance details

Defined in ExifTool

filterByTag :: (Tag -> Bool) -> Metadata -> Metadata Source #

Filter metadata by tag name.

(~~) :: Metadata -> Tag -> Metadata infixl 8 Source #

Filter metadata by fuzzy tag name matching. Tag names are matched ignoring case, and empty components of the given tag name are considered wildcards. Examples:

  • m ~~ Tag "EXIF" "IFD0" "XResolution" matches exactly the given tag name (ignoring case)
  • m ~~ Tag "exif" "" "xresolution" matches all EXIF tags with name xresolution (ignoring case), including EXIF:IFD0:XResolution and EXIF:IFD1:XResolution
  • m ~~ Tag "XMP" "" "" matches all XMP tags

Note that ~~ has higher precedence than <>, so m ~~ t <> m ~~ t' == (m ~~ t) <> (m ~~ t') which makes combining filters easy.

Hint: This operator is useful to find exact tag names in ghci.