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

Safe HaskellNone
LanguageHaskell2010

Data.Redis.Command

Contents

Synopsis

Types

data Command :: * -> * where Source #

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 Source #

Pub/Sub commands.

data RedisError Source #

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 RedisType Source #

The types redis reports via type.

data TTL Source #

A type representing time-to-live values.

Constructors

NoTTL 
TTL !Int64 
Instances
Eq TTL Source # 
Instance details

Defined in Data.Redis.Command

Methods

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

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

Ord TTL Source # 
Instance details

Defined in Data.Redis.Command

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 Source # 
Instance details

Defined in Data.Redis.Command

Methods

showsPrec :: Int -> TTL -> ShowS #

show :: TTL -> String #

showList :: [TTL] -> ShowS #

data Side Source #

Used in linsert to specify the insertion point.

Constructors

Before 
After 
Instances
Eq Side Source # 
Instance details

Defined in Data.Redis.Command

Methods

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

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

Ord Side Source # 
Instance details

Defined in Data.Redis.Command

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 Source # 
Instance details

Defined in Data.Redis.Command

Methods

showsPrec :: Int -> Side -> ShowS #

show :: Side -> String #

showList :: [Side] -> ShowS #

data Choose Source #

Constructors

One

Exactly one element

Dist !Int64

n distint elements

Arb !Int64

n arbitrary (i.e. potentially repeated) elements

Instances
Eq Choose Source # 
Instance details

Defined in Data.Redis.Command

Methods

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

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

Ord Choose Source # 
Instance details

Defined in Data.Redis.Command

Show Choose Source # 
Instance details

Defined in Data.Redis.Command

data Aggregate Source #

Constructors

None

no aggregation

Min

take the minimum score

Max

take the maximum score

Sum

addition of scores

data Min Source #

Constructors

MinIncl !ByteString

lower bound (inclusive)

MinExcl !ByteString

lower bound (exclusive)

MinInf

infinite lower bound

Instances
Eq Min Source # 
Instance details

Defined in Data.Redis.Command

Methods

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

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

Ord Min Source # 
Instance details

Defined in Data.Redis.Command

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 Source # 
Instance details

Defined in Data.Redis.Command

Methods

showsPrec :: Int -> Min -> ShowS #

show :: Min -> String #

showList :: [Min] -> ShowS #

data Max Source #

Constructors

MaxIncl !ByteString

upper bound (inclusive)

MaxExcl !ByteString

upper bound (exclusive)

MaxInf

infinite upper bound

Instances
Eq Max Source # 
Instance details

Defined in Data.Redis.Command

Methods

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

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

Ord Max Source # 
Instance details

Defined in Data.Redis.Command

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 Source # 
Instance details

Defined in Data.Redis.Command

Methods

showsPrec :: Int -> Max -> ShowS #

show :: Max -> String #

showList :: [Max] -> ShowS #

data ScoreList a Source #

Constructors

ScoreList 

Fields

Instances
Eq a => Eq (ScoreList a) Source # 
Instance details

Defined in Data.Redis.Command

Methods

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

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

Ord a => Ord (ScoreList a) Source # 
Instance details

Defined in Data.Redis.Command

Show a => Show (ScoreList a) Source # 
Instance details

Defined in Data.Redis.Command

newtype Seconds Source #

Constructors

Seconds Int64 

newtype Milliseconds Source #

Constructors

Milliseconds Int64 

newtype Timestamp Source #

Constructors

Timestamp Int64 

newtype Key Source #

Redis key type

Constructors

Key 

Fields

Instances
Eq Key Source # 
Instance details

Defined in Data.Redis.Command

Methods

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

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

Ord Key Source # 
Instance details

Defined in Data.Redis.Command

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 Source # 
Instance details

Defined in Data.Redis.Command

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

IsString Key Source # 
Instance details

Defined in Data.Redis.Command

Methods

fromString :: String -> Key #

FromByteString Key Source # 
Instance details

Defined in Data.Redis.Command

Methods

parser :: Parser Key #

Cursor

data Cursor Source #

