{-# LANGUAGE FlexibleContexts  #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE Safe              #-}
{-# LANGUAGE TypeFamilies      #-}
module Relude.Container.One
    ( One (..)
    ) where
import Relude.Base (Char)
import Relude.Container.Reexport (HashMap, HashSet, Hashable, IntMap, IntSet, Map, Set, uncurry)
import Relude.Numeric (Int, Word8)
import qualified Data.List.NonEmpty as NE
import qualified Data.Sequence as SEQ
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as BSL
import qualified Data.ByteString.Short as SBS
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
import qualified Data.HashMap.Strict as HM
import qualified Data.HashSet as HashSet
import qualified Data.IntMap as IM
import qualified Data.IntSet as IS
import qualified Data.Map as M
import qualified Data.Set as Set
class One x where
    
    type OneItem x
    
    one :: OneItem x -> x
instance One [a] where
    type OneItem [a] = a
    one :: a -> [a]
    one :: a -> [a]
one = (a -> [a] -> [a]
forall a. a -> [a] -> [a]
:[])
    {-# INLINE one #-}
instance One (NE.NonEmpty a) where
    type OneItem (NE.NonEmpty a) = a
    one :: a -> NE.NonEmpty a
    one :: a -> NonEmpty a
one = (a -> [a] -> NonEmpty a
forall a. a -> [a] -> NonEmpty a
NE.:|[])
    {-# INLINE one #-}
instance One (SEQ.Seq a) where
    type OneItem (SEQ.Seq a) = a
    one :: a -> SEQ.Seq a
    one :: a -> Seq a
one = a -> Seq a
forall a. a -> Seq a
SEQ.singleton
    {-# INLINE one #-}
instance One T.Text where
    type OneItem T.Text = Char
    one :: Char -> T.Text
    one :: Char -> Text
one = Char -> Text
T.singleton
    {-# INLINE one #-}
instance One TL.Text where
    type OneItem TL.Text = Char
    one :: Char -> TL.Text
    one :: Char -> Text
one = Char -> Text
TL.singleton
    {-# INLINE one #-}
instance One BS.ByteString where
    type OneItem BS.ByteString = Word8
    one :: Word8 -> BS.ByteString
    one :: Word8 -> ByteString
one = Word8 -> ByteString
BS.singleton
    {-# INLINE one #-}
instance One BSL.ByteString where
    type OneItem BSL.ByteString = Word8
    one :: Word8 -> BSL.ByteString
    one :: Word8 -> ByteString
one = Word8 -> ByteString
BSL.singleton
    {-# INLINE one #-}
instance One SBS.ShortByteString where
    type OneItem SBS.ShortByteString = Word8
    one :: Word8 -> SBS.ShortByteString
    one :: Word8 -> ShortByteString
one x :: Word8
x = [Word8] -> ShortByteString
SBS.pack [Word8
x]
    {-# INLINE one #-}
instance One (Map k v) where
    type OneItem (Map k v) = (k, v)
    one :: (k, v) -> Map k v
    one :: (k, v) -> Map k v
one = (k -> v -> Map k v) -> (k, v) -> Map k v
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry k -> v -> Map k v
forall k a. k -> a -> Map k a
M.singleton
    {-# INLINE one #-}
instance Hashable k => One (HashMap k v) where
    type OneItem (HashMap k v) = (k, v)
    one :: (k, v) -> HashMap k v
    one :: (k, v) -> HashMap k v
one = (k -> v -> HashMap k v) -> (k, v) -> HashMap k v
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry k -> v -> HashMap k v
forall k v. Hashable k => k -> v -> HashMap k v
HM.singleton
    {-# INLINE one #-}
instance One (IntMap v) where
    type OneItem (IntMap v) = (Int, v)
    one :: (Int, v) -> IntMap v
    one :: (Int, v) -> IntMap v
one = (Int -> v -> IntMap v) -> (Int, v) -> IntMap v
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Int -> v -> IntMap v
forall a. Int -> a -> IntMap a
IM.singleton
    {-# INLINE one #-}
instance One (Set a) where
    type OneItem (Set a) = a
    one :: a -> Set a
    one :: a -> Set a
one = a -> Set a
forall a. a -> Set a
Set.singleton
    {-# INLINE one #-}
instance Hashable a => One (HashSet a) where
    type OneItem (HashSet a) = a
    one :: a -> HashSet a
    one :: a -> HashSet a
one = a -> HashSet a
forall a. Hashable a => a -> HashSet a
HashSet.singleton
    {-# INLINE one #-}
instance One IntSet where
    type OneItem IntSet = Int
    one :: Int -> IntSet
    one :: Int -> IntSet
one = Int -> IntSet
IS.singleton
    {-# INLINE one #-}