module Data.LocalStorage where
import Data.Text
import FFI
import Prelude
setLocalStorage :: Text -> Text -> Fay ()
setLocalStorage :: Text -> Text -> Fay ()
setLocalStorage = [Char] -> Text -> Text -> Fay ()
forall s a. IsString s => s -> a
ffi [Char]
"(function() { localStorage[%1] = %2; })()"
getLocalStorage :: Text -> Fay (Defined Text)
getLocalStorage :: Text -> Fay (Defined Text)
getLocalStorage = [Char] -> Text -> Fay (Defined Text)
forall s a. IsString s => s -> a
ffi [Char]
"localStorage[%1]"
removeLocalStorage :: Text -> Fay ()
removeLocalStorage :: Text -> Fay ()
removeLocalStorage = [Char] -> Text -> Fay ()
forall s a. IsString s => s -> a
ffi [Char]
"localStorage.removeItem(%1)"
hasLocalStorage :: Bool
hasLocalStorage :: Bool
hasLocalStorage = [Char] -> Bool
forall s a. IsString s => s -> a
ffi [Char]
"typeof(Storage) !== 'undefined'"