{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
module Codec.QRCode.Data.QRImage
( QRImage(..)
, toList
, toMatrix
) where
import Codec.QRCode.Base
import qualified Data.Vector.Unboxed as UV
import Codec.QRCode.Data.ErrorLevel
data QRImage
= QRImage
{ qrVersion :: Int
, qrErrorLevel :: ErrorLevel
, qrImageSize :: Int
, qrImageData :: UV.Vector Bool
}
toList
:: (IsList l, Item l ~ a)
=> a
-> a
-> QRImage
-> l
{-# INLINEABLE toList #-}
toList bl wh QRImage{..} =
fromListN
(qrImageSize * qrImageSize)
(map
(bool wh bl)
(UV.toList qrImageData)
)
toMatrix
:: (IsList l, Item l ~ k, IsList k, Item k ~ a)
=> a
-> a
-> QRImage
-> l
{-# INLINEABLE toMatrix #-}
toMatrix bl wh QRImage{..} =
fromListN
qrImageSize
(map
go
[0, qrImageSize - 1]
)
where
go ofs =
fromListN
qrImageSize
(map
(bool wh bl)
(UV.toList $ UV.take qrImageSize $ UV.drop (ofs * qrImageSize) qrImageData)
)