-- |
-- Module      : Data.Manifold.Mesh
-- Copyright   : (c) Justus Sagemüller 2018
-- License     : GPL v3
-- 
-- Maintainer  : (@) jsagemue $ uni-koeln.de
-- Stability   : experimental
-- Portability : portable
-- 

{-# LANGUAGE TypeFamilies        #-}
{-# LANGUAGE FlexibleContexts    #-}
{-# LANGUAGE ConstraintKinds     #-}

module Data.Manifold.Mesh where

import Data.Manifold.Types.Primitive
import Math.Manifold.Core.PseudoAffine
import Data.Manifold.PseudoAffine
import Data.Simplex.Abstract

import Data.Manifold.Web
import Data.Manifold.Web.Internal
import Data.Manifold.FibreBundle

import GHC.Exts (Constraint)

-- | A mesh is a container data structure whose nodes are in some way located
--   distributed over a manifold, and are aware of the topology by way of having
--   access to their neighbours. Any such grid can be seen as a 'PointsWeb', but it
--   may have extra structure (e.g. rectangular) in addition to that.
class SimplexSpanning (MeshDomainSpace ) => Mesh  where
  type MeshDomainSpace  :: *
  type MeshGridDataConstraint  y :: Constraint
  type MeshGridDataConstraint  y = ()
  
  asWeb :: MeshGridDataConstraint  y
             =>  y -> PointsWeb (MeshDomainSpace ) y
  
  meshSimplicesInWeb ::  y -> [AbstractSimplex (Needle (MeshDomainSpace )) WebNodeId]
  
  meshSimplices :: MeshGridDataConstraint  y
             =>  y -> [SimplexF (MeshDomainSpace ) y]
  meshSimplices mesh
    = map (fmap $ \i -> case indexWeb web i of
                         Just (x,info) -> (info^.thisNodeData):@.x
                         Nothing -> error $ "Faulty `Mesh` instance: node #"++show i
                                                     ++" not in web." )
          nodeRefs
   where web = webLocalInfo $ asWeb mesh
         nodeRefs = meshSimplicesInWeb mesh
  
  extrapolateGrid :: (WithField  Manifold y, Connected y, MeshGridDataConstraint  y)
                        =>  y -> MeshDomainSpace  -> y

-- | A mesh that “covers” the entire manifold, i.e. any point lies between some nodes
--   of the mesh.
class Mesh  => CoveringMesh  where
  interpolateGrid :: (WithField  Manifold y, Connected y, MeshGridDataConstraint  y)
                        =>  y -> MeshDomainSpace  -> y
  interpolateGrid = extrapolateGrid