{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE DeriveGeneric #-}
module Codec.Xlsx.Types.Protection
( SheetProtection(..)
, fullSheetProtection
, noSheetProtection
, LegacyPassword
, legacyPassword
, sprLegacyPassword
, sprSheet
, sprObjects
, sprScenarios
, sprFormatCells
, sprFormatColumns
, sprFormatRows
, sprInsertColumns
, sprInsertRows
, sprInsertHyperlinks
, sprDeleteColumns
, sprDeleteRows
, sprSelectLockedCells
, sprSort
, sprAutoFilter
, sprPivotTables
, sprSelectUnlockedCells
) where
import GHC.Generics (Generic)
import Control.Arrow (first)
#ifdef USE_MICROLENS
import Lens.Micro.TH (makeLenses)
#else
import Control.Lens (makeLenses)
#endif
import Control.DeepSeq (NFData)
import Data.Bits
import Data.Char
import Data.Maybe (catMaybes)
import Data.Text (Text)
import qualified Data.Text as T
import Data.Text.Lazy (toStrict)
import Data.Text.Lazy.Builder (toLazyText)
import Data.Text.Lazy.Builder.Int (hexadecimal)
import Codec.Xlsx.Parser.Internal
import Codec.Xlsx.Writer.Internal
newtype LegacyPassword =
LegacyPassword Text
deriving (LegacyPassword -> LegacyPassword -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LegacyPassword -> LegacyPassword -> Bool
$c/= :: LegacyPassword -> LegacyPassword -> Bool
== :: LegacyPassword -> LegacyPassword -> Bool
$c== :: LegacyPassword -> LegacyPassword -> Bool
Eq, Int -> LegacyPassword -> ShowS
[LegacyPassword] -> ShowS
LegacyPassword -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LegacyPassword] -> ShowS
$cshowList :: [LegacyPassword] -> ShowS
show :: LegacyPassword -> String
$cshow :: LegacyPassword -> String
showsPrec :: Int -> LegacyPassword -> ShowS
$cshowsPrec :: Int -> LegacyPassword -> ShowS
Show, forall x. Rep LegacyPassword x -> LegacyPassword
forall x. LegacyPassword -> Rep LegacyPassword x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LegacyPassword x -> LegacyPassword
$cfrom :: forall x. LegacyPassword -> Rep LegacyPassword x
Generic)
instance NFData LegacyPassword
legacyPassword :: Text -> LegacyPassword
legacyPassword :: Text -> LegacyPassword
legacyPassword = Text -> LegacyPassword
LegacyPassword forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Text
hex forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {t :: * -> *}. Foldable t => t Int -> Int
legacyHash forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map Char -> Int
ord forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack
where
hex :: Int -> Text
hex = Text -> Text
toStrict forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> Text
toLazyText forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Integral a => a -> Builder
hexadecimal
legacyHash :: t Int -> Int
legacyHash t Int
bs =
forall {a}. (Bits a, Num a) => a -> a
mutHash (forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (\Int
b Int
hash -> Int
b forall a. Bits a => a -> a -> a
`xor` forall {a}. (Bits a, Num a) => a -> a
mutHash Int
hash) Int
0 t Int
bs) forall a. Bits a => a -> a -> a
`xor` (forall (t :: * -> *) a. Foldable t => t a -> Int
length t Int
bs) forall a. Bits a => a -> a -> a
`xor`
Int
0xCE4B
mutHash :: a -> a
mutHash a
ph = ((a
ph forall a. Bits a => a -> Int -> a
`shiftR` Int
14) forall a. Bits a => a -> a -> a
.&. a
1) forall a. Bits a => a -> a -> a
.|. ((a
ph forall a. Bits a => a -> Int -> a
`shiftL` Int
1) forall a. Bits a => a -> a -> a
.&. a
0x7fff)
data SheetProtection = SheetProtection
{ SheetProtection -> Maybe LegacyPassword
_sprLegacyPassword :: Maybe LegacyPassword
, SheetProtection -> Bool
_sprSheet :: Bool
, SheetProtection -> Bool
_sprAutoFilter :: Bool
, SheetProtection -> Bool
_sprDeleteColumns :: Bool
, SheetProtection -> Bool
_sprDeleteRows :: Bool
, SheetProtection -> Bool
_sprFormatCells :: Bool
, SheetProtection -> Bool
_sprFormatColumns :: Bool
, SheetProtection -> Bool
_sprFormatRows :: Bool
, SheetProtection -> Bool
_sprInsertColumns :: Bool
, SheetProtection -> Bool
_sprInsertHyperlinks :: Bool
, SheetProtection -> Bool
_sprInsertRows :: Bool
, SheetProtection -> Bool
_sprObjects :: Bool
, SheetProtection -> Bool
_sprPivotTables :: Bool
, SheetProtection -> Bool
_sprScenarios :: Bool
, SheetProtection -> Bool
_sprSelectLockedCells :: Bool
, SheetProtection -> Bool
_sprSelectUnlockedCells :: Bool
, SheetProtection -> Bool
_sprSort :: Bool
} deriving (SheetProtection -> SheetProtection -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SheetProtection -> SheetProtection -> Bool
$c/= :: SheetProtection -> SheetProtection -> Bool
== :: SheetProtection -> SheetProtection -> Bool
$c== :: SheetProtection -> SheetProtection -> Bool
Eq, Int -> SheetProtection -> ShowS
[SheetProtection] -> ShowS
SheetProtection -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SheetProtection] -> ShowS
$cshowList :: [SheetProtection] -> ShowS
show :: SheetProtection -> String
$cshow :: SheetProtection -> String
showsPrec :: Int -> SheetProtection -> ShowS
$cshowsPrec :: Int -> SheetProtection -> ShowS
Show, forall x. Rep SheetProtection x -> SheetProtection
forall x. SheetProtection -> Rep SheetProtection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SheetProtection x -> SheetProtection
$cfrom :: forall x. SheetProtection -> Rep SheetProtection x
Generic)
instance NFData SheetProtection
makeLenses ''SheetProtection
noSheetProtection :: SheetProtection
noSheetProtection :: SheetProtection
noSheetProtection =
SheetProtection
{ _sprLegacyPassword :: Maybe LegacyPassword
_sprLegacyPassword = forall a. Maybe a
Nothing
, _sprSheet :: Bool
_sprSheet = Bool
False
, _sprAutoFilter :: Bool
_sprAutoFilter = Bool
False
, _sprDeleteColumns :: Bool
_sprDeleteColumns = Bool
False
, _sprDeleteRows :: Bool
_sprDeleteRows = Bool
False
, _sprFormatCells :: Bool
_sprFormatCells = Bool
False
, _sprFormatColumns :: Bool
_sprFormatColumns = Bool
False
, _sprFormatRows :: Bool
_sprFormatRows = Bool
False
, _sprInsertColumns :: Bool
_sprInsertColumns = Bool
False
, _sprInsertHyperlinks :: Bool
_sprInsertHyperlinks = Bool
False
, _sprInsertRows :: Bool
_sprInsertRows = Bool
False
, _sprObjects :: Bool
_sprObjects = Bool
False
, _sprPivotTables :: Bool
_sprPivotTables = Bool
False
, _sprScenarios :: Bool
_sprScenarios = Bool
False
, _sprSelectLockedCells :: Bool
_sprSelectLockedCells = Bool
False
, _sprSelectUnlockedCells :: Bool
_sprSelectUnlockedCells = Bool
False
, _sprSort :: Bool
_sprSort = Bool
False
}
fullSheetProtection :: SheetProtection
fullSheetProtection :: SheetProtection
fullSheetProtection =
SheetProtection
{ _sprLegacyPassword :: Maybe LegacyPassword
_sprLegacyPassword = forall a. Maybe a
Nothing
, _sprSheet :: Bool
_sprSheet = Bool
True
, _sprAutoFilter :: Bool
_sprAutoFilter = Bool
True
, _sprDeleteColumns :: Bool
_sprDeleteColumns = Bool
True
, _sprDeleteRows :: Bool
_sprDeleteRows = Bool
True
, _sprFormatCells :: Bool
_sprFormatCells = Bool
True
, _sprFormatColumns :: Bool
_sprFormatColumns = Bool
True
, _sprFormatRows :: Bool
_sprFormatRows = Bool
True
, _sprInsertColumns :: Bool
_sprInsertColumns = Bool
True
, _sprInsertHyperlinks :: Bool
_sprInsertHyperlinks = Bool
True
, _sprInsertRows :: Bool
_sprInsertRows = Bool
True
, _sprObjects :: Bool
_sprObjects = Bool
True
, _sprPivotTables :: Bool
_sprPivotTables = Bool
True
, _sprScenarios :: Bool
_sprScenarios = Bool
True
, _sprSelectLockedCells :: Bool
_sprSelectLockedCells = Bool
True
, _sprSelectUnlockedCells :: Bool
_sprSelectUnlockedCells = Bool
True
, _sprSort :: Bool
_sprSort = Bool
True
}
instance FromCursor SheetProtection where
fromCursor :: Cursor -> [SheetProtection]
fromCursor Cursor
cur = do
Maybe LegacyPassword
_sprLegacyPassword <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"password" Cursor
cur
Bool
_sprSheet <- forall a. FromAttrVal a => Name -> a -> Cursor -> [a]
fromAttributeDef Name
"sheet" Bool
False Cursor
cur
Bool
_sprAutoFilter <- forall a. FromAttrVal a => Name -> a -> Cursor -> [a]
fromAttributeDef Name
"autoFilter" Bool
True Cursor
cur
Bool
_sprDeleteColumns <- forall a. FromAttrVal a => Name -> a -> Cursor -> [a]
fromAttributeDef Name
"deleteColumns" Bool
True Cursor
cur
Bool
_sprDeleteRows <- forall a. FromAttrVal a => Name -> a -> Cursor -> [a]
fromAttributeDef Name
"deleteRows" Bool
True Cursor
cur
Bool
_sprFormatCells <- forall a. FromAttrVal a => Name -> a -> Cursor -> [a]
fromAttributeDef Name
"formatCells" Bool
True Cursor
cur
Bool
_sprFormatColumns <- forall a. FromAttrVal a => Name -> a -> Cursor -> [a]
fromAttributeDef Name
"formatColumns" Bool
True Cursor
cur
Bool
_sprFormatRows <- forall a. FromAttrVal a => Name -> a -> Cursor -> [a]
fromAttributeDef Name
"formatRows" Bool
True Cursor
cur
Bool
_sprInsertColumns <- forall a. FromAttrVal a => Name -> a -> Cursor -> [a]
fromAttributeDef Name
"insertColumns" Bool
True Cursor
cur
Bool
_sprInsertHyperlinks <- forall a. FromAttrVal a => Name -> a -> Cursor -> [a]
fromAttributeDef Name
"insertHyperlinks" Bool
True Cursor
cur
Bool
_sprInsertRows <- forall a. FromAttrVal a => Name -> a -> Cursor -> [a]
fromAttributeDef Name
"insertRows" Bool
True Cursor
cur
Bool
_sprObjects <- forall a. FromAttrVal a => Name -> a -> Cursor -> [a]
fromAttributeDef Name
"objects" Bool
False Cursor
cur
Bool
_sprPivotTables <- forall a. FromAttrVal a => Name -> a -> Cursor -> [a]
fromAttributeDef Name
"pivotTables" Bool
True Cursor
cur
Bool
_sprScenarios <- forall a. FromAttrVal a => Name -> a -> Cursor -> [a]
fromAttributeDef Name
"scenarios" Bool
False Cursor
cur
Bool
_sprSelectLockedCells <- forall a. FromAttrVal a => Name -> a -> Cursor -> [a]
fromAttributeDef Name
"selectLockedCells" Bool
False Cursor
cur
Bool
_sprSelectUnlockedCells <- forall a. FromAttrVal a => Name -> a -> Cursor -> [a]
fromAttributeDef Name
"selectUnlockedCells" Bool
False Cursor
cur
Bool
_sprSort <- forall a. FromAttrVal a => Name -> a -> Cursor -> [a]
fromAttributeDef Name
"sort" Bool
True Cursor
cur
forall (m :: * -> *) a. Monad m => a -> m a
return SheetProtection {Bool
Maybe LegacyPassword
_sprSort :: Bool
_sprSelectUnlockedCells :: Bool
_sprSelectLockedCells :: Bool
_sprScenarios :: Bool
_sprPivotTables :: Bool
_sprObjects :: Bool
_sprInsertRows :: Bool
_sprInsertHyperlinks :: Bool
_sprInsertColumns :: Bool
_sprFormatRows :: Bool
_sprFormatColumns :: Bool
_sprFormatCells :: Bool
_sprDeleteRows :: Bool
_sprDeleteColumns :: Bool
_sprAutoFilter :: Bool
_sprSheet :: Bool
_sprLegacyPassword :: Maybe LegacyPassword
_sprSort :: Bool
_sprSelectUnlockedCells :: Bool
_sprSelectLockedCells :: Bool
_sprScenarios :: Bool
_sprPivotTables :: Bool
_sprObjects :: Bool
_sprInsertRows :: Bool
_sprInsertHyperlinks :: Bool
_sprInsertColumns :: Bool
_sprFormatRows :: Bool
_sprFormatColumns :: Bool
_sprFormatCells :: Bool
_sprDeleteRows :: Bool
_sprDeleteColumns :: Bool
_sprAutoFilter :: Bool
_sprSheet :: Bool
_sprLegacyPassword :: Maybe LegacyPassword
..}
instance FromXenoNode SheetProtection where
fromXenoNode :: Node -> Either Text SheetProtection
fromXenoNode Node
root =
forall a. Node -> AttrParser a -> Either Text a
parseAttributes Node
root forall a b. (a -> b) -> a -> b
$ do
Maybe LegacyPassword
_sprLegacyPassword <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"password"
Bool
_sprSheet <- forall a. FromAttrBs a => ByteString -> a -> AttrParser a
fromAttrDef ByteString
"sheet" Bool
False
Bool
_sprAutoFilter <- forall a. FromAttrBs a => ByteString -> a -> AttrParser a
fromAttrDef ByteString
"autoFilter" Bool
True
Bool
_sprDeleteColumns <- forall a. FromAttrBs a => ByteString -> a -> AttrParser a
fromAttrDef ByteString
"deleteColumns" Bool
True
Bool
_sprDeleteRows <- forall a. FromAttrBs a => ByteString -> a -> AttrParser a
fromAttrDef ByteString
"deleteRows" Bool
True
Bool
_sprFormatCells <- forall a. FromAttrBs a => ByteString -> a -> AttrParser a
fromAttrDef ByteString
"formatCells" Bool
True
Bool
_sprFormatColumns <- forall a. FromAttrBs a => ByteString -> a -> AttrParser a
fromAttrDef ByteString
"formatColumns" Bool
True
Bool
_sprFormatRows <- forall a. FromAttrBs a => ByteString -> a -> AttrParser a
fromAttrDef ByteString
"formatRows" Bool
True
Bool
_sprInsertColumns <- forall a. FromAttrBs a => ByteString -> a -> AttrParser a
fromAttrDef ByteString
"insertColumns" Bool
True
Bool
_sprInsertHyperlinks <- forall a. FromAttrBs a => ByteString -> a -> AttrParser a
fromAttrDef ByteString
"insertHyperlinks" Bool
True
Bool
_sprInsertRows <- forall a. FromAttrBs a => ByteString -> a -> AttrParser a
fromAttrDef ByteString
"insertRows" Bool
True
Bool
_sprObjects <- forall a. FromAttrBs a => ByteString -> a -> AttrParser a
fromAttrDef ByteString
"objects" Bool
False
Bool
_sprPivotTables <- forall a. FromAttrBs a => ByteString -> a -> AttrParser a
fromAttrDef ByteString
"pivotTables" Bool
True
Bool
_sprScenarios <- forall a. FromAttrBs a => ByteString -> a -> AttrParser a
fromAttrDef ByteString
"scenarios" Bool
False
Bool
_sprSelectLockedCells <- forall a. FromAttrBs a => ByteString -> a -> AttrParser a
fromAttrDef ByteString
"selectLockedCells" Bool
False
Bool
_sprSelectUnlockedCells <- forall a. FromAttrBs a => ByteString -> a -> AttrParser a
fromAttrDef ByteString
"selectUnlockedCells" Bool
False
Bool
_sprSort <- forall a. FromAttrBs a => ByteString -> a -> AttrParser a
fromAttrDef ByteString
"sort" Bool
True
forall (m :: * -> *) a. Monad m => a -> m a
return SheetProtection {Bool
Maybe LegacyPassword
_sprSort :: Bool
_sprSelectUnlockedCells :: Bool
_sprSelectLockedCells :: Bool
_sprScenarios :: Bool
_sprPivotTables :: Bool
_sprObjects :: Bool
_sprInsertRows :: Bool
_sprInsertHyperlinks :: Bool
_sprInsertColumns :: Bool
_sprFormatRows :: Bool
_sprFormatColumns :: Bool
_sprFormatCells :: Bool
_sprDeleteRows :: Bool
_sprDeleteColumns :: Bool
_sprAutoFilter :: Bool
_sprSheet :: Bool
_sprLegacyPassword :: Maybe LegacyPassword
_sprSort :: Bool
_sprSelectUnlockedCells :: Bool
_sprSelectLockedCells :: Bool
_sprScenarios :: Bool
_sprPivotTables :: Bool
_sprObjects :: Bool
_sprInsertRows :: Bool
_sprInsertHyperlinks :: Bool
_sprInsertColumns :: Bool
_sprFormatRows :: Bool
_sprFormatColumns :: Bool
_sprFormatCells :: Bool
_sprDeleteRows :: Bool
_sprDeleteColumns :: Bool
_sprAutoFilter :: Bool
_sprSheet :: Bool
_sprLegacyPassword :: Maybe LegacyPassword
..}
instance FromAttrVal LegacyPassword where
fromAttrVal :: Reader LegacyPassword
fromAttrVal = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first Text -> LegacyPassword
LegacyPassword) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. FromAttrVal a => Reader a
fromAttrVal
instance FromAttrBs LegacyPassword where
fromAttrBs :: ByteString -> Either Text LegacyPassword
fromAttrBs = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> LegacyPassword
LegacyPassword forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. FromAttrBs a => ByteString -> Either Text a
fromAttrBs
instance ToElement SheetProtection where
toElement :: Name -> SheetProtection -> Element
toElement Name
nm SheetProtection {Bool
Maybe LegacyPassword
_sprSort :: Bool
_sprSelectUnlockedCells :: Bool
_sprSelectLockedCells :: Bool
_sprScenarios :: Bool
_sprPivotTables :: Bool
_sprObjects :: Bool
_sprInsertRows :: Bool
_sprInsertHyperlinks :: Bool
_sprInsertColumns :: Bool
_sprFormatRows :: Bool
_sprFormatColumns :: Bool
_sprFormatCells :: Bool
_sprDeleteRows :: Bool
_sprDeleteColumns :: Bool
_sprAutoFilter :: Bool
_sprSheet :: Bool
_sprLegacyPassword :: Maybe LegacyPassword
_sprSort :: SheetProtection -> Bool
_sprSelectUnlockedCells :: SheetProtection -> Bool
_sprSelectLockedCells :: SheetProtection -> Bool
_sprScenarios :: SheetProtection -> Bool
_sprPivotTables :: SheetProtection -> Bool
_sprObjects :: SheetProtection -> Bool
_sprInsertRows :: SheetProtection -> Bool
_sprInsertHyperlinks :: SheetProtection -> Bool
_sprInsertColumns :: SheetProtection -> Bool
_sprFormatRows :: SheetProtection -> Bool
_sprFormatColumns :: SheetProtection -> Bool
_sprFormatCells :: SheetProtection -> Bool
_sprDeleteRows :: SheetProtection -> Bool
_sprDeleteColumns :: SheetProtection -> Bool
_sprAutoFilter :: SheetProtection -> Bool
_sprSheet :: SheetProtection -> Bool
_sprLegacyPassword :: SheetProtection -> Maybe LegacyPassword
..} =
Name -> [(Name, Text)] -> Element
leafElement Name
nm forall a b. (a -> b) -> a -> b
$
forall a. [Maybe a] -> [a]
catMaybes
[ Name
"password" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe LegacyPassword
_sprLegacyPassword
, Name
"sheet" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Bool -> Maybe Bool
justTrue Bool
_sprSheet
, Name
"autoFilter" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Bool -> Maybe Bool
justFalse Bool
_sprAutoFilter
, Name
"deleteColumns" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Bool -> Maybe Bool
justFalse Bool
_sprDeleteColumns
, Name
"deleteRows" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Bool -> Maybe Bool
justFalse Bool
_sprDeleteRows
, Name
"formatCells" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Bool -> Maybe Bool
justFalse Bool
_sprFormatCells
, Name
"formatColumns" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Bool -> Maybe Bool
justFalse Bool
_sprFormatColumns
, Name
"formatRows" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Bool -> Maybe Bool
justFalse Bool
_sprFormatRows
, Name
"insertColumns" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Bool -> Maybe Bool
justFalse Bool
_sprInsertColumns
, Name
"insertHyperlinks" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Bool -> Maybe Bool
justFalse Bool
_sprInsertHyperlinks
, Name
"insertRows" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Bool -> Maybe Bool
justFalse Bool
_sprInsertRows
, Name
"objects" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Bool -> Maybe Bool
justTrue Bool
_sprObjects
, Name
"pivotTables" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Bool -> Maybe Bool
justFalse Bool
_sprPivotTables
, Name
"scenarios" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Bool -> Maybe Bool
justTrue Bool
_sprScenarios
, Name
"selectLockedCells" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Bool -> Maybe Bool
justTrue Bool
_sprSelectLockedCells
, Name
"selectUnlockedCells" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Bool -> Maybe Bool
justTrue Bool
_sprSelectUnlockedCells
, Name
"sort" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Bool -> Maybe Bool
justFalse Bool
_sprSort
]
instance ToAttrVal LegacyPassword where
toAttrVal :: LegacyPassword -> Text
toAttrVal (LegacyPassword Text
hash) = Text
hash