redis-resp-0.4.0: REdis Serialization Protocol (RESP) implementation.

Safe HaskellNone
LanguageHaskell2010

Data.Redis.Command

Contents

Synopsis

Types

data Command :: * -> * where #

Redis commands.

Constructors

Ping :: Resp -> Command () 
Echo :: FromByteString a => Resp -> Command a 
Auth :: Resp -> Command () 
Quit :: Resp -> Command () 
Select :: Resp -> Command () 
BgRewriteAOF :: Resp -> Command () 
BgSave :: Resp -> Command () 
Save :: Resp -> Command () 
DbSize :: Resp -> Command Int64 
FlushAll :: Resp -> Command () 
FlushDb :: Resp -> Command () 
LastSave :: Resp -> Command Int64 
Multi :: Resp -> Command () 
Watch :: Resp -> Command () 
Unwatch :: Resp -> Command () 
Discard :: Resp -> Command () 
Exec :: Resp -> Command () 
Del :: Resp -> Command Int64 
Dump :: Resp -> Command (Maybe ByteString) 
Exists :: Resp -> Command Bool 
Expire :: Resp -> Command Bool 
ExpireAt :: Resp -> Command Bool 
Persist :: Resp -> Command Bool 
Keys :: Resp -> Command [Key] 
RandomKey :: Resp -> Command (Maybe Key) 
Rename :: Resp -> Command () 
RenameNx :: Resp -> Command Bool 
Sort :: FromByteString a => Resp -> Command [a] 
Ttl :: Resp -> Command (Maybe TTL) 
Type :: Resp -> Command (Maybe RedisType) 
Scan :: FromByteString a => Resp -> Command (Cursor, [a]) 
Append :: Resp -> Command Int64 
Get :: FromByteString a => Resp -> Command (Maybe a) 
GetRange :: FromByteString a => Resp -> Command a 
GetSet :: FromByteString a => Resp -> Command (Maybe a) 
MGet :: FromByteString a => Resp -> Command [Maybe a] 
MSet :: Resp -> Command () 
MSetNx :: Resp -> Command Bool 
Set :: Resp -> Command Bool 
SetRange :: Resp -> Command Int64 
StrLen :: Resp -> Command Int64 
BitAnd :: Resp -> Command Int64 
BitCount :: Resp -> Command Int64 
BitNot :: Resp -> Command Int64 
BitOr :: Resp -> Command Int64 
BitPos :: Resp -> Command Int64 
BitXOr :: Resp -> Command Int64 
GetBit :: Resp -> Command Int64 
SetBit :: Resp -> Command Int64 
Decr :: Resp -> Command Int64 
DecrBy :: Resp -> Command Int64 
Incr :: Resp -> Command Int64 
IncrBy :: Resp -> Command Int64 
IncrByFloat :: Resp -> Command Double 
HDel :: Resp -> Command Int64 
HExists :: Resp -> Command Bool 
HGet :: FromByteString a => Resp -> Command (Maybe a) 
HGetAll :: FromByteString a => Resp -> Command [(Field, a)] 
HIncrBy :: Resp -> Command Int64 
HIncrByFloat :: Resp -> Command Double 
HKeys :: Resp -> Command [Field] 
HLen :: Resp -> Command Int64 
HMGet :: FromByteString a => Resp -> Command [Maybe a] 
HMSet :: Resp -> Command () 
HSet :: Resp -> Command Bool 
HSetNx :: Resp -> Command Bool 
HVals :: FromByteString a => Resp -> Command [a] 
HScan :: FromByteString a => Resp -> Command (Cursor, [a]) 
BLPop :: FromByteString a => Int64 -> Resp -> Command (Maybe (Key, a)) 
BRPop :: FromByteString a => Int64 -> Resp -> Command (Maybe (Key, a)) 
BRPopLPush :: FromByteString a => Int64 -> Resp -> Command (Maybe a) 
LIndex :: FromByteString a => Resp -> Command (Maybe a) 
LInsert :: Resp -> Command Int64 
LLen :: Resp -> Command Int64 
LPop :: FromByteString a => Resp -> Command (Maybe a) 
LPush :: Resp -> Command Int64 
LPushX :: Resp -> Command Int64 
LRange :: FromByteString a => Resp -> Command [a] 
LRem :: Resp -> Command Int64 
LSet :: Resp -> Command () 
LTrim :: Resp -> Command () 
RPop :: FromByteString a => Resp -> Command (Maybe a) 
RPopLPush :: FromByteString a => Resp -> Command (Maybe a) 
RPush :: Resp -> Command Int64 
RPushX :: Resp -> Command Int64 
SAdd :: Resp -> Command Int64 
SCard :: Resp -> Command Int64 
SDiff :: FromByteString a => Resp -> Command [a] 
SDiffStore :: Resp -> Command Int64 
SInter :: FromByteString a => Resp -> Command [a] 
SInterStore :: Resp -> Command Int64 
SIsMember :: Resp -> Command Bool 
SMembers :: FromByteString a => Resp -> Command [a] 
SMove :: Resp -> Command Bool 
SPop :: FromByteString a => Resp -> Command (Maybe a) 
SRandMember :: FromByteString a => Choose -> Resp -> Command [a] 
SRem :: Resp -> Command Int64 
SScan :: FromByteString a => Resp -> Command (Cursor, [a]) 
SUnion :: FromByteString a => Resp -> Command [a] 
SUnionStore :: Resp -> Command Int64 
ZAdd :: Resp -> Command Int64 
ZCard :: Resp -> Command Int64 
ZCount :: Resp -> Command Int64 
ZIncrBy :: Resp -> Command Double 
ZInterStore :: Resp -> Command Int64 
ZLexCount :: Resp -> Command Int64 
ZRange :: FromByteString a => Bool -> Resp -> Command (ScoreList a) 
ZRangeByLex :: FromByteString a => Resp -> Command [a] 
ZRangeByScore :: FromByteString a => Bool -> Resp -> Command (ScoreList a) 
ZRank :: Resp -> Command (Maybe Int64) 
ZRem :: Resp -> Command Int64 
ZRemRangeByLex :: Resp -> Command Int64 
ZRemRangeByRank :: Resp -> Command Int64 
ZRemRangeByScore :: Resp -> Command Int64 
ZRevRange :: FromByteString a => Bool -> Resp -> Command (ScoreList a) 
ZRevRangeByScore :: FromByteString a => Bool -> Resp -> Command (ScoreList a) 
ZRevRank :: Resp -> Command (Maybe Int64) 
ZScan :: FromByteString a => Resp -> Command (Cursor, [a]) 
ZScore :: Resp -> Command (Maybe Double) 
ZUnionStore :: Resp -> Command Int64 
PfAdd :: Resp -> Command Bool 
PfCount :: Resp -> Command Int64 
PfMerge :: Resp -> Command () 
Publish :: Resp -> Command Int64 

