exiftool-0.2.0.0: Haskell bindings to ExifTool
Copyright(c) Martin Hoppenheit 2020-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 OverloadedStrings #-}

import Data.Text (Text)
import ExifTool

data Foo = Foo
  { description :: Text,
    resolution :: Int
  }
  deriving (Show)

main :: IO ()
main = withExifTool $ \et -> do
  m <- readMeta et [] "a.jpg"
  print $ Foo <$> get (Tag "Description") m <*> get (Tag "XResolution") m
  let m' = del (Tag "Description") . set (Tag "XResolution") (42 :: Int) $ m
  writeMeta et m' "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 or write metadata in a file with the respective functions.

readMeta :: ExifTool -> [Tag] -> FilePath -> IO Metadata Source #

Read the given tags from a file. Use an empty tag list to return all metadata. Tag names are returned in "simple" form without any leading group prefixes, independent of how they are specified in the given tag list.

Since: 0.2.0.0

readMetaEither :: ExifTool -> [Tag] -> FilePath -> IO (Either Text Metadata) Source #

Like readMeta, but ExifTool errors are returned as Left values instead of leading to runtime errors.

Since: 0.2.0.0

writeMeta :: ExifTool -> Metadata -> FilePath -> IO () Source #

Write metadata to a file. The file is modified in place, make sure you have the necessary backups!

Since: 0.2.0.0

writeMetaEither :: ExifTool -> Metadata -> FilePath -> IO (Either Text ()) Source #

Like writeMeta, but ExifTool errors are returned as Left values instead of leading to runtime errors.

Since: 0.2.0.0

Metadata is represented by a set of Tag/Value pairs that can be queried and manipulated with the respective functions.

data Metadata Source #

A set of ExifTool tag/value pairs. Use get, set and del to query and manipulate this set.

Instances

Instances details
Eq Metadata Source # 
Instance details

Defined in ExifTool

Show Metadata Source # 
Instance details

Defined in ExifTool

Semigroup Metadata Source # 
Instance details

Defined in ExifTool

Monoid Metadata Source # 
Instance details

Defined in ExifTool

newtype Tag Source #

An ExifTool tag name like Tag Description or Tag "EXIF:IFD0:XResolution".

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 #

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

stripGroups :: Tag -> Tag Source #

Remove group prefixes from a tag name e.g., stripGroups (Tag "XMP:XMP-dc:Description") == Tag Description.

data Value Source #

An ExifTool tag value, enclosed in a type wrapper. The type wrapper can usually be ignored when using the FromValue and ToValue instances.

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

ToValue Value Source # 
Instance details

Defined in ExifTool

Methods

toValue :: Value -> Value Source #

FromValue Value Source # 
Instance details

Defined in ExifTool

class FromValue a where Source #

Data types that a Value can be turned into.

Since: 0.2.0.0

Methods

fromValue :: Value -> Maybe a Source #

Instances

Instances details
FromValue Bool Source # 
Instance details

Defined in ExifTool

FromValue Double Source # 
Instance details

Defined in ExifTool

FromValue Float Source # 
Instance details

Defined in ExifTool

FromValue Int Source # 
Instance details

Defined in ExifTool

FromValue Integer Source # 
Instance details

Defined in ExifTool

FromValue ByteString Source # 
Instance details

Defined in ExifTool

FromValue Text Source # 
Instance details

Defined in ExifTool

FromValue Value Source # 
Instance details

Defined in ExifTool

FromValue a => FromValue [a] Source # 
Instance details

Defined in ExifTool

Methods

fromValue :: Value -> Maybe [a] Source #

class ToValue a where Source #

Data types that can be turned into a Value.

Since: 0.2.0.0

Methods

toValue :: a -> Value Source #

Instances

Instances details
ToValue Bool Source # 
Instance details

Defined in ExifTool

Methods

toValue :: Bool -> Value Source #

ToValue Double Source # 
Instance details

Defined in ExifTool

Methods

toValue :: Double -> Value Source #

ToValue Float Source # 
Instance details

Defined in ExifTool

Methods

toValue :: Float -> Value Source #

ToValue Int Source # 
Instance details

Defined in ExifTool

Methods

toValue :: Int -> Value Source #

ToValue Integer Source # 
Instance details

Defined in ExifTool

ToValue ByteString Source # 
Instance details

Defined in ExifTool

ToValue Text Source # 
Instance details

Defined in ExifTool

Methods

toValue :: Text -> Value Source #

ToValue Value Source # 
Instance details

Defined in ExifTool

Methods

toValue :: Value -> Value Source #

ToValue a => ToValue [a] Source # 
Instance details

Defined in ExifTool

Methods

toValue :: [a] -> Value Source #

get :: FromValue a => Tag -> Metadata -> Maybe a Source #

Retrieve the value of a tag. Tag case is ignored i.e., get (Tag "Description)" m == get (Tag "description") m.

Since: 0.2.0.0

set :: ToValue a => Tag -> a -> Metadata -> Metadata Source #

Set a tag to a (new) value. Tag case is ignored.

Since: 0.2.0.0

del :: Tag -> Metadata -> Metadata Source #

Delete a tag (i.e., set its value to a marker that will make ExifTool delete it when writeMeta is called). Tag case is ignored.

Since: 0.2.0.0