rename KeyPath -> IDBKey and fix IDBObjectStore type signature

This commit is contained in:
KtorZ 2017-06-29 11:21:30 +02:00
parent 757377cb2b
commit 5454bfa567
No known key found for this signature in database
GPG Key ID: 3F72E8BC2894C015
6 changed files with 214 additions and 170 deletions

View File

@ -47,41 +47,3 @@ exports._showIDBTransaction = function _showIDBTransaction(tx) {
', mode: ' + tx.mode +
' })';
};
exports._dateTimeToForeign = function _dateTimeToForeign(y, m, d, h, mi, s, ms) {
return new Date(y, m, d, h, mi, s, ms);
};
exports._readDateTime = function _readDateTime(parse, right, left, date) {
if (Object.getPrototypeOf(date) !== Date.prototype) {
return left(typeof date);
}
const y = date.getFullYear();
const m = date.getMonth() + 1;
const d = date.getDate();
const h = date.getHours();
const mi = date.getMinutes();
const s = date.getSeconds();
const ms = date.getMilliseconds();
const mdate = parse(y)(m)(d)(h)(mi)(s)(ms);
if (mdate == null) {
return left(typeof date); // TODO Could return better error
}
return right(mdate);
};
exports._unsafeReadDateTime = function _unsafeReadDateTime(parse, date) {
const y = date.getFullYear();
const m = date.getMonth() + 1;
const d = date.getDate();
const h = date.getHours();
const mi = date.getMinutes();
const s = date.getSeconds();
const ms = date.getMilliseconds();
return parse(y)(m)(d)(h)(mi)(s)(ms);
};

View File

