module HaskellWorks.Data.Empty
( Empty(..)
) where
import qualified Data.ByteString as BS
import Data.Int
import qualified Data.Vector as DV
import qualified Data.Vector.Storable as DVS
import Data.Word
import HaskellWorks.Data.Container
class Container a => Empty a where
empty :: a
instance Empty [a] where
empty = []
instance Empty BS.ByteString where
empty = BS.empty
instance Empty (DV.Vector Word8) where
empty = DV.empty
instance Empty (DV.Vector Word16) where
empty = DV.empty
instance Empty (DV.Vector Word32) where
empty = DV.empty
instance Empty (DV.Vector Word64) where
empty = DV.empty
instance Empty (DVS.Vector Word8) where
empty = DVS.empty
instance Empty (DVS.Vector Word16) where
empty = DVS.empty
instance Empty (DVS.Vector Word32) where
empty = DVS.empty
instance Empty (DVS.Vector Word64) where
empty = DVS.empty
instance Empty (DV.Vector Int8) where
empty = DV.empty
instance Empty (DV.Vector Int16) where
empty = DV.empty
instance Empty (DV.Vector Int32) where
empty = DV.empty
instance Empty (DV.Vector Int64) where
empty = DV.empty
instance Empty (DVS.Vector Int8) where
empty = DVS.empty
instance Empty (DVS.Vector Int16) where
empty = DVS.empty
instance Empty (DVS.Vector Int32) where
empty = DVS.empty
instance Empty (DVS.Vector Int64) where
empty = DVS.empty
instance Empty (DVS.Vector Int) where
empty = DVS.empty