{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ScopedTypeVariables #-}
#if __GLASGOW_HASKELL__ >= 702
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE DeriveGeneric #-}
#endif
#if __GLASGOW_HASKELL__ >= 707
{-# LANGUAGE DataKinds #-}
#endif

#if __GLASGOW_HASKELL__ >= 800
{-# LANGUAGE DeriveLift #-}
#endif

#ifndef MIN_VERSION_hashable
#define MIN_VERSION_hashable(x,y,z) 1
#endif

#ifndef MIN_VERSION_vector
#define MIN_VERSION_vector(x,y,z) 1
#endif

#ifndef MIN_VERSION_transformers
#define MIN_VERSION_transformers(x,y,z) 1
#endif

#ifndef MIN_VERSION_base
#define MIN_VERSION_base(x,y,z) 1
#endif

-----------------------------------------------------------------------------
-- |
-- Copyright   :  (C) 2012-2015 Edward Kmett
-- License     :  BSD-style (see the file LICENSE)
--
-- Maintainer  :  Edward Kmett <ekmett@gmail.com>
-- Stability   :  experimental
-- Portability :  non-portable
--
-- 1-D Vectors
----------------------------------------------------------------------------
module Linear.V1
  ( V1(..)
  , R1(..)
  , ex
  ) where

import Control.Applicative
import Control.DeepSeq (NFData)
import Control.Monad (liftM)
import Control.Monad.Fix
import Control.Monad.Zip
import Control.Lens as Lens
import Data.Binary as Binary
import Data.Bytes.Serial
import Data.Serialize as Cereal
import Data.Data
import Data.Distributive
import Data.Foldable
import qualified Data.Foldable.WithIndex as WithIndex
import Data.Functor.Bind
import Data.Functor.Classes
import Data.Functor.Rep
import qualified Data.Functor.WithIndex as WithIndex
import Data.Hashable
#if (MIN_VERSION_hashable(1,2,5))
import Data.Hashable.Lifted
#endif
import Data.Semigroup.Foldable
import qualified Data.Traversable.WithIndex as WithIndex
#if __GLASGOW_HASKELL__ >= 707
import qualified Data.Vector as V
import Linear.V
#endif
import Foreign.Storable (Storable)
import GHC.Arr (Ix(..))
#if __GLASGOW_HASKELL__ >= 702
import GHC.Generics (Generic)
#endif
#if __GLASGOW_HASKELL__ >= 706
import GHC.Generics (Generic1)
#endif
#if __GLASGOW_HASKELL__ >= 800
import Language.Haskell.TH.Syntax (Lift)
#endif
import Linear.Metric
import Linear.Epsilon
import Linear.Vector
import Prelude hiding (sum)
import System.Random
#if !(MIN_VERSION_base(4,11,0))
import Data.Semigroup
#endif

import qualified Data.Vector.Generic.Mutable as M
import qualified Data.Vector.Generic as G
import qualified Data.Vector.Unboxed.Base as U

-- $setup
-- >>> import Control.Applicative
-- >>> import Control.Lens
-- >>> import qualified Data.Foldable as F
-- >>> let sum xs = F.sum xs

-- | A 1-dimensional vector
--
-- >>> pure 1 :: V1 Int
-- V1 1
--
-- >>> V1 2 + V1 3
-- V1 5
--
-- >>> V1 2 * V1 3
-- V1 6
--
-- >>> sum (V1 2)
-- 2

--data V2 a = V2 !a !a deriving (Eq,Ord,Show,Read,Data,Typeable)
newtype V1 a = V1 a
  deriving (V1 a -> V1 a -> Bool
(V1 a -> V1 a -> Bool) -> (V1 a -> V1 a -> Bool) -> Eq (V1 a)
forall a. Eq a => V1 a -> V1 a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: V1 a -> V1 a -> Bool
$c/= :: forall a. Eq a => V1 a -> V1 a -> Bool
== :: V1 a -> V1 a -> Bool
$c== :: forall a. Eq a => V1 a -> V1 a -> Bool
Eq,Eq (V1 a)
Eq (V1 a)
-> (V1 a -> V1 a -> Ordering)
-> (V1 a -> V1 a -> Bool)
-> (V1 a -> V1 a -> Bool)
-> (V1 a -> V1 a -> Bool)
-> (V1 a -> V1 a -> Bool)
-> (V1 a -> V1 a -> V1 a)
-> (V1 a -> V1 a -> V1 a)
-> Ord (V1 a)
V1 a -> V1 a -> Bool
V1 a -> V1 a -> Ordering
V1 a -> V1 a -> V1 a
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall a. Ord a => Eq (V1 a)
forall a. Ord a => V1 a -> V1 a -> Bool
forall a. Ord a => V1 a -> V1 a -> Ordering
forall a. Ord a => V1 a -> V1 a -> V1 a
min :: V1 a -> V1 a -> V1 a
$cmin :: forall a. Ord a => V1 a -> V1 a -> V1 a
max :: V1 a -> V1 a -> V1 a
$cmax :: forall a. Ord a => V1 a -> V1 a -> V1 a
>= :: V1 a -> V1 a -> Bool
$c>= :: forall a. Ord a => V1 a -> V1 a -> Bool
> :: V1 a -> V1 a -> Bool
$c> :: forall a. Ord a => V1 a -> V1 a -> Bool
<= :: V1 a -> V1 a -> Bool
$c<= :: forall a. Ord a => V1 a -> V1 a -> Bool
< :: V1 a -> V1 a -> Bool
$c< :: forall a. Ord a => V1 a -> V1 a -> Bool
compare :: V1 a -> V1 a -> Ordering
$ccompare :: forall a. Ord a => V1 a -> V1 a -> Ordering
$cp1Ord :: forall a. Ord a => Eq (V1 a)
Ord,Int -> V1 a -> ShowS
[V1 a] -> ShowS
V1 a -> String
(Int -> V1 a -> ShowS)
-> (V1 a -> String) -> ([V1 a] -> ShowS) -> Show (V1 a)
forall a. Show a => Int -> V1 a -> ShowS
forall a. Show a => [V1 a] -> ShowS
forall a. Show a => V1 a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [V1 a] -> ShowS
$cshowList :: forall a. Show a => [V1 a] -> ShowS
show :: V1 a -> String
$cshow :: forall a. Show a => V1 a -> String
showsPrec :: Int -> V1 a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> V1 a -> ShowS
Show,ReadPrec [V1 a]
ReadPrec (V1 a)
Int -> ReadS (V1 a)
ReadS [V1 a]
(Int -> ReadS (V1 a))
-> ReadS [V1 a]
-> ReadPrec (V1 a)
-> ReadPrec [V1 a]
-> Read (V1 a)
forall a. Read a => ReadPrec [V1 a]
forall a. Read a => ReadPrec (V1 a)
forall a. Read a => Int -> ReadS (V1 a)
forall a. Read a => ReadS [V1 a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [V1 a]
$creadListPrec :: forall a. Read a => ReadPrec [V1 a]
readPrec :: ReadPrec (V1 a)
$creadPrec :: forall a. Read a => ReadPrec (V1 a)
readList :: ReadS [V1 a]
$creadList :: forall a. Read a => ReadS [V1 a]
readsPrec :: Int -> ReadS (V1 a)
$creadsPrec :: forall a. Read a => Int -> ReadS (V1 a)
Read,Typeable (V1 a)
DataType
Constr
Typeable (V1 a)
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> V1 a -> c (V1 a))
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c (V1 a))
-> (V1 a -> Constr)
-> (V1 a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c (V1 a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (V1 a)))
-> ((forall b. Data b => b -> b) -> V1 a -> V1 a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> V1 a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> V1 a -> r)
-> (forall u. (forall d. Data d => d -> u) -> V1 a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> V1 a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> V1 a -> m (V1 a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> V1 a -> m (V1 a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> V1 a -> m (V1 a))
-> Data (V1 a)
V1 a -> DataType
V1 a -> Constr
(forall d. Data d => c (t d)) -> Maybe (c (V1 a))
(forall b. Data b => b -> b) -> V1 a -> V1 a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> V1 a -> c (V1 a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (V1 a)
forall a. Data a => Typeable (V1 a)
forall a. Data a => V1 a -> DataType
forall a. Data a => V1 a -> Constr
forall a. Data a => (forall b. Data b => b -> b) -> V1 a -> V1 a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> V1 a -> u
forall a u. Data a => (forall d. Data d => d -> u) -> V1 a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> V1 a -> r
forall a r r'.
Data a =>
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> V1 a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> V1 a -> m (V1 a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> V1 a -> m (V1 a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (V1 a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> V1 a -> c (V1 a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (V1 a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (V1 a))
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> V1 a -> u
forall u. (forall d. Data d => d -> u) -> V1 a -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> V1 a -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> V1 a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> V1 a -> m (V1 a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> V1 a -> m (V1 a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (V1 a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> V1 a -> c (V1 a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (V1 a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (V1 a))
$cV1 :: Constr
$tV1 :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> V1 a -> m (V1 a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> V1 a -> m (V1 a)
gmapMp :: (forall d. Data d => d -> m d) -> V1 a -> m (V1 a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> V1 a -> m (V1 a)
gmapM :: (forall d. Data d => d -> m d) -> V1 a -> m (V1 a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> V1 a -> m (V1 a)
gmapQi :: Int -> (forall d. Data d => d -> u) -> V1 a -> u
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> V1 a -> u
gmapQ :: (forall d. Data d => d -> u) -> V1 a -> [u]
$cgmapQ :: forall a u. Data a => (forall d. Data d => d -> u) -> V1 a -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> V1 a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> V1 a -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> V1 a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> V1 a -> r
gmapT :: (forall b. Data b => b -> b) -> V1 a -> V1 a
$cgmapT :: forall a. Data a => (forall b. Data b => b -> b) -> V1 a -> V1 a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (V1 a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (V1 a))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (V1 a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (V1 a))
dataTypeOf :: V1 a -> DataType
$cdataTypeOf :: forall a. Data a => V1 a -> DataType
toConstr :: V1 a -> Constr
$ctoConstr :: forall a. Data a => V1 a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (V1 a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (V1 a)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> V1 a -> c (V1 a)
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> V1 a -> c (V1 a)
$cp1Data :: forall a. Data a => Typeable (V1 a)
Data,Typeable,
            a -> V1 b -> V1 a
(a -> b) -> V1 a -> V1 b
(forall a b. (a -> b) -> V1 a -> V1 b)
-> (forall a b. a -> V1 b -> V1 a) -> Functor V1
forall a b. a -> V1 b -> V1 a
forall a b. (a -> b) -> V1 a -> V1 b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> V1 b -> V1 a
$c<$ :: forall a b. a -> V1 b -> V1 a
fmap :: (a -> b) -> V1 a -> V1 b
$cfmap :: forall a b. (a -> b) -> V1 a -> V1 b
Functor,Functor V1
Foldable V1
Functor V1
-> Foldable V1
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> V1 a -> f (V1 b))
-> (forall (f :: * -> *) a. Applicative f => V1 (f a) -> f (V1 a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> V1 a -> m (V1 b))
-> (forall (m :: * -> *) a. Monad m => V1 (m a) -> m (V1 a))
-> Traversable V1
(a -> f b) -> V1 a -> f (V1 b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => V1 (m a) -> m (V1 a)
forall (f :: * -> *) a. Applicative f => V1 (f a) -> f (V1 a)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> V1 a -> m (V1 b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> V1 a -> f (V1 b)
sequence :: V1 (m a) -> m (V1 a)
$csequence :: forall (m :: * -> *) a. Monad m => V1 (m a) -> m (V1 a)
mapM :: (a -> m b) -> V1 a -> m (V1 b)
$cmapM :: forall (m :: * -> *) a b. Monad m => (a -> m b) -> V1 a -> m (V1 b)
sequenceA :: V1 (f a) -> f (V1 a)
$csequenceA :: forall (f :: * -> *) a. Applicative f => V1 (f a) -> f (V1 a)
traverse :: (a -> f b) -> V1 a -> f (V1 b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> V1 a -> f (V1 b)
$cp2Traversable :: Foldable V1
$cp1Traversable :: Functor V1
Traversable,
            Num (V1 a)
Num (V1 a) -> (V1 a -> Bool) -> Epsilon (V1 a)
V1 a -> Bool
forall a. Num a -> (a -> Bool) -> Epsilon a
forall a. Epsilon a => Num (V1 a)
forall a. Epsilon a => V1 a -> Bool
nearZero :: V1 a -> Bool
$cnearZero :: forall a. Epsilon a => V1 a -> Bool
$cp1Epsilon :: forall a. Epsilon a => Num (V1 a)
Epsilon,Ptr b -> Int -> IO (V1 a)
Ptr b -> Int -> V1 a -> IO ()
Ptr (V1 a) -> IO (V1 a)
Ptr (V1 a) -> Int -> IO (V1 a)
Ptr (V1 a) -> Int -> V1 a -> IO ()
Ptr (V1 a) -> V1 a -> IO ()
V1 a -> Int
(V1 a -> Int)
-> (V1 a -> Int)
-> (Ptr (V1 a) -> Int -> IO (V1 a))
-> (Ptr (V1 a) -> Int -> V1 a -> IO ())
-> (forall b. Ptr b -> Int -> IO (V1 a))
-> (forall b. Ptr b -> Int -> V1 a -> IO ())
-> (Ptr (V1 a) -> IO (V1 a))
-> (Ptr (V1 a) -> V1 a -> IO ())
-> Storable (V1 a)
forall b. Ptr b -> Int -> IO (V1 a)
forall b. Ptr b -> Int -> V1 a -> IO ()
forall a. Storable a => Ptr (V1 a) -> IO (V1 a)
forall a. Storable a => Ptr (V1 a) -> Int -> IO (V1 a)
forall a. Storable a => Ptr (V1 a) -> Int -> V1 a -> IO ()
forall a. Storable a => Ptr (V1 a) -> V1 a -> IO ()
forall a. Storable a => V1 a -> Int
forall a b. Storable a => Ptr b -> Int -> IO (V1 a)
forall a b. Storable a => Ptr b -> Int -> V1 a -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr (V1 a) -> V1 a -> IO ()
$cpoke :: forall a. Storable a => Ptr (V1 a) -> V1 a -> IO ()
peek :: Ptr (V1 a) -> IO (V1 a)
$cpeek :: forall a. Storable a => Ptr (V1 a) -> IO (V1 a)
pokeByteOff :: Ptr b -> Int -> V1 a -> IO ()
$cpokeByteOff :: forall a b. Storable a => Ptr b -> Int -> V1 a -> IO ()
peekByteOff :: Ptr b -> Int -> IO (V1 a)
$cpeekByteOff :: forall a b. Storable a => Ptr b -> Int -> IO (V1 a)
pokeElemOff :: Ptr (V1 a) -> Int -> V1 a -> IO ()
$cpokeElemOff :: forall a. Storable a => Ptr (V1 a) -> Int -> V1 a -> IO ()
peekElemOff :: Ptr (V1 a) -> Int -> IO (V1 a)
$cpeekElemOff :: forall a. Storable a => Ptr (V1 a) -> Int -> IO (V1 a)
alignment :: V1 a -> Int
$calignment :: forall a. Storable a => V1 a -> Int
sizeOf :: V1 a -> Int
$csizeOf :: forall a. Storable a => V1 a -> Int
Storable,V1 a -> ()
(V1 a -> ()) -> NFData (V1 a)
forall a. NFData a => V1 a -> ()
forall a. (a -> ()) -> NFData a
rnf :: V1 a -> ()
$crnf :: forall a. NFData a => V1 a -> ()
NFData
#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 702
           ,(forall x. V1 a -> Rep (V1 a) x)
-> (forall x. Rep (V1 a) x -> V1 a) -> Generic (V1 a)
forall x. Rep (V1 a) x -> V1 a
forall x. V1 a -> Rep (V1 a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (V1 a) x -> V1 a
forall a x. V1 a -> Rep (V1 a) x
$cto :: forall a x. Rep (V1 a) x -> V1 a
$cfrom :: forall a x. V1 a -> Rep (V1 a) x
Generic
#endif
#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 706
           ,(forall a. V1 a -> Rep1 V1 a)
-> (forall a. Rep1 V1 a -> V1 a) -> Generic1 V1
forall a. Rep1 V1 a -> V1 a
forall a. V1 a -> Rep1 V1 a
forall k (f :: k -> *).
(forall (a :: k). f a -> Rep1 f a)
-> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f
$cto1 :: forall a. Rep1 V1 a -> V1 a
$cfrom1 :: forall a. V1 a -> Rep1 V1 a
Generic1
#endif
#if __GLASGOW_HASKELL__ >= 800
           ,V1 a -> Q Exp
V1 a -> Q (TExp (V1 a))
(V1 a -> Q Exp) -> (V1 a -> Q (TExp (V1 a))) -> Lift (V1 a)
forall a. Lift a => V1 a -> Q Exp
forall a. Lift a => V1 a -> Q (TExp (V1 a))
forall t. (t -> Q Exp) -> (t -> Q (TExp t)) -> Lift t
liftTyped :: V1 a -> Q (TExp (V1 a))
$cliftTyped :: forall a. Lift a => V1 a -> Q (TExp (V1 a))
lift :: V1 a -> Q Exp
$clift :: forall a. Lift a => V1 a -> Q Exp
Lift
#endif
           )

instance Foldable V1 where
  foldMap :: (a -> m) -> V1 a -> m
foldMap a -> m
f (V1 a
a) = a -> m
f a
a
#if __GLASGOW_HASKELL__ >= 710
  null :: V1 a -> Bool
null V1 a
_ = Bool
False
  length :: V1 a -> Int
length V1 a
_ = Int
1
#endif

#if __GLASGOW_HASKELL__ >= 707
instance Finite V1 where
  type Size V1 = 1
  toV :: V1 a -> V (Size V1) a
toV (V1 a
a) = Vector a -> V 1 a
forall k (n :: k) a. Vector a -> V n a
V (a -> Vector a
forall a. a -> Vector a
V.singleton a
a)
  fromV :: V (Size V1) a -> V1 a
fromV (V Vector a
v) = a -> V1 a
forall a. a -> V1 a
V1 (Vector a
v Vector a -> Int -> a
forall a. Vector a -> Int -> a
V.! Int
0)
#endif

instance Foldable1 V1 where
  foldMap1 :: (a -> m) -> V1 a -> m
foldMap1 a -> m
f (V1 a
a) = a -> m
f a
a
  {-# INLINE foldMap1 #-}

instance Traversable1 V1 where
  traverse1 :: (a -> f b) -> V1 a -> f (V1 b)
traverse1 a -> f b
f (V1 a
a) = b -> V1 b
forall a. a -> V1 a
V1 (b -> V1 b) -> f b -> f (V1 b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
a
  {-# INLINE traverse1 #-}

instance Apply V1 where
  V1 a -> b
f <.> :: V1 (a -> b) -> V1 a -> V1 b
<.> V1 a
x = b -> V1 b
forall a. a -> V1 a
V1 (a -> b
f a
x)
  {-# INLINE (<.>) #-}

instance Applicative V1 where
  pure :: a -> V1 a
pure = a -> V1 a
forall a. a -> V1 a
V1
  {-# INLINE pure #-}
  V1 a -> b
f <*> :: V1 (a -> b) -> V1 a -> V1 b
<*> V1 a
x = b -> V1 b
forall a. a -> V1 a
V1 (a -> b
f a
x)
  {-# INLINE (<*>) #-}

instance Additive V1 where
  zero :: V1 a
zero = a -> V1 a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
0
  {-# INLINE zero #-}
  liftU2 :: (a -> a -> a) -> V1 a -> V1 a -> V1 a
liftU2 = (a -> a -> a) -> V1 a -> V1 a -> V1 a
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2
  {-# INLINE liftU2 #-}
  liftI2 :: (a -> b -> c) -> V1 a -> V1 b -> V1 c
liftI2 = (a -> b -> c) -> V1 a -> V1 b -> V1 c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2
  {-# INLINE liftI2 #-}

instance Bind V1 where
  V1 a
a >>- :: V1 a -> (a -> V1 b) -> V1 b
>>- a -> V1 b
f = a -> V1 b
f a
a
  {-# INLINE (>>-) #-}

instance Monad V1 where
  return :: a -> V1 a
return = a -> V1 a
forall a. a -> V1 a
V1
  {-# INLINE return #-}
  V1 a
a >>= :: V1 a -> (a -> V1 b) -> V1 b
>>= a -> V1 b
f = a -> V1 b
f a
a
  {-# INLINE (>>=) #-}

instance Num a => Num (V1 a) where
  + :: V1 a -> V1 a -> V1 a
(+) = (a -> a -> a) -> V1 a -> V1 a -> V1 a
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> a
forall a. Num a => a -> a -> a
(+)
  {-# INLINE (+) #-}
  (-) = (a -> a -> a) -> V1 a -> V1 a -> V1 a
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (-)
  {-# INLINE (-) #-}
  * :: V1 a -> V1 a -> V1 a
(*) = (a -> a -> a) -> V1 a -> V1 a -> V1 a
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> a
forall a. Num a => a -> a -> a
(*)
  {-# INLINE (*) #-}
  negate :: V1 a -> V1 a
negate = (a -> a) -> V1 a -> V1 a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Num a => a -> a
negate
  {-# INLINE negate #-}
  abs :: V1 a -> V1 a
abs = (a -> a) -> V1 a -> V1 a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Num a => a -> a
abs
  {-# INLINE abs #-}
  signum :: V1 a -> V1 a
signum = (a -> a) -> V1 a -> V1 a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Num a => a -> a
signum
  {-# INLINE signum #-}
  fromInteger :: Integer -> V1 a
fromInteger = a -> V1 a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a -> V1 a) -> (Integer -> a) -> Integer -> V1 a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> a
forall a. Num a => Integer -> a
fromInteger
  {-# INLINE fromInteger #-}

instance Fractional a => Fractional (V1 a) where
  recip :: V1 a -> V1 a
recip = (a -> a) -> V1 a -> V1 a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Fractional a => a -> a
recip
  {-# INLINE recip #-}
  / :: V1 a -> V1 a -> V1 a
(/) = (a -> a -> a) -> V1 a -> V1 a -> V1 a
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> a
forall a. Fractional a => a -> a -> a
(/)
  {-# INLINE (/) #-}
  fromRational :: Rational -> V1 a
fromRational = a -> V1 a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a -> V1 a) -> (Rational -> a) -> Rational -> V1 a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rational -> a
forall a. Fractional a => Rational -> a
fromRational
  {-# INLINE fromRational #-}

instance Floating a => Floating (V1 a) where
    pi :: V1 a
pi = a -> V1 a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
forall a. Floating a => a
pi
    {-# INLINE pi #-}
    exp :: V1 a -> V1 a
exp = (a -> a) -> V1 a -> V1 a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
exp
    {-# INLINE exp #-}
    sqrt :: V1 a -> V1 a
sqrt = (a -> a) -> V1 a -> V1 a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
sqrt
    {-# INLINE sqrt #-}
    log :: V1 a -> V1 a
log = (a -> a) -> V1 a -> V1 a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
log
    {-# INLINE log #-}
    ** :: V1 a -> V1 a -> V1 a
(**) = (a -> a -> a) -> V1 a -> V1 a -> V1 a
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> a
forall a. Floating a => a -> a -> a
(**)
    {-# INLINE (**) #-}
    logBase :: V1 a -> V1 a -> V1 a
logBase = (a -> a -> a) -> V1 a -> V1 a -> V1 a
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> a
forall a. Floating a => a -> a -> a
logBase
    {-# INLINE logBase #-}
    sin :: V1 a -> V1 a
sin = (a -> a) -> V1 a -> V1 a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
sin
    {-# INLINE sin #-}
    tan :: V1 a -> V1 a
tan = (a -> a) -> V1 a -> V1 a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
tan
    {-# INLINE tan #-}
    cos :: V1 a -> V1 a
cos = (a -> a) -> V1 a -> V1 a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
cos
    {-# INLINE cos #-}
    asin :: V1 a -> V1 a
asin = (a -> a) -> V1 a -> V1 a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
asin
    {-# INLINE asin #-}
    atan :: V1 a -> V1 a
atan = (a -> a) -> V1 a -> V1 a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
atan
    {-# INLINE atan #-}
    acos :: V1 a -> V1 a
acos = (a -> a) -> V1 a -> V1 a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
acos
    {-# INLINE acos #-}
    sinh :: V1 a -> V1 a
sinh = (a -> a) -> V1 a -> V1 a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
sinh
    {-# INLINE sinh #-}
    tanh :: V1 a -> V1 a
tanh = (a -> a) -> V1 a -> V1 a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
tanh
    {-# INLINE tanh #-}
    cosh :: V1 a -> V1 a
cosh = (a -> a) -> V1 a -> V1 a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
cosh
    {-# INLINE cosh #-}
    asinh :: V1 a -> V1 a
asinh = (a -> a) -> V1 a -> V1 a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
asinh
    {-# INLINE asinh #-}
    atanh :: V1 a -> V1 a
atanh = (a -> a) -> V1 a -> V1 a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
atanh
    {-# INLINE atanh #-}
    acosh :: V1 a -> V1 a
acosh = (a -> a) -> V1 a -> V1 a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
acosh
    {-# INLINE acosh #-}

instance Hashable a => Hashable (V1 a) where
#if (MIN_VERSION_hashable(1,2,1)) || !(MIN_VERSION_hashable(1,2,0))
  hash :: V1 a -> Int
hash (V1 a
a) = a -> Int
forall a. Hashable a => a -> Int
hash a
a
#endif
  hashWithSalt :: Int -> V1 a -> Int
hashWithSalt Int
s (V1 a
a) = Int
s Int -> a -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` a
a

#if (MIN_VERSION_hashable(1,2,5))
instance Hashable1 V1 where
  liftHashWithSalt :: (Int -> a -> Int) -> Int -> V1 a -> Int
liftHashWithSalt Int -> a -> Int
h Int
s (V1 a
a) = Int -> a -> Int
h Int
s a
a
  {-# INLINE liftHashWithSalt #-}
#endif

instance Metric V1 where
  dot :: V1 a -> V1 a -> a
dot (V1 a
a) (V1 a
b) = a
a a -> a -> a
forall a. Num a => a -> a -> a
* a
b
  {-# INLINE dot #-}

-- | A space that has at least 1 basis vector '_x'.
class R1 t where
  -- |
  -- >>> V1 2 ^._x
  -- 2
  --
  -- >>> V1 2 & _x .~ 3
  -- V1 3
  --
  _x :: Lens' (t a) a

ex :: R1 t => E t
ex :: E t
ex = (forall x. Lens' (t x) x) -> E t
forall (t :: * -> *). (forall x. Lens' (t x) x) -> E t
E forall x. Lens' (t x) x
forall (t :: * -> *) a. R1 t => Lens' (t a) a
_x

instance R1 V1 where
  _x :: (a -> f a) -> V1 a -> f (V1 a)
_x a -> f a
f (V1 a
a) = a -> V1 a
forall a. a -> V1 a
V1 (a -> V1 a) -> f a -> f (V1 a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f a
f a
a
  {-# INLINE _x #-}

instance R1 Identity where
  _x :: (a -> f a) -> Identity a -> f (Identity a)
_x a -> f a
f (Identity a
a) = a -> Identity a
forall a. a -> Identity a
Identity (a -> Identity a) -> f a -> f (Identity a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f a
f a
a
  {-# INLINE _x #-}

instance Distributive V1 where
  distribute :: f (V1 a) -> V1 (f a)
distribute f (V1 a)
f = f a -> V1 (f a)
forall a. a -> V1 a
V1 ((V1 a -> a) -> f (V1 a) -> f a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(V1 a
x) -> a
x) f (V1 a)
f)
  {-# INLINE distribute #-}

instance Ix a => Ix (V1 a) where
  {-# SPECIALISE instance Ix (V1 Int) #-}

  range :: (V1 a, V1 a) -> [V1 a]
range (V1 a
l1, V1 a
u1) =
    [ a -> V1 a
forall a. a -> V1 a
V1 a
i1 | a
i1 <- (a, a) -> [a]
forall a. Ix a => (a, a) -> [a]
range (a
l1,a
u1) ]
  {-# INLINE range #-}

  unsafeIndex :: (V1 a, V1 a) -> V1 a -> Int
unsafeIndex (V1 a
l1,V1 a
u1) (V1 a
i1) = (a, a) -> a -> Int
forall a. Ix a => (a, a) -> a -> Int
unsafeIndex (a
l1,a
u1) a
i1
  {-# INLINE unsafeIndex #-}

  inRange :: (V1 a, V1 a) -> V1 a -> Bool
inRange (V1 a
l1,V1 a
u1) (V1 a
i1) = (a, a) -> a -> Bool
forall a. Ix a => (a, a) -> a -> Bool
inRange (a
l1,a
u1) a
i1
  {-# INLINE inRange #-}

instance Representable V1 where
  type Rep V1 = E V1
  tabulate :: (Rep V1 -> a) -> V1 a
tabulate Rep V1 -> a
f = a -> V1 a
forall a. a -> V1 a
V1 (Rep V1 -> a
f Rep V1
forall (t :: * -> *). R1 t => E t
ex)
  {-# INLINE tabulate #-}
  index :: V1 a -> Rep V1 -> a
index V1 a
xs (E l) = Getting a (V1 a) a -> V1 a -> a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting a (V1 a) a
forall a. Lens' (V1 a) a
l V1 a
xs
  {-# INLINE index #-}

instance WithIndex.FunctorWithIndex (E V1) V1 where
  imap :: (E V1 -> a -> b) -> V1 a -> V1 b
imap E V1 -> a -> b
f (V1 a
a) = b -> V1 b
forall a. a -> V1 a
V1 (E V1 -> a -> b
f E V1
forall (t :: * -> *). R1 t => E t
ex a
a)
  {-# INLINE imap #-}

instance WithIndex.FoldableWithIndex (E V1) V1 where
  ifoldMap :: (E V1 -> a -> m) -> V1 a -> m
ifoldMap E V1 -> a -> m
f (V1 a
a) = E V1 -> a -> m
f E V1
forall (t :: * -> *). R1 t => E t
ex a
a
  {-# INLINE ifoldMap #-}

instance WithIndex.TraversableWithIndex (E V1) V1 where
  itraverse :: (E V1 -> a -> f b) -> V1 a -> f (V1 b)
itraverse E V1 -> a -> f b
f (V1 a
a) = b -> V1 b
forall a. a -> V1 a
V1 (b -> V1 b) -> f b -> f (V1 b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> E V1 -> a -> f b
f E V1
forall (t :: * -> *). R1 t => E t
ex a
a
  {-# INLINE itraverse #-}

#if !MIN_VERSION_lens(5,0,0)
instance Lens.FunctorWithIndex     (E V1) V1 where imap      = WithIndex.imap
instance Lens.FoldableWithIndex    (E V1) V1 where ifoldMap  = WithIndex.ifoldMap
instance Lens.TraversableWithIndex (E V1) V1 where itraverse = WithIndex.itraverse
#endif

type instance Index (V1 a) = E V1
type instance IxValue (V1 a) = a

instance Ixed (V1 a) where
  ix :: Index (V1 a) -> Traversal' (V1 a) (IxValue (V1 a))
ix Index (V1 a)
i = E V1 -> forall a. Lens' (V1 a) a
forall (t :: * -> *). E t -> forall x. Lens' (t x) x
el Index (V1 a)
E V1
i
  {-# INLINE ix #-}

instance Each (V1 a) (V1 b) a b where
  each :: (a -> f b) -> V1 a -> f (V1 b)
each a -> f b
f (V1 a
x) = b -> V1 b
forall a. a -> V1 a
V1 (b -> V1 b) -> f b -> f (V1 b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
x
  {-# INLINE each #-}

newtype instance U.Vector    (V1 a) = V_V1  (U.Vector    a)
newtype instance U.MVector s (V1 a) = MV_V1 (U.MVector s a)
instance U.Unbox a => U.Unbox (V1 a)

instance U.Unbox a => M.MVector U.MVector (V1 a) where
  {-# INLINE basicLength #-}
  {-# INLINE basicUnsafeSlice #-}
  {-# INLINE basicOverlaps #-}
  {-# INLINE basicUnsafeNew #-}
  {-# INLINE basicUnsafeRead #-}
  {-# INLINE basicUnsafeWrite #-}
  basicLength :: MVector s (V1 a) -> Int
basicLength (MV_V1 v) = MVector s a -> Int
forall (v :: * -> * -> *) a s. MVector v a => v s a -> Int
M.basicLength MVector s a
v
  basicUnsafeSlice :: Int -> Int -> MVector s (V1 a) -> MVector s (V1 a)
basicUnsafeSlice Int
m Int
n (MV_V1 v) = MVector s a -> MVector s (V1 a)
forall s a. MVector s a -> MVector s (V1 a)
MV_V1 (Int -> Int -> MVector s a -> MVector s a
forall (v :: * -> * -> *) a s.
MVector v a =>
Int -> Int -> v s a -> v s a
M.basicUnsafeSlice Int
m Int
n MVector s a
v)
  basicOverlaps :: MVector s (V1 a) -> MVector s (V1 a) -> Bool
basicOverlaps (MV_V1 v) (MV_V1 u) = MVector s a -> MVector s a -> Bool
forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> v s a -> Bool
M.basicOverlaps MVector s a
v MVector s a
u
  basicUnsafeNew :: Int -> m (MVector (PrimState m) (V1 a))
basicUnsafeNew Int
n = (MVector (PrimState m) a -> MVector (PrimState m) (V1 a))
-> m (MVector (PrimState m) a) -> m (MVector (PrimState m) (V1 a))
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM MVector (PrimState m) a -> MVector (PrimState m) (V1 a)
forall s a. MVector s a -> MVector s (V1 a)
MV_V1 (Int -> m (MVector (PrimState m) a)
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
Int -> m (v (PrimState m) a)
M.basicUnsafeNew Int
n)
  basicUnsafeRead :: MVector (PrimState m) (V1 a) -> Int -> m (V1 a)
basicUnsafeRead (MV_V1 v) Int
i = (a -> V1 a) -> m a -> m (V1 a)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM a -> V1 a
forall a. a -> V1 a
V1 (MVector (PrimState m) a -> Int -> m a
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> m a
M.basicUnsafeRead MVector (PrimState m) a
v Int
i)
  basicUnsafeWrite :: MVector (PrimState m) (V1 a) -> Int -> V1 a -> m ()
basicUnsafeWrite (MV_V1 v) Int
i (V1 a
x) = MVector (PrimState m) a -> Int -> a -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> a -> m ()
M.basicUnsafeWrite MVector (PrimState m) a
v Int
i a
x
#if MIN_VERSION_vector(0,11,0)
  basicInitialize :: MVector (PrimState m) (V1 a) -> m ()
basicInitialize (MV_V1 v) = MVector (PrimState m) a -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> m ()
M.basicInitialize MVector (PrimState m) a
v
  {-# INLINE basicInitialize #-}
#endif

instance U.Unbox a => G.Vector U.Vector (V1 a) where
  {-# INLINE basicUnsafeFreeze #-}
  {-# INLINE basicUnsafeThaw   #-}
  {-# INLINE basicLength       #-}
  {-# INLINE basicUnsafeSlice  #-}
  {-# INLINE basicUnsafeIndexM #-}
  basicUnsafeFreeze :: Mutable Vector (PrimState m) (V1 a) -> m (Vector (V1 a))
basicUnsafeFreeze (MV_V1 v) = (Vector a -> Vector (V1 a)) -> m (Vector a) -> m (Vector (V1 a))
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM Vector a -> Vector (V1 a)
forall a. Vector a -> Vector (V1 a)
V_V1 (Mutable Vector (PrimState m) a -> m (Vector a)
forall (v :: * -> *) a (m :: * -> *).
(Vector v a, PrimMonad m) =>
Mutable v (PrimState m) a -> m (v a)
G.basicUnsafeFreeze MVector (PrimState m) a
Mutable Vector (PrimState m) a
v)
  basicUnsafeThaw :: Vector (V1 a) -> m (Mutable Vector (PrimState m) (V1 a))
basicUnsafeThaw (V_V1 v) = (MVector (PrimState m) a -> MVector (PrimState m) (V1 a))
-> m (MVector (PrimState m) a) -> m (MVector (PrimState m) (V1 a))
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM MVector (PrimState m) a -> MVector (PrimState m) (V1 a)
forall s a. MVector s a -> MVector s (V1 a)
MV_V1 (Vector a -> m (Mutable Vector (PrimState m) a)
forall (v :: * -> *) a (m :: * -> *).
(Vector v a, PrimMonad m) =>
v a -> m (Mutable v (PrimState m) a)
G.basicUnsafeThaw Vector a
v)
  basicLength :: Vector (V1 a) -> Int
basicLength (V_V1 v) = Vector a -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
G.basicLength Vector a
v
  basicUnsafeSlice :: Int -> Int -> Vector (V1 a) -> Vector (V1 a)
basicUnsafeSlice Int
m Int
n (V_V1 v) = Vector a -> Vector (V1 a)
forall a. Vector a -> Vector (V1 a)
V_V1 (Int -> Int -> Vector a -> Vector a
forall (v :: * -> *) a. Vector v a => Int -> Int -> v a -> v a
G.basicUnsafeSlice Int
m Int
n Vector a
v)
  basicUnsafeIndexM :: Vector (V1 a) -> Int -> m (V1 a)
basicUnsafeIndexM (V_V1 v) Int
i = (a -> V1 a) -> m a -> m (V1 a)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM a -> V1 a
forall a. a -> V1 a
V1 (Vector a -> Int -> m a
forall (v :: * -> *) a (m :: * -> *).
(Vector v a, Monad m) =>
v a -> Int -> m a
G.basicUnsafeIndexM Vector a
v Int
i)

instance MonadZip V1 where
  mzip :: V1 a -> V1 b -> V1 (a, b)
mzip (V1 a
a) (V1 b
b) = (a, b) -> V1 (a, b)
forall a. a -> V1 a
V1 (a
a, b
b)
  mzipWith :: (a -> b -> c) -> V1 a -> V1 b -> V1 c
mzipWith a -> b -> c
f (V1 a
a) (V1 b
b) = c -> V1 c
forall a. a -> V1 a
V1 (a -> b -> c
f a
a b
b)
  munzip :: V1 (a, b) -> (V1 a, V1 b)
munzip (V1 (a
a,b
b)) = (a -> V1 a
forall a. a -> V1 a
V1 a
a, b -> V1 b
forall a. a -> V1 a
V1 b
b)

instance MonadFix V1 where
  mfix :: (a -> V1 a) -> V1 a
mfix a -> V1 a
f = a -> V1 a
forall a. a -> V1 a
V1 (let V1 a
a = a -> V1 a
f a
a in a
a)

instance Bounded a => Bounded (V1 a) where
  minBound :: V1 a
minBound = a -> V1 a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
forall a. Bounded a => a
minBound
  {-# INLINE minBound #-}
  maxBound :: V1 a
maxBound = a -> V1 a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
forall a. Bounded a => a
maxBound
  {-# INLINE maxBound #-}

instance Serial1 V1 where
  serializeWith :: (a -> m ()) -> V1 a -> m ()
serializeWith a -> m ()
f (V1 a
a) = a -> m ()
f a
a
  deserializeWith :: m a -> m (V1 a)
deserializeWith m a
m = a -> V1 a
forall a. a -> V1 a
V1 (a -> V1 a) -> m a -> m (V1 a)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` m a
m

instance Serial a => Serial (V1 a) where
  serialize :: V1 a -> m ()
serialize (V1 a
a) = a -> m ()
forall a (m :: * -> *). (Serial a, MonadPut m) => a -> m ()
serialize a
a
  deserialize :: m (V1 a)
deserialize = a -> V1 a
forall a. a -> V1 a
V1 (a -> V1 a) -> m a -> m (V1 a)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` m a
forall a (m :: * -> *). (Serial a, MonadGet m) => m a
deserialize

instance Binary a => Binary (V1 a) where
  put :: V1 a -> Put
put = (a -> Put) -> V1 a -> Put
forall (f :: * -> *) (m :: * -> *) a.
(Serial1 f, MonadPut m) =>
(a -> m ()) -> f a -> m ()
serializeWith a -> Put
forall t. Binary t => t -> Put
Binary.put
  get :: Get (V1 a)
get = Get a -> Get (V1 a)
forall (f :: * -> *) (m :: * -> *) a.
(Serial1 f, MonadGet m) =>
m a -> m (f a)
deserializeWith Get a
forall t. Binary t => Get t
Binary.get

instance Serialize a => Serialize (V1 a) where
  put :: Putter (V1 a)
put = (a -> PutM ()) -> Putter (V1 a)
forall (f :: * -> *) (m :: * -> *) a.
(Serial1 f, MonadPut m) =>
(a -> m ()) -> f a -> m ()
serializeWith a -> PutM ()
forall t. Serialize t => Putter t
Cereal.put
  get :: Get (V1 a)
get = Get a -> Get (V1 a)
forall (f :: * -> *) (m :: * -> *) a.
(Serial1 f, MonadGet m) =>
m a -> m (f a)
deserializeWith Get a
forall t. Serialize t => Get t
Cereal.get

instance Random a => Random (V1 a) where
  random :: g -> (V1 a, g)
random g
g = case g -> (a, g)
forall a g. (Random a, RandomGen g) => g -> (a, g)
random g
g of (a
a, g
g') -> (a -> V1 a
forall a. a -> V1 a
V1 a
a, g
g')
  randoms :: g -> [V1 a]
randoms g
g = a -> V1 a
forall a. a -> V1 a
V1 (a -> V1 a) -> [a] -> [V1 a]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> g -> [a]
forall a g. (Random a, RandomGen g) => g -> [a]
randoms g
g
  randomR :: (V1 a, V1 a) -> g -> (V1 a, g)
randomR (V1 a
a, V1 a
b) g
g = case (a, a) -> g -> (a, g)
forall a g. (Random a, RandomGen g) => (a, a) -> g -> (a, g)
randomR (a
a, a
b) g
g of (a
a', g
g') -> (a -> V1 a
forall a. a -> V1 a
V1 a
a', g
g')
  randomRs :: (V1 a, V1 a) -> g -> [V1 a]
randomRs (V1 a
a, V1 a
b) g
g = a -> V1 a
forall a. a -> V1 a
V1 (a -> V1 a) -> [a] -> [V1 a]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (a, a) -> g -> [a]
forall a g. (Random a, RandomGen g) => (a, a) -> g -> [a]
randomRs (a
a, a
b) g
g

#if (MIN_VERSION_transformers(0,5,0)) || !(MIN_VERSION_transformers(0,4,0))
instance Eq1 V1 where
  liftEq :: (a -> b -> Bool) -> V1 a -> V1 b -> Bool
liftEq a -> b -> Bool
f (V1 a
a) (V1 b
b) = a -> b -> Bool
f a
a b
b
instance Ord1 V1 where
  liftCompare :: (a -> b -> Ordering) -> V1 a -> V1 b -> Ordering
liftCompare a -> b -> Ordering
f (V1 a
a) (V1 b
b) = a -> b -> Ordering
f a
a b
b
instance Show1 V1 where
  liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> V1 a -> ShowS
liftShowsPrec Int -> a -> ShowS
f [a] -> ShowS
_ Int
d (V1 a
a) = Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
10) (ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ String -> ShowS
showString String
"V1 " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> a -> ShowS
f Int
d a
a
instance Read1 V1 where
  liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (V1 a)
liftReadsPrec Int -> ReadS a
f ReadS [a]
_ = (String -> ReadS (V1 a)) -> Int -> ReadS (V1 a)
forall a. (String -> ReadS a) -> Int -> ReadS a
readsData ((String -> ReadS (V1 a)) -> Int -> ReadS (V1 a))
-> (String -> ReadS (V1 a)) -> Int -> ReadS (V1 a)
forall a b. (a -> b) -> a -> b
$ (Int -> ReadS a) -> String -> (a -> V1 a) -> String -> ReadS (V1 a)
forall a t.
(Int -> ReadS a) -> String -> (a -> t) -> String -> ReadS t
readsUnaryWith Int -> ReadS a
f String
"V1" a -> V1 a
forall a. a -> V1 a
V1
#else
instance Eq1 V1 where eq1 = (==)
instance Ord1 V1 where compare1 = compare
instance Show1 V1 where showsPrec1 = showsPrec
instance Read1 V1 where readsPrec1 = readsPrec
#endif

instance Field1 (V1 a) (V1 b) a b where
  _1 :: (a -> f b) -> V1 a -> f (V1 b)
_1 a -> f b
f (V1 a
x) = b -> V1 b
forall a. a -> V1 a
V1 (b -> V1 b) -> f b -> f (V1 b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
x

instance Semigroup a => Semigroup (V1 a) where
 <> :: V1 a -> V1 a -> V1 a
(<>) = (a -> a -> a) -> V1 a -> V1 a -> V1 a
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> a
forall a. Semigroup a => a -> a -> a
(<>)

instance Monoid a => Monoid (V1 a) where
  mempty :: V1 a
mempty = a -> V1 a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
forall a. Monoid a => a
mempty
#if !(MIN_VERSION_base(4,11,0))
  mappend = liftA2 mappend
#endif