@ -1,29 +1,36 @@
module Database.IndexedDB.Core where
module Database.IndexedDB.Core
( INDEXED_DB
, IDBCursorSource(..)
, IDBDatabase
, IDBIndex
, IDBKeyCursor
, IDBKeyRange
, IDBObjectStore
, IDBTransaction
, IDBTransactionMode(..)
, IDBValueCursor
, module Database.IndexedDB.IDBCursorDirection
, module Database.IndexedDB.IDBKey
) where
import Prelude
import Control.Alt ((<|>))
import Control.Monad.Aff (Aff)
import Control.Monad.Eff (kind Effect, Eff)
import Control.Monad.Eff.Exception (EXCEPTION)
import Control.Monad.Except (ExceptT(..), runExceptT)
import Data.Date as Date
import Data.DateTime as DateTime
import Data.DateTime (DateTime(..), Date(..), Time(..))
import Data.Either (Either(..), isRight)
import Data.Enum (fromEnum, toEnum)
import Data.Foreign as Foreign
import Data.Foreign (Foreign, F)
import Data.Function.Uncurried as Fn
import Data.Function.Uncurried (Fn2, Fn4, Fn7)
import Data.Identity (Identity(..))
import Data.List.NonEmpty (NonEmptyList(..))
import Data.List.Types (List(..))
import Data.Maybe (Maybe)
import Data.NonEmpty (NonEmpty(..))
import Data.Nullable (Nullable, toNullable)
import Data.Time as Time
import Data.Traversable (traverse)
import Database.IndexedDB.IDBCursorDirection
import Database.IndexedDB.IDBKey
data IDBTransactionMode = ReadOnly | ReadWrite | VersionChange
data IDBCursorSource = IDBObjectStore IDBObjectStore | IDBIndex IDBIndex
foreign import data INDEXED_DB :: Effect
@ -32,120 +39,34 @@ foreign import data INDEXED_DB :: Effect
foreign import data IDBDatabase :: Type
foreign import _showIDBDatabase :: IDBDatabase -> String
instance showIDBDatabase :: Show IDBDatabase where
show = _showIDBDatabase
foreign import data IDBIndex :: Type
foreign import data IDBKeyCursor :: Type
foreign import data IDBKeyRange :: Type
foreign import data IDBObjectStore :: Type
foreign import data IDBTransaction :: Type
foreign import data IDBValueCursor :: Type
foreign import _showIDBDatabase :: IDBDatabase -> String
instance showIDBDatabase :: Show IDBDatabase where
show = _showIDBDatabase
foreign import _showIDBObjectStore :: IDBObjectStore -> String
instance showIDBObjectStore :: Show IDBObjectStore where
show = _showIDBObjectStore
foreign import data IDBTransaction :: Type
foreign import _showIDBTransaction :: IDBTransaction -> String
instance showIDBTransaction :: Show IDBTransaction where
show = _showIDBTransaction
data IDBTransactionMode = ReadOnly | ReadWrite | VersionChange
data IDBCursorDirection = Next | NextUnique | Prev | PrevUnique
foreign import data IDBKeyRange :: Type
foreign import data IDBCursorWithValue :: Type
foreign import data IDBKeyCursor :: Type
foreign import data IDBIndex :: Type
newtype KeyPath = KeyPath Foreign
instance showIDBCursorDirection :: Show IDBCursorDirection where
show Next = "next"
show NextUnique = "nextunique"
show Prev = "prev"
show PrevUnique = "prevunique"
instance eqKeyPath :: Eq KeyPath where
eq a b = (runExceptT >>> runIdentity >>> isRight) $
eq <$> ((fromKeyPath a) :: F Int) <*> fromKeyPath b
<|>
eq <$> ((fromKeyPath a) :: F String) <*> fromKeyPath b
<|>
eq <$> ((fromKeyPath a) :: F DateTime) <*> fromKeyPath b
where
runIdentity :: forall a. Identity a -> a
runIdentity (Identity a) = a
class Index a where
toKeyPath :: a -> KeyPath
fromKeyPath :: KeyPath -> F a
unsafeFromKeyPath :: KeyPath -> a
instance indexInt :: Index Int where
toKeyPath = Foreign.toForeign >>> KeyPath
fromKeyPath (KeyPath f) = Foreign.readInt f
unsafeFromKeyPath (KeyPath f) = Foreign.unsafeFromForeign f
instance indexString :: Index String where
toKeyPath = Foreign.toForeign >>> KeyPath
fromKeyPath (KeyPath f) = Foreign.readString f
unsafeFromKeyPath (KeyPath f) = Foreign.unsafeFromForeign f
instance indexDate :: Index DateTime where
toKeyPath (DateTime d t) = KeyPath $ Fn.runFn7 _dateTimeToForeign
(fromEnum $ Date.year d)
(fromEnum $ Date.month d)
(fromEnum $ Date.day d)
(fromEnum $ Time.hour t)
(fromEnum $ Time.minute t)
(fromEnum $ Time.second t)
(fromEnum $ Time.millisecond t)
fromKeyPath (KeyPath f) = Fn.runFn4 _readDateTime dateTime dateTimeF dateTimeE f
unsafeFromKeyPath (KeyPath f) = Fn.runFn2 _unsafeReadDateTime dateTime f
instance indexArray :: Index a => Index (Array a) where
toKeyPath = Foreign.toForeign >>> KeyPath
fromKeyPath (KeyPath f) = Foreign.readArray f >>= traverse (KeyPath >>> fromKeyPath)
unsafeFromKeyPath (KeyPath f) = map unsafeFromKeyPath (Foreign.unsafeFromForeign f)
foreign import _dateTimeToForeign :: Fn7 Int Int Int Int Int Int Int Foreign
foreign import _readDateTime :: Fn4 (Int -> Int -> Int -> Int -> Int -> Int -> Int -> Nullable DateTime) (DateTime -> F DateTime) (String -> F DateTime) Foreign (F DateTime)
foreign import _unsafeReadDateTime :: Fn2 (Int -> Int -> Int -> Int -> Int -> Int -> Int -> Nullable DateTime) Foreign DateTime
dateTime :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> Nullable DateTime
dateTime y m d h mi s ms =
toNullable $ DateTime
<$> (Date.canonicalDate <$> toEnum y <*> toEnum m <*> toEnum d)
<*> (Time <$> toEnum h <*> toEnum mi <*> toEnum s <*> toEnum ms)
dateTimeF :: DateTime -> F DateTime
dateTimeF =
Right >>> Identity >>> ExceptT
dateTimeE :: String -> F DateTime
dateTimeE =
Foreign.TypeMismatch "Date" >>> flip NonEmpty Nil >>> NonEmptyList >>> Left >>> Identity >>> ExceptT

