-- |
-- Module      : Math.Manifold.Core.Types
-- Copyright   : (c) Justus Sagemüller 2016
-- License     : GPL v3
-- 
-- Maintainer  : (@) sagemueller $ geo.uni-koeln.de
-- Stability   : experimental
-- Portability : portable
-- 
-- Several low-dimensional manifolds, represented in some simple way as Haskell
-- data types. All these are in the 'PseudoAffine' class.
-- 


{-# LANGUAGE TypeFamilies             #-}


module Math.Manifold.Core.Types where


import Data.VectorSpace
import Math.Manifold.VectorSpace.ZeroDimensional
import Data.AffineSpace
import Data.Basis
import Data.Void
import Data.Monoid

import Control.Applicative (Const(..), Alternative(..))




-- | The zero-dimensional sphere is actually just two points. Implementation might
--   therefore change to @ℝ⁰ 'Control.Category.Constrained.+' ℝ⁰@: the disjoint sum of two
--   single-point spaces.
data S⁰ = PositiveHalfSphere | NegativeHalfSphere deriving(Eq, Show)

otherHalfSphere :: S⁰ -> S⁰
otherHalfSphere PositiveHalfSphere = NegativeHalfSphere
otherHalfSphere NegativeHalfSphere = PositiveHalfSphere

-- | The unit circle.
newtype  =  { φParamS¹ :: Double -- ^ Must be in range @[-π, π[@.
                } deriving (Show)




type ℝP¹ = 




-- | The “one-dimensional disk” – really just the line segment between
--   the two points -1 and 1 of 'S⁰', i.e. this is simply a closed interval.
newtype  =  { xParamD¹ :: Double -- ^ Range @[-1, 1]@.
                } deriving (Show)
fromIntv0to1 ::  -> 
fromIntv0to1 x | x<0        =  (-1)
               | x>1        =  1
               | otherwise  =  $ x*2 - 1



type  = Double
type ℝ⁰ = ZeroDim 




instance VectorSpace () where
  type Scalar () = 
  _ *^ () = ()

instance HasBasis () where
  type Basis () = Void
  basisValue = absurd
  decompose () = []
  decompose' () = absurd
instance InnerSpace () where
  () <.> () = 0