{-# LANGUAGE OverloadedStrings #-}

module Text.LaTeX.Packages.Hyperref
 ( -- * Hyperref package
   hyperref
   -- * Hyperref commands
 , HRefOption (..)
 , URL
 , createURL
 , href
 , url
 , nolinkurl
 , hyperbaseurl
 , hyperimage
 , autoref
 , nameref
   -- * Package options
 , pdftex
 , pdftitle
 , pdfauthor
 , pdfsubject
 , pdfcreator
 , pdfproducer
 , pdfkeywords
 , pdftrapped
 , pdfstartpage
 , pdfpagelayout
 , PdfPageLayout(..)
   ) where

import Text.LaTeX.Base.Syntax
import Text.LaTeX.Base.Class
import Text.LaTeX.Base.Render
import Text.LaTeX.Base.Types
import Data.Text (pack)

-- | The 'hyperref' package.
--
-- > usepackage [] hyperref
hyperref :: PackageName
hyperref :: PackageName
hyperref = PackageName
"hyperref"

data HRefOption =
   PDFRemoteStartView
 | PDFNewWindow
 | HRefPage Int
   deriving Int -> HRefOption -> ShowS
[HRefOption] -> ShowS
HRefOption -> PackageName
(Int -> HRefOption -> ShowS)
-> (HRefOption -> PackageName)
-> ([HRefOption] -> ShowS)
-> Show HRefOption
forall a.
(Int -> a -> ShowS)
-> (a -> PackageName) -> ([a] -> ShowS) -> Show a
showList :: [HRefOption] -> ShowS
$cshowList :: [HRefOption] -> ShowS
show :: HRefOption -> PackageName
$cshow :: HRefOption -> PackageName
showsPrec :: Int -> HRefOption -> ShowS
$cshowsPrec :: Int -> HRefOption -> ShowS
Show

instance Render HRefOption where
 render :: HRefOption -> Text
render HRefOption
PDFRemoteStartView = Text
"pdfremotestartview"
 render HRefOption
PDFNewWindow = Text
"pdfnewwindow"
 render (HRefPage Int
n) = Text
"page=" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text
forall a. Render a => a -> Text
render Int
n

newtype URL = URL String deriving Int -> URL -> ShowS
[URL] -> ShowS
URL -> PackageName
(Int -> URL -> ShowS)
-> (URL -> PackageName) -> ([URL] -> ShowS) -> Show URL
forall a.
(Int -> a -> ShowS)
-> (a -> PackageName) -> ([a] -> ShowS) -> Show a
showList :: [URL] -> ShowS
$cshowList :: [URL] -> ShowS
show :: URL -> PackageName
$cshow :: URL -> PackageName
showsPrec :: Int -> URL -> ShowS
$cshowsPrec :: Int -> URL -> ShowS
Show

instance Render URL where
 render :: URL -> Text
render (URL PackageName
str) = PackageName -> Text
forall a. IsString a => PackageName -> a
fromString PackageName
str

createURL :: String -> URL
createURL :: PackageName -> URL
createURL = PackageName -> URL
URL
-- TODO: This function should check that the input
-- String is a valid URL.

-- | 'fromString' = 'createURL'.
instance IsString URL where
 fromString :: PackageName -> URL
fromString = PackageName -> URL
createURL

-- | Reference to an 'URL'.
href :: LaTeXC l => [HRefOption] -> URL -> l -> l
href :: [HRefOption] -> URL -> l -> l
href [HRefOption]
options URL
u = (LaTeX -> LaTeX) -> l -> l
forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL ((LaTeX -> LaTeX) -> l -> l) -> (LaTeX -> LaTeX) -> l -> l
forall a b. (a -> b) -> a -> b
$ \LaTeX
t -> PackageName -> [TeXArg] -> LaTeX
TeXComm PackageName
"href" [ [LaTeX] -> TeXArg
MOptArg ([LaTeX] -> TeXArg) -> [LaTeX] -> TeXArg
forall a b. (a -> b) -> a -> b
$ (HRefOption -> LaTeX) -> [HRefOption] -> [LaTeX]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap HRefOption -> LaTeX
forall a l. (Render a, LaTeXC l) => a -> l
rendertex [HRefOption]
options
                                              , LaTeX -> TeXArg
FixArg  (LaTeX -> TeXArg) -> LaTeX -> TeXArg
forall a b. (a -> b) -> a -> b
$ URL -> LaTeX
forall a l. (Render a, LaTeXC l) => a -> l
rendertex URL
u
                                              , LaTeX -> TeXArg
FixArg LaTeX
t ]

-- | Write an 'URL' hyperlinked.
url :: LaTeXC l => URL -> l
url :: URL -> l
url URL
u = LaTeX -> l
forall l. LaTeXC l => LaTeX -> l
fromLaTeX (LaTeX -> l) -> LaTeX -> l
forall a b. (a -> b) -> a -> b
$ PackageName -> [TeXArg] -> LaTeX
TeXComm PackageName
"url" [ LaTeX -> TeXArg
FixArg (LaTeX -> TeXArg) -> LaTeX -> TeXArg
forall a b. (a -> b) -> a -> b
$ URL -> LaTeX
forall a l. (Render a, LaTeXC l) => a -> l
rendertex URL
u ]

-- | Write an 'URL' without creating a hyperlink.
nolinkurl :: LaTeXC l => URL -> l
nolinkurl :: URL -> l
nolinkurl URL
u = LaTeX -> l
forall l. LaTeXC l => LaTeX -> l
fromLaTeX (LaTeX -> l) -> LaTeX -> l
forall a b. (a -> b) -> a -> b
$ PackageName -> [TeXArg] -> LaTeX
TeXComm PackageName
"nolinkurl" [ LaTeX -> TeXArg
FixArg (LaTeX -> TeXArg) -> LaTeX -> TeXArg
forall a b. (a -> b) -> a -> b
$ URL -> LaTeX
forall a l. (Render a, LaTeXC l) => a -> l
rendertex URL
u ]

-- | Establish a base 'URL'.
hyperbaseurl :: LaTeXC l => URL -> l
hyperbaseurl :: URL -> l
hyperbaseurl URL
u = LaTeX -> l
forall l. LaTeXC l => LaTeX -> l
fromLaTeX (LaTeX -> l) -> LaTeX -> l
forall a b. (a -> b) -> a -> b
$ PackageName -> [TeXArg] -> LaTeX
TeXComm PackageName
"hyperbaseurl" [ LaTeX -> TeXArg
FixArg (LaTeX -> TeXArg) -> LaTeX -> TeXArg
forall a b. (a -> b) -> a -> b
$ URL -> LaTeX
forall a l. (Render a, LaTeXC l) => a -> l
rendertex URL
u ]

-- | @hyperimage imgURL t@:
--  The link to the image referenced by the @imgURL@ is inserted, using @t@ as the anchor.
hyperimage :: LaTeXC l => URL -> l -> l
hyperimage :: URL -> l -> l
hyperimage URL
u = (LaTeX -> LaTeX) -> l -> l
forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL ((LaTeX -> LaTeX) -> l -> l) -> (LaTeX -> LaTeX) -> l -> l
forall a b. (a -> b) -> a -> b
$ \LaTeX
t -> PackageName -> [TeXArg] -> LaTeX
TeXComm PackageName
"hyperimage" [ LaTeX -> TeXArg
FixArg (LaTeX -> TeXArg) -> LaTeX -> TeXArg
forall a b. (a -> b) -> a -> b
$ URL -> LaTeX
forall a l. (Render a, LaTeXC l) => a -> l
rendertex URL
u , LaTeX -> TeXArg
FixArg LaTeX
t ]

-- | This is a replacement for the usual 'ref' command that places a contextual label in front of the reference.
autoref :: LaTeXC l => Label -> l
autoref :: Label -> l
autoref Label
l = LaTeX -> l
forall l. LaTeXC l => LaTeX -> l
fromLaTeX (LaTeX -> l) -> LaTeX -> l
forall a b. (a -> b) -> a -> b
$ PackageName -> [TeXArg] -> LaTeX
TeXComm PackageName
"autoref" [ LaTeX -> TeXArg
FixArg (LaTeX -> TeXArg) -> LaTeX -> TeXArg
forall a b. (a -> b) -> a -> b
$ Label -> LaTeX
forall a l. (Render a, LaTeXC l) => a -> l
rendertex Label
l ]

-- | Similar to 'autoref', but inserts text corresponding to the section name.
--   Note that this command comes from the /nameref/ package, but it's automatically
--   included when importing 'hyperref'.
nameref :: LaTeXC l => Label -> l
nameref :: Label -> l
nameref Label
l = LaTeX -> l
forall l. LaTeXC l => LaTeX -> l
fromLaTeX (LaTeX -> l) -> LaTeX -> l
forall a b. (a -> b) -> a -> b
$ PackageName -> [TeXArg] -> LaTeX
TeXComm PackageName
"nameref" [ LaTeX -> TeXArg
FixArg (LaTeX -> TeXArg) -> LaTeX -> TeXArg
forall a b. (a -> b) -> a -> b
$ Label -> LaTeX
forall a l. (Render a, LaTeXC l) => a -> l
rendertex Label
l ]

-- | Creates a single-parameter package option.
packageOption :: LaTeXC l => Text -> l -> l
packageOption :: Text -> l -> l
packageOption Text
n l
p = Text -> l
forall l. LaTeXC l => Text -> l
raw Text
n l -> l -> l
forall a. Semigroup a => a -> a -> a
<> Text -> l
forall l. LaTeXC l => Text -> l
raw Text
"={" l -> l -> l
forall a. Semigroup a => a -> a -> a
<> l
p l -> l -> l
forall a. Semigroup a => a -> a -> a
<> Text -> l
forall l. LaTeXC l => Text -> l
raw Text
"}"

-- | This package option selects the pdfTeX backend for the Hyperref package.
pdftex :: LaTeXC l => l
pdftex :: l
pdftex = Text -> l
forall l. LaTeXC l => Text -> l
raw Text
"pdftex"

-- | This package option sets the document information Title field.
pdftitle :: LaTeXC l => l -> l
pdftitle :: l -> l
pdftitle = Text -> l -> l
forall l. LaTeXC l => Text -> l -> l
packageOption Text
"pdftitle"

-- | This package option sets the document information Author field.
pdfauthor :: LaTeXC l => l -> l
pdfauthor :: l -> l
pdfauthor = Text -> l -> l
forall l. LaTeXC l => Text -> l -> l
packageOption Text
"pdfauthor"

-- | This package option sets the document information Subject field.
pdfsubject :: LaTeXC l => l -> l
pdfsubject :: l -> l
pdfsubject = Text -> l -> l
forall l. LaTeXC l => Text -> l -> l
packageOption Text
"pdfsubject"

-- | This package option sets the document information Creator field.
pdfcreator :: LaTeXC l => l -> l
pdfcreator :: l -> l
pdfcreator = Text -> l -> l
forall l. LaTeXC l => Text -> l -> l
packageOption Text
"pdfcreator"

-- | This package option sets the document information Producer field.
pdfproducer :: LaTeXC l => l -> l
pdfproducer :: l -> l
pdfproducer = Text -> l -> l
forall l. LaTeXC l => Text -> l -> l
packageOption Text
"pdfproducer"

-- | This package option sets the document information Keywords field.
pdfkeywords :: LaTeXC l => l -> l
pdfkeywords :: l -> l
pdfkeywords = Text -> l -> l
forall l. LaTeXC l => Text -> l -> l
packageOption Text
"pdfkeywords"

-- | This package option sets the document information Trapped entry.
-- An 'Nothing' value means, the entry is not set. 
pdftrapped :: LaTeXC l => Maybe Bool -> l
pdftrapped :: Maybe Bool -> l
pdftrapped Maybe Bool
Nothing = Text -> l -> l
forall l. LaTeXC l => Text -> l -> l
packageOption Text
"pdftrapped" l
forall a. Monoid a => a
mempty
pdftrapped (Just Bool
t) = Text -> l -> l
forall l. LaTeXC l => Text -> l -> l
packageOption Text
"pdftrapped" (l -> l) -> (Bool -> l) -> Bool -> l
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> l
forall l. LaTeXC l => Text -> l
raw (Text -> l) -> (Bool -> Text) -> Bool -> l
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PackageName -> Text
pack (PackageName -> Text) -> (Bool -> PackageName) -> Bool -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> PackageName
forall a. Show a => a -> PackageName
show (Bool -> l) -> Bool -> l
forall a b. (a -> b) -> a -> b
$ Bool
t

-- | This package option determines on which page the PDF file is opened.
pdfstartpage :: LaTeXC l => l -> l
pdfstartpage :: l -> l
pdfstartpage = Text -> l -> l
forall l. LaTeXC l => Text -> l -> l
packageOption Text
"pdfstartpage"

-- | This package option sets the layout of PDF pages.
pdfpagelayout :: LaTeXC l => PdfPageLayout -> l
pdfpagelayout :: PdfPageLayout -> l
pdfpagelayout = Text -> l -> l
forall l. LaTeXC l => Text -> l -> l
packageOption Text
"pdfpagelayout" (l -> l) -> (PdfPageLayout -> l) -> PdfPageLayout -> l
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> l
forall l. LaTeXC l => Text -> l
raw (Text -> l) -> (PdfPageLayout -> Text) -> PdfPageLayout -> l
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PackageName -> Text
pack (PackageName -> Text)
-> (PdfPageLayout -> PackageName) -> PdfPageLayout -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PdfPageLayout -> PackageName
forall a. Show a => a -> PackageName
show

-- | Specification for how pages of a PDF should be displayed.
data PdfPageLayout = SinglePage -- ^ Displays a single page; advancing flips the page.
                   | OneColumn -- ^ Displays a single page; advancing flips the page.
                   | TwoColumnLeft -- ^ Displays the document in two columns, odd-numbered pages to the left.
                   | TwoColumnRight -- ^ Displays the document in two columns, odd-numbered pages to the right.
                   | TwoPageLeft -- ^ Displays two pages, odd-numbered pages to the left (since PDF 1.5).
                   | TwoPageRight -- ^ Displays two pages, odd-numbered pages to the right (since PDF 1.5).
  deriving (PdfPageLayout -> PdfPageLayout -> Bool
(PdfPageLayout -> PdfPageLayout -> Bool)
-> (PdfPageLayout -> PdfPageLayout -> Bool) -> Eq PdfPageLayout
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PdfPageLayout -> PdfPageLayout -> Bool
$c/= :: PdfPageLayout -> PdfPageLayout -> Bool
== :: PdfPageLayout -> PdfPageLayout -> Bool
$c== :: PdfPageLayout -> PdfPageLayout -> Bool
Eq, Eq PdfPageLayout
Eq PdfPageLayout
-> (PdfPageLayout -> PdfPageLayout -> Ordering)
-> (PdfPageLayout -> PdfPageLayout -> Bool)
-> (PdfPageLayout -> PdfPageLayout -> Bool)
-> (PdfPageLayout -> PdfPageLayout -> Bool)
-> (PdfPageLayout -> PdfPageLayout -> Bool)
-> (PdfPageLayout -> PdfPageLayout -> PdfPageLayout)
-> (PdfPageLayout -> PdfPageLayout -> PdfPageLayout)
-> Ord PdfPageLayout
PdfPageLayout -> PdfPageLayout -> Bool
PdfPageLayout -> PdfPageLayout -> Ordering
PdfPageLayout -> PdfPageLayout -> PdfPageLayout
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PdfPageLayout -> PdfPageLayout -> PdfPageLayout
$cmin :: PdfPageLayout -> PdfPageLayout -> PdfPageLayout
max :: PdfPageLayout -> PdfPageLayout -> PdfPageLayout
$cmax :: PdfPageLayout -> PdfPageLayout -> PdfPageLayout
>= :: PdfPageLayout -> PdfPageLayout -> Bool
$c>= :: PdfPageLayout -> PdfPageLayout -> Bool
> :: PdfPageLayout -> PdfPageLayout -> Bool
$c> :: PdfPageLayout -> PdfPageLayout -> Bool
<= :: PdfPageLayout -> PdfPageLayout -> Bool
$c<= :: PdfPageLayout -> PdfPageLayout -> Bool
< :: PdfPageLayout -> PdfPageLayout -> Bool
$c< :: PdfPageLayout -> PdfPageLayout -> Bool
compare :: PdfPageLayout -> PdfPageLayout -> Ordering
$ccompare :: PdfPageLayout -> PdfPageLayout -> Ordering
$cp1Ord :: Eq PdfPageLayout
Ord, ReadPrec [PdfPageLayout]
ReadPrec PdfPageLayout
Int -> ReadS PdfPageLayout
ReadS [PdfPageLayout]
(Int -> ReadS PdfPageLayout)
-> ReadS [PdfPageLayout]
-> ReadPrec PdfPageLayout
-> ReadPrec [PdfPageLayout]
-> Read PdfPageLayout
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PdfPageLayout]
$creadListPrec :: ReadPrec [PdfPageLayout]
readPrec :: ReadPrec PdfPageLayout
$creadPrec :: ReadPrec PdfPageLayout
readList :: ReadS [PdfPageLayout]
$creadList :: ReadS [PdfPageLayout]
readsPrec :: Int -> ReadS PdfPageLayout
$creadsPrec :: Int -> ReadS PdfPageLayout
Read, Int -> PdfPageLayout -> ShowS
[PdfPageLayout] -> ShowS
PdfPageLayout -> PackageName
(Int -> PdfPageLayout -> ShowS)
-> (PdfPageLayout -> PackageName)
-> ([PdfPageLayout] -> ShowS)
-> Show PdfPageLayout
forall a.
(Int -> a -> ShowS)
-> (a -> PackageName) -> ([a] -> ShowS) -> Show a
showList :: [PdfPageLayout] -> ShowS
$cshowList :: [PdfPageLayout] -> ShowS
show :: PdfPageLayout -> PackageName
$cshow :: PdfPageLayout -> PackageName
showsPrec :: Int -> PdfPageLayout -> ShowS
$cshowsPrec :: Int -> PdfPageLayout -> ShowS
Show)