View File

@ -0,0 +1,27 @@
module Database.IndexedDB.IDBCursorDirection where
import Prelude (class Show)
import Data.Maybe (Maybe(..))
data IDBCursorDirection = Next | NextUnique | Prev | PrevUnique
instance showIDBCursorDirection :: Show IDBCursorDirection where
show x =
case x of
Next -> "next"
NextUnique -> "nextunique"
Prev -> "prev"
PrevUnique -> "prevunique"
fromString :: String -> Maybe IDBCursorDirection
fromString s =
case s of
"next" -> Just Next
"nextunique" -> Just NextUnique
"prev" -> Just Prev
"prevunique" -> Just PrevUnique
_ -> Nothing

View File

@ -0,0 +1,37 @@
exports._dateTimeToForeign = function _dateTimeToForeign(y, m, d, h, mi, s, ms) {
return new Date(y, m, d, h, mi, s, ms);
};
exports._readDateTime = function _readDateTime(parse, right, left, date) {
if (Object.getPrototypeOf(date) !== Date.prototype) {
return left(typeof date);
}
const y = date.getFullYear();
const m = date.getMonth() + 1;
const d = date.getDate();
const h = date.getHours();
const mi = date.getMinutes();
const s = date.getSeconds();
const ms = date.getMilliseconds();
const mdate = parse(y)(m)(d)(h)(mi)(s)(ms);
if (mdate == null) {
return left(typeof date); // TODO Could return better error
}
return right(mdate);
};
exports._unsafeReadDateTime = function _unsafeReadDateTime(parse, date) {
const y = date.getFullYear();
const m = date.getMonth() + 1;
const d = date.getDate();
const h = date.getHours();
const mi = date.getMinutes();
const s = date.getSeconds();
const ms = date.getMilliseconds();
return parse(y)(m)(d)(h)(mi)(s)(ms);
};

View File

@ -0,0 +1,97 @@
module Database.IndexedDB.IDBKey
( IDBKey
, class IsIDBKey, toIDBKey , fromIDBKey , unsafeFromIDBKey
) where
import Prelude
import Control.Alt ((<|>))
import Control.Monad.Except (ExceptT(..), runExceptT)
import Data.Date as Date
import Data.DateTime (DateTime(..), Time(..))
import Data.Enum (fromEnum, toEnum)
import Data.Foreign as Foreign
import Data.Foreign (Foreign, F)
import Data.Function.Uncurried as Fn
import Data.Function.Uncurried (Fn2, Fn4, Fn7)
import Data.List.NonEmpty (NonEmptyList(..))
import Data.List.Types (List(..))
import Data.NonEmpty (NonEmpty(..))
import Data.Either (Either(..), isRight)
import Data.Identity (Identity(..))
import Data.Nullable (Nullable, toNullable)
import Data.Time as Time
import Data.Traversable (traverse)
newtype IDBKey = IDBKey Foreign
class IsIDBKey a where
toIDBKey :: a -> IDBKey
fromIDBKey :: IDBKey -> F a
unsafeFromIDBKey :: IDBKey -> a
instance eqIDBKey :: Eq IDBKey where
eq a b = (runExceptT >>> runIdentity >>> isRight) $
eq <$> ((fromIDBKey a) :: F Int) <*> fromIDBKey b
<|>
eq <$> ((fromIDBKey a) :: F String) <*> fromIDBKey b
<|>
eq <$> ((fromIDBKey a) :: F DateTime) <*> fromIDBKey b
where
runIdentity :: forall a. Identity a -> a
runIdentity (Identity x) = x
instance isIDBKeyInt :: IsIDBKey Int where
toIDBKey = Foreign.toForeign >>> IDBKey
fromIDBKey (IDBKey f) = Foreign.readInt f
unsafeFromIDBKey (IDBKey f) = Foreign.unsafeFromForeign f
instance isIDBKeyString :: IsIDBKey String where
toIDBKey = Foreign.toForeign >>> IDBKey
fromIDBKey (IDBKey f) = Foreign.readString f
unsafeFromIDBKey (IDBKey f) = Foreign.unsafeFromForeign f
instance isIDBKeyDate :: IsIDBKey DateTime where
toIDBKey (DateTime d t) = IDBKey $ Fn.runFn7 _dateTimeToForeign
(fromEnum $ Date.year d)
(fromEnum $ Date.month d)
(fromEnum $ Date.day d)
(fromEnum $ Time.hour t)
(fromEnum $ Time.minute t)
(fromEnum $ Time.second t)
(fromEnum $ Time.millisecond t)
fromIDBKey (IDBKey f) = Fn.runFn4 _readDateTime dateTime dateTimeF dateTimeE f
unsafeFromIDBKey (IDBKey f) = Fn.runFn2 _unsafeReadDateTime dateTime f
instance isIDBKeyArray :: IsIDBKey a => IsIDBKey (Array a) where
toIDBKey = Foreign.toForeign >>> IDBKey
fromIDBKey (IDBKey f) = Foreign.readArray f >>= traverse (IDBKey >>> fromIDBKey)
unsafeFromIDBKey (IDBKey f) = map unsafeFromIDBKey (Foreign.unsafeFromForeign f)
foreign import _dateTimeToForeign :: Fn7 Int Int Int Int Int Int Int Foreign
foreign import _readDateTime :: Fn4 (Int -> Int -> Int -> Int -> Int -> Int -> Int -> Nullable DateTime) (DateTime -> F DateTime) (String -> F DateTime) Foreign (F DateTime)
foreign import _unsafeReadDateTime :: Fn2 (Int -> Int -> Int -> Int -> Int -> Int -> Int -> Nullable DateTime) Foreign DateTime
dateTime :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> Nullable DateTime
dateTime y m d h mi s ms =
toNullable $ DateTime
<$> (Date.canonicalDate <$> toEnum y <*> toEnum m <*> toEnum d)
<*> (Time <$> toEnum h <*> toEnum mi <*> toEnum s <*> toEnum ms)
dateTimeF :: DateTime -> F DateTime
dateTimeF =
Right >>> Identity >>> ExceptT
dateTimeE :: String -> F DateTime
dateTimeE =
Foreign.TypeMismatch "Date" >>> flip NonEmpty Nil >>> NonEmptyList >>> Left >>> Identity >>> ExceptT

