{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE TypeFamilies #-} module HaskellWorks.Data.Head ( Container(..) , Head(..) ) where import Data.Int import Data.Word import HaskellWorks.Data.Container import Prelude hiding (head) import qualified Data.ByteString as BS import qualified Data.List as L import qualified Data.Vector as DV import qualified Data.Vector.Storable as DVS class Container v => Head v where head :: v -> Elem v instance Head [a] where head :: [a] -> Elem [a] head = [a] -> Elem [a] forall a. [a] -> a L.head {-# INLINE head #-} instance Head BS.ByteString where head :: ByteString -> Elem ByteString head = ByteString -> Word8 ByteString -> Elem ByteString BS.head {-# INLINE head #-} instance Head (DV.Vector Word8) where head :: Vector Word8 -> Elem (Vector Word8) head = Vector Word8 -> Elem (Vector Word8) forall a. Vector a -> a DV.head {-# INLINE head #-} instance Head (DV.Vector Word16) where head :: Vector Word16 -> Elem (Vector Word16) head = Vector Word16 -> Elem (Vector Word16) forall a. Vector a -> a DV.head {-# INLINE head #-} instance Head (DV.Vector Word32) where head :: Vector Word32 -> Elem (Vector Word32) head = Vector Word32 -> Elem (Vector Word32) forall a. Vector a -> a DV.head {-# INLINE head #-} instance Head (DV.Vector Word64) where head :: Vector Word64 -> Elem (Vector Word64) head = Vector Word64 -> Elem (Vector Word64) forall a. Vector a -> a DV.head {-# INLINE head #-} instance Head (DVS.Vector Word8) where head :: Vector Word8 -> Elem (Vector Word8) head = Vector Word8 -> Elem (Vector Word8) forall a. Storable a => Vector a -> a DVS.head {-# INLINE head #-} instance Head (DVS.Vector Word16) where head :: Vector Word16 -> Elem (Vector Word16) head = Vector Word16 -> Elem (Vector Word16) forall a. Storable a => Vector a -> a DVS.head {-# INLINE head #-} instance Head (DVS.Vector Word32) where head :: Vector Word32 -> Elem (Vector Word32) head = Vector Word32 -> Elem (Vector Word32) forall a. Storable a => Vector a -> a DVS.head {-# INLINE head #-} instance Head (DVS.Vector Word64) where head :: Vector Word64 -> Elem (Vector Word64) head = Vector Word64 -> Elem (Vector Word64) forall a. Storable a => Vector a -> a DVS.head {-# INLINE head #-} instance Head (DV.Vector Int8) where head :: Vector Int8 -> Elem (Vector Int8) head = Vector Int8 -> Elem (Vector Int8) forall a. Vector a -> a DV.head {-# INLINE head #-} instance Head (DV.Vector Int16) where head :: Vector Int16 -> Elem (Vector Int16) head = Vector Int16 -> Elem (Vector Int16) forall a. Vector a -> a DV.head {-# INLINE head #-} instance Head (DV.Vector Int32) where head :: Vector Int32 -> Elem (Vector Int32) head = Vector Int32 -> Elem (Vector Int32) forall a. Vector a -> a DV.head {-# INLINE head #-} instance Head (DV.Vector Int64) where head :: Vector Int64 -> Elem (Vector Int64) head = Vector Int64 -> Elem (Vector Int64) forall a. Vector a -> a DV.head {-# INLINE head #-} instance Head (DVS.Vector Int8) where head :: Vector Int8 -> Elem (Vector Int8) head = Vector Int8 -> Elem (Vector Int8) forall a. Storable a => Vector a -> a DVS.head {-# INLINE head #-} instance Head (DVS.Vector Int16) where head :: Vector Int16 -> Elem (Vector Int16) head = Vector Int16 -> Elem (Vector Int16) forall a. Storable a => Vector a -> a DVS.head {-# INLINE head #-} instance Head (DVS.Vector Int32) where head :: Vector Int32 -> Elem (Vector Int32) head = Vector Int32 -> Elem (Vector Int32) forall a. Storable a => Vector a -> a DVS.head {-# INLINE head #-} instance Head (DVS.Vector Int64) where head :: Vector Int64 -> Elem (Vector Int64) head = Vector Int64 -> Elem (Vector Int64) forall a. Storable a => Vector a -> a DVS.head {-# INLINE head #-} instance Head (DVS.Vector Int) where head :: Vector Int -> Elem (Vector Int) head = Vector Int -> Elem (Vector Int) forall a. Storable a => Vector a -> a DVS.head {-# INLINE head #-}