{-# LANGUAGE OverloadedStrings #-}

-- | Select new font encodings using the @fontenc@ package.
module Text.LaTeX.Packages.Fontenc (
   -- * Fontenc package
   fontenc
   -- * Font encodings
 , FontEnc (..)
 , useencoding
   ) where

import Text.LaTeX.Base
import Text.LaTeX.Base.Class

-- Fontenc package

-- | The @fontenc@ package.
--   It is recommended to use the 'useencoding' function
--   to import it.
fontenc :: PackageName
fontenc :: PackageName
fontenc = PackageName
"fontenc"

-- Font encodings

-- | Font encodings.
data FontEnc = T1 | OT1 deriving Int -> FontEnc -> ShowS
[FontEnc] -> ShowS
FontEnc -> PackageName
forall a.
(Int -> a -> ShowS)
-> (a -> PackageName) -> ([a] -> ShowS) -> Show a
showList :: [FontEnc] -> ShowS
$cshowList :: [FontEnc] -> ShowS
show :: FontEnc -> PackageName
$cshow :: FontEnc -> PackageName
showsPrec :: Int -> FontEnc -> ShowS
$cshowsPrec :: Int -> FontEnc -> ShowS
Show

instance Render FontEnc where
 render :: FontEnc -> Text
render FontEnc
T1 = Text
"T1"
 render FontEnc
OT1 = Text
"OT1"

instance Texy FontEnc where
 texy :: forall l. LaTeXC l => FontEnc -> l
texy = forall t l. (Texy t, LaTeXC l) => t -> l
texy forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Render a => a -> Text
render

-- | In the preamble, select encodings to use in your document.
--   The last one will be the default encoding. Example:
--
-- > useencoding [T1]
--
--   It imports the @fontenc@ package. In fact:
--
-- > useencoding xs = usepackage (fmap texy xs) fontenc
--
useencoding :: LaTeXC l => [FontEnc] -> l
useencoding :: forall l. LaTeXC l => [FontEnc] -> l
useencoding [FontEnc]
xs = forall l. LaTeXC l => [l] -> PackageName -> l
usepackage (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall t l. (Texy t, LaTeXC l) => t -> l
texy [FontEnc]
xs) PackageName
fontenc