{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE OverloadedStrings #-} {-| This implements the API. Generally, the data stored knows about its own key using via the 'OrchestrateData' class instance defined for it. -} -- TODO: exchange *KV for *V (should reflect the parameters required). module Database.Orchestrate.KeyValue ( -- * Data Types KVList -- * API Functions -- ** Accessing Data , getKV , listKV -- ** Adding and Updating Data , putKV , putV , postV -- ** Deleting Data , deleteKV , deleteV , purgeKV , purgeV ) where import Control.Applicative import Control.Arrow import Control.Error import Control.Lens import Control.Monad (join, void) import Data.Aeson import qualified Data.Text as T import Network.Wreq import Database.Orchestrate.Types import Database.Orchestrate.Utils -- | This retrieves a value from a collection. -- -- > getKV "contacts" "mom" getKV :: FromJSON v => Collection -> Key -> OrchestrateIO (Maybe v) getKV c k = join . fmap (decode . (^.responseBody)) <$> api404 [] [c, k] [] getWith -- | This inserts data into the database or updates existing data using -- a key generated by the 'OrchestrateData' instance. -- -- > putKV data NoMatch putKV :: OrchestrateData v => v -- ^ The data to store in the database. -> IfMatch' -- ^ If specified, this operation only succeeds -- if the ref specified matches the -- currently stored ref for this data. -> OrchestrateIO Location -- ^ Returns the location of the data. putKV v = putV (dataKey v) v -- | This inserts data into the database or updates data in the database. -- This overrides the key provided by the data type's 'OrchestrateData' -- instance. However, it still requires an implementation of that data type -- for the collection name. -- -- > putV "key" data NoMatch putV :: OrchestrateData v => Key -- ^ The key to store the data under. -> v -- ^ The data to store. -> IfMatch' -- ^ If specified, this operation only succeeds -- if the ref specified matches the currently -- stored ref for this data. -> OrchestrateIO Location -- ^ Returns the location of the data. putV k v m = getLocation <$> api (ifMatch' m) [tableName v, k] [] (rot putWith v') where v' = toJSON v -- | This inserts data in the database, generating a new database key for -- it. -- -- > postV data postV :: OrchestrateData v => v -- ^ The data to store. -> OrchestrateIO (Location, Maybe Key) -- ^ The 'Location' and key for the data. postV v = (id &&& firstOf locationKey) . getLocation <$> api [] [tableName v] [] (rot postWith (toJSON v)) -- | This removes data from the database. -- -- > deleteKV data Nothing deleteKV :: OrchestrateData v => v -- ^ The data to remove. -> IfMatch -- ^ If given, this operation only succeeds -- if the ref specified matches the currently -- stored ref for this data. -> OrchestrateIO () deleteKV v = deleteV (dataKey v) v -- | This removes data from the database. -- -- > deleteV "key" data Nothing deleteV :: OrchestrateData v => Key -- ^ The key the data is stored under. -> v -- ^ The data to remove. -> IfMatch -- ^ If given, this operation only succeeds -- if the ref specified matches the -- currently stored ref for this data. -> OrchestrateIO () deleteV k v m = void $ apiCheck (ifMatch m) [tableName v, k] [] deleteWith -- | This purges data from the database. Purging not only removes the data, -- but also all history and secondary items for it. -- -- > purgeKV data Nothing purgeKV :: OrchestrateData v => v -- ^ The data to remove. -> IfMatch -- ^ If given, this operation only succeeds -- if the ref specified matches the -- currently stored ref for this data. -> OrchestrateIO () purgeKV v = purgeV (dataKey v) v -- | This purges data from the database. Purging not only removes the data, -- but also all history and secondary items for it. -- -- > purgeV "key" data Nothing purgeV :: OrchestrateData v => Key -- ^ The key the data is stored under. -> v -- ^ The data to remove. -> IfMatch -- ^ If given, this operation only succeeds -- if the ref specified matches the -- currently stored ref for this data. -> OrchestrateIO () purgeV k v m = void $ apiCheck (ifMatch m) [tableName v, k] ["purge" := ("true" :: T.Text)] deleteWith -- | This lists all the data in the collection within the range given. -- -- > listKV "coll-name" Nothing (Open, Open) listKV :: FromJSON v => Collection -- ^ The collection to list data from. -> Maybe Int -- ^ The maximum number of items to retrieve. -> Range Key -- ^ The range of keys to query. -> OrchestrateIO (KVList v) -- ^ Returns a collection of data. listKV c limit (start, end) = apiCheckDecode [] [c] ps getWith where ps = catMaybes [ ("limit" :=) <$> limit , rangeStart "Key" start , rangeEnd "Key" end ] -- | A list of data returned by 'listKV'. -- -- [@v@] The type of the data contained in the list. type KVList v = ResultList (ResultItem Path v)