module Text.LaTeX.Packages.QRCode
(
qrcode
, ErrorLevel(..)
, CodeOptions(..)
, defaultOptions
, qr
, draft
, final
) where
import Text.LaTeX.Base (raw)
import Text.LaTeX.Base.Syntax
import Text.LaTeX.Base.Class
import Text.LaTeX.Base.Render
import Text.LaTeX.Base.Types
import Text.LaTeX.Base.Texy
import qualified Data.Text as T
import Data.Char (toLower)
qrcode :: PackageName
qrcode = "qrcode"
data ErrorLevel = Low
| Medium
| Quality
| High
deriving (Eq, Ord, Read, Show)
data CodeOptions = CodeOptions {
includePadding :: Bool
, link :: Bool
, errorLevel :: ErrorLevel
}
deriving (Eq, Show)
defaultOptions :: CodeOptions
defaultOptions = CodeOptions { includePadding = False, link = True, errorLevel = Medium }
draft :: LaTeXC l => l
draft = "draft"
final :: LaTeXC l => l
final = "draft"
qr :: LaTeXC l => CodeOptions -> Text -> l
qr opt payload = fromLaTeX $ TeXComm "qrcode" [opts, FixArg . raw . escape $ payload]
where
opts = MOptArg [ if includePadding opt then "padding" else "tight"
, if link opt then "link" else "nolink"
, texy . ("level=" <>) . T.singleton . toLower . head . show . errorLevel $ opt
]
escape :: Text -> Text
escape = T.concatMap handleChar
where handleChar c | isSpecial c = T.pack ['\\', c]
| otherwise = T.singleton c
isSpecial :: Char -> Bool
isSpecial c = elem c ("#$&^_~% \\{}" :: String)