#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 702
#endif
#ifndef MIN_VERSION_hashable
#define MIN_VERSION_hashable
#endif
module Linear.V0
( V0(..)
) where
import Control.Applicative
import Control.DeepSeq (NFData(rnf))
import Control.Lens
import Control.Monad.Fix
import Control.Monad.Zip
import Data.Data
import Data.Distributive
import Data.Foldable
import Data.Functor.Rep
import Data.Functor.Bind
import Data.Hashable
import Data.Ix
import Data.Semigroup
import Foreign.Storable (Storable(..))
#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 702
import GHC.Generics (Generic)
#endif
#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 706
import GHC.Generics (Generic1)
#endif
import qualified Data.Vector.Generic.Mutable as M
import qualified Data.Vector.Generic as G
import qualified Data.Vector.Unboxed.Base as U
import Linear.Metric
import Linear.Epsilon
import Linear.Vector
import Prelude hiding (sum)
data V0 a = V0 deriving (Eq,Ord,Show,Read,Ix,Enum,Data,Typeable
#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 702
,Generic
#endif
#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 706
,Generic1
#endif
)
instance Functor V0 where
fmap _ V0 = V0
_ <$ _ = V0
instance Foldable V0 where
foldMap _ V0 = mempty
instance Traversable V0 where
traverse _ V0 = pure V0
instance Apply V0 where
V0 <.> V0 = V0
instance Applicative V0 where
pure _ = V0
V0 <*> V0 = V0
instance Additive V0 where
zero = V0
liftU2 _ V0 V0 = V0
liftI2 _ V0 V0 = V0
instance Bind V0 where
V0 >>- _ = V0
instance Monad V0 where
return _ = V0
V0 >>= _ = V0
instance Num (V0 a) where
V0 + V0 = V0
V0 V0 = V0
V0 * V0 = V0
negate V0 = V0
abs V0 = V0
signum V0 = V0
fromInteger _ = V0
instance Fractional (V0 a) where
recip _ = V0
V0 / V0 = V0
fromRational _ = V0
instance Metric V0 where
dot V0 V0 = 0
instance Distributive V0 where
distribute _ = V0
instance Hashable (V0 a) where
#if (MIN_VERSION_hashable(1,2,1)) || !(MIN_VERSION_hashable(1,2,0))
hash V0 = 0
#endif
hashWithSalt s V0 = s
instance Epsilon a => Epsilon (V0 a) where
nearZero _ = True
instance Storable a => Storable (V0 a) where
sizeOf _ = 0
alignment _ = 1
poke _ V0 = return ()
peek _ = return V0
instance FunctorWithIndex (E V0) V0 where
imap _ V0 = V0
instance FoldableWithIndex (E V0) V0 where
ifoldMap _ V0 = mempty
instance TraversableWithIndex (E V0) V0 where
itraverse _ V0 = pure V0
instance Representable V0 where
type Rep V0 = E V0
tabulate _ = V0
index xs (E l) = view l xs
type instance Index (V0 a) = E V0
type instance IxValue (V0 a) = a
instance Ixed (V0 a) where
ix = el
instance Each (V0 a) (V0 b) a b where
each = traverse
newtype instance U.Vector (V0 a) = V_V0 Int
newtype instance U.MVector s (V0 a) = MV_V0 Int
instance U.Unbox (V0 a)
instance M.MVector U.MVector (V0 a) where
basicLength (MV_V0 n) = n
basicUnsafeSlice _ n _ = MV_V0 n
basicOverlaps _ _ = False
basicUnsafeNew n = return (MV_V0 n)
basicUnsafeRead _ _ = return V0
basicUnsafeWrite _ _ _ = return ()
instance G.Vector U.Vector (V0 a) where
basicUnsafeFreeze (MV_V0 n) = return (V_V0 n)
basicUnsafeThaw (V_V0 n) = return (MV_V0 n)
basicLength (V_V0 n) = n
basicUnsafeSlice _ n _ = V_V0 n
basicUnsafeIndexM _ _ = return V0
instance MonadZip V0 where
mzip V0 V0 = V0
mzipWith _ V0 V0 = V0
munzip V0 = (V0, V0)
instance MonadFix V0 where
mfix _ = V0
instance Bounded (V0 a) where
minBound = V0
maxBound = V0
instance NFData (V0 a) where
rnf V0 = ()