{-# LANGUAGE PatternSynonyms #-}

-----------------------------------------------------------------------------
-- |
-- Copyright   : (C) 2015 Dimitri Sabadie
-- License     : BSD3
--
-- Maintainer  : Dimitri Sabadie <dimitri.sabadie@gmail.com>
-- Stability   : experimental
-- Portability : portable
--
-----------------------------------------------------------------------------

module Codec.Wavefront.Face where

-- |A face index is a triplet of indices. @'FaceIndex' vi vti vni@ is a face that indexes the
-- locations with @vi@, the texture coordinates with @vti@ and the normals with @vni@. An index set
-- to 'Nothing' means /no information/. That is, if @vni == 'Nothing'@, then that 'FaceIndex'
-- doesn’t have a normal associated with.
data FaceIndex = FaceIndex {
    FaceIndex -> Int
faceLocIndex :: {-# UNPACK #-} !Int
  , FaceIndex -> Maybe Int
faceTexCoordIndex :: !(Maybe Int)
  , FaceIndex -> Maybe Int
faceNorIndex :: !(Maybe Int)
  } deriving (FaceIndex -> FaceIndex -> Bool
(FaceIndex -> FaceIndex -> Bool)
-> (FaceIndex -> FaceIndex -> Bool) -> Eq FaceIndex
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FaceIndex -> FaceIndex -> Bool
$c/= :: FaceIndex -> FaceIndex -> Bool
== :: FaceIndex -> FaceIndex -> Bool
$c== :: FaceIndex -> FaceIndex -> Bool
Eq,Int -> FaceIndex -> ShowS
[FaceIndex] -> ShowS
FaceIndex -> String
(Int -> FaceIndex -> ShowS)
-> (FaceIndex -> String)
-> ([FaceIndex] -> ShowS)
-> Show FaceIndex
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FaceIndex] -> ShowS
$cshowList :: [FaceIndex] -> ShowS
show :: FaceIndex -> String
$cshow :: FaceIndex -> String
showsPrec :: Int -> FaceIndex -> ShowS
$cshowsPrec :: Int -> FaceIndex -> ShowS
Show)

-- |A face gathers several 'FaceIndex' to build up faces. It has a least three vertices
data Face = Face FaceIndex FaceIndex FaceIndex [FaceIndex] deriving (Face -> Face -> Bool
(Face -> Face -> Bool) -> (Face -> Face -> Bool) -> Eq Face
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Face -> Face -> Bool
$c/= :: Face -> Face -> Bool
== :: Face -> Face -> Bool
$c== :: Face -> Face -> Bool
Eq,Int -> Face -> ShowS
[Face] -> ShowS
Face -> String
(Int -> Face -> ShowS)
-> (Face -> String) -> ([Face] -> ShowS) -> Show Face
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Face] -> ShowS
$cshowList :: [Face] -> ShowS
show :: Face -> String
$cshow :: Face -> String
showsPrec :: Int -> Face -> ShowS
$cshowsPrec :: Int -> Face -> ShowS
Show)

pattern Triangle :: FaceIndex -> FaceIndex -> FaceIndex -> Face
pattern $bTriangle :: FaceIndex -> FaceIndex -> FaceIndex -> Face
$mTriangle :: forall r.
Face
-> (FaceIndex -> FaceIndex -> FaceIndex -> r) -> (Void# -> r) -> r
Triangle a b c = Face a b c []

pattern Quad :: FaceIndex -> FaceIndex -> FaceIndex -> FaceIndex -> Face
pattern $bQuad :: FaceIndex -> FaceIndex -> FaceIndex -> FaceIndex -> Face
$mQuad :: forall r.
Face
-> (FaceIndex -> FaceIndex -> FaceIndex -> FaceIndex -> r)
-> (Void# -> r)
-> r
Quad a b c d = Face a b c [d]