data PubSubCommand r where #

Pub/Sub commands.

data RedisError #

Redis error type.

Constructors

RedisError !ByteString

General error case.

InvalidResponse !String

The received response is invalid or unexpected (e.g. a bulk string instead of an integer).

InvalidConversion !String

ByteString conversion using FromByteString failed.

data TTL #

A type representing time-to-live values.

Constructors

NoTTL 
TTL !Int64 

Instances

Eq TTL # 

Methods

(==) :: TTL -> TTL -> Bool #

(/=) :: TTL -> TTL -> Bool #

Ord TTL # 

Methods

compare :: TTL -> TTL -> Ordering #

(<) :: TTL -> TTL -> Bool #

(<=) :: TTL -> TTL -> Bool #

(>) :: TTL -> TTL -> Bool #

(>=) :: TTL -> TTL -> Bool #

max :: TTL -> TTL -> TTL #

min :: TTL -> TTL -> TTL #

Show TTL # 

Methods

showsPrec :: Int -> TTL -> ShowS #

show :: TTL -> String #

showList :: [TTL] -> ShowS #

data Side #

Used in linsert to specify the insertion point.

Constructors

Before 
After 

Instances

Eq Side # 

Methods

(==) :: Side -> Side -> Bool #

(/=) :: Side -> Side -> Bool #

