{-# LANGUAGE OverloadedStrings #-}
module Text.LaTeX.Packages.QRCode
(
qrcode
, ErrorLevel(..)
, CodeOptions(..)
, defaultOptions
, qr
, draft
, final
) where
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
qrcode :: PackageName
qrcode :: PackageName
qrcode = PackageName
"qrcode"
data ErrorLevel = Low
| Medium
| Quality
| High
deriving (ErrorLevel -> ErrorLevel -> Bool
(ErrorLevel -> ErrorLevel -> Bool)
-> (ErrorLevel -> ErrorLevel -> Bool) -> Eq ErrorLevel
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ErrorLevel -> ErrorLevel -> Bool
== :: ErrorLevel -> ErrorLevel -> Bool
$c/= :: ErrorLevel -> ErrorLevel -> Bool
/= :: ErrorLevel -> ErrorLevel -> Bool
Eq, Eq ErrorLevel
Eq ErrorLevel =>
(ErrorLevel -> ErrorLevel -> Ordering)
-> (ErrorLevel -> ErrorLevel -> Bool)
-> (ErrorLevel -> ErrorLevel -> Bool)
-> (ErrorLevel -> ErrorLevel -> Bool)
-> (ErrorLevel -> ErrorLevel -> Bool)
-> (ErrorLevel -> ErrorLevel -> ErrorLevel)
-> (ErrorLevel -> ErrorLevel -> ErrorLevel)
-> Ord ErrorLevel
ErrorLevel -> ErrorLevel -> Bool
ErrorLevel -> ErrorLevel -> Ordering
ErrorLevel -> ErrorLevel -> ErrorLevel
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
$ccompare :: ErrorLevel -> ErrorLevel -> Ordering
compare :: ErrorLevel -> ErrorLevel -> Ordering
$c< :: ErrorLevel -> ErrorLevel -> Bool
< :: ErrorLevel -> ErrorLevel -> Bool
$c<= :: ErrorLevel -> ErrorLevel -> Bool
<= :: ErrorLevel -> ErrorLevel -> Bool
$c> :: ErrorLevel -> ErrorLevel -> Bool
> :: ErrorLevel -> ErrorLevel -> Bool
$c>= :: ErrorLevel -> ErrorLevel -> Bool
>= :: ErrorLevel -> ErrorLevel -> Bool
$cmax :: ErrorLevel -> ErrorLevel -> ErrorLevel
max :: ErrorLevel -> ErrorLevel -> ErrorLevel
$cmin :: ErrorLevel -> ErrorLevel -> ErrorLevel
min :: ErrorLevel -> ErrorLevel -> ErrorLevel
Ord, ReadPrec [ErrorLevel]
ReadPrec ErrorLevel
Int -> ReadS ErrorLevel
ReadS [ErrorLevel]
(Int -> ReadS ErrorLevel)
-> ReadS [ErrorLevel]
-> ReadPrec ErrorLevel
-> ReadPrec [ErrorLevel]
-> Read ErrorLevel
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ErrorLevel
readsPrec :: Int -> ReadS ErrorLevel
$creadList :: ReadS [ErrorLevel]
readList :: ReadS [ErrorLevel]
$creadPrec :: ReadPrec ErrorLevel
readPrec :: ReadPrec ErrorLevel
$creadListPrec :: ReadPrec [ErrorLevel]
readListPrec :: ReadPrec [ErrorLevel]
Read, Int -> ErrorLevel -> ShowS
[ErrorLevel] -> ShowS
ErrorLevel -> PackageName
(Int -> ErrorLevel -> ShowS)
-> (ErrorLevel -> PackageName)
-> ([ErrorLevel] -> ShowS)
-> Show ErrorLevel
forall a.
(Int -> a -> ShowS)
-> (a -> PackageName) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ErrorLevel -> ShowS
showsPrec :: Int -> ErrorLevel -> ShowS
$cshow :: ErrorLevel -> PackageName
show :: ErrorLevel -> PackageName
$cshowList :: [ErrorLevel] -> ShowS
showList :: [ErrorLevel] -> ShowS
Show)
data CodeOptions = CodeOptions {
CodeOptions -> Bool
includePadding :: Bool
, CodeOptions -> Bool
link :: Bool
, CodeOptions -> ErrorLevel
errorLevel :: ErrorLevel
}
deriving (CodeOptions -> CodeOptions -> Bool
(CodeOptions -> CodeOptions -> Bool)
-> (CodeOptions -> CodeOptions -> Bool) -> Eq CodeOptions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CodeOptions -> CodeOptions -> Bool
== :: CodeOptions -> CodeOptions -> Bool
$c/= :: CodeOptions -> CodeOptions -> Bool
/= :: CodeOptions -> CodeOptions -> Bool
Eq, Int -> CodeOptions -> ShowS
[CodeOptions] -> ShowS
CodeOptions -> PackageName
(Int -> CodeOptions -> ShowS)
-> (CodeOptions -> PackageName)
-> ([CodeOptions] -> ShowS)
-> Show CodeOptions
forall a.
(Int -> a -> ShowS)
-> (a -> PackageName) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CodeOptions -> ShowS
showsPrec :: Int -> CodeOptions -> ShowS
$cshow :: CodeOptions -> PackageName
show :: CodeOptions -> PackageName
$cshowList :: [CodeOptions] -> ShowS
showList :: [CodeOptions] -> ShowS
Show)
defaultOptions :: CodeOptions
defaultOptions :: CodeOptions
defaultOptions = CodeOptions { includePadding :: Bool
includePadding = Bool
False, link :: Bool
link = Bool
True, errorLevel :: ErrorLevel
errorLevel = ErrorLevel
Medium }
draft :: LaTeXC l => l
draft :: forall l. LaTeXC l => l
draft = l
"draft"
final :: LaTeXC l => l
final :: forall l. LaTeXC l => l
final = l
"final"
qr :: LaTeXC l => CodeOptions -> Text -> l
qr :: forall l. LaTeXC l => CodeOptions -> Text -> l
qr CodeOptions
opt Text
payload = 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
"qrcode" [TeXArg
opts, LaTeX -> TeXArg
FixArg (LaTeX -> TeXArg) -> (Text -> LaTeX) -> Text -> TeXArg
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> LaTeX
forall l. LaTeXC l => Text -> l
raw (Text -> LaTeX) -> (Text -> Text) -> Text -> LaTeX
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
escape (Text -> TeXArg) -> Text -> TeXArg
forall a b. (a -> b) -> a -> b
$ Text
payload]
where
opts :: TeXArg
opts = [LaTeX] -> TeXArg
MOptArg [ if CodeOptions -> Bool
includePadding CodeOptions
opt then LaTeX
"padding" else LaTeX
"tight"
, if CodeOptions -> Bool
link CodeOptions
opt then LaTeX
"link" else LaTeX
"nolink"
, Text -> LaTeX
forall l. LaTeXC l => Text -> l
forall t l. (Texy t, LaTeXC l) => t -> l
texy (Text -> LaTeX) -> (CodeOptions -> Text) -> CodeOptions -> LaTeX
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text
"level=" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>) (Text -> Text) -> (CodeOptions -> Text) -> CodeOptions -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Text
T.singleton (Char -> Text) -> (CodeOptions -> Char) -> CodeOptions -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PackageName -> Char
forall a. HasCallStack => [a] -> a
head (PackageName -> Char)
-> (CodeOptions -> PackageName) -> CodeOptions -> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ErrorLevel -> PackageName
forall a. Show a => a -> PackageName
show (ErrorLevel -> PackageName)
-> (CodeOptions -> ErrorLevel) -> CodeOptions -> PackageName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CodeOptions -> ErrorLevel
errorLevel (CodeOptions -> LaTeX) -> CodeOptions -> LaTeX
forall a b. (a -> b) -> a -> b
$ CodeOptions
opt
]
escape :: Text -> Text
escape :: Text -> Text
escape = (Char -> Text) -> Text -> Text
T.concatMap Char -> Text
handleChar
where handleChar :: Char -> Text
handleChar Char
c | Char -> Bool
isSpecial Char
c = PackageName -> Text
T.pack [Char
'\\', Char
c]
| Bool
otherwise = Char -> Text
T.singleton Char
c
isSpecial :: Char -> Bool
isSpecial :: Char -> Bool
isSpecial Char
c = Char
c Char -> PackageName -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (PackageName
"#$&^_~% \\{}" :: String)