-----------------------------------------------------------------------------
-- |
-- Module      :  Miso.FFI.Storage
-- Copyright   :  (C) 2016-2018 David M. Johnson
-- License     :  BSD3-style (see the file LICENSE)
-- Maintainer  :  David M. Johnson <djohnson.m@gmail.com>
-- Stability   :  experimental
-- Portability :  non-portable
----------------------------------------------------------------------------
module Miso.FFI.Storage
  ( Storage
  , localStorage
  , sessionStorage
  , getItem
  , removeItem
  , setItem
  , length
  , clear
  ) where

import GHCJS.Types
import Prelude hiding (length)

import Language.Javascript.JSaddle ((!), (#), JSM, fromJSValUnchecked, jsg)
import Miso.String hiding (length)

newtype Storage = Storage JSVal

localStorage :: JSM Storage
localStorage :: JSM Storage
localStorage = JSVal -> Storage
Storage (JSVal -> Storage) -> JSM JSVal -> JSM Storage
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ([Char] -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg [Char]
"window" JSM JSVal -> [Char] -> JSM JSVal
forall this name.
(MakeObject this, ToJSString name) =>
this -> name -> JSM JSVal
! [Char]
"localStorage")

sessionStorage :: JSM Storage
sessionStorage :: JSM Storage
sessionStorage = JSVal -> Storage
Storage (JSVal -> Storage) -> JSM JSVal -> JSM Storage
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ([Char] -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg [Char]
"window" JSM JSVal -> [Char] -> JSM JSVal
forall this name.
(MakeObject this, ToJSString name) =>
this -> name -> JSM JSVal
! [Char]
"sessionStorage")

getItem :: Storage -> MisoString -> JSM JSVal
getItem :: Storage -> MisoString -> JSM JSVal
getItem (Storage JSVal
s) MisoString
key =
  JSVal
s JSVal -> [Char] -> [MisoString] -> JSM JSVal
forall this name args.
(MakeObject this, ToJSString name, MakeArgs args) =>
this -> name -> args -> JSM JSVal
# [Char]
"getItem" ([MisoString] -> JSM JSVal) -> [MisoString] -> JSM JSVal
forall a b. (a -> b) -> a -> b
$ [MisoString
key]

removeItem :: Storage -> MisoString -> JSM ()
removeItem :: Storage -> MisoString -> JSM ()
removeItem (Storage JSVal
s) MisoString
key = do
  JSVal
_ <- JSVal
s JSVal -> [Char] -> [MisoString] -> JSM JSVal
forall this name args.
(MakeObject this, ToJSString name, MakeArgs args) =>
this -> name -> args -> JSM JSVal
# [Char]
"removeItem" ([MisoString] -> JSM JSVal) -> [MisoString] -> JSM JSVal
forall a b. (a -> b) -> a -> b
$ [MisoString
key]
  () -> JSM ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()

setItem :: Storage -> MisoString -> MisoString -> JSM ()
setItem :: Storage -> MisoString -> MisoString -> JSM ()
setItem (Storage JSVal
s) MisoString
key MisoString
val = do
  JSVal
_ <- JSVal
s JSVal -> [Char] -> (MisoString, MisoString) -> JSM JSVal
forall this name args.
(MakeObject this, ToJSString name, MakeArgs args) =>
this -> name -> args -> JSM JSVal
# [Char]
"setItem" ((MisoString, MisoString) -> JSM JSVal)
-> (MisoString, MisoString) -> JSM JSVal
forall a b. (a -> b) -> a -> b
$ (MisoString
key, MisoString
val)
  () -> JSM ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()

length :: Storage -> JSM Int
length :: Storage -> JSM Int
length (Storage JSVal
s) = JSVal -> JSM Int
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked (JSVal -> JSM Int) -> JSM JSVal -> JSM Int
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< JSVal
s JSVal -> [Char] -> JSM JSVal
forall this name.
(MakeObject this, ToJSString name) =>
this -> name -> JSM JSVal
! [Char]
"length"

clear :: Storage -> JSM ()
clear :: Storage -> JSM ()
clear (Storage JSVal
s) = do
  JSVal
_ <- JSVal
s JSVal -> [Char] -> () -> JSM JSVal
forall this name args.
(MakeObject this, ToJSString name, MakeArgs args) =>
this -> name -> args -> JSM JSVal
# [Char]
"clear" (() -> JSM JSVal) -> () -> JSM JSVal
forall a b. (a -> b) -> a -> b
$ ()
  () -> JSM ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()