-- |
-- Module      : Math.Manifold.Core.PseudoAffine
-- Copyright   : (c) Justus Sagemüller 2016
-- License     : GPL v3
-- 
-- Maintainer  : (@) jsag $ hvl.no
-- Stability   : experimental
-- Portability : portable
-- 

{-# LANGUAGE FlexibleInstances        #-}
{-# LANGUAGE UndecidableInstances     #-}
{-# LANGUAGE TypeFamilies             #-}
{-# LANGUAGE FlexibleContexts         #-}
{-# LANGUAGE GADTs                    #-}
{-# LANGUAGE DefaultSignatures        #-}
{-# LANGUAGE DeriveGeneric            #-}
{-# LANGUAGE StandaloneDeriving       #-}
{-# LANGUAGE UnicodeSyntax            #-}
{-# LANGUAGE EmptyCase                #-}
{-# LANGUAGE ConstraintKinds          #-}
{-# LANGUAGE ScopedTypeVariables      #-}
{-# LANGUAGE TypeOperators            #-}
{-# LANGUAGE CPP                      #-}


module Math.Manifold.Core.PseudoAffine where

import Data.VectorSpace
import Data.AffineSpace
import Data.Basis

import Data.Fixed (mod')
import Data.Void

import Math.Manifold.Core.Types.Internal
import Math.Manifold.VectorSpace.ZeroDimensional

import Control.Applicative
import Control.Arrow

import qualified GHC.Generics as Gnrx
import GHC.Generics (Generic, (:*:)(..))

import Data.CallStack (HasCallStack)

type ℝeal r = (RealFloat r, PseudoAffine r, Semimanifold r, Needle r ~ r)

-- | This is the reified form of the property that the interior of a semimanifold
--   is a manifold. These constraints would ideally be expressed directly as
--   superclass constraints, but that would require the @UndecidableSuperclasses@
--   extension, which is not reliable yet.
-- 
-- Also, if all those equality constraints are in scope, GHC tends to infer needlessly
-- complicated types like @'Needle' ('Needle' ('Needle' x))@, which is
-- the same as just @'Needle' x@.
data SemimanifoldWitness x where
  SemimanifoldWitness ::
      ( Semimanifold (Needle x)
      , Needle (Needle x) ~ Needle x )
     => SemimanifoldWitness x

data PseudoAffineWitness x where
  PseudoAffineWitness :: PseudoAffine (Needle x)
     => SemimanifoldWitness x -> PseudoAffineWitness x

infix 6 .-~., .-~!
infixl 6 .+~^, .-~^

class AdditiveGroup (Needle x) => Semimanifold x where
  -- | The space of “ways” starting from some reference point
  --   and going to some particular target point. Hence,
  --   the name: like a compass needle, but also with an actual length.
  --   For affine spaces, 'Needle' is simply the space of
  --   line segments (aka vectors) between two points, i.e. the same as 'Diff'.
  --   The 'AffineManifold' constraint makes that requirement explicit.
  -- 
  --   This space should be isomorphic to the tangent space (and in fact
  --   serves an in many ways similar role), however whereas the tangent space
  --   of a manifold is really infinitesimally small, needles actually allow
  --   macroscopic displacements.
  type Needle x :: *
  type Needle x = GenericNeedle x
  
  -- | Generalisation of the translation operation '.+^' to possibly non-flat
  --   manifolds, instead of affine spaces.
  (.+~^) :: x -> Needle x -> x
  default (.+~^) :: ( Generic x, Semimanifold (VRep x)
                    , Needle x ~ GenericNeedle x )
        => x -> Needle x -> x
  x
p.+~^GenericNeedle Needle (VRep x)
v = forall a x. Generic a => Rep a x -> a
Gnrx.to (forall a x. Generic a => a -> Rep a x
Gnrx.from x
pforall x. Semimanifold x => x -> Needle x -> x
.+~^Needle (VRep x)
v :: Gnrx.Rep x Void)
  
  -- | Shorthand for @\\p v -> p .+~^ 'negateV' v@, which should obey the /asymptotic/ law
  --   
  -- @
  -- p .-~^ v .+~^ v ≅ p
  -- @
  --   
  --   Meaning: if @v@ is scaled down with sufficiently small factors /η/, then
  --   the difference @(p.-~^v.+~^v) .-~. p@ should eventually scale down even faster:
  --   as /O/ (/η/²). For large vectors, it may however behave differently,
  --   except in flat spaces (where all this should be equivalent to the 'AffineSpace'
  --   instance).
  (.-~^) :: x -> Needle x -> x
  x
p .-~^ Needle x
v = x
p forall x. Semimanifold x => x -> Needle x -> x
.+~^ forall v. AdditiveGroup v => v -> v
negateV Needle x
v
  
  semimanifoldWitness :: SemimanifoldWitness x
  default semimanifoldWitness ::
      ( Semimanifold (Needle x), Needle (Needle x) ~ Needle x )
     => SemimanifoldWitness x
  semimanifoldWitness = forall x.
(Semimanifold (Needle x), Needle (Needle x) ~ Needle x) =>
SemimanifoldWitness x
SemimanifoldWitness

  
-- | This is the class underlying what we understand as manifolds. 
--   
--   The interface is almost identical to the better-known
--   'AffineSpace' class, but we don't require associativity of '.+~^' with '^+^'
--   – except in an /asymptotic sense/ for small vectors.
--   
--   That innocent-looking change makes the class applicable to vastly more general types:
--   while an affine space is basically nothing but a vector space without particularly
--   designated origin, a pseudo-affine space can have nontrivial topology on the global
--   scale, and yet be used in practically the same way as an affine space. At least the
--   usual spheres and tori make good instances, perhaps the class is in fact equivalent to
--   manifolds in their usual maths definition (with an atlas of charts: a family of
--   overlapping regions of the topological space, each homeomorphic to the 'Needle'
--   vector space or some simply-connected subset thereof).
-- 
--   The 'Semimanifold' and 'PseudoAffine' classes can be @anyclass@-derived
--   or empty-instantiated based on 'Generic' for product types (including newtypes) of
--   existing 'PseudoAffine' instances. For example, the definition
--
-- @
-- data Cylinder = CylinderPolar { zCyl :: !D¹, φCyl :: !S¹ }
--   deriving (Generic, Semimanifold, PseudoAffine)
-- @
-- 
--   is equivalent to
--
-- @
-- data Cylinder = CylinderPolar { zCyl :: !D¹, φCyl :: !S¹ }
--
-- data CylinderNeedle = CylinderPolarNeedle { δzCyl :: !(Needle D¹), δφCyl :: !(Needle S¹) }
-- 
-- instance Semimanifold Cylinder where
--   type Needle Cylinder = CylinderNeedle
--   CylinderPolar z φ .+~^ CylinderPolarNeedle δz δφ
--        = CylinderPolar (z.+~^δz) (φ.+~^δφ)
-- 
-- instance PseudoAffine Cylinder where
--   CylinderPolar z₁ φ₁ .-~. CylinderPolar z₀ φ₀
--        = CylinderPolarNeedle <$> z₁.-~.z₀ <*> φ₁.-~.φ₀
--   CylinderPolar z₁ φ₁ .-~! CylinderPolar z₀ φ₀
--        = CylinderPolarNeedle (z₁.-~!z₀) (φ₁.-~.φ₀)
-- @
class Semimanifold x => PseudoAffine x where
  -- | The path reaching from one point to another.
  --   Should only yield 'Nothing' if the points are on disjoint segments
  --   of a non&#x2013;path-connected space.
  --
  --   For a connected manifold, you may define this method as
  --
  -- @
  --   p.-~.q = pure (p.-~!q)
  -- @
  (.-~.) :: x -> x -> Maybe (Needle x)
  default (.-~.) :: ( Generic x, PseudoAffine (VRep x)
                    , Needle x ~ GenericNeedle x )
        => x -> x -> Maybe (Needle x)
  x
p.-~.x
q = forall x. Needle (VRep x) -> GenericNeedle x
GenericNeedle forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a x. Generic a => a -> Rep a x
Gnrx.from x
p forall x. PseudoAffine x => x -> x -> Maybe (Needle x)
.-~. (forall a x. Generic a => a -> Rep a x
Gnrx.from x
q :: Gnrx.Rep x Void)
  
  -- | Unsafe version of '.-~.'. If the two points lie in disjoint regions,
  --   the behaviour is undefined.
  -- 
  --   Whenever @p@ and @q@ lie in a connected region, the identity
  --   
  -- @
  -- p .+~^ (q.-~.p) ≡ q
  -- @
  --   
  --   should hold (up to possible floating point rounding etc.).
  --   Meanwhile, you will in general have
  -- 
  -- @
  -- (p.+~^v).-~^v ≠ p
  -- @
  -- 
  -- (though in many instances this is at least for sufficiently small @v@ approximately equal).
  (.-~!) :: HasCallStack => x -> x -> Needle x
  default (.-~!) :: ( Generic x, PseudoAffine (VRep x)
                    , Needle x ~ GenericNeedle x )
        => x -> x -> Needle x
  x
p.-~!x
q = forall x. Needle (VRep x) -> GenericNeedle x
GenericNeedle forall a b. (a -> b) -> a -> b
$ forall a x. Generic a => a -> Rep a x
Gnrx.from x
p forall x. (PseudoAffine x, HasCallStack) => x -> x -> Needle x
.-~! (forall a x. Generic a => a -> Rep a x
Gnrx.from x
q :: Gnrx.Rep x Void)
  {-# INLINE (.-~!) #-}
  
  pseudoAffineWitness :: PseudoAffineWitness x
  default pseudoAffineWitness ::
      PseudoAffine (Needle x)
     => PseudoAffineWitness x
  pseudoAffineWitness = forall x.
PseudoAffine (Needle x) =>
SemimanifoldWitness x -> PseudoAffineWitness x
PseudoAffineWitness forall x. Semimanifold x => SemimanifoldWitness x
semimanifoldWitness
  

  
  
-- | A fibre bundle combines points in the /base space/ @b@ with points in the /fibre/
--   @f@. The type @FibreBundle b f@ is thus isomorphic to the tuple space @(b,f)@, but
--   it can have a different topology, the prime example being 'TangentBundle', where
--   nearby points may have differently-oriented tangent spaces.
data FibreBundle b f = FibreBundle
      { forall b f. FibreBundle b f -> b
baseSpace :: !b
      , forall b f. FibreBundle b f -> f
fibreSpace :: !f
      } deriving (forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall b f x. Rep (FibreBundle b f) x -> FibreBundle b f
forall b f x. FibreBundle b f -> Rep (FibreBundle b f) x
$cto :: forall b f x. Rep (FibreBundle b f) x -> FibreBundle b f
$cfrom :: forall b f x. FibreBundle b f -> Rep (FibreBundle b f) x
Generic, Int -> FibreBundle b f -> ShowS
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall b f. (Show b, Show f) => Int -> FibreBundle b f -> ShowS
forall b f. (Show b, Show f) => [FibreBundle b f] -> ShowS
forall b f. (Show b, Show f) => FibreBundle b f -> String
showList :: [FibreBundle b f] -> ShowS
$cshowList :: forall b f. (Show b, Show f) => [FibreBundle b f] -> ShowS
show :: FibreBundle b f -> String
$cshow :: forall b f. (Show b, Show f) => FibreBundle b f -> String
showsPrec :: Int -> FibreBundle b f -> ShowS
$cshowsPrec :: forall b f. (Show b, Show f) => Int -> FibreBundle b f -> ShowS
Show)

-- | Points on a manifold, combined with vectors in the respective tangent space.
type TangentBundle m = FibreBundle m (Needle m)
  


-- | Interpolate between points, approximately linearly. For
--   points that aren't close neighbours (i.e. lie in an almost
--   flat region), the pathway is basically undefined – save for
--   its end points.
-- 
--   A proper, really well-defined (on global scales) interpolation
--   only makes sense on a Riemannian manifold, as 'Data.Manifold.Riemannian.Geodesic'.
palerp ::  x. (PseudoAffine x, VectorSpace (Needle x))
    => x -> x -> Maybe (Scalar (Needle x) -> x)
palerp :: forall x.
(PseudoAffine x, VectorSpace (Needle x)) =>
x -> x -> Maybe (Scalar (Needle x) -> x)
palerp x
p₀ x
p₁ = case x
p₁forall x. PseudoAffine x => x -> x -> Maybe (Needle x)
.-~.x
p₀ of
  Just Needle x
v -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ \Scalar (Needle x)
t -> x
p₀ forall x. Semimanifold x => x -> Needle x -> x
.+~^ Scalar (Needle x)
t forall v. VectorSpace v => Scalar v -> v -> v
*^ Needle x
v
  Maybe (Needle x)
_      -> forall a. Maybe a
Nothing

-- | Like 'palerp', but actually restricted to the interval between the points,
--   with a signature like 'Data.Manifold.Riemannian.geodesicBetween'
--   rather than 'Data.AffineSpace.alerp'.
palerpB ::  x. (PseudoAffine x, VectorSpace (Needle x), Scalar (Needle x) ~ )
                  => x -> x -> Maybe ( -> x)
palerpB :: forall x.
(PseudoAffine x, VectorSpace (Needle x),
 Scalar (Needle x) ~ Double) =>
x -> x -> Maybe (D¹ -> x)
palerpB x
p₀ x
p₁ = case x
p₁forall x. PseudoAffine x => x -> x -> Maybe (Needle x)
.-~.x
p₀ of
  Just Needle x
v -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ \( Double
t) -> x
p₀ forall x. Semimanifold x => x -> Needle x -> x
.+~^ ((Double
tforall a. Num a => a -> a -> a
+Double
1)forall a. Fractional a => a -> a -> a
/Double
2) forall v. VectorSpace v => Scalar v -> v -> v
*^ Needle x
v
  Maybe (Needle x)
_ -> forall a. Maybe a
Nothing

-- | Like 'alerp', but actually restricted to the interval between the points.
alerpB ::  x. (AffineSpace x, VectorSpace (Diff x), Scalar (Diff x) ~ )
                   => x -> x ->  -> x
alerpB :: forall x.
(AffineSpace x, VectorSpace (Diff x), Scalar (Diff x) ~ Double) =>
x -> x -> D¹ -> x
alerpB x
p1 x
p2 = case x
p2 forall p. AffineSpace p => p -> p -> Diff p
.-. x
p1 of
  Diff x
v -> \( Double
t) -> x
p1 forall p. AffineSpace p => p -> Diff p -> p
.+^ ((Double
tforall a. Num a => a -> a -> a
+Double
1)forall a. Fractional a => a -> a -> a
/Double
2) forall v. VectorSpace v => Scalar v -> v -> v
*^ Diff x
v



#define deriveAffine(c,t)               \
instance (c) => Semimanifold (t) where { \
  type Needle (t) = Diff (t);             \
  (.+~^) = (.+^) };                        \
instance (c) => PseudoAffine (t) where {    \
  a.-~.b = pure (a.-.b);                     \
  (.-~!) = (.-.) }

deriveAffine((),Double)
deriveAffine((),Float)
deriveAffine((),Rational)

instance Semimanifold (ZeroDim k) where
  type Needle (ZeroDim k) = ZeroDim k
  ZeroDim k
Origin .+~^ :: ZeroDim k -> Needle (ZeroDim k) -> ZeroDim k
.+~^ ZeroDim k
Needle (ZeroDim k)
Origin = forall s. ZeroDim s
Origin
  ZeroDim k
Origin .-~^ :: ZeroDim k -> Needle (ZeroDim k) -> ZeroDim k
.-~^ ZeroDim k
Needle (ZeroDim k)
Origin = forall s. ZeroDim s
Origin
instance PseudoAffine (ZeroDim k) where
  ZeroDim k
Origin .-~! :: HasCallStack => ZeroDim k -> ZeroDim k -> Needle (ZeroDim k)
.-~! ZeroDim k
Origin = forall s. ZeroDim s
Origin
  ZeroDim k
Origin .-~. :: ZeroDim k -> ZeroDim k -> Maybe (Needle (ZeroDim k))
.-~. ZeroDim k
Origin = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall s. ZeroDim s
Origin

instance  a b . (Semimanifold a, Semimanifold b) => Semimanifold (a,b) where
  type Needle (a,b) = (Needle a, Needle b)
  (a
a,b
b).+~^ :: (a, b) -> Needle (a, b) -> (a, b)
.+~^(Needle a
v,Needle b
w) = (a
aforall x. Semimanifold x => x -> Needle x -> x
.+~^Needle a
v, b
bforall x. Semimanifold x => x -> Needle x -> x
.+~^Needle b
w)
  (a
a,b
b).-~^ :: (a, b) -> Needle (a, b) -> (a, b)
.-~^(Needle a
v,Needle b
w) = (a
aforall x. Semimanifold x => x -> Needle x -> x
.-~^Needle a
v, b
bforall x. Semimanifold x => x -> Needle x -> x
.-~^Needle b
w)
  semimanifoldWitness :: SemimanifoldWitness (a, b)
semimanifoldWitness = case ( forall x. Semimanifold x => SemimanifoldWitness x
semimanifoldWitness :: SemimanifoldWitness a
                             , forall x. Semimanifold x => SemimanifoldWitness x
semimanifoldWitness :: SemimanifoldWitness b ) of
     (SemimanifoldWitness a
SemimanifoldWitness, SemimanifoldWitness b
SemimanifoldWitness) -> forall x.
(Semimanifold (Needle x), Needle (Needle x) ~ Needle x) =>
SemimanifoldWitness x
SemimanifoldWitness
instance (PseudoAffine a, PseudoAffine b) => PseudoAffine (a,b) where
  (a
a,b
b).-~. :: (a, b) -> (a, b) -> Maybe (Needle (a, b))
.-~.(a
c,b
d) = forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (,) (a
aforall x. PseudoAffine x => x -> x -> Maybe (Needle x)
.-~.a
c) (b
bforall x. PseudoAffine x => x -> x -> Maybe (Needle x)
.-~.b
d)
  (a
a,b
b).-~! :: HasCallStack => (a, b) -> (a, b) -> Needle (a, b)
.-~!(a
c,b
d) = (a
aforall x. (PseudoAffine x, HasCallStack) => x -> x -> Needle x
.-~!a
c, b
bforall x. (PseudoAffine x, HasCallStack) => x -> x -> Needle x
.-~!b
d)
  pseudoAffineWitness :: PseudoAffineWitness (a, b)
pseudoAffineWitness = case ( forall x. PseudoAffine x => PseudoAffineWitness x
pseudoAffineWitness :: PseudoAffineWitness a
                             , forall x. PseudoAffine x => PseudoAffineWitness x
pseudoAffineWitness :: PseudoAffineWitness b ) of
             (  PseudoAffineWitness (SemimanifoldWitness a
SemimanifoldWitness)
              , PseudoAffineWitness (SemimanifoldWitness b
SemimanifoldWitness) )
              ->forall x.
PseudoAffine (Needle x) =>
SemimanifoldWitness x -> PseudoAffineWitness x
PseudoAffineWitness (forall x.
(Semimanifold (Needle x), Needle (Needle x) ~ Needle x) =>
SemimanifoldWitness x
SemimanifoldWitness)

instance  a b c . (Semimanifold a, Semimanifold b, Semimanifold c)
                          => Semimanifold (a,b,c) where
  type Needle (a,b,c) = (Needle a, Needle b, Needle c)
  (a
a,b
b,c
c).+~^ :: (a, b, c) -> Needle (a, b, c) -> (a, b, c)
.+~^(Needle a
v,Needle b
w,Needle c
x) = (a
aforall x. Semimanifold x => x -> Needle x -> x
.+~^Needle a
v, b
bforall x. Semimanifold x => x -> Needle x -> x
.+~^Needle b
w, c
cforall x. Semimanifold x => x -> Needle x -> x
.+~^Needle c
x)
  (a
a,b
b,c
c).-~^ :: (a, b, c) -> Needle (a, b, c) -> (a, b, c)
.-~^(Needle a
v,Needle b
w,Needle c
x) = (a
aforall x. Semimanifold x => x -> Needle x -> x
.-~^Needle a
v, b
bforall x. Semimanifold x => x -> Needle x -> x
.-~^Needle b
w, c
cforall x. Semimanifold x => x -> Needle x -> x
.-~^Needle c
x)
  semimanifoldWitness :: SemimanifoldWitness (a, b, c)
semimanifoldWitness = case ( forall x. Semimanifold x => SemimanifoldWitness x
semimanifoldWitness :: SemimanifoldWitness a
                             , forall x. Semimanifold x => SemimanifoldWitness x
semimanifoldWitness :: SemimanifoldWitness b
                             , forall x. Semimanifold x => SemimanifoldWitness x
semimanifoldWitness :: SemimanifoldWitness c ) of
             ( SemimanifoldWitness a
SemimanifoldWitness, SemimanifoldWitness b
SemimanifoldWitness, SemimanifoldWitness c
SemimanifoldWitness )
                   -> forall x.
(Semimanifold (Needle x), Needle (Needle x) ~ Needle x) =>
SemimanifoldWitness x
SemimanifoldWitness
instance (PseudoAffine a, PseudoAffine b, PseudoAffine c) => PseudoAffine (a,b,c) where
  (a
a,b
b,c
c).-~! :: HasCallStack => (a, b, c) -> (a, b, c) -> Needle (a, b, c)
.-~!(a
d,b
e,c
f) = (a
aforall x. (PseudoAffine x, HasCallStack) => x -> x -> Needle x
.-~!a
d, b
bforall x. (PseudoAffine x, HasCallStack) => x -> x -> Needle x
.-~!b
e, c
cforall x. (PseudoAffine x, HasCallStack) => x -> x -> Needle x
.-~!c
f)
  (a
a,b
b,c
c).-~. :: (a, b, c) -> (a, b, c) -> Maybe (Needle (a, b, c))
.-~.(a
d,b
e,c
f) = forall (f :: * -> *) a b c d.
Applicative f =>
(a -> b -> c -> d) -> f a -> f b -> f c -> f d
liftA3 (,,) (a
aforall x. PseudoAffine x => x -> x -> Maybe (Needle x)
.-~.a
d) (b
bforall x. PseudoAffine x => x -> x -> Maybe (Needle x)
.-~.b
e) (c
cforall x. PseudoAffine x => x -> x -> Maybe (Needle x)
.-~.c
f)
  pseudoAffineWitness :: PseudoAffineWitness (a, b, c)
pseudoAffineWitness = case ( forall x. PseudoAffine x => PseudoAffineWitness x
pseudoAffineWitness :: PseudoAffineWitness a
                             , forall x. PseudoAffine x => PseudoAffineWitness x
pseudoAffineWitness :: PseudoAffineWitness b
                             , forall x. PseudoAffine x => PseudoAffineWitness x
pseudoAffineWitness :: PseudoAffineWitness c ) of
             (  PseudoAffineWitness SemimanifoldWitness a
SemimanifoldWitness
              , PseudoAffineWitness SemimanifoldWitness b
SemimanifoldWitness
              , PseudoAffineWitness SemimanifoldWitness c
SemimanifoldWitness )
              ->forall x.
PseudoAffine (Needle x) =>
SemimanifoldWitness x -> PseudoAffineWitness x
PseudoAffineWitness forall x.
(Semimanifold (Needle x), Needle (Needle x) ~ Needle x) =>
SemimanifoldWitness x
SemimanifoldWitness







instance Semimanifold (ℝP⁰_ r) where
  type Needle (ℝP⁰_ r) = ZeroDim r
  ℝP⁰_ r
p .+~^ :: ℝP⁰_ r -> Needle (ℝP⁰_ r) -> ℝP⁰_ r
.+~^ ZeroDim r
Needle (ℝP⁰_ r)
Origin = ℝP⁰_ r
p
  ℝP⁰_ r
p .-~^ :: ℝP⁰_ r -> Needle (ℝP⁰_ r) -> ℝP⁰_ r
.-~^ ZeroDim r
Needle (ℝP⁰_ r)
Origin = ℝP⁰_ r
p
instance PseudoAffine (ℝP⁰_ r) where
  ℝP⁰_ r
ℝPZero .-~! :: HasCallStack => ℝP⁰_ r -> ℝP⁰_ r -> Needle (ℝP⁰_ r)
.-~! ℝP⁰_ r
ℝPZero = forall s. ZeroDim s
Origin
  ℝP⁰_ r
ℝPZero .-~. :: ℝP⁰_ r -> ℝP⁰_ r -> Maybe (Needle (ℝP⁰_ r))
.-~. ℝP⁰_ r
ℝPZero = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall s. ZeroDim s
Origin

instance ℝeal r => Semimanifold (ℝP¹_ r) where
  type Needle (ℝP¹_ r) = r
  HemisphereℝP¹Polar r
r₀ .+~^ :: ℝP¹_ r -> Needle (ℝP¹_ r) -> ℝP¹_ r
.+~^ Needle (ℝP¹_ r)
δr = forall r. r -> ℝP¹_ r
HemisphereℝP¹Polar forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall r. RealFloat r => r -> r
toℝP¹range forall a b. (a -> b) -> a -> b
$ r
r₀ forall a. Num a => a -> a -> a
+ Needle (ℝP¹_ r)
δr
instance ℝeal r => PseudoAffine (ℝP¹_ r) where
  ℝP¹_ r
p.-~. :: ℝP¹_ r -> ℝP¹_ r -> Maybe (Needle (ℝP¹_ r))
.-~.ℝP¹_ r
q = forall (f :: * -> *) a. Applicative f => a -> f a
pure (ℝP¹_ r
pforall x. (PseudoAffine x, HasCallStack) => x -> x -> Needle x
.-~!ℝP¹_ r
q)
  HemisphereℝP¹Polar r
φ₁ .-~! :: HasCallStack => ℝP¹_ r -> ℝP¹_ r -> Needle (ℝP¹_ r)
.-~! HemisphereℝP¹Polar r
φ₀
     | r
δφ forall a. Ord a => a -> a -> Bool
> forall a. Floating a => a
piforall a. Fractional a => a -> a -> a
/r
2     = r
δφ forall a. Num a => a -> a -> a
- forall a. Floating a => a
pi
     | r
δφ forall a. Ord a => a -> a -> Bool
< (-forall a. Floating a => a
piforall a. Fractional a => a -> a -> a
/r
2)  = r
δφ forall a. Num a => a -> a -> a
+ forall a. Floating a => a
pi
     | Bool
otherwise     = r
δφ
   where δφ :: r
δφ = r
φ₁ forall a. Num a => a -> a -> a
- r
φ₀






tau :: RealFloat r => r
tau :: forall r. RealFloat r => r
tau = r
2 forall a. Num a => a -> a -> a
* forall a. Floating a => a
pi

toS¹range :: RealFloat r => r -> r
toS¹range :: forall r. RealFloat r => r -> r
toS¹range r
φ = (r
φforall a. Num a => a -> a -> a
+forall a. Floating a => a
pi)forall a. Real a => a -> a -> a
`mod'`forall r. RealFloat r => r
tau forall a. Num a => a -> a -> a
- forall a. Floating a => a
pi

toℝP¹range :: RealFloat r => r -> r
toℝP¹range :: forall r. RealFloat r => r -> r
toℝP¹range r
φ = (r
φforall a. Num a => a -> a -> a
+forall a. Floating a => a
piforall a. Fractional a => a -> a -> a
/r
2)forall a. Real a => a -> a -> a
`mod'`forall a. Floating a => a
pi forall a. Num a => a -> a -> a
- forall a. Floating a => a
piforall a. Fractional a => a -> a -> a
/r
2

toUnitrange :: RealFloat r => r -> r
toUnitrange :: forall r. RealFloat r => r -> r
toUnitrange r
φ = (r
φforall a. Num a => a -> a -> a
+r
1)forall a. Real a => a -> a -> a
`mod'`r
2 forall a. Num a => a -> a -> a
- r
1






data NeedleProductSpace f g p = NeedleProductSpace
            !(Needle (f p)) !(Needle (g p)) deriving (forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (f :: * -> *) (g :: * -> *) p x.
Rep (NeedleProductSpace f g p) x -> NeedleProductSpace f g p
forall (f :: * -> *) (g :: * -> *) p x.
NeedleProductSpace f g p -> Rep (NeedleProductSpace f g p) x
$cto :: forall (f :: * -> *) (g :: * -> *) p x.
Rep (NeedleProductSpace f g p) x -> NeedleProductSpace f g p
$cfrom :: forall (f :: * -> *) (g :: * -> *) p x.
NeedleProductSpace f g p -> Rep (NeedleProductSpace f g p) x
Generic)
instance (Semimanifold (f p), Semimanifold (g p))
    => AdditiveGroup (NeedleProductSpace f g p)
instance ( Semimanifold (f p), Semimanifold (g p)
         , VectorSpace (Needle (f p)), VectorSpace (Needle (g p))
         , Scalar (Needle (f p)) ~ Scalar (Needle (g p)) )
    => VectorSpace (NeedleProductSpace f g p)
instance ( Semimanifold (f p), Semimanifold (g p)
         , InnerSpace (Needle (f p)), InnerSpace (Needle (g p))
         , Scalar (Needle (f p)) ~ Scalar (Needle (g p))
         , Num (Scalar (Needle (f p))) )
    => InnerSpace (NeedleProductSpace f g p)
instance (Semimanifold (f p), Semimanifold (g p))
    => AffineSpace (NeedleProductSpace f g p) where
  type Diff (NeedleProductSpace f g p) = NeedleProductSpace f g p
  .+^ :: NeedleProductSpace f g p
-> Diff (NeedleProductSpace f g p) -> NeedleProductSpace f g p
(.+^) = forall v. AdditiveGroup v => v -> v -> v
(^+^)
  .-. :: NeedleProductSpace f g p
-> NeedleProductSpace f g p -> Diff (NeedleProductSpace f g p)
(.-.) = forall v. AdditiveGroup v => v -> v -> v
(^-^)
instance (Semimanifold (f p), Semimanifold (g p))
    => Semimanifold (NeedleProductSpace f g p) where
  type Needle (NeedleProductSpace f g p) = NeedleProductSpace f g p
  .+~^ :: NeedleProductSpace f g p
-> Needle (NeedleProductSpace f g p) -> NeedleProductSpace f g p
(.+~^) = forall v. AdditiveGroup v => v -> v -> v
(^+^)
instance (PseudoAffine (f p), PseudoAffine (g p))
    => PseudoAffine (NeedleProductSpace f g p) where
  NeedleProductSpace f g p
p.-~. :: NeedleProductSpace f g p
-> NeedleProductSpace f g p
-> Maybe (Needle (NeedleProductSpace f g p))
.-~.NeedleProductSpace f g p
q = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ NeedleProductSpace f g p
pforall p. AffineSpace p => p -> p -> Diff p
.-.NeedleProductSpace f g p
q
  .-~! :: HasCallStack =>
NeedleProductSpace f g p
-> NeedleProductSpace f g p -> Needle (NeedleProductSpace f g p)
(.-~!) = forall p. AffineSpace p => p -> p -> Diff p
(.-.)
instance ( Semimanifold (f p), Semimanifold (g p)
         , HasBasis (Needle (f p)), HasBasis (Needle (g p))
         , Scalar (Needle (f p)) ~ Scalar (Needle (g p)) )
    => HasBasis (NeedleProductSpace f g p) where
  type Basis (NeedleProductSpace f g p) = Either (Basis (Needle (f p)))
                                                     (Basis (Needle (g p)))
  basisValue :: Basis (NeedleProductSpace f g p) -> NeedleProductSpace f g p
basisValue (Left Basis (Needle (f p))
bf) = forall (f :: * -> *) (g :: * -> *) p.
Needle (f p) -> Needle (g p) -> NeedleProductSpace f g p
NeedleProductSpace (forall v. HasBasis v => Basis v -> v
basisValue Basis (Needle (f p))
bf) forall v. AdditiveGroup v => v
zeroV
  basisValue (Right Basis (Needle (g p))
bg) = forall (f :: * -> *) (g :: * -> *) p.
Needle (f p) -> Needle (g p) -> NeedleProductSpace f g p
NeedleProductSpace forall v. AdditiveGroup v => v
zeroV (forall v. HasBasis v => Basis v -> v
basisValue Basis (Needle (g p))
bg)
  decompose :: NeedleProductSpace f g p
-> [(Basis (NeedleProductSpace f g p),
     Scalar (NeedleProductSpace f g p))]
decompose (NeedleProductSpace Needle (f p)
vf Needle (g p)
vg)
        = forall a b. (a -> b) -> [a] -> [b]
map (forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first forall a b. a -> Either a b
Left) (forall v. HasBasis v => v -> [(Basis v, Scalar v)]
decompose Needle (f p)
vf) forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map (forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first forall a b. b -> Either a b
Right) (forall v. HasBasis v => v -> [(Basis v, Scalar v)]
decompose Needle (g p)
vg)
  decompose' :: NeedleProductSpace f g p
-> Basis (NeedleProductSpace f g p)
-> Scalar (NeedleProductSpace f g p)
decompose' (NeedleProductSpace Needle (f p)
vf Needle (g p)
_) (Left Basis (Needle (f p))
bf) = forall v. HasBasis v => v -> Basis v -> Scalar v
decompose' Needle (f p)
vf Basis (Needle (f p))
bf
  decompose' (NeedleProductSpace Needle (f p)
_ Needle (g p)
vg) (Right Basis (Needle (g p))
bg) = forall v. HasBasis v => v -> Basis v -> Scalar v
decompose' Needle (g p)
vg Basis (Needle (g p))
bg




newtype GenericNeedle x = GenericNeedle {forall x. GenericNeedle x -> Needle (VRep x)
getGenericNeedle :: Needle (VRep x)}
    deriving (forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall x x. Rep (GenericNeedle x) x -> GenericNeedle x
forall x x. GenericNeedle x -> Rep (GenericNeedle x) x
$cto :: forall x x. Rep (GenericNeedle x) x -> GenericNeedle x
$cfrom :: forall x x. GenericNeedle x -> Rep (GenericNeedle x) x
Generic)

instance AdditiveGroup (Needle (VRep x)) => AdditiveGroup (GenericNeedle x) where
  GenericNeedle Needle (VRep x)
v ^+^ :: GenericNeedle x -> GenericNeedle x -> GenericNeedle x
^+^ GenericNeedle Needle (VRep x)
w = forall x. Needle (VRep x) -> GenericNeedle x
GenericNeedle forall a b. (a -> b) -> a -> b
$ Needle (VRep x)
v forall v. AdditiveGroup v => v -> v -> v
^+^ Needle (VRep x)
w
  negateV :: GenericNeedle x -> GenericNeedle x
negateV = forall x. Needle (VRep x) -> GenericNeedle x
GenericNeedle forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall v. AdditiveGroup v => v -> v
negateV forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall x. GenericNeedle x -> Needle (VRep x)
getGenericNeedle
  zeroV :: GenericNeedle x
zeroV = forall x. Needle (VRep x) -> GenericNeedle x
GenericNeedle forall v. AdditiveGroup v => v
zeroV
instance VectorSpace (Needle (VRep x)) => VectorSpace (GenericNeedle x) where
  type Scalar (GenericNeedle x) = Scalar (Needle (VRep x))
  *^ :: Scalar (GenericNeedle x) -> GenericNeedle x -> GenericNeedle x
(*^) Scalar (GenericNeedle x)
μ = forall x. Needle (VRep x) -> GenericNeedle x
GenericNeedle forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall v. VectorSpace v => Scalar v -> v -> v
(*^) Scalar (GenericNeedle x)
μ forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall x. GenericNeedle x -> Needle (VRep x)
getGenericNeedle
instance InnerSpace (Needle (VRep x)) => InnerSpace (GenericNeedle x) where
  GenericNeedle Needle (VRep x)
v <.> :: GenericNeedle x -> GenericNeedle x -> Scalar (GenericNeedle x)
<.> GenericNeedle Needle (VRep x)
w = Needle (VRep x)
v forall v. InnerSpace v => v -> v -> Scalar v
<.> Needle (VRep x)
w
instance AdditiveGroup (Needle (VRep x)) => AffineSpace (GenericNeedle x) where
  type Diff (GenericNeedle x) = GenericNeedle x
  .-. :: GenericNeedle x -> GenericNeedle x -> Diff (GenericNeedle x)
(.-.) = forall v. AdditiveGroup v => v -> v -> v
(^-^)
  .+^ :: GenericNeedle x -> Diff (GenericNeedle x) -> GenericNeedle x
(.+^) = forall v. AdditiveGroup v => v -> v -> v
(^+^)
instance AdditiveGroup (Needle (VRep x)) => Semimanifold (GenericNeedle x) where
  type Needle (GenericNeedle x) = GenericNeedle x
  .+~^ :: GenericNeedle x -> Needle (GenericNeedle x) -> GenericNeedle x
(.+~^) = forall p. AffineSpace p => p -> Diff p -> p
(.+^)
instance AdditiveGroup (Needle (VRep x)) => PseudoAffine (GenericNeedle x) where
  GenericNeedle Needle (VRep x)
v .-~. :: GenericNeedle x
-> GenericNeedle x -> Maybe (Needle (GenericNeedle x))
.-~. GenericNeedle Needle (VRep x)
w = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall x. Needle (VRep x) -> GenericNeedle x
GenericNeedle (Needle (VRep x)
v forall v. AdditiveGroup v => v -> v -> v
^-^ Needle (VRep x)
w)
  GenericNeedle Needle (VRep x)
v .-~! :: HasCallStack =>
GenericNeedle x -> GenericNeedle x -> Needle (GenericNeedle x)
.-~! GenericNeedle Needle (VRep x)
w = forall x. Needle (VRep x) -> GenericNeedle x
GenericNeedle (Needle (VRep x)
v forall v. AdditiveGroup v => v -> v -> v
^-^ Needle (VRep x)
w)




instance  a s . Semimanifold a => Semimanifold (Gnrx.Rec0 a s) where
  type Needle (Gnrx.Rec0 a s) = Needle a
  semimanifoldWitness :: SemimanifoldWitness (Rec0 a s)
semimanifoldWitness = case forall x. Semimanifold x => SemimanifoldWitness x
semimanifoldWitness :: SemimanifoldWitness a of
           SemimanifoldWitness a
SemimanifoldWitness
               -> forall x.
(Semimanifold (Needle x), Needle (Needle x) ~ Needle x) =>
SemimanifoldWitness x
SemimanifoldWitness
  Gnrx.K1 a
p .+~^ :: Rec0 a s -> Needle (Rec0 a s) -> Rec0 a s
.+~^ Needle (Rec0 a s)
v = forall k i c (p :: k). c -> K1 i c p
Gnrx.K1 forall a b. (a -> b) -> a -> b
$ a
p forall x. Semimanifold x => x -> Needle x -> x
.+~^ Needle (Rec0 a s)
v
instance  f p i c . Semimanifold (f p) => Semimanifold (Gnrx.M1 i c f p) where
  type Needle (Gnrx.M1 i c f p) = Needle (f p)
  semimanifoldWitness :: SemimanifoldWitness (M1 i c f p)
semimanifoldWitness = case forall x. Semimanifold x => SemimanifoldWitness x
semimanifoldWitness :: SemimanifoldWitness (f p) of
           SemimanifoldWitness (f p)
SemimanifoldWitness -> forall x.
(Semimanifold (Needle x), Needle (Needle x) ~ Needle x) =>
SemimanifoldWitness x
SemimanifoldWitness
  Gnrx.M1 f p
p.+~^ :: M1 i c f p -> Needle (M1 i c f p) -> M1 i c f p
.+~^Needle (M1 i c f p)
v = forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
Gnrx.M1 forall a b. (a -> b) -> a -> b
$ f p
pforall x. Semimanifold x => x -> Needle x -> x
.+~^Needle (M1 i c f p)
v
instance  f g p . (Semimanifold (f p), Semimanifold (g p))
         => Semimanifold ((f :*: g) p) where
  type Needle ((f:*:g) p) = NeedleProductSpace f g p
  semimanifoldWitness :: SemimanifoldWitness ((:*:) f g p)
semimanifoldWitness = case ( forall x. Semimanifold x => SemimanifoldWitness x
semimanifoldWitness :: SemimanifoldWitness (f p)
                             , forall x. Semimanifold x => SemimanifoldWitness x
semimanifoldWitness :: SemimanifoldWitness (g p) ) of
           ( SemimanifoldWitness (f p)
SemimanifoldWitness, SemimanifoldWitness (g p)
SemimanifoldWitness )
               -> forall x.
(Semimanifold (Needle x), Needle (Needle x) ~ Needle x) =>
SemimanifoldWitness x
SemimanifoldWitness
  (f p
p:*:g p
q).+~^ :: (:*:) f g p -> Needle ((:*:) f g p) -> (:*:) f g p
.+~^(NeedleProductSpace Needle (f p)
v Needle (g p)
w) = (f p
pforall x. Semimanifold x => x -> Needle x -> x
.+~^Needle (f p)
v) forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
:*: (g p
qforall x. Semimanifold x => x -> Needle x -> x
.+~^Needle (g p)
w)




instance  a s . PseudoAffine a => PseudoAffine (Gnrx.Rec0 a s) where
  pseudoAffineWitness :: PseudoAffineWitness (Rec0 a s)
pseudoAffineWitness = case forall x. PseudoAffine x => PseudoAffineWitness x
pseudoAffineWitness :: PseudoAffineWitness a of
           PseudoAffineWitness SemimanifoldWitness a
SemimanifoldWitness
               -> forall x.
PseudoAffine (Needle x) =>
SemimanifoldWitness x -> PseudoAffineWitness x
PseudoAffineWitness forall x.
(Semimanifold (Needle x), Needle (Needle x) ~ Needle x) =>
SemimanifoldWitness x
SemimanifoldWitness
  Gnrx.K1 a
p .-~. :: Rec0 a s -> Rec0 a s -> Maybe (Needle (Rec0 a s))
.-~. Gnrx.K1 a
q = a
p forall x. PseudoAffine x => x -> x -> Maybe (Needle x)
.-~. a
q
  Gnrx.K1 a
p .-~! :: HasCallStack => Rec0 a s -> Rec0 a s -> Needle (Rec0 a s)
.-~! Gnrx.K1 a
q = a
p forall x. (PseudoAffine x, HasCallStack) => x -> x -> Needle x
.-~! a
q
instance  f p i c . PseudoAffine (f p) => PseudoAffine (Gnrx.M1 i c f p) where
  pseudoAffineWitness :: PseudoAffineWitness (M1 i c f p)
pseudoAffineWitness = case forall x. PseudoAffine x => PseudoAffineWitness x
pseudoAffineWitness :: PseudoAffineWitness (f p) of
           PseudoAffineWitness SemimanifoldWitness (f p)
SemimanifoldWitness
               -> forall x.
PseudoAffine (Needle x) =>
SemimanifoldWitness x -> PseudoAffineWitness x
PseudoAffineWitness forall x.
(Semimanifold (Needle x), Needle (Needle x) ~ Needle x) =>
SemimanifoldWitness x
SemimanifoldWitness
  Gnrx.M1 f p
p .-~. :: M1 i c f p -> M1 i c f p -> Maybe (Needle (M1 i c f p))
.-~. Gnrx.M1 f p
q = f p
p forall x. PseudoAffine x => x -> x -> Maybe (Needle x)
.-~. f p
q
  Gnrx.M1 f p
p .-~! :: HasCallStack => M1 i c f p -> M1 i c f p -> Needle (M1 i c f p)
.-~! Gnrx.M1 f p
q = f p
p forall x. (PseudoAffine x, HasCallStack) => x -> x -> Needle x
.-~! f p
q
instance  f g p . (PseudoAffine (f p), PseudoAffine (g p))
         => PseudoAffine ((f :*: g) p) where
  pseudoAffineWitness :: PseudoAffineWitness ((:*:) f g p)
pseudoAffineWitness = case ( forall x. PseudoAffine x => PseudoAffineWitness x
pseudoAffineWitness :: PseudoAffineWitness (f p)
                             , forall x. PseudoAffine x => PseudoAffineWitness x
pseudoAffineWitness :: PseudoAffineWitness (g p) ) of
           ( PseudoAffineWitness SemimanifoldWitness (f p)
SemimanifoldWitness
            ,PseudoAffineWitness SemimanifoldWitness (g p)
SemimanifoldWitness )
               -> forall x.
PseudoAffine (Needle x) =>
SemimanifoldWitness x -> PseudoAffineWitness x
PseudoAffineWitness forall x.
(Semimanifold (Needle x), Needle (Needle x) ~ Needle x) =>
SemimanifoldWitness x
SemimanifoldWitness
  (f p
pf:*:g p
pg) .-~. :: (:*:) f g p -> (:*:) f g p -> Maybe (Needle ((:*:) f g p))
.-~. (f p
qf:*:g p
qg) = forall (f :: * -> *) (g :: * -> *) p.
Needle (f p) -> Needle (g p) -> NeedleProductSpace f g p
NeedleProductSpace forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (f p
pfforall x. PseudoAffine x => x -> x -> Maybe (Needle x)
.-~.f p
qf) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (g p
pgforall x. PseudoAffine x => x -> x -> Maybe (Needle x)
.-~.g p
qg)
  (f p
pf:*:g p
pg) .-~! :: HasCallStack => (:*:) f g p -> (:*:) f g p -> Needle ((:*:) f g p)
.-~! (f p
qf:*:g p
qg) = forall (f :: * -> *) (g :: * -> *) p.
Needle (f p) -> Needle (g p) -> NeedleProductSpace f g p
NeedleProductSpace     (f p
pfforall x. (PseudoAffine x, HasCallStack) => x -> x -> Needle x
.-~!f p
qf)     (g p
pgforall x. (PseudoAffine x, HasCallStack) => x -> x -> Needle x
.-~!g p
qg)


type VRep x = Gnrx.Rep x Void



-- | A (closed) cone over a space @x@ is the product of @x@ with the closed interval 'D¹'
--   of “heights”,
--   except on its “tip”: here, @x@ is smashed to a single point.
--   
--   This construct becomes (homeomorphic-to-) an actual geometric cone (and to 'D²') in the
--   special case @x = 'S¹'@.
data CD¹ x = CD¹ { forall x. CD¹ x -> Scalar (Needle x)
hParamCD¹ :: !(Scalar (Needle x)) -- ^ Range @[0, 1]@
                 , forall x. CD¹ x -> x
pParamCD¹ :: !x                   -- ^ Irrelevant at @h = 0@.
                 } deriving (forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall x x. Rep (CD¹ x) x -> CD¹ x
forall x x. CD¹ x -> Rep (CD¹ x) x
$cto :: forall x x. Rep (CD¹ x) x -> CD¹ x
$cfrom :: forall x x. CD¹ x -> Rep (CD¹ x) x
Generic)
deriving instance (Show x, Show (Scalar (Needle x))) => Show (CD¹ x)


-- | An open cone is homeomorphic to a closed cone without the “lid”,
--   i.e. without the “last copy” of @x@, at the far end of the height
--   interval. Since that means the height does not include its supremum, it is actually
--   more natural to express it as the entire real ray, hence the name.
data Cℝay x = Cℝay { forall x. Cℝay x -> Scalar (Needle x)
hParamCℝay :: !(Scalar (Needle x))  -- ^ Range @[0, ∞[@
                   , forall x. Cℝay x -> x
pParamCℝay :: !x                    -- ^ Irrelevant at @h = 0@.
                   } deriving (forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall x x. Rep (Cℝay x) x -> Cℝay x
forall x x. Cℝay x -> Rep (Cℝay x) x
$cto :: forall x x. Rep (Cℝay x) x -> Cℝay x
$cfrom :: forall x x. Cℝay x -> Rep (Cℝay x) x
Generic)
deriving instance (Show x, Show (Scalar (Needle x))) => Show (Cℝay x)