{-# LANGUAGE Strict #-}
module Tgraph.Compose
( compose
, composeF
, partCompose
, partComposeF
, tryPartCompose
, partCompFacesFrom
, partComposeFaces
, DartWingInfo(..)
, getDartWingInfo
, getDartWingInfoForced
, composedFaceGroups
) where
import Data.List (find, foldl', partition)
import qualified Data.IntMap.Strict as VMap (IntMap,lookup,(!),alter,empty)
import Data.Maybe (mapMaybe)
import qualified Data.IntSet as IntSet (empty,insert,toList,member)
import Tgraph.Prelude
import Tgraph.Force ( Forced(), forgetF, labelAsForced )
compose:: Tgraph -> Tgraph
compose :: Tgraph -> Tgraph
compose = ([TileFace], Tgraph) -> Tgraph
forall a b. (a, b) -> b
snd (([TileFace], Tgraph) -> Tgraph)
-> (Tgraph -> ([TileFace], Tgraph)) -> Tgraph -> Tgraph
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Tgraph -> ([TileFace], Tgraph)
partCompose
partCompose:: Tgraph -> ([TileFace],Tgraph)
partCompose :: Tgraph -> ([TileFace], Tgraph)
partCompose Tgraph
g = Try ([TileFace], Tgraph) -> ([TileFace], Tgraph)
forall a. Try a -> a
runTry (Try ([TileFace], Tgraph) -> ([TileFace], Tgraph))
-> Try ([TileFace], Tgraph) -> ([TileFace], Tgraph)
forall a b. (a -> b) -> a -> b
$ String -> Try ([TileFace], Tgraph) -> Try ([TileFace], Tgraph)
forall a. String -> Try a -> Try a
onFail String
"partCompose:\n" (Try ([TileFace], Tgraph) -> Try ([TileFace], Tgraph))
-> Try ([TileFace], Tgraph) -> Try ([TileFace], Tgraph)
forall a b. (a -> b) -> a -> b
$ Tgraph -> Try ([TileFace], Tgraph)
tryPartCompose Tgraph
g
tryPartCompose:: Tgraph -> Try ([TileFace],Tgraph)
tryPartCompose :: Tgraph -> Try ([TileFace], Tgraph)
tryPartCompose Tgraph
g =
do let (~[TileFace]
remainder,[TileFace]
newFaces) = Tgraph -> ([TileFace], [TileFace])
partComposeFaces Tgraph
g
Tgraph
checked <- String -> Try Tgraph -> Try Tgraph
forall a. String -> Try a -> Try a
onFail String
"tryPartCompose:\n" (Try Tgraph -> Try Tgraph) -> Try Tgraph -> Try Tgraph
forall a b. (a -> b) -> a -> b
$ [TileFace] -> Try Tgraph
tryConnectedNoCross [TileFace]
newFaces
([TileFace], Tgraph) -> Try ([TileFace], Tgraph)
forall a. a -> Either ShowS a
forall (m :: * -> *) a. Monad m => a -> m a
return ([TileFace]
remainder,Tgraph
checked)
partComposeFaces:: Tgraph -> ([TileFace],[TileFace])
partComposeFaces :: Tgraph -> ([TileFace], [TileFace])
partComposeFaces = DartWingInfo -> ([TileFace], [TileFace])
partCompFacesFrom (DartWingInfo -> ([TileFace], [TileFace]))
-> (Tgraph -> DartWingInfo) -> Tgraph -> ([TileFace], [TileFace])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Tgraph -> DartWingInfo
getDartWingInfo
partComposeFacesF :: Forced Tgraph -> ([TileFace],[TileFace])
partComposeFacesF :: Forced Tgraph -> ([TileFace], [TileFace])
partComposeFacesF = DartWingInfo -> ([TileFace], [TileFace])
partCompFacesFrom (DartWingInfo -> ([TileFace], [TileFace]))
-> (Forced Tgraph -> DartWingInfo)
-> Forced Tgraph
-> ([TileFace], [TileFace])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Forced Tgraph -> DartWingInfo
getDartWingInfoForced
partComposeF:: Forced Tgraph -> ([TileFace], Forced Tgraph)
partComposeF :: Forced Tgraph -> ([TileFace], Forced Tgraph)
partComposeF Forced Tgraph
fg = ([TileFace]
remainder, Tgraph -> Forced Tgraph
forall a. a -> Forced a
labelAsForced (Tgraph -> Forced Tgraph) -> Tgraph -> Forced Tgraph
forall a b. (a -> b) -> a -> b
$ [TileFace] -> Tgraph
makeUncheckedTgraph [TileFace]
newfaces) where
(~[TileFace]
remainder,[TileFace]
newfaces) = Forced Tgraph -> ([TileFace], [TileFace])
partComposeFacesF Forced Tgraph
fg
composeF:: Forced Tgraph -> Forced Tgraph
composeF :: Forced Tgraph -> Forced Tgraph
composeF = ([TileFace], Forced Tgraph) -> Forced Tgraph
forall a b. (a, b) -> b
snd (([TileFace], Forced Tgraph) -> Forced Tgraph)
-> (Forced Tgraph -> ([TileFace], Forced Tgraph))
-> Forced Tgraph
-> Forced Tgraph
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Forced Tgraph -> ([TileFace], Forced Tgraph)
partComposeF
data DartWingInfo = DartWingInfo
{ DartWingInfo -> [Vertex]
largeKiteCentres :: [Vertex]
, DartWingInfo -> [Vertex]
largeDartBases :: [Vertex]
, DartWingInfo -> [Vertex]
unknowns :: [Vertex]
, DartWingInfo -> IntMap [TileFace]
faceMap :: VMap.IntMap [TileFace]
, DartWingInfo -> [TileFace]
unMapped :: [TileFace]
} deriving Vertex -> DartWingInfo -> ShowS
[DartWingInfo] -> ShowS
DartWingInfo -> String
(Vertex -> DartWingInfo -> ShowS)
-> (DartWingInfo -> String)
-> ([DartWingInfo] -> ShowS)
-> Show DartWingInfo
forall a.
(Vertex -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Vertex -> DartWingInfo -> ShowS
showsPrec :: Vertex -> DartWingInfo -> ShowS
$cshow :: DartWingInfo -> String
show :: DartWingInfo -> String
$cshowList :: [DartWingInfo] -> ShowS
showList :: [DartWingInfo] -> ShowS
Show
getDartWingInfo:: Tgraph -> DartWingInfo
getDartWingInfo :: Tgraph -> DartWingInfo
getDartWingInfo = Bool -> Tgraph -> DartWingInfo
getDWIassumeF Bool
False
getDartWingInfoForced :: Forced Tgraph -> DartWingInfo
getDartWingInfoForced :: Forced Tgraph -> DartWingInfo
getDartWingInfoForced Forced Tgraph
fg = Bool -> Tgraph -> DartWingInfo
getDWIassumeF Bool
True (Forced Tgraph -> Tgraph
forall a. Forced a -> a
forgetF Forced Tgraph
fg)
getDWIassumeF:: Bool -> Tgraph -> DartWingInfo
getDWIassumeF :: Bool -> Tgraph -> DartWingInfo
getDWIassumeF Bool
isForced Tgraph
g =
DartWingInfo { largeKiteCentres :: [Vertex]
largeKiteCentres = IntSet -> [Vertex]
IntSet.toList IntSet
allKcs
, largeDartBases :: [Vertex]
largeDartBases = IntSet -> [Vertex]
IntSet.toList IntSet
allDbs
, unknowns :: [Vertex]
unknowns = IntSet -> [Vertex]
IntSet.toList IntSet
allUnks
, faceMap :: IntMap [TileFace]
faceMap = IntMap [TileFace]
dwFMap
, unMapped :: [TileFace]
unMapped = [TileFace]
unused
} where
([TileFace]
drts,[TileFace]
kts) = (TileFace -> Bool) -> [TileFace] -> ([TileFace], [TileFace])
forall a. (a -> Bool) -> [a] -> ([a], [a])
partition TileFace -> Bool
forall rep. HalfTile rep -> Bool
isDart (Tgraph -> [TileFace]
forall a. HasFaces a => a -> [TileFace]
faces Tgraph
g)
(IntMap [TileFace]
dwFMap,[TileFace]
unused) = ((IntMap [TileFace], [TileFace])
-> TileFace -> (IntMap [TileFace], [TileFace]))
-> (IntMap [TileFace], [TileFace])
-> [TileFace]
-> (IntMap [TileFace], [TileFace])
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (IntMap [TileFace], [TileFace])
-> TileFace -> (IntMap [TileFace], [TileFace])
insertK (IntMap [TileFace]
dartWMap,[]) [TileFace]
kts
where
dartWMap :: IntMap [TileFace]
dartWMap = (IntMap [TileFace] -> TileFace -> IntMap [TileFace])
-> IntMap [TileFace] -> [TileFace] -> IntMap [TileFace]
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' IntMap [TileFace] -> TileFace -> IntMap [TileFace]
insertD IntMap [TileFace]
forall a. IntMap a
VMap.empty [TileFace]
drts
insertD :: IntMap [TileFace] -> TileFace -> IntMap [TileFace]
insertD IntMap [TileFace]
vmap TileFace
f = (Maybe [TileFace] -> Maybe [TileFace])
-> Vertex -> IntMap [TileFace] -> IntMap [TileFace]
forall a. (Maybe a -> Maybe a) -> Vertex -> IntMap a -> IntMap a
VMap.alter (TileFace -> Maybe [TileFace] -> Maybe [TileFace]
forall {a}. a -> Maybe [a] -> Maybe [a]
addD TileFace
f) (TileFace -> Vertex
wingV TileFace
f) IntMap [TileFace]
vmap
addD :: a -> Maybe [a] -> Maybe [a]
addD a
f Maybe [a]
Nothing = [a] -> Maybe [a]
forall a. a -> Maybe a
Just [a
f]
addD a
f (Just [a]
fs) = [a] -> Maybe [a]
forall a. a -> Maybe a
Just (a
fa -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
fs)
insertK :: (IntMap [TileFace], [TileFace])
-> TileFace -> (IntMap [TileFace], [TileFace])
insertK (IntMap [TileFace]
vmap,[TileFace]
unsd) TileFace
f =
let op :: Vertex
op = TileFace -> Vertex
oppV TileFace
f
org :: Vertex
org = TileFace -> Vertex
originV TileFace
f
in case (Vertex -> IntMap [TileFace] -> Maybe [TileFace]
forall a. Vertex -> IntMap a -> Maybe a
VMap.lookup Vertex
op IntMap [TileFace]
vmap, Vertex -> IntMap [TileFace] -> Maybe [TileFace]
forall a. Vertex -> IntMap a -> Maybe a
VMap.lookup Vertex
org IntMap [TileFace]
vmap) of
(Just [TileFace]
_ ,Just [TileFace]
_) -> ((Maybe [TileFace] -> Maybe [TileFace])
-> Vertex -> IntMap [TileFace] -> IntMap [TileFace]
forall a. (Maybe a -> Maybe a) -> Vertex -> IntMap a -> IntMap a
VMap.alter (TileFace -> Maybe [TileFace] -> Maybe [TileFace]
forall {a}. a -> Maybe [a] -> Maybe [a]
addK TileFace
f) (TileFace -> Vertex
oppV TileFace
f) (IntMap [TileFace] -> IntMap [TileFace])
-> IntMap [TileFace] -> IntMap [TileFace]
forall a b. (a -> b) -> a -> b
$ (Maybe [TileFace] -> Maybe [TileFace])
-> Vertex -> IntMap [TileFace] -> IntMap [TileFace]
forall a. (Maybe a -> Maybe a) -> Vertex -> IntMap a -> IntMap a
VMap.alter (TileFace -> Maybe [TileFace] -> Maybe [TileFace]
forall {a}. a -> Maybe [a] -> Maybe [a]
addK TileFace
f) (TileFace -> Vertex
originV TileFace
f) IntMap [TileFace]
vmap, [TileFace]
unsd)
(Just [TileFace]
_ , Maybe [TileFace]
Nothing) -> ((Maybe [TileFace] -> Maybe [TileFace])
-> Vertex -> IntMap [TileFace] -> IntMap [TileFace]
forall a. (Maybe a -> Maybe a) -> Vertex -> IntMap a -> IntMap a
VMap.alter (TileFace -> Maybe [TileFace] -> Maybe [TileFace]
forall {a}. a -> Maybe [a] -> Maybe [a]
addK TileFace
f) (TileFace -> Vertex
oppV TileFace
f) IntMap [TileFace]
vmap, [TileFace]
unsd)
(Maybe [TileFace]
Nothing, Just [TileFace]
_ ) -> ((Maybe [TileFace] -> Maybe [TileFace])
-> Vertex -> IntMap [TileFace] -> IntMap [TileFace]
forall a. (Maybe a -> Maybe a) -> Vertex -> IntMap a -> IntMap a
VMap.alter (TileFace -> Maybe [TileFace] -> Maybe [TileFace]
forall {a}. a -> Maybe [a] -> Maybe [a]
addK TileFace
f) (TileFace -> Vertex
originV TileFace
f) IntMap [TileFace]
vmap, [TileFace]
unsd)
(Maybe [TileFace]
Nothing, Maybe [TileFace]
Nothing) -> (IntMap [TileFace]
vmap, TileFace
fTileFace -> [TileFace] -> [TileFace]
forall a. a -> [a] -> [a]
:[TileFace]
unsd)
addK :: a -> Maybe [a] -> Maybe [a]
addK a
_ Maybe [a]
Nothing = Maybe [a]
forall a. Maybe a
Nothing
addK a
f (Just [a]
fs) = [a] -> Maybe [a]
forall a. a -> Maybe a
Just (a
fa -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
fs)
(IntSet
allKcs,IntSet
allDbs,IntSet
allUnks) = ((IntSet, IntSet, IntSet) -> TileFace -> (IntSet, IntSet, IntSet))
-> (IntSet, IntSet, IntSet)
-> [TileFace]
-> (IntSet, IntSet, IntSet)
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (IntSet, IntSet, IntSet) -> TileFace -> (IntSet, IntSet, IntSet)
processD (IntSet
IntSet.empty, IntSet
IntSet.empty, IntSet
IntSet.empty) [TileFace]
drts
processD :: (IntSet, IntSet, IntSet) -> TileFace -> (IntSet, IntSet, IntSet)
processD (IntSet
kcs, IntSet
dbs, IntSet
unks) rd :: TileFace
rd@(RD (Vertex
orig, Vertex
w, Vertex
_)) =
if Vertex
w Vertex -> IntSet -> Bool
`IntSet.member` IntSet
kcs Bool -> Bool -> Bool
|| Vertex
w Vertex -> IntSet -> Bool
`IntSet.member` IntSet
dbs then (IntSet
kcs, IntSet
dbs, IntSet
unks) else
let
fcs :: [TileFace]
fcs = IntMap [TileFace]
dwFMap IntMap [TileFace] -> Vertex -> [TileFace]
forall a. IntMap a -> Vertex -> a
VMap.! Vertex
w
in
if Vertex
w Vertex -> [Vertex] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (TileFace -> Vertex) -> [TileFace] -> [Vertex]
forall a b. (a -> b) -> [a] -> [b]
map TileFace -> Vertex
originV ((TileFace -> Bool) -> [TileFace] -> [TileFace]
forall a. (a -> Bool) -> [a] -> [a]
filter TileFace -> Bool
forall rep. HalfTile rep -> Bool
isKite [TileFace]
fcs) then (IntSet
kcs,Vertex -> IntSet -> IntSet
IntSet.insert Vertex
w IntSet
dbs,IntSet
unks) else
if (Vertex
w,Vertex
orig) (Vertex, Vertex) -> [(Vertex, Vertex)] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (TileFace -> (Vertex, Vertex)) -> [TileFace] -> [(Vertex, Vertex)]
forall a b. (a -> b) -> [a] -> [b]
map TileFace -> (Vertex, Vertex)
longE ((TileFace -> Bool) -> [TileFace] -> [TileFace]
forall a. (a -> Bool) -> [a] -> [a]
filter TileFace -> Bool
forall rep. HalfTile rep -> Bool
isLD [TileFace]
fcs) then (Vertex -> IntSet -> IntSet
IntSet.insert Vertex
w IntSet
kcs,IntSet
dbs,IntSet
unks) else
if Bool
isForced Bool -> Bool -> Bool
|| [TileFace] -> Vertex
forall a. [a] -> Vertex
forall (t :: * -> *) a. Foldable t => t a -> Vertex
length [TileFace]
fcs Vertex -> Vertex -> Bool
forall a. Eq a => a -> a -> Bool
== Vertex
1 then (IntSet
kcs, IntSet
dbs, Vertex -> IntSet -> IntSet
IntSet.insert Vertex
w IntSet
unks) else
case TileFace -> [TileFace] -> Maybe TileFace
findFarK TileFace
rd [TileFace]
fcs of
Maybe TileFace
Nothing -> (IntSet
kcs,IntSet
dbs,Vertex -> IntSet -> IntSet
IntSet.insert Vertex
w IntSet
unks)
Just rk :: TileFace
rk@(RK (Vertex, Vertex, Vertex)
_) ->
case (TileFace -> Bool) -> [TileFace] -> Maybe TileFace
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (TileFace -> TileFace -> Bool
matchingShortE TileFace
rk) [TileFace]
fcs of
Just (LK (Vertex, Vertex, Vertex)
_) -> (Vertex -> IntSet -> IntSet
IntSet.insert Vertex
w IntSet
kcs,IntSet
dbs,IntSet
unks)
Just (LD (Vertex, Vertex, Vertex)
_) -> (IntSet
kcs,Vertex -> IntSet -> IntSet
IntSet.insert Vertex
w IntSet
dbs,IntSet
unks)
Maybe TileFace
_ -> let
newfcs :: [TileFace]
newfcs = (TileFace -> Bool) -> [TileFace] -> [TileFace]
forall a. (a -> Bool) -> [a] -> [a]
filter (Vertex -> TileFace -> Bool
isAtV (TileFace -> Vertex
wingV TileFace
rk)) (Tgraph -> [TileFace]
forall a. HasFaces a => a -> [TileFace]
faces Tgraph
g)
in
case (TileFace -> Bool) -> [TileFace] -> Maybe TileFace
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (TileFace -> TileFace -> Bool
matchingLongE TileFace
rk) [TileFace]
newfcs of
Maybe TileFace
Nothing -> (IntSet
kcs,IntSet
dbs,Vertex -> IntSet -> IntSet
IntSet.insert Vertex
w IntSet
unks)
Just (LD (Vertex, Vertex, Vertex)
_) -> (Vertex -> IntSet -> IntSet
IntSet.insert Vertex
w IntSet
kcs,IntSet
dbs,IntSet
unks)
Just lk :: TileFace
lk@(LK (Vertex, Vertex, Vertex)
_) ->
case (TileFace -> Bool) -> [TileFace] -> Maybe TileFace
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (TileFace -> TileFace -> Bool
matchingShortE TileFace
lk) [TileFace]
newfcs of
Just (RK (Vertex, Vertex, Vertex)
_) -> (Vertex -> IntSet -> IntSet
IntSet.insert Vertex
w IntSet
kcs,IntSet
dbs,IntSet
unks)
Just (RD (Vertex, Vertex, Vertex)
_) -> (IntSet
kcs,Vertex -> IntSet -> IntSet
IntSet.insert Vertex
w IntSet
dbs,IntSet
unks)
Maybe TileFace
_ -> (IntSet
kcs,IntSet
dbs,Vertex -> IntSet -> IntSet
IntSet.insert Vertex
w IntSet
unks)
Just TileFace
_ -> String -> (IntSet, IntSet, IntSet)
forall a. HasCallStack => String -> a
error String
"getDartWingInfo: illegal case for matchingLongE of a right kite"
Just TileFace
_ -> String -> (IntSet, IntSet, IntSet)
forall a. HasCallStack => String -> a
error String
"getDartWingInfo: non-kite returned by findFarK"
processD (IntSet
kcs, IntSet
dbs, IntSet
unks) ld :: TileFace
ld@(LD (Vertex
orig, Vertex
_, Vertex
w)) =
if Vertex
w Vertex -> IntSet -> Bool
`IntSet.member` IntSet
kcs Bool -> Bool -> Bool
|| Vertex
w Vertex -> IntSet -> Bool
`IntSet.member` IntSet
dbs then (IntSet
kcs, IntSet
dbs, IntSet
unks) else
let
fcs :: [TileFace]
fcs = IntMap [TileFace]
dwFMap IntMap [TileFace] -> Vertex -> [TileFace]
forall a. IntMap a -> Vertex -> a
VMap.! Vertex
w
in
if [TileFace] -> Vertex
forall a. [a] -> Vertex
forall (t :: * -> *) a. Foldable t => t a -> Vertex
length [TileFace]
fcs Vertex -> Vertex -> Bool
forall a. Eq a => a -> a -> Bool
==Vertex
1 then (IntSet
kcs, IntSet
dbs, Vertex -> IntSet -> IntSet
IntSet.insert Vertex
w IntSet
unks) else
if Vertex
w Vertex -> [Vertex] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (TileFace -> Vertex) -> [TileFace] -> [Vertex]
forall a b. (a -> b) -> [a] -> [b]
map TileFace -> Vertex
originV ((TileFace -> Bool) -> [TileFace] -> [TileFace]
forall a. (a -> Bool) -> [a] -> [a]
filter TileFace -> Bool
forall rep. HalfTile rep -> Bool
isKite [TileFace]
fcs) then (IntSet
kcs,Vertex -> IntSet -> IntSet
IntSet.insert Vertex
w IntSet
dbs,IntSet
unks) else
if (Vertex
w,Vertex
orig) (Vertex, Vertex) -> [(Vertex, Vertex)] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (TileFace -> (Vertex, Vertex)) -> [TileFace] -> [(Vertex, Vertex)]
forall a b. (a -> b) -> [a] -> [b]
map TileFace -> (Vertex, Vertex)
longE ((TileFace -> Bool) -> [TileFace] -> [TileFace]
forall a. (a -> Bool) -> [a] -> [a]
filter TileFace -> Bool
forall rep. HalfTile rep -> Bool
isRD [TileFace]
fcs) then (Vertex -> IntSet -> IntSet
IntSet.insert Vertex
w IntSet
kcs,IntSet
dbs,IntSet
unks) else
if Bool
isForced then (IntSet
kcs, IntSet
dbs, Vertex -> IntSet -> IntSet
IntSet.insert Vertex
w IntSet
unks) else
case TileFace -> [TileFace] -> Maybe TileFace
findFarK TileFace
ld [TileFace]
fcs of
Maybe TileFace
Nothing -> (IntSet
kcs,IntSet
dbs,Vertex -> IntSet -> IntSet
IntSet.insert Vertex
w IntSet
unks)
Just lk :: TileFace
lk@(LK (Vertex, Vertex, Vertex)
_) ->
case (TileFace -> Bool) -> [TileFace] -> Maybe TileFace
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (TileFace -> TileFace -> Bool
matchingShortE TileFace
lk) [TileFace]
fcs of
Just (RK (Vertex, Vertex, Vertex)
_) -> (Vertex -> IntSet -> IntSet
IntSet.insert Vertex
w IntSet
kcs,IntSet
dbs,IntSet
unks)
Just (RD (Vertex, Vertex, Vertex)
_) -> (IntSet
kcs,Vertex -> IntSet -> IntSet
IntSet.insert Vertex
w IntSet
dbs,IntSet
unks)
Maybe TileFace
_ -> let
newfcs :: [TileFace]
newfcs = (TileFace -> Bool) -> [TileFace] -> [TileFace]
forall a. (a -> Bool) -> [a] -> [a]
filter (Vertex -> TileFace -> Bool
isAtV (TileFace -> Vertex
wingV TileFace
lk)) (Tgraph -> [TileFace]
forall a. HasFaces a => a -> [TileFace]
faces Tgraph
g)
in
case (TileFace -> Bool) -> [TileFace] -> Maybe TileFace
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (TileFace -> TileFace -> Bool
matchingLongE TileFace
lk) [TileFace]
newfcs of
Maybe TileFace
Nothing -> (IntSet
kcs,IntSet
dbs,Vertex -> IntSet -> IntSet
IntSet.insert Vertex
w IntSet
unks)
Just (RD (Vertex, Vertex, Vertex)
_) -> (Vertex -> IntSet -> IntSet
IntSet.insert Vertex
w IntSet
kcs,IntSet
dbs,IntSet
unks)
Just rk :: TileFace
rk@(RK (Vertex, Vertex, Vertex)
_) ->
case (TileFace -> Bool) -> [TileFace] -> Maybe TileFace
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (TileFace -> TileFace -> Bool
matchingShortE TileFace
rk) [TileFace]
newfcs of
Just (LK (Vertex, Vertex, Vertex)
_) -> (Vertex -> IntSet -> IntSet
IntSet.insert Vertex
w IntSet
kcs,IntSet
dbs,IntSet
unks)
Just (LD (Vertex, Vertex, Vertex)
_) -> (IntSet
kcs,Vertex -> IntSet -> IntSet
IntSet.insert Vertex
w IntSet
dbs,IntSet
unks)
Maybe TileFace
_ -> (IntSet
kcs,IntSet
dbs,Vertex -> IntSet -> IntSet
IntSet.insert Vertex
w IntSet
unks)
Just TileFace
_ -> String -> (IntSet, IntSet, IntSet)
forall a. HasCallStack => String -> a
error String
"getDartWingInfo: illegal case for matchingLongE of a left kite"
Just TileFace
_ -> String -> (IntSet, IntSet, IntSet)
forall a. HasCallStack => String -> a
error String
"getDartWingInfo: non-kite returned by findFarK"
processD (IntSet, IntSet, IntSet)
_ TileFace
_ = String -> (IntSet, IntSet, IntSet)
forall a. HasCallStack => String -> a
error String
"getDartWingInfo: processD applied to non-dart"
findFarK :: TileFace -> [TileFace] -> Maybe TileFace
findFarK :: TileFace -> [TileFace] -> Maybe TileFace
findFarK rd :: TileFace
rd@(RD (Vertex, Vertex, Vertex)
_) [TileFace]
fcs = do TileFace
lk <- (TileFace -> Bool) -> [TileFace] -> Maybe TileFace
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (TileFace -> TileFace -> Bool
matchingShortE TileFace
rd) ((TileFace -> Bool) -> [TileFace] -> [TileFace]
forall a. (a -> Bool) -> [a] -> [a]
filter TileFace -> Bool
forall rep. HalfTile rep -> Bool
isLK [TileFace]
fcs)
(TileFace -> Bool) -> [TileFace] -> Maybe TileFace
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (TileFace -> TileFace -> Bool
matchingJoinE TileFace
lk) ((TileFace -> Bool) -> [TileFace] -> [TileFace]
forall a. (a -> Bool) -> [a] -> [a]
filter TileFace -> Bool
forall rep. HalfTile rep -> Bool
isRK [TileFace]
fcs)
findFarK ld :: TileFace
ld@(LD (Vertex, Vertex, Vertex)
_) [TileFace]
fcs = do TileFace
rk <- (TileFace -> Bool) -> [TileFace] -> Maybe TileFace
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (TileFace -> TileFace -> Bool
matchingShortE TileFace
ld) ((TileFace -> Bool) -> [TileFace] -> [TileFace]
forall a. (a -> Bool) -> [a] -> [a]
filter TileFace -> Bool
forall rep. HalfTile rep -> Bool
isRK [TileFace]
fcs)
(TileFace -> Bool) -> [TileFace] -> Maybe TileFace
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (TileFace -> TileFace -> Bool
matchingJoinE TileFace
rk) ((TileFace -> Bool) -> [TileFace] -> [TileFace]
forall a. (a -> Bool) -> [a] -> [a]
filter TileFace -> Bool
forall rep. HalfTile rep -> Bool
isLK [TileFace]
fcs)
findFarK TileFace
_ [TileFace]
_ = String -> Maybe TileFace
forall a. HasCallStack => String -> a
error String
"getDartWingInfo: findFarK applied to non-dart face"
partCompFacesFrom :: DartWingInfo -> ([TileFace],[TileFace])
partCompFacesFrom :: DartWingInfo -> ([TileFace], [TileFace])
partCompFacesFrom DartWingInfo
dwInfo = ([TileFace]
remainder, [TileFace]
newFaces) where
remainder :: [TileFace]
remainder = DartWingInfo -> [TileFace]
unMapped DartWingInfo
dwInfo [TileFace] -> [TileFace] -> [TileFace]
forall a. [a] -> [a] -> [a]
++ (Vertex -> [TileFace]) -> [Vertex] -> [TileFace]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (DartWingInfo -> IntMap [TileFace]
faceMap DartWingInfo
dwInfo VMap.!) (DartWingInfo -> [Vertex]
unknowns DartWingInfo
dwInfo)
newFaces :: [TileFace]
newFaces = [TileFace]
newRDs [TileFace] -> [TileFace] -> [TileFace]
forall a. [a] -> [a] -> [a]
++ [TileFace]
newLDs [TileFace] -> [TileFace] -> [TileFace]
forall a. [a] -> [a] -> [a]
++ [TileFace]
newRKs [TileFace] -> [TileFace] -> [TileFace]
forall a. [a] -> [a] -> [a]
++ [TileFace]
newLKs
newRDs :: [TileFace]
newRDs = ([TileFace] -> TileFace) -> [[TileFace]] -> [TileFace]
forall a b. (a -> b) -> [a] -> [b]
map [TileFace] -> TileFace
makenewRD [[TileFace]]
groupRDs
groupRDs :: [[TileFace]]
groupRDs = (Vertex -> Maybe [TileFace]) -> [Vertex] -> [[TileFace]]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe Vertex -> Maybe [TileFace]
groupRD (DartWingInfo -> [Vertex]
largeDartBases DartWingInfo
dwInfo)
makenewRD :: [TileFace] -> TileFace
makenewRD [TileFace
rd,TileFace
lk] = Vertex -> Vertex -> Vertex -> TileFace
makeRD (TileFace -> Vertex
originV TileFace
lk) (TileFace -> Vertex
originV TileFace
rd) (TileFace -> Vertex
oppV TileFace
lk)
makenewRD [TileFace]
_ = String -> TileFace
forall a. HasCallStack => String -> a
error String
"composedFaceGroups: RD case"
groupRD :: Vertex -> Maybe [TileFace]
groupRD Vertex
v = do [TileFace]
fcs <- Vertex -> IntMap [TileFace] -> Maybe [TileFace]
forall a. Vertex -> IntMap a -> Maybe a
VMap.lookup Vertex
v (DartWingInfo -> IntMap [TileFace]
faceMap DartWingInfo
dwInfo)
TileFace
rd <- (TileFace -> Bool) -> [TileFace] -> Maybe TileFace
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find TileFace -> Bool
forall rep. HalfTile rep -> Bool
isRD [TileFace]
fcs
TileFace
lk <- (TileFace -> Bool) -> [TileFace] -> Maybe TileFace
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (TileFace -> TileFace -> Bool
matchingShortE TileFace
rd) [TileFace]
fcs
[TileFace] -> Maybe [TileFace]
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return [TileFace
rd,TileFace
lk]
newLDs :: [TileFace]
newLDs = ([TileFace] -> TileFace) -> [[TileFace]] -> [TileFace]
forall a b. (a -> b) -> [a] -> [b]
map [TileFace] -> TileFace
makenewLD [[TileFace]]
groupLDs
groupLDs :: [[TileFace]]
groupLDs = (Vertex -> Maybe [TileFace]) -> [Vertex] -> [[TileFace]]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe Vertex -> Maybe [TileFace]
groupLD (DartWingInfo -> [Vertex]
largeDartBases DartWingInfo
dwInfo)
makenewLD :: [TileFace] -> TileFace
makenewLD [TileFace
ld,TileFace
rk] = Vertex -> Vertex -> Vertex -> TileFace
makeLD (TileFace -> Vertex
originV TileFace
rk) (TileFace -> Vertex
oppV TileFace
rk) (TileFace -> Vertex
originV TileFace
ld)
makenewLD [TileFace]
_ = String -> TileFace
forall a. HasCallStack => String -> a
error String
"composedFaceGroups: LD case"
groupLD :: Vertex -> Maybe [TileFace]
groupLD Vertex
v = do [TileFace]
fcs <- Vertex -> IntMap [TileFace] -> Maybe [TileFace]
forall a. Vertex -> IntMap a -> Maybe a
VMap.lookup Vertex
v (DartWingInfo -> IntMap [TileFace]
faceMap DartWingInfo
dwInfo)
TileFace
ld <- (TileFace -> Bool) -> [TileFace] -> Maybe TileFace
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find TileFace -> Bool
forall rep. HalfTile rep -> Bool
isLD [TileFace]
fcs
TileFace
rk <- (TileFace -> Bool) -> [TileFace] -> Maybe TileFace
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (TileFace -> TileFace -> Bool
matchingShortE TileFace
ld) [TileFace]
fcs
[TileFace] -> Maybe [TileFace]
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return [TileFace
ld,TileFace
rk]
newRKs :: [TileFace]
newRKs = ([TileFace] -> TileFace) -> [[TileFace]] -> [TileFace]
forall a b. (a -> b) -> [a] -> [b]
map [TileFace] -> TileFace
makenewRK [[TileFace]]
groupRKs
groupRKs :: [[TileFace]]
groupRKs = (Vertex -> Maybe [TileFace]) -> [Vertex] -> [[TileFace]]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe Vertex -> Maybe [TileFace]
groupRK (DartWingInfo -> [Vertex]
largeKiteCentres DartWingInfo
dwInfo)
makenewRK :: [TileFace] -> TileFace
makenewRK [TileFace
rd,TileFace
_,TileFace
rk] = Vertex -> Vertex -> Vertex -> TileFace
makeRK (TileFace -> Vertex
originV TileFace
rd) (TileFace -> Vertex
wingV TileFace
rk) (TileFace -> Vertex
originV TileFace
rk)
makenewRK [TileFace]
_ = String -> TileFace
forall a. HasCallStack => String -> a
error String
"composedFaceGroups: RK case"
groupRK :: Vertex -> Maybe [TileFace]
groupRK Vertex
v = do [TileFace]
fcs <- Vertex -> IntMap [TileFace] -> Maybe [TileFace]
forall a. Vertex -> IntMap a -> Maybe a
VMap.lookup Vertex
v (DartWingInfo -> IntMap [TileFace]
faceMap DartWingInfo
dwInfo)
TileFace
rd <- (TileFace -> Bool) -> [TileFace] -> Maybe TileFace
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find TileFace -> Bool
forall rep. HalfTile rep -> Bool
isRD [TileFace]
fcs
TileFace
lk <- (TileFace -> Bool) -> [TileFace] -> Maybe TileFace
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (TileFace -> TileFace -> Bool
matchingShortE TileFace
rd) [TileFace]
fcs
TileFace
rk <- (TileFace -> Bool) -> [TileFace] -> Maybe TileFace
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (TileFace -> TileFace -> Bool
matchingJoinE TileFace
lk) [TileFace]
fcs
[TileFace] -> Maybe [TileFace]
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return [TileFace
rd,TileFace
lk,TileFace
rk]
newLKs :: [TileFace]
newLKs = ([TileFace] -> TileFace) -> [[TileFace]] -> [TileFace]
forall a b. (a -> b) -> [a] -> [b]
map [TileFace] -> TileFace
makenewLK [[TileFace]]
groupLKs
groupLKs :: [[TileFace]]
groupLKs = (Vertex -> Maybe [TileFace]) -> [Vertex] -> [[TileFace]]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe Vertex -> Maybe [TileFace]
groupLK (DartWingInfo -> [Vertex]
largeKiteCentres DartWingInfo
dwInfo)
makenewLK :: [TileFace] -> TileFace
makenewLK [TileFace
ld,TileFace
_,TileFace
lk] = Vertex -> Vertex -> Vertex -> TileFace
makeLK (TileFace -> Vertex
originV TileFace
ld) (TileFace -> Vertex
originV TileFace
lk) (TileFace -> Vertex
wingV TileFace
lk)
makenewLK [TileFace]
_ = String -> TileFace
forall a. HasCallStack => String -> a
error String
"composedFaceGroups: LK case"
groupLK :: Vertex -> Maybe [TileFace]
groupLK Vertex
v = do [TileFace]
fcs <- Vertex -> IntMap [TileFace] -> Maybe [TileFace]
forall a. Vertex -> IntMap a -> Maybe a
VMap.lookup Vertex
v (DartWingInfo -> IntMap [TileFace]
faceMap DartWingInfo
dwInfo)
TileFace
ld <- (TileFace -> Bool) -> [TileFace] -> Maybe TileFace
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find TileFace -> Bool
forall rep. HalfTile rep -> Bool
isLD [TileFace]
fcs
TileFace
rk <- (TileFace -> Bool) -> [TileFace] -> Maybe TileFace
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (TileFace -> TileFace -> Bool
matchingShortE TileFace
ld) [TileFace]
fcs
TileFace
lk <- (TileFace -> Bool) -> [TileFace] -> Maybe TileFace
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (TileFace -> TileFace -> Bool
matchingJoinE TileFace
rk) [TileFace]
fcs
[TileFace] -> Maybe [TileFace]
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return [TileFace
ld,TileFace
rk,TileFace
lk]
composedFaceGroups :: DartWingInfo -> [(TileFace,[TileFace])]
composedFaceGroups :: DartWingInfo -> [(TileFace, [TileFace])]
composedFaceGroups DartWingInfo
dwInfo = [(TileFace, [TileFace])]
faceGroupRDs [(TileFace, [TileFace])]
-> [(TileFace, [TileFace])] -> [(TileFace, [TileFace])]
forall a. [a] -> [a] -> [a]
++ [(TileFace, [TileFace])]
faceGroupLDs [(TileFace, [TileFace])]
-> [(TileFace, [TileFace])] -> [(TileFace, [TileFace])]
forall a. [a] -> [a] -> [a]
++ [(TileFace, [TileFace])]
faceGroupRKs [(TileFace, [TileFace])]
-> [(TileFace, [TileFace])] -> [(TileFace, [TileFace])]
forall a. [a] -> [a] -> [a]
++ [(TileFace, [TileFace])]
faceGroupLKs where
faceGroupRDs :: [(TileFace, [TileFace])]
faceGroupRDs = ([TileFace] -> (TileFace, [TileFace]))
-> [[TileFace]] -> [(TileFace, [TileFace])]
forall a b. (a -> b) -> [a] -> [b]
map (\[TileFace]
gp -> ([TileFace] -> TileFace
makenewRD [TileFace]
gp,[TileFace]
gp)) [[TileFace]]
groupRDs
groupRDs :: [[TileFace]]
groupRDs = (Vertex -> Maybe [TileFace]) -> [Vertex] -> [[TileFace]]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe Vertex -> Maybe [TileFace]
groupRD (DartWingInfo -> [Vertex]
largeDartBases DartWingInfo
dwInfo)
makenewRD :: [TileFace] -> TileFace
makenewRD [TileFace
rd,TileFace
lk] = Vertex -> Vertex -> Vertex -> TileFace
makeRD (TileFace -> Vertex
originV TileFace
lk) (TileFace -> Vertex
originV TileFace
rd) (TileFace -> Vertex
oppV TileFace
lk)
makenewRD [TileFace]
_ = String -> TileFace
forall a. HasCallStack => String -> a
error String
"composedFaceGroups: RD case"
groupRD :: Vertex -> Maybe [TileFace]
groupRD Vertex
v = do [TileFace]
fcs <- Vertex -> IntMap [TileFace] -> Maybe [TileFace]
forall a. Vertex -> IntMap a -> Maybe a
VMap.lookup Vertex
v (DartWingInfo -> IntMap [TileFace]
faceMap DartWingInfo
dwInfo)
TileFace
rd <- (TileFace -> Bool) -> [TileFace] -> Maybe TileFace
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find TileFace -> Bool
forall rep. HalfTile rep -> Bool
isRD [TileFace]
fcs
TileFace
lk <- (TileFace -> Bool) -> [TileFace] -> Maybe TileFace
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (TileFace -> TileFace -> Bool
matchingShortE TileFace
rd) [TileFace]
fcs
[TileFace] -> Maybe [TileFace]
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return [TileFace
rd,TileFace
lk]
faceGroupLDs :: [(TileFace, [TileFace])]
faceGroupLDs = ([TileFace] -> (TileFace, [TileFace]))
-> [[TileFace]] -> [(TileFace, [TileFace])]
forall a b. (a -> b) -> [a] -> [b]
map (\[TileFace]
gp -> ([TileFace] -> TileFace
makenewLD [TileFace]
gp,[TileFace]
gp)) [[TileFace]]
groupLDs
groupLDs :: [[TileFace]]
groupLDs = (Vertex -> Maybe [TileFace]) -> [Vertex] -> [[TileFace]]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe Vertex -> Maybe [TileFace]
groupLD (DartWingInfo -> [Vertex]
largeDartBases DartWingInfo
dwInfo)
makenewLD :: [TileFace] -> TileFace
makenewLD [TileFace
ld,TileFace
rk] = Vertex -> Vertex -> Vertex -> TileFace
makeLD (TileFace -> Vertex
originV TileFace
rk) (TileFace -> Vertex
oppV TileFace
rk) (TileFace -> Vertex
originV TileFace
ld)
makenewLD [TileFace]
_ = String -> TileFace
forall a. HasCallStack => String -> a
error String
"composedFaceGroups: LD case"
groupLD :: Vertex -> Maybe [TileFace]
groupLD Vertex
v = do [TileFace]
fcs <- Vertex -> IntMap [TileFace] -> Maybe [TileFace]
forall a. Vertex -> IntMap a -> Maybe a
VMap.lookup Vertex
v (DartWingInfo -> IntMap [TileFace]
faceMap DartWingInfo
dwInfo)
TileFace
ld <- (TileFace -> Bool) -> [TileFace] -> Maybe TileFace
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find TileFace -> Bool
forall rep. HalfTile rep -> Bool
isLD [TileFace]
fcs
TileFace
rk <- (TileFace -> Bool) -> [TileFace] -> Maybe TileFace
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (TileFace -> TileFace -> Bool
matchingShortE TileFace
ld) [TileFace]
fcs
[TileFace] -> Maybe [TileFace]
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return [TileFace
ld,TileFace
rk]
faceGroupRKs :: [(TileFace, [TileFace])]
faceGroupRKs = ([TileFace] -> (TileFace, [TileFace]))
-> [[TileFace]] -> [(TileFace, [TileFace])]
forall a b. (a -> b) -> [a] -> [b]
map (\[TileFace]
gp -> ([TileFace] -> TileFace
makenewRK [TileFace]
gp,[TileFace]
gp)) [[TileFace]]
groupRKs
groupRKs :: [[TileFace]]
groupRKs = (Vertex -> Maybe [TileFace]) -> [Vertex] -> [[TileFace]]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe Vertex -> Maybe [TileFace]
groupRK (DartWingInfo -> [Vertex]
largeKiteCentres DartWingInfo
dwInfo)
makenewRK :: [TileFace] -> TileFace
makenewRK [TileFace
rd,TileFace
_,TileFace
rk] = Vertex -> Vertex -> Vertex -> TileFace
makeRK (TileFace -> Vertex
originV TileFace
rd) (TileFace -> Vertex
wingV TileFace
rk) (TileFace -> Vertex
originV TileFace
rk)
makenewRK [TileFace]
_ = String -> TileFace
forall a. HasCallStack => String -> a
error String
"composedFaceGroups: RK case"
groupRK :: Vertex -> Maybe [TileFace]
groupRK Vertex
v = do [TileFace]
fcs <- Vertex -> IntMap [TileFace] -> Maybe [TileFace]
forall a. Vertex -> IntMap a -> Maybe a
VMap.lookup Vertex
v (DartWingInfo -> IntMap [TileFace]
faceMap DartWingInfo
dwInfo)
TileFace
rd <- (TileFace -> Bool) -> [TileFace] -> Maybe TileFace
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find TileFace -> Bool
forall rep. HalfTile rep -> Bool
isRD [TileFace]
fcs
TileFace
lk <- (TileFace -> Bool) -> [TileFace] -> Maybe TileFace
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (TileFace -> TileFace -> Bool
matchingShortE TileFace
rd) [TileFace]
fcs
TileFace
rk <- (TileFace -> Bool) -> [TileFace] -> Maybe TileFace
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (TileFace -> TileFace -> Bool
matchingJoinE TileFace
lk) [TileFace]
fcs
[TileFace] -> Maybe [TileFace]
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return [TileFace
rd,TileFace
lk,TileFace
rk]
faceGroupLKs :: [(TileFace, [TileFace])]
faceGroupLKs = ([TileFace] -> (TileFace, [TileFace]))
-> [[TileFace]] -> [(TileFace, [TileFace])]
forall a b. (a -> b) -> [a] -> [b]
map (\[TileFace]
gp -> ([TileFace] -> TileFace
makenewLK [TileFace]
gp,[TileFace]
gp)) [[TileFace]]
groupLKs
groupLKs :: [[TileFace]]
groupLKs = (Vertex -> Maybe [TileFace]) -> [Vertex] -> [[TileFace]]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe Vertex -> Maybe [TileFace]
groupLK (DartWingInfo -> [Vertex]
largeKiteCentres DartWingInfo
dwInfo)
makenewLK :: [TileFace] -> TileFace
makenewLK [TileFace
ld,TileFace
_,TileFace
lk] = Vertex -> Vertex -> Vertex -> TileFace
makeLK (TileFace -> Vertex
originV TileFace
ld) (TileFace -> Vertex
originV TileFace
lk) (TileFace -> Vertex
wingV TileFace
lk)
makenewLK [TileFace]
_ = String -> TileFace
forall a. HasCallStack => String -> a
error String
"composedFaceGroups: LK case"
groupLK :: Vertex -> Maybe [TileFace]
groupLK Vertex
v = do [TileFace]
fcs <- Vertex -> IntMap [TileFace] -> Maybe [TileFace]
forall a. Vertex -> IntMap a -> Maybe a
VMap.lookup Vertex
v (DartWingInfo -> IntMap [TileFace]
faceMap DartWingInfo
dwInfo)
TileFace
ld <- (TileFace -> Bool) -> [TileFace] -> Maybe TileFace
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find TileFace -> Bool
forall rep. HalfTile rep -> Bool
isLD [TileFace]
fcs
TileFace
rk <- (TileFace -> Bool) -> [TileFace] -> Maybe TileFace
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (TileFace -> TileFace -> Bool
matchingShortE TileFace
ld) [TileFace]
fcs
TileFace
lk <- (TileFace -> Bool) -> [TileFace] -> Maybe TileFace
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (TileFace -> TileFace -> Bool
matchingJoinE TileFace
rk) [TileFace]
fcs
[TileFace] -> Maybe [TileFace]
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return [TileFace
ld,TileFace
rk,TileFace
lk]