{-# LANGUAGE PatternSynonyms #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Optics.Empty
( AsEmpty(..)
, pattern Empty
) where
import qualified Data.ByteString as StrictB
import qualified Data.ByteString.Lazy as LazyB
import Data.HashMap.Lazy (HashMap)
import qualified Data.HashMap.Lazy as HashMap
import Data.HashSet (HashSet)
import qualified Data.HashSet as HashSet
import qualified Data.Text as StrictT
import qualified Data.Text.Lazy as LazyT
import qualified Data.Vector as Vector
import qualified Data.Vector.Storable as Storable
import qualified Data.Vector.Unboxed as Unboxed
import Optics.Core
instance AsEmpty (HashMap k a) where
_Empty :: Prism' (HashMap k a) ()
_Empty = HashMap k a -> (HashMap k a -> Bool) -> Prism' (HashMap k a) ()
forall a. a -> (a -> Bool) -> Prism' a ()
nearly HashMap k a
forall k v. HashMap k v
HashMap.empty HashMap k a -> Bool
forall k v. HashMap k v -> Bool
HashMap.null
{-# INLINE _Empty #-}
instance AsEmpty (HashSet a) where
_Empty :: Prism' (HashSet a) ()
_Empty = HashSet a -> (HashSet a -> Bool) -> Prism' (HashSet a) ()
forall a. a -> (a -> Bool) -> Prism' a ()
nearly HashSet a
forall a. HashSet a
HashSet.empty HashSet a -> Bool
forall a. HashSet a -> Bool
HashSet.null
{-# INLINE _Empty #-}
instance AsEmpty (Vector.Vector a) where
_Empty :: Prism' (Vector a) ()
_Empty = Vector a -> (Vector a -> Bool) -> Prism' (Vector a) ()
forall a. a -> (a -> Bool) -> Prism' a ()
nearly Vector a
forall a. Vector a
Vector.empty Vector a -> Bool
forall a. Vector a -> Bool
Vector.null
{-# INLINE _Empty #-}
instance Unboxed.Unbox a => AsEmpty (Unboxed.Vector a) where
_Empty :: Prism' (Vector a) ()
_Empty = Vector a -> (Vector a -> Bool) -> Prism' (Vector a) ()
forall a. a -> (a -> Bool) -> Prism' a ()
nearly Vector a
forall a. Unbox a => Vector a
Unboxed.empty Vector a -> Bool
forall a. Unbox a => Vector a -> Bool
Unboxed.null
{-# INLINE _Empty #-}
instance Storable.Storable a => AsEmpty (Storable.Vector a) where
_Empty :: Prism' (Vector a) ()
_Empty = Vector a -> (Vector a -> Bool) -> Prism' (Vector a) ()
forall a. a -> (a -> Bool) -> Prism' a ()
nearly Vector a
forall a. Storable a => Vector a
Storable.empty Vector a -> Bool
forall a. Storable a => Vector a -> Bool
Storable.null
{-# INLINE _Empty #-}
instance AsEmpty StrictB.ByteString where
_Empty :: Prism' ByteString ()
_Empty = ByteString -> (ByteString -> Bool) -> Prism' ByteString ()
forall a. a -> (a -> Bool) -> Prism' a ()
nearly ByteString
StrictB.empty ByteString -> Bool
StrictB.null
{-# INLINE _Empty #-}
instance AsEmpty LazyB.ByteString where
_Empty :: Prism' ByteString ()
_Empty = ByteString -> (ByteString -> Bool) -> Prism' ByteString ()
forall a. a -> (a -> Bool) -> Prism' a ()
nearly ByteString
LazyB.empty ByteString -> Bool
LazyB.null
{-# INLINE _Empty #-}
instance AsEmpty StrictT.Text where
_Empty :: Prism' Text ()
_Empty = Text -> (Text -> Bool) -> Prism' Text ()
forall a. a -> (a -> Bool) -> Prism' a ()
nearly Text
StrictT.empty Text -> Bool
StrictT.null
{-# INLINE _Empty #-}
instance AsEmpty LazyT.Text where
_Empty :: Prism' Text ()
_Empty = Text -> (Text -> Bool) -> Prism' Text ()
forall a. a -> (a -> Bool) -> Prism' a ()
nearly Text
LazyT.empty Text -> Bool
LazyT.null
{-# INLINE _Empty #-}