View File

@ -31,8 +31,8 @@ import Data.Nullable (Nullable, toMaybe, toNullable)
import Database.IndexedDB.Core
foreign import _add :: forall value eff. Fn3 IDBObjectStore value (Nullable KeyPath) (Aff (idb :: INDEXED_DB, exception :: EXCEPTION | eff) KeyPath)
add :: forall value eff. IDBObjectStore -> value -> Maybe KeyPath -> Aff (idb :: INDEXED_DB, exception :: EXCEPTION | eff) KeyPath
foreign import _add :: forall value eff. Fn3 IDBObjectStore value (Nullable IDBKey) (Aff (idb :: INDEXED_DB, exception :: EXCEPTION | eff) IDBKey)
add :: forall value eff. IDBObjectStore -> value -> Maybe IDBKey -> Aff (idb :: INDEXED_DB, exception :: EXCEPTION | eff) IDBKey
add store value mkey =
Fn.runFn3 _add store value (toNullable mkey)
@ -49,8 +49,8 @@ count store range =
Fn.runFn2 _count store (toNullable range)
foreign import _createIndex :: forall eff. Fn4 IDBObjectStore String (Array KeyPath) { unique :: Boolean, multiEntry :: Boolean } (Eff (idb :: INDEXED_DB, exception :: EXCEPTION) IDBIndex)
createIndex :: forall eff. IDBObjectStore -> String -> (Array KeyPath) -> { unique :: Boolean, multiEntry :: Boolean } -> Eff (idb :: INDEXED_DB, exception :: EXCEPTION) IDBIndex
foreign import _createIndex :: forall eff. Fn4 IDBObjectStore String (Array String) { unique :: Boolean, multiEntry :: Boolean } (Eff (idb :: INDEXED_DB, exception :: EXCEPTION) IDBIndex)
createIndex :: forall eff. IDBObjectStore -> String -> (Array String) -> { unique :: Boolean, multiEntry :: Boolean } -> Eff (idb :: INDEXED_DB, exception :: EXCEPTION) IDBIndex
createIndex store name path params =
Fn.runFn4 _createIndex store name path params
@ -73,20 +73,20 @@ get store range =
toMaybe <$> Fn.runFn2 _get store (toNullable range)
foreign import _getKey :: forall eff. Fn2 IDBObjectStore (Nullable IDBKeyRange) (Aff (idb :: INDEXED_DB, exception :: EXCEPTION | eff) (Nullable KeyPath))
getKey :: forall eff. IDBObjectStore -> Maybe IDBKeyRange -> Aff (idb :: INDEXED_DB, exception :: EXCEPTION | eff) (Maybe KeyPath)
foreign import _getKey :: forall eff. Fn2 IDBObjectStore (Nullable IDBKeyRange) (Aff (idb :: INDEXED_DB, exception :: EXCEPTION | eff) (Nullable IDBKey))
getKey :: forall eff. IDBObjectStore -> Maybe IDBKeyRange -> Aff (idb :: INDEXED_DB, exception :: EXCEPTION | eff) (Maybe IDBKey)
getKey store range =
toMaybe <$> Fn.runFn2 _getKey store (toNullable range)
foreign import _getAllKeys :: forall eff. Fn3 IDBObjectStore (Nullable IDBKeyRange) (Nullable Int) (Aff (idb :: INDEXED_DB, exception :: EXCEPTION | eff) (Array KeyPath))
getAllKeys :: forall eff. IDBObjectStore -> Maybe IDBKeyRange -> Maybe Int -> Aff (idb :: INDEXED_DB, exception :: EXCEPTION | eff) (Array KeyPath)
foreign import _getAllKeys :: forall eff. Fn3 IDBObjectStore (Nullable IDBKeyRange) (Nullable Int) (Aff (idb :: INDEXED_DB, exception :: EXCEPTION | eff) (Array IDBKey))
getAllKeys :: forall eff. IDBObjectStore -> Maybe IDBKeyRange -> Maybe Int -> Aff (idb :: INDEXED_DB, exception :: EXCEPTION | eff) (Array IDBKey)
getAllKeys store range count =
Fn.runFn3 _getAllKeys store (toNullable range) (toNullable count)
foreign import _openCursor :: forall eff. Fn3 IDBObjectStore (Nullable IDBKeyRange) (Nullable IDBCursorDirection) (Aff (idb :: INDEXED_DB, exception :: EXCEPTION | eff) IDBCursorWithValue)
openCursor :: forall eff. IDBObjectStore -> Maybe IDBKeyRange -> Maybe IDBCursorDirection -> Aff (idb :: INDEXED_DB, exception :: EXCEPTION | eff) IDBCursorWithValue
foreign import _openCursor :: forall eff. Fn3 IDBObjectStore (Nullable IDBKeyRange) (Nullable IDBCursorDirection) (Aff (idb :: INDEXED_DB, exception :: EXCEPTION | eff) IDBValueCursor)
openCursor :: forall eff. IDBObjectStore -> Maybe IDBKeyRange -> Maybe IDBCursorDirection -> Aff (idb :: INDEXED_DB, exception :: EXCEPTION | eff) IDBValueCursor
openCursor store range dir =
Fn.runFn3 _openCursor store (toNullable range) (toNullable dir)
@ -112,7 +112,7 @@ foreign import keyPath :: IDBObjectStore -> Array String
foreign import name :: IDBObjectStore -> String
foreign import _put :: forall value eff. Fn3 IDBObjectStore value (Nullable KeyPath) (Aff (idb :: INDEXED_DB, exception :: EXCEPTION | eff) KeyPath)
put :: forall value eff. IDBObjectStore -> value -> Maybe KeyPath -> Aff (idb :: INDEXED_DB, exception :: EXCEPTION | eff) KeyPath
foreign import _put :: forall value eff. Fn3 IDBObjectStore value (Nullable IDBKey) (Aff (idb :: INDEXED_DB, exception :: EXCEPTION | eff) IDBKey)
put :: forall value eff. IDBObjectStore -> value -> Maybe IDBKey -> Aff (idb :: INDEXED_DB, exception :: EXCEPTION | eff) IDBKey
put store value mkey =
Fn.runFn3 _put store value (toNullable mkey)