Ord Side # 

Methods

compare :: Side -> Side -> Ordering #

(<) :: Side -> Side -> Bool #

(<=) :: Side -> Side -> Bool #

(>) :: Side -> Side -> Bool #

(>=) :: Side -> Side -> Bool #

max :: Side -> Side -> Side #

min :: Side -> Side -> Side #

Show Side # 

Methods

showsPrec :: Int -> Side -> ShowS #

show :: Side -> String #

showList :: [Side] -> ShowS #

data Choose #

Constructors

One

Exactly one element

Dist !Int64

n distint elements

Arb !Int64

n arbitrary (i.e. potentially repeated) elements

Instances

data Aggregate #

Constructors

None

no aggregation

Min

take the minimum score

Max

take the maximum score

Sum

addition of scores

data Min #

Constructors

MinIncl !ByteString

lower bound (inclusive)

MinExcl !ByteString

lower bound (exclusive)

MinInf

infinite lower bound

Instances

Eq Min # 

Methods

(==) :: Min -> Min -> Bool #

(/=) :: Min -> Min -> Bool #

Ord Min # 

Methods

compare :: Min -> Min -> Ordering #

(<) :: Min -> Min -> Bool #

(<=) :: Min -> Min -> Bool #

(>) :: Min -> Min -> Bool #

(>=) :: Min -> Min -> Bool #

max :: Min -> Min -> Min #

min :: Min -> Min -> Min #

Show Min # 

Methods

showsPrec :: Int -> Min -> ShowS #

show :: Min -> String #

showList :: [Min] -> ShowS #

data Max #

Constructors

MaxIncl !ByteString

upper bound (inclusive)

MaxExcl !ByteString

upper bound (exclusive)

MaxInf

infinite upper bound

Instances

Eq Max # 

Methods

(==) :: Max -> Max -> Bool #

(/=) :: Max -> Max -> Bool #

Ord Max # 

Methods

compare :: Max -> Max -> Ordering #

(<) :: Max -> Max -> Bool #

(<=) :: Max -> Max -> Bool #

(>) :: Max -> Max -> Bool #

(>=) :: Max -> Max -> Bool #

max :: Max -> Max -> Max #

min :: Max -> Max -> Max #

Show Max # 

Methods

showsPrec :: Int -> Max -> ShowS #

show :: Max -> String #

showList :: [Max] -> ShowS #

data ScoreList a #

Constructors

ScoreList 

Fields

Instances

Eq a => Eq (ScoreList a) # 

Methods

(==) :: ScoreList a -> ScoreList a -> Bool #

(/=) :: ScoreList a -> ScoreList a -> Bool #

Ord a => Ord (ScoreList a) # 
Show a => Show (ScoreList a) # 

newtype Seconds #

Constructors

Seconds Int64 

newtype Milliseconds #

Constructors

Milliseconds Int64 

newtype Timestamp #

Constructors

Timestamp Int64 

type Index = Int64 #

newtype Key #

Redis key type

Constructors

Key 

Fields

Instances

Eq Key # 

Methods

(==) :: Key -> Key -> Bool #

(/=) :: Key -> Key -> Bool #

Ord Key # 

Methods

compare :: Key -> Key -> Ordering #

(<) :: Key -> Key -> Bool #

(<=) :: Key -> Key -> Bool #

(>) :: Key -> Key -> Bool #

(>=) :: Key -> Key -> Bool #

max :: Key -> Key -> Key #

min :: Key -> Key -> Key #

Show Key # 

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

IsString Key # 

Methods

fromString :: String -> Key #

FromByteString Key # 

Methods

parser :: Parser Key #

Cursor

Non-empty lists

