module Database.Redis.General
    ( RedisReply(..)
    , keyExists
    , keyExistsB
    , keyDelete
    , keyDeleteB
    , keyType
    , keys
    , keysB
    , keyRandom
    , keyRename
    , select
    , toUTF8
    , ping
    , unwrapReply
    ) where


import           System.IO

import           Database.Redis.Internal


------------------------------------------------------------------------------
-- | Calls @EXISTS@ (<http://code.google.com/p/redis/wiki/ExistsCommand>)
-- with a 'String' argument
keyExists :: Handle
          -> String                -- ^ key
          -> IO (Maybe RedisReply)
keyExists h key = request h $ map toUTF8 ["EXISTS", key]


-- | Calls @EXISTS@ with a 'ByteString' argument
keyExistsB :: Handle
           -> ByteString            -- ^ key
           -> IO (Maybe RedisReply)
keyExistsB h key = request h [toUTF8 "EXISTS", key]


------------------------------------------------------------------------------
-- | Calls @DEL@ (<http://code.google.com/p/redis/wiki/DelCommand>) with a
-- list of 'String' arguments.
keyDelete :: Handle
          -> [String]              -- ^ keys to delete
          -> IO (Maybe RedisReply)
keyDelete h ks = request h $ map toUTF8 ("DEL":ks)


-- | Calls @DEL@ with a list of 'ByteString' arguments.
keyDeleteB :: Handle
           -> [ByteString]          -- ^ keys to delete
           -> IO (Maybe RedisReply)
keyDeleteB h ks = request h ((toUTF8 "DEL"):ks)


------------------------------------------------------------------------------
-- | Calls @TYPE@ (<http://code.google.com/p/redis/wiki/TypeCommand>) with a
-- 'String' argument.
keyType :: Handle
        -> String
        -> IO (Maybe RedisReply)
keyType h key = request h $ map toUTF8 ["TYPE", key]


------------------------------------------------------------------------------
-- | Calls @KEYS@ (<http://code.google.com/p/redis/wiki/KeysCommand>) with a
-- 'String' argument
keys :: Handle
     -> String  -- ^ key pattern
     -> IO (Maybe RedisReply)
keys h pattern = request h $ map toUTF8 ["KEYS", pattern]


-- | Calls @KEYS@ with a 'ByteString' argument
keysB :: Handle
      -> ByteString -- ^ key pattern
      -> IO (Maybe RedisReply)
keysB h pattern = request h [toUTF8 "KEYS", pattern]


------------------------------------------------------------------------------
-- | Calls @RANDOMKEY@ (<http://code.google.com/p/redis/wiki/RandomkeyCommand>)
keyRandom :: Handle
          -> IO (Maybe RedisReply)
keyRandom h = request h [toUTF8 "RANDOMKEY"]


-- | RENAME
keyRename :: Handle
          -> String  -- ^ old key name
          -> String  -- ^ new key name
          -> IO (Maybe RedisReply)
keyRename h old new = request h $ map toUTF8 ["RENAME", old, new]

-- RENAMENX
-- DBSIZE
-- EXPIRE
-- PERSIST
-- TTL


------------------------------------------------------------------------------
-- | SELECT
select :: Handle
       -> Int  -- ^ the database to switch to
       -> IO (Maybe RedisReply)
select h i = request h $ map toUTF8 ["SELECT", show i]


-- MOVE
-- FLUSHDB
-- FLUSHALL

------------------------------------------------------------------------------
ping :: Handle
     -> IO (Maybe RedisReply)
ping h = request h $ map toUTF8 ["PING"]