{-# LANGUAGE OverloadedStrings, CPP #-}

-- | Add acronyms to your documents using this module.
--
--   Define and render acronyms in a document, where the first occurrance is the
--   long variant, and the next ones are the shorter variant.
module Text.LaTeX.Packages.Acronym
 ( -- * Acronym package
   pacronym
   -- * Package options
 , footnote, nohyperlinks, printonlyused, withpage, smaller, dua, nolist
 -- * Types
 , Acronym(..)
 -- functions
 , ac, acf, acs, acl, acp, acfp, acsp, aclp, acfi, acsu, aclu, iac, iac2
 , ac', acf', acs', acl', acp', acfp', acsp', aclp', acfi', acsu', aclu', iac', iac2'
 , acresetall, acused
 , acroextra
 , acronym
 , acro, acro'
 , acroM, acroM'
   ) where

import Data.String(IsString(fromString))

import Text.LaTeX.Base.Class(LaTeXC, comm0, comm1, comm2, liftL, liftL2)
import Text.LaTeX.Base.Syntax(LaTeX(TeXComm, TeXEnv), TeXArg(FixArg, OptArg))
import Text.LaTeX.Base.Types(PackageName)
import Text.LaTeX.Base.Writer(LaTeXT)

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

-- | Redefines the `\acf` and `\acfp` commands making the full
--   name appear as a footnote
footnote :: LaTeXC l => l
footnote :: l
footnote = l
"footnote"

-- | If hyperref is loaded, all acronyms will link to their glossary entry. With
--   the `nohyperlinks` option, these links are suppressed.
nohyperlinks :: LaTeXC l => l
nohyperlinks :: l
nohyperlinks = l
"nohyperlinks"

-- | We need a marker which is set if the option `printonlyused` was used.
printonlyused :: LaTeXC l => l
printonlyused :: l
printonlyused = l
"printonlyused"

-- | A marker which tells us to print page numbers.
withpage :: LaTeXC l => l
withpage :: l
withpage = l
"withpage"

-- | The option `smaller` leads to a redefinition of `\acsfont`. We want to make
--   the acronym appear smaller. Since this should be done in a
--   context-sensitive way, we rely on the macro \textsmaller provided by the
--   `relsize` package. As `\RequiredPackage` cannot be used inside
--   `\DeclareOption`, we need a boolean variable.
smaller :: LaTeXC l => l
smaller :: l
smaller = l
"smaller"

-- | The option `dua` stands for "don't use acronyms". It leads to a
--   redefinition of `\ac` and `\acp` making the full name appear all the time
--   and suppressing all acronyms but the explicitly requested by `\acf` and
--   `\acfp`.
dua :: LaTeXC l => l
dua :: l
dua = l
"dua"

-- | The option `nolist` stands for "don't write the list of acronyms".
nolist :: LaTeXC l => l
nolist :: l
nolist = l
"nolist"

-- | An acronym type with a label, this is used to generate commands linked to
--   this acronym.
newtype Acronym = Acronym { Acronym -> PackageName
acronymLabel :: String }

_acronymLabel :: IsString s => Acronym -> s
_acronymLabel :: Acronym -> s
_acronymLabel = PackageName -> s
forall a. IsString a => PackageName -> a
fromString (PackageName -> s) -> (Acronym -> PackageName) -> Acronym -> s
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Acronym -> PackageName
acronymLabel

_acronymC1 :: LaTeXC l => String -> Acronym -> l
_acronymC1 :: PackageName -> Acronym -> l
_acronymC1 = ((l -> l) -> (Acronym -> l) -> Acronym -> l
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Acronym -> l
forall s. IsString s => Acronym -> s
_acronymLabel) ((l -> l) -> Acronym -> l)
-> (PackageName -> l -> l) -> PackageName -> Acronym -> l
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PackageName -> l -> l
forall l. LaTeXC l => PackageName -> l -> l
comm1

-- | Enter an acronym inside the text. The first time the acronym is used, it
--   will specify the full name, and between parenthesis, the short name. If you
--   specified the `footnote` option, it will print the short name, and add a
--   footnote with the long name. The next time, only the short time is printed.
ac :: LaTeXC l => Acronym -> l
ac :: Acronym -> l
ac = PackageName -> Acronym -> l
forall l. LaTeXC l => PackageName -> Acronym -> l
_acronymC1 PackageName
"ac"

-- | You can use this command to later in the text again print the full name of
--   the acronym, this stands for "full acronym", it always prints the full
--   name, and the acronym between parenthesis.
acf :: LaTeXC l => Acronym -> l
acf :: Acronym -> l
acf = PackageName -> Acronym -> l
forall l. LaTeXC l => PackageName -> Acronym -> l
_acronymC1 PackageName
"acf"

-- | This will enter the short version of the acronym inside the text.
acs :: LaTeXC l => Acronym -> l
acs :: Acronym -> l
acs = PackageName -> Acronym -> l
forall l. LaTeXC l => PackageName -> Acronym -> l
_acronymC1 PackageName
"acs"

-- | This will enter the expanded version of the acronym in the text, without
--   mentioning the acronym between parenthesis.
acl :: LaTeXC l => Acronym -> l
acl :: Acronym -> l
acl = PackageName -> Acronym -> l
forall l. LaTeXC l => PackageName -> Acronym -> l
_acronymC1 PackageName
"acl"

-- | This works the same way as `ac`, except that it will make the short and the
--   long forms into plurals.
acp :: LaTeXC l => Acronym -> l
acp :: Acronym -> l
acp = PackageName -> Acronym -> l
forall l. LaTeXC l => PackageName -> Acronym -> l
_acronymC1 PackageName
"acp"

-- | This works the same way as `acf`, except tah it will make the short and
--   long forms into plurals.
acfp :: LaTeXC l => Acronym -> l
acfp :: Acronym -> l
acfp = PackageName -> Acronym -> l
forall l. LaTeXC l => PackageName -> Acronym -> l
_acronymC1 PackageName
"acfp"

-- | Works the same way as `acs`, but makes the short form into a plural.
acsp :: LaTeXC l => Acronym -> l
acsp :: Acronym -> l
acsp = PackageName -> Acronym -> l
forall l. LaTeXC l => PackageName -> Acronym -> l
_acronymC1 PackageName
"acsp"

-- | Works the same way as `acl`, but makes the long form into a plural.
aclp :: LaTeXC l => Acronym -> l
aclp :: Acronym -> l
aclp = PackageName -> Acronym -> l
forall l. LaTeXC l => PackageName -> Acronym -> l
_acronymC1 PackageName
"aclp"

-- | Prints the full name acronym in italics and the abbreviated form in an
-- upshaped form.
acfi :: LaTeXC l => Acronym -> l
acfi :: Acronym -> l
acfi = PackageName -> Acronym -> l
forall l. LaTeXC l => PackageName -> Acronym -> l
_acronymC1 PackageName
"acfi"

-- | Prints the short form of the acronym, and marks it as used.
acsu :: LaTeXC l => Acronym -> l
acsu :: Acronym -> l
acsu = PackageName -> Acronym -> l
forall l. LaTeXC l => PackageName -> Acronym -> l
_acronymC1 PackageName
"acsu"

-- | Prints the long form of the acronym and marks it as used.
aclu :: LaTeXC l => Acronym -> l
aclu :: Acronym -> l
aclu = PackageName -> Acronym -> l
forall l. LaTeXC l => PackageName -> Acronym -> l
_acronymC1 PackageName
"aclu"

-- | Works the same way as the `ac` command, but prefixes it with an appropriate
-- indefinite article.
iac :: LaTeXC l => Acronym -> l
iac :: Acronym -> l
iac = PackageName -> Acronym -> l
forall l. LaTeXC l => PackageName -> Acronym -> l
_acronymC1 PackageName
"iac"

-- | Works the same way as the `ac` command, but prefixes it with an appropriate
-- upper case indefinite article.
iac2 :: LaTeXC l => Acronym -> l
iac2 :: Acronym -> l
iac2 = PackageName -> Acronym -> l
forall l. LaTeXC l => PackageName -> Acronym -> l
_acronymC1 PackageName
"Iac"

-- | Enter an acronym inside the text. It will specify the full name, and
--   between parenthesis, the short name. If you specified the `footnote`
--   option, it will print the short name, and add a footnote with the long
--   name. This does not mark the acronym as used.
ac' :: LaTeXC l => Acronym -> l
ac' :: Acronym -> l
ac' = PackageName -> Acronym -> l
forall l. LaTeXC l => PackageName -> Acronym -> l
_acronymC1 PackageName
"ac*"

-- | You can use this command to later in the text again print the full name of
--   the acronym, this stands for "full acronym", it always prints the full
--   name, and the acronym between parenthesis. This does not mark the
--   acronym as used.
acf' :: LaTeXC l => Acronym -> l
acf' :: Acronym -> l
acf' = PackageName -> Acronym -> l
forall l. LaTeXC l => PackageName -> Acronym -> l
_acronymC1 PackageName
"acf*"

-- | This will enter the short version of the acronym inside the text.
-- This does not mark the acronym as used.
acs' :: LaTeXC l => Acronym -> l
acs' :: Acronym -> l
acs' = PackageName -> Acronym -> l
forall l. LaTeXC l => PackageName -> Acronym -> l
_acronymC1 PackageName
"acs*"

-- | This will enter the expanded version of the acronym in the text, without
--   mentioning the acronym between parenthesis. This does not mark the acronym
--   as used.
acl' :: LaTeXC l => Acronym -> l
acl' :: Acronym -> l
acl' = PackageName -> Acronym -> l
forall l. LaTeXC l => PackageName -> Acronym -> l
_acronymC1 PackageName
"acl*"

-- | This works the same way as `ac`, except that it will make the short and the
--   long forms into plurals. This does not mark the acronym as used.
acp' :: LaTeXC l => Acronym -> l
acp' :: Acronym -> l
acp' = PackageName -> Acronym -> l
forall l. LaTeXC l => PackageName -> Acronym -> l
_acronymC1 PackageName
"acp*"

-- | This works the same way as `acf`, except tah it will make the short and
--   long forms into plurals. This does not mark the acronym as used.
acfp' :: LaTeXC l => Acronym -> l
acfp' :: Acronym -> l
acfp' = PackageName -> Acronym -> l
forall l. LaTeXC l => PackageName -> Acronym -> l
_acronymC1 PackageName
"acfp*"

-- | Works the same way as `acs`, but makes the short form into a plural. This
--   does not mark the acronym as used.
acsp' :: LaTeXC l => Acronym -> l
acsp' :: Acronym -> l
acsp' = PackageName -> Acronym -> l
forall l. LaTeXC l => PackageName -> Acronym -> l
_acronymC1 PackageName
"acsp*"

-- | Works the same way as `acl`, but makes the long form into a plural. This
--   does not mark the acronym as used.
aclp' :: LaTeXC l => Acronym -> l
aclp' :: Acronym -> l
aclp' = PackageName -> Acronym -> l
forall l. LaTeXC l => PackageName -> Acronym -> l
_acronymC1 PackageName
"aclp*"

-- | Prints the full name acronym in italics and the abbreviated form in an
-- upshaped form. This does not mark the acronym as used.
acfi' :: LaTeXC l => Acronym -> l
acfi' :: Acronym -> l
acfi' = PackageName -> Acronym -> l
forall l. LaTeXC l => PackageName -> Acronym -> l
_acronymC1 PackageName
"acfi*"

-- | Prints the short form of the acronym, and marks it as used. This does not
--   mark the acronym as used.
acsu' :: LaTeXC l => Acronym -> l
acsu' :: Acronym -> l
acsu' = PackageName -> Acronym -> l
forall l. LaTeXC l => PackageName -> Acronym -> l
_acronymC1 PackageName
"acsu*"

-- | Prints the long form of the acronym and marks it as used. This does not mark
--   the acronym as used.
aclu' :: LaTeXC l => Acronym -> l
aclu' :: Acronym -> l
aclu' = PackageName -> Acronym -> l
forall l. LaTeXC l => PackageName -> Acronym -> l
_acronymC1 PackageName
"aclu*"

-- | Works the same way as the `ac` command, but prefixes it with an appropriate
-- indefinite article. This does not mark the acronym as used.
iac' :: LaTeXC l => Acronym -> l
iac' :: Acronym -> l
iac' = PackageName -> Acronym -> l
forall l. LaTeXC l => PackageName -> Acronym -> l
_acronymC1 PackageName
"iac*"

-- | Works the same way as the `ac` command, but prefixes it with an appropriate
-- upper case indefinite article. This does not mark the acronym as used.
iac2' :: LaTeXC l => Acronym -> l
iac2' :: Acronym -> l
iac2' = PackageName -> Acronym -> l
forall l. LaTeXC l => PackageName -> Acronym -> l
_acronymC1 PackageName
"Iac*"

-- | The memory of the marco `ac` is flushed, afterwards, `ac` will print the
--   full name of any acronym, and the acronym within parenthesis.
acresetall :: LaTeXC l => l
acresetall :: l
acresetall = PackageName -> l
forall l. LaTeXC l => PackageName -> l
comm0 PackageName
"acresetall"

-- | Marks an acronym as useed, as if it has been called with `ac`, but without
--   printing anything. In the future, only the short form of the acronym will
--   be printed. `acresetall` undoes this.
acused :: LaTeXC l => Acronym -> l
acused :: Acronym -> l
acused = PackageName -> Acronym -> l
forall l. LaTeXC l => PackageName -> Acronym -> l
_acronymC1 PackageName
"acused"

-- | This can be used inside the `acro` part to add extra data to the list of
--   acrynyms, this will *not* be included when rendering the acronym in the
--   document itself.
acroextra :: LaTeXC l => l -> l
acroextra :: l -> l
acroextra = PackageName -> l -> l
forall l. LaTeXC l => PackageName -> l -> l
comm1 PackageName
"acroextra"

-- | Define an acronym environment to write the acronym definitions to.
acronym :: LaTeXC l => l -> l
acronym :: l -> l
acronym = (LaTeX -> LaTeX) -> l -> l
forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL (PackageName -> [TeXArg] -> LaTeX -> LaTeX
TeXEnv PackageName
"acronym" [])

-- | Define an acronym with a label and both a short, and a long name. This
--   returns the LaTeX code to define the acronym, and the `Acronym` object
--   to use in the rest of the code.
acro :: LaTeXC l => String -> l -> l -> (l, Acronym)
acro :: PackageName -> l -> l -> (l, Acronym)
acro PackageName
str l
l2 l
l3 = ((LaTeX -> LaTeX -> LaTeX) -> l -> l -> l
forall l. LaTeXC l => (LaTeX -> LaTeX -> LaTeX) -> l -> l -> l
liftL2 (\LaTeX
la LaTeX
lb -> PackageName -> [TeXArg] -> LaTeX
TeXComm PackageName
"acro" [LaTeX -> TeXArg
FixArg (PackageName -> LaTeX
forall a. IsString a => PackageName -> a
fromString PackageName
str), LaTeX -> TeXArg
OptArg LaTeX
la, LaTeX -> TeXArg
FixArg LaTeX
lb]) l
l2 l
l3, PackageName -> Acronym
Acronym PackageName
str)

-- | The monadic variant of the `acro` function where the `Acronym` is returned
--   as a result of the definition.
acroM :: Monad m => String -> LaTeXT m () -> LaTeXT m () -> LaTeXT m Acronym
acroM :: PackageName -> LaTeXT m () -> LaTeXT m () -> LaTeXT m Acronym
acroM PackageName
str LaTeXT m ()
l2 LaTeXT m ()
l3 = (LaTeXT m () -> Acronym -> LaTeXT m Acronym)
-> (LaTeXT m (), Acronym) -> LaTeXT m Acronym
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry ((Acronym -> LaTeXT m () -> LaTeXT m Acronym)
-> LaTeXT m () -> Acronym -> LaTeXT m Acronym
forall a b c. (a -> b -> c) -> b -> a -> c
flip ((() -> Acronym) -> LaTeXT m () -> LaTeXT m Acronym
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((() -> Acronym) -> LaTeXT m () -> LaTeXT m Acronym)
-> (Acronym -> () -> Acronym)
-> Acronym
-> LaTeXT m ()
-> LaTeXT m Acronym
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Acronym -> () -> Acronym
forall a b. a -> b -> a
const)) (PackageName -> LaTeXT m () -> LaTeXT m () -> (LaTeXT m (), Acronym)
forall l. LaTeXC l => PackageName -> l -> l -> (l, Acronym)
acro PackageName
str LaTeXT m ()
l2 LaTeXT m ()
l3)

-- | Define an acronym with a label, and only a long name. This returns the
--   LaTeX code to define the acronym, and the `Acronym` object to use in the
--   rest of the code.
acro' :: LaTeXC l => String -> l -> (l, Acronym)
acro' :: PackageName -> l -> (l, Acronym)
acro' PackageName
str l
l = (PackageName -> l -> l -> l
forall l. LaTeXC l => PackageName -> l -> l -> l
comm2 PackageName
"acro" (PackageName -> l
forall a. IsString a => PackageName -> a
fromString PackageName
str) l
l, PackageName -> Acronym
Acronym PackageName
str)

-- | The monadic variant of the `acro'` function, where the `Acronym` is
--   returned as result of the definition.
acroM' :: Monad m => String -> LaTeXT m () -> LaTeXT m Acronym
acroM' :: PackageName -> LaTeXT m () -> LaTeXT m Acronym
acroM' PackageName
str LaTeXT m ()
l2 = (LaTeXT m () -> Acronym -> LaTeXT m Acronym)
-> (LaTeXT m (), Acronym) -> LaTeXT m Acronym
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry ((Acronym -> LaTeXT m () -> LaTeXT m Acronym)
-> LaTeXT m () -> Acronym -> LaTeXT m Acronym
forall a b c. (a -> b -> c) -> b -> a -> c
flip ((() -> Acronym) -> LaTeXT m () -> LaTeXT m Acronym
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((() -> Acronym) -> LaTeXT m () -> LaTeXT m Acronym)
-> (Acronym -> () -> Acronym)
-> Acronym
-> LaTeXT m ()
-> LaTeXT m Acronym
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Acronym -> () -> Acronym
forall a b. a -> b -> a
const)) (PackageName -> LaTeXT m () -> (LaTeXT m (), Acronym)
forall l. LaTeXC l => PackageName -> l -> (l, Acronym)
acro' PackageName
str LaTeXT m ()
l2)