Instances
Eq Cursor Source # 
Instance details

Defined in Data.Redis.Command

Methods

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

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

Ord Cursor Source # 
Instance details

Defined in Data.Redis.Command

Show Cursor Source # 
Instance details

Defined in Data.Redis.Command

FromByteString Cursor Source # 
Instance details

Defined in Data.Redis.Command

Methods

parser :: Parser Cursor #

Non-empty lists

one :: a -> NonEmpty a Source #

Options

data Opts (a :: Symbol) Source #

Command options

Instances
Semigroup (Opts a) Source # 
Instance details

Defined in Data.Redis.Command

Methods

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

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

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

Monoid (Opts a) Source # 
Instance details

Defined in Data.Redis.Command

Methods

mempty :: Opts a #

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

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

none :: Monoid m => m Source #

Bit

data BitEnd Source #

Instances
Semigroup BitEnd Source # 
Instance details

Defined in Data.Redis.Command

Monoid BitEnd Source # 
Instance details

Defined in Data.Redis.Command

Commands

Connection

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

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

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

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

Server

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

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

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

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

Transactions

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

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

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

Note that all commands following multi and until exec are queued by a Redis server. Therefore the result of any such command is not available until the exec command completes. For example, the following is an invalid Redis program:

 multi
 x <- hexists "FOO" "BAR"
 unless x (void $ hset "FOO" "BAR" 1)
 exec

This pattern is usually indicative of the desire for a transactional check-and-set operation, which may be achieved instead by the following valid command sequence:

 watch ("FOO" R.:| [])
 x <- hexists "FOO" "BAR"
 multi
 unless x (void $ hset "FOO" "BAR" 1)
 exec

For more information on Redis transactions and conditional updates, see https://redis.io/topics/transactions.

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

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

Keys

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

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

Strings

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

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

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

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

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

ex :: Seconds -> Opts "SET" Source #

xx :: Opts "SET" Source #

nx :: Opts "SET" Source #

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

Bits

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

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

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

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

Hashes

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

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

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

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

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

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

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

Lists

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

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

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

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

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

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

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

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

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

Sets

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

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

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

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

Sorted Sets

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

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

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

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

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

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

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

HyperLogLog

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

Scan

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

count :: Int64 -> Opts "SCAN" Source #

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

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

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

Sort

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

by :: ByteString -> Opts "SORT" Source #

asc :: Opts "SORT" Source #

desc :: Opts "SORT" Source #

alpha :: Opts "SORT" Source #

store :: Key -> Opts "SORT" Source #

Pub/Sub

Response Reading

Re-exports

data NonEmpty a #

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

Since: base-4.9.0.0

Constructors

a :| [a] infixr 5 
Instances
Monad NonEmpty

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

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

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

return :: a -> NonEmpty a #

fail :: String -> NonEmpty a #

Functor NonEmpty

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

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

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

Applicative NonEmpty

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

pure :: a -> NonEmpty a #

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

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

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

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

Foldable NonEmpty

Since: base-4.9.0.0

Instance details

Defined in Data.Foldable

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

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

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) #

Eq1 NonEmpty

Since: base-4.10.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

Ord1 NonEmpty

Since: base-4.10.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

Read1 NonEmpty

Since: base-4.10.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (NonEmpty a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [NonEmpty a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (NonEmpty a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [NonEmpty a] #

Show1 NonEmpty

Since: base-4.10.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> NonEmpty a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [NonEmpty a] -> ShowS #

IsList (NonEmpty a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Exts

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) 
Instance details

Defined in GHC.Base

Methods

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

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

Ord a => Ord (NonEmpty a) 
Instance details

Defined in GHC.Base

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) 
Instance details

Defined in GHC.Read

Show a => Show (NonEmpty a) 
Instance details

Defined in GHC.Show

Methods

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

show :: NonEmpty a -> String #

showList :: [NonEmpty a] -> ShowS #

Semigroup (NonEmpty a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

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

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

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

type Item (NonEmpty a) 
Instance details

Defined in GHC.Exts

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.