one :: a -> NonEmpty a #

Options

data Opts a #

Command options

Instances

Monoid (Opts a) # 

Methods

mempty :: Opts a #

mappend :: Opts a -> Opts a -> Opts a #

mconcat :: [Opts a] -> Opts a #

none :: Monoid m => m #

Bit

data BitEnd #

Instances

Commands

Connection

auth :: Monad m => ByteString -> Redis m () #

echo :: (Monad m, ToByteString a, FromByteString a) => a -> Redis m a #

ping :: Monad m => Redis m () #

quit :: Monad m => Redis m () #

select :: Monad m => Int64 -> Redis m () #

Server

bgrewriteaof :: Monad m => Redis m () #

bgsave :: Monad m => Redis m () #

flushall :: Monad m => Redis m () #

flushdb :: Monad m => Redis m () #

save :: Monad m => Redis m () #

Transactions

discard :: Monad m => Redis m () #

exec :: Monad m => Redis m () #

multi :: Monad m => Redis m () #

unwatch :: Monad m => Redis m () #

watch :: Monad m => NonEmpty Key -> Redis m () #

Keys

exists :: Monad m => Key -> Redis m Bool #

expire :: Monad m => Key -> Seconds -> Redis m Bool #

keys :: Monad m => ByteString -> Redis m [Key] #

persist :: Monad m => Key -> Redis m Bool #

rename :: Monad m => Key -> Key -> Redis m () #

renamenx :: Monad m => Key -> Key -> Redis m Bool #

ttl :: Monad m => Key -> Redis m (Maybe TTL) #

Strings

append :: (Monad m, ToByteString a) => Key -> a -> Redis m Int64 #

decr :: Monad m => Key -> Redis m Int64 #

decrby :: Monad m => Key -> Int64 -> Redis m Int64 #

get :: (Monad m, FromByteString a) => Key -> Redis m (Maybe a) #

getrange :: (Monad m, FromByteString a) => Key -> Int64 -> Int64 -> Redis m a #

getset :: (Monad m, ToByteString a, FromByteString b) => Key -> a -> Redis m (Maybe b) #

incr :: Monad m => Key -> Redis m Int64 #

incrby :: Monad m => Key -> Int64 -> Redis m Int64 #

mset :: (Monad m, ToByteString a) => NonEmpty (Key, a) -> Redis m () #

msetnx :: (Monad m, ToByteString a) => NonEmpty (Key, a) -> Redis m Bool #

set :: (Monad m, ToByteString a) => Key -> a -> Opts "SET" -> Redis m Bool #

ex :: Seconds -> Opts "SET" #

px :: Milliseconds -> Opts "SET" #

xx :: Opts "SET" #

nx :: Opts "SET" #

setrange :: (Monad m, ToByteString a) => Key -> Int64 -> a -> Redis m Int64 #

strlen :: Monad m => Key -> Redis m Int64 #

Bits

bitcount :: Monad m => Key -> Opts "RANGE" -> Redis m Int64 #

range :: Int64 -> Int64 -> Opts "RANGE" #

bitnot :: Monad m => Key -> Key -> Redis m Int64 #

bitpos :: Monad m => Key -> Bool -> BitStart -> BitEnd -> Redis m Int64 #

getbit :: Monad m => Key -> Int64 -> Redis m Int64 #

setbit :: Monad m => Key -> Int64 -> Bool -> Redis m Int64 #

Hashes

hexists :: Monad m => Key -> Field -> Redis m Bool #

hget :: (Monad m, FromByteString a) => Key -> Field -> Redis m (Maybe a) #

hgetall :: (Monad m, FromByteString a) => Key -> Redis m [(Field, a)] #

hincrby :: Monad m => Key -> Field -> Int64 -> Redis m Int64 #

hkeys :: Monad m => Key -> Redis m [Field] #

hlen :: Monad m => Key -> Redis m Int64 #

hmset :: (Monad m, ToByteString a) => Key -> NonEmpty (Field, a) -> Redis m () #

