module Database.Redis.General
    ( keyExists, keyExistsB
    , keyDelete, keyDeleteB
    , keyType, keyTypeB
    , keys, keysB
    , keyRandom
    , keyRename
    , keyRenameNX
    , databaseSize
    , keyTimeToLive
    , keyExpire
    , keyExpireAt
    , keyPersist
    , keyMove
    , flushDB
    , flushAll
    , select
    , ping
    , unwrapReply
    ) where


import           Data.Maybe

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 -- ^ key
        -> IO (Maybe RedisReply)
keyType h key = request h $ map toUTF8 ["TYPE", key]


-- | Calls @TYPE@ (<http://code.google.com/p/redis/wiki/TypeCommand>) with a
-- 'ByteString' argument.
keyTypeB :: Handle
         -> ByteString -- ^ key
         -> IO (Maybe RedisReply)
keyTypeB h key = request h [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"]


------------------------------------------------------------------------------
-- | Calls @RENAME@ (<http://code.google.com/p/redis/wiki/RenameCommand>) with
-- 'String' arguments.
keyRename :: Handle
          -> String  -- ^ old key name
          -> String  -- ^ new key name
          -> IO (Maybe RedisReply)
keyRename h old new = request h $ map toUTF8 ["RENAME", old, new]


------------------------------------------------------------------------------
-- | Calls  @RENAMENX@ (<http://code.google.com/p/redis/wiki/RenamenxCommand>)
-- with 'String' arguments.
keyRenameNX :: Handle
            -> String  -- ^ old key name
            -> String  -- ^ new key name
            -> IO (Maybe RedisReply)
keyRenameNX h old new = request h $ map toUTF8 ["RENAMENX", old, new]


------------------------------------------------------------------------------
-- | DBSIZE
databaseSize :: Handle
             -> IO (Maybe RedisReply)
databaseSize h = request h [toUTF8 "SELECT"]


------------------------------------------------------------------------------
-- | EXPIRE
keyExpire :: Handle
          -> String  -- ^ key
          -> Int     -- ^ number of seconds intil expiry
          -> IO (Maybe RedisReply)
keyExpire h key i = request h $ map toUTF8 ["EXPIRE", key, show i]


------------------------------------------------------------------------------
-- | EXPIREAT
keyExpireAt :: Handle
            -> String  -- ^ key
            -> Int     -- ^ unix time of expiry
            -> IO (Maybe RedisReply)
keyExpireAt h key i = request h $ map toUTF8 ["EXPIREAT", key, show i]


------------------------------------------------------------------------------
-- | PERSIST
keyPersist :: Handle
           -> String  -- ^ key
           -> IO (Maybe RedisReply)
keyPersist h key = request h $ map toUTF8 ["PERSIST", key]


------------------------------------------------------------------------------
-- TTL
keyTimeToLive :: Handle
              -> String  -- ^ key
              -> IO (Maybe RedisReply)
keyTimeToLive h key = request h $ map toUTF8 ["PERSIST", key]


------------------------------------------------------------------------------
-- | Calls @SELECT@ (<http://code.google.com/p/redis/wiki/SelectCommand>)
-- with an 'Int' argument
select :: Handle
       -> Int  -- ^ the database to switch to
       -> IO (Maybe RedisReply)
select h i = request h $ map toUTF8 ["SELECT", show i]


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


------------------------------------------------------------------------------
-- | FLUSHDB
flushDB :: Handle
        -> IO (Maybe RedisReply)
flushDB h = request h [toUTF8 "FLUSHDB"]


-- | FLUSHALL
flushAll :: Handle
         -> IO (Maybe RedisReply)
flushAll h = request h [toUTF8 "FLUSHALL"]


------------------------------------------------------------------------------
-- | The PING command should return PONG
ping :: Handle
     -> IO (Maybe RedisReply)
ping h = request h $ map toUTF8 ["PING"]


------------------------------------------------------------------------------
-- | Placeholder for a better-designed function
unwrapReply :: Maybe RedisReply -> [String]
unwrapReply reply =
    case reply of
      Just (RedisSingle x)    -> map fromUTF8 [x]
      Just (RedisError x)     -> map fromUTF8 [x]
      Just (RedisInteger x)   -> [show x]
      Just (RedisBulk x)      -> map fromUTF8 $ catMaybes $ map bulks x
      Just _                  -> ["Error handling here"]
      Nothing                 -> ["Nada"]
  where
    bulks rs = case rs of
        Just (RedisBulk [Just (RedisSingle x)]) -> Just x
        Nothing                                 -> Nothing