hset :: (Monad m, ToByteString a) => Key -> Field -> a -> Redis m Bool #

hsetnx :: (Monad m, ToByteString a) => Key -> Field -> a -> Redis m Bool #

hvals :: (Monad m, FromByteString a) => Key -> Redis m [a] #

Lists

brpoplpush :: (Monad m, FromByteString a) => Key -> Key -> Seconds -> Redis m (Maybe a) #

lindex :: (Monad m, FromByteString a) => Key -> Index -> Redis m (Maybe a) #

linsert :: (Monad m, ToByteString a) => Key -> Side -> a -> a -> Redis m Int64 #

llen :: Monad m => Key -> Redis m Int64 #

lpop :: (Monad m, FromByteString a) => Key -> Redis m (Maybe a) #

lpush :: (Monad m, ToByteString a) => Key -> NonEmpty a -> Redis m Int64 #

lpushx :: (Monad m, ToByteString a) => Key -> a -> Redis m Int64 #

lrange :: (Monad m, FromByteString a) => Key -> Int64 -> Int64 -> Redis m [a] #

lrem :: (Monad m, ToByteString a) => Key -> Int64 -> a -> Redis m Int64 #

lset :: (Monad m, ToByteString a) => Key -> Int64 -> a -> Redis m () #

ltrim :: Monad m => Key -> Int64 -> Int64 -> Redis m () #

rpop :: (Monad m, FromByteString a) => Key -> Redis m (Maybe a) #

rpoplpush :: (Monad m, FromByteString a) => Key -> Key -> Redis m (Maybe a) #

rpush :: (Monad m, ToByteString a) => Key -> NonEmpty a -> Redis m Int64 #

rpushx :: (Monad m, ToByteString a) => Key -> a -> Redis m Int64 #

Sets

sadd :: (Monad m, ToByteString a) => Key -> NonEmpty a -> Redis m Int64 #

scard :: Monad m => Key -> Redis m Int64 #

sdiff :: (Monad m, FromByteString a) => NonEmpty Key -> Redis m [a] #

sinter :: (Monad m, FromByteString a) => NonEmpty Key -> Redis m [a] #

sismember :: (Monad m, ToByteString a) => Key -> a -> Redis m Bool #

smembers :: (Monad m, FromByteString a) => Key -> Redis m [a] #

smove :: (Monad m, ToByteString a) => Key -> Key -> a -> Redis m Bool #

spop :: (Monad m, FromByteString a) => Key -> Redis m (Maybe a) #

srandmember :: (Monad m, FromByteString a) => Key -> Choose -> Redis m [a] #

srem :: (Monad m, ToByteString a) => Key -> NonEmpty a -> Redis m Int64 #

sunion :: (Monad m, FromByteString a) => NonEmpty Key -> Redis m [a] #

Sorted Sets

zadd :: (Monad m, ToByteString a) => Key -> NonEmpty (Double, a) -> Redis m Int64 #

zcard :: Monad m => Key -> Redis m Int64 #

zcount :: Monad m => Key -> Double -> Double -> Redis m Int64 #

zincrby :: (Monad m, ToByteString a) => Key -> Double -> a -> Redis m Double #

zlexcount :: Monad m => Key -> Min -> Max -> Redis m Int64 #

zrange :: (Monad m, FromByteString a) => Key -> Int64 -> Int64 -> Bool -> Redis m (ScoreList a) #

zrangebylex :: (Monad m, FromByteString a) => Key -> Min -> Max -> Opts "LIMIT" -> Redis m [a] #

zrangebyscore :: (Monad m, FromByteString a) => Key -> Double -> Double -> Bool -> Opts "LIMIT" -> Redis m (ScoreList a) #

zrank :: (Monad m, ToByteString a) => Key -> a -> Redis m (Maybe Int64) #

zrem :: (Monad m, ToByteString a) => Key -> NonEmpty a -> Redis m Int64 #

zremrangebylex :: Monad m => Key -> Min -> Max -> Redis m Int64 #

zrevrangebyscore :: (Monad m, FromByteString a) => Key -> Double -> Double -> Bool -> Opts "LIMIT" -> Redis m (ScoreList a) #

zrevrange :: (Monad m, FromByteString a) => Key -> Int64 -> Int64 -> Bool -> Redis m (ScoreList a) #

zrevrank :: (Monad m, ToByteString a) => Key -> a -> Redis m (Maybe Int64) #

zscore :: (Monad m, ToByteString a) => Key -> a -> Redis m (Maybe Double) #

HyperLogLog

pfadd :: (Monad m, ToByteString a) => Key -> NonEmpty a -> Redis m Bool #

pfmerge :: Monad m => Key -> NonEmpty Key -> Redis m () #

Scan

scan :: (Monad m, FromByteString a) => Cursor -> Opts "SCAN" -> Redis m (Cursor, [a]) #

match :: ByteString -> Opts "SCAN" #

count :: Int64 -> Opts "SCAN" #

hscan :: (Monad m, FromByteString a) => Key -> Cursor -> Opts "SCAN" -> Redis m (Cursor, [a]) #

sscan :: (Monad m, FromByteString a) => Key -> Cursor -> Opts "SCAN" -> Redis m (Cursor, [a]) #

zscan :: (Monad m, FromByteString a) => Key -> Cursor -> Opts "SCAN" -> Redis m (Cursor, [a]) #

Sort

sort :: (Monad m, FromByteString a) => Key -> Opts "SORT" -> Redis m [a] #

by :: ByteString -> Opts "SORT" #

limit :: Int64 -> Int64 -> Opts o #

asc :: Opts "SORT" #

desc :: Opts "SORT" #

alpha :: Opts "SORT" #

store :: Key -> Opts "SORT" #

Pub/Sub

unsubscribe :: Monad m => [ByteString] -> PubSub m () #

Response Reading

anyStr :: String -> Resp -> Result () #

Re-exports

data NonEmpty a :: * -> * #

Non-empty (and non-strict) list type.

Since: 4.9.0.0

Constructors

a :| [a] infixr 5 

Instances

Monad NonEmpty 

Methods

(>>=) :: NonEmpty a -> (a -> NonEmpty b) -> NonEmpty b #

(>>) :: NonEmpty a -> NonEmpty b -> NonEmpty b #

return :: a -> NonEmpty a #

fail :: String -> NonEmpty a #

Functor NonEmpty 

Methods

fmap :: (a -> b) -> NonEmpty a -> NonEmpty b #

(<$) :: a -> NonEmpty b -> NonEmpty a #

MonadFix NonEmpty 

Methods

mfix :: (a -> NonEmpty a) -> NonEmpty a #

Applicative NonEmpty 

Methods

pure :: a -> NonEmpty a #

(<*>) :: NonEmpty (a -> b) -> NonEmpty a -> NonEmpty b #

(*>) :: NonEmpty a -> NonEmpty b -> NonEmpty b #

(<*) :: NonEmpty a -> NonEmpty b -> NonEmpty a #

Foldable NonEmpty 

Methods

fold :: Monoid m => NonEmpty m -> m #

foldMap :: Monoid m => (a -> m) -> NonEmpty a -> m #

foldr :: (a -> b -> b) -> b -> NonEmpty a -> b #

foldr' :: (a -> b -> b) -> b -> NonEmpty a -> b #

foldl :: (b -> a -> b) -> b -> NonEmpty a -> b #

foldl' :: (b -> a -> b) -> b -> NonEmpty a -> b #

foldr1 :: (a -> a -> a) -> NonEmpty a -> a #

foldl1 :: (a -> a -> a) -> NonEmpty a -> a #

toList :: NonEmpty a -> [a] #

null :: NonEmpty a -> Bool #

length :: NonEmpty a -> Int #

elem :: Eq a => a -> NonEmpty a -> Bool #

maximum :: Ord a => NonEmpty a -> a #

minimum :: Ord a => NonEmpty a -> a #

sum :: Num a => NonEmpty a -> a #

product :: Num a => NonEmpty a -> a #

Traversable NonEmpty 

Methods

traverse :: Applicative f => (a -> f b) -> NonEmpty a -> f (NonEmpty b) #

sequenceA :: Applicative f => NonEmpty (f a) -> f (NonEmpty a) #

mapM :: Monad m => (a -> m b) -> NonEmpty a -> m (NonEmpty b) #

sequence :: Monad m => NonEmpty (m a) -> m (NonEmpty a) #

Generic1 NonEmpty 

Associated Types

type Rep1 (NonEmpty :: * -> *) :: * -> * #

Methods

from1 :: NonEmpty a -> Rep1 NonEmpty a #

to1 :: Rep1 NonEmpty a -> NonEmpty a #

MonadZip NonEmpty 

Methods

mzip :: NonEmpty a -> NonEmpty b -> NonEmpty (a, b) #

mzipWith :: (a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c #

munzip :: NonEmpty (a, b) -> (NonEmpty a, NonEmpty b) #

IsList (NonEmpty a) 

Associated Types

type Item (NonEmpty a) :: * #

Methods

fromList :: [Item (NonEmpty a)] -> NonEmpty a #

fromListN :: Int -> [Item (NonEmpty a)] -> NonEmpty a #

toList :: NonEmpty a -> [Item (NonEmpty a)] #

Eq a => Eq (NonEmpty a) 

Methods

(==) :: NonEmpty a -> NonEmpty a -> Bool #

(/=) :: NonEmpty a -> NonEmpty a -> Bool #

Data a => Data (NonEmpty a) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NonEmpty a -> c (NonEmpty a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (NonEmpty a) #

toConstr :: NonEmpty a -> Constr #

dataTypeOf :: NonEmpty a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (NonEmpty a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (NonEmpty a)) #

gmapT :: (forall b. Data b => b -> b) -> NonEmpty a -> NonEmpty a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NonEmpty a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NonEmpty a -> r #

gmapQ :: (forall d. Data d => d -> u) -> NonEmpty a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NonEmpty a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NonEmpty a -> m (NonEmpty a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NonEmpty a -> m (NonEmpty a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NonEmpty a -> m (NonEmpty a) #

Ord a => Ord (NonEmpty a) 

Methods

compare :: NonEmpty a -> NonEmpty a -> Ordering #

(<) :: NonEmpty a -> NonEmpty a -> Bool #

(<=) :: NonEmpty a -> NonEmpty a -> Bool #

(>) :: NonEmpty a -> NonEmpty a -> Bool #

(>=) :: NonEmpty a -> NonEmpty a -> Bool #

max :: NonEmpty a -> NonEmpty a -> NonEmpty a #

min :: NonEmpty a -> NonEmpty a -> NonEmpty a #

Read a => Read (NonEmpty a) 
Show a => Show (NonEmpty a) 

Methods

showsPrec :: Int -> NonEmpty a -> ShowS #

show :: NonEmpty a -> String #

showList :: [NonEmpty a] -> ShowS #

Generic (NonEmpty a) 

Associated Types

type Rep (NonEmpty a) :: * -> * #

Methods

from :: NonEmpty a -> Rep (NonEmpty a) x #

to :: Rep (NonEmpty a) x -> NonEmpty a #

Semigroup (NonEmpty a) 

Methods

(<>) :: NonEmpty a -> NonEmpty a -> NonEmpty a #

sconcat :: NonEmpty (NonEmpty a) -> NonEmpty a #

stimes :: Integral b => b -> NonEmpty a -> NonEmpty a #

type Rep1 NonEmpty 
type Rep (NonEmpty a) 
type Item (NonEmpty a) 
type Item (NonEmpty a) = a

nonEmpty :: [a] -> Maybe (NonEmpty a) #

nonEmpty efficiently turns a normal list into a NonEmpty stream, producing Nothing if the input is empty.