{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE GADTs #-}
module Numeric.LAPACK.Matrix.Extent.Private where
import Numeric.LAPACK.Shape.Private (Unchecked(deconsUnchecked))
import Numeric.LAPACK.Wrapper (Flip(Flip, getFlip))
import Data.Array.Comfort.Shape ((:+:)((:+:)))
import Control.DeepSeq (NFData, rnf)
import Data.Maybe.HT (toMaybe)
import Data.Eq.HT (equating)
data family Extent vertical horizontal :: * -> * -> *
instance
(C vertical, C horizontal, NFData height, NFData width) =>
NFData (Extent vertical horizontal height width) where
rnf :: Extent vertical horizontal height width -> ()
rnf =
Accessor () height width vertical horizontal
-> Extent vertical horizontal height width -> ()
forall a height width vert horiz.
Accessor a height width vert horiz
-> Extent vert horiz height width -> a
getAccessor (Accessor () height width vertical horizontal
-> Extent vertical horizontal height width -> ())
-> Accessor () height width vertical horizontal
-> Extent vertical horizontal height width
-> ()
forall a b. (a -> b) -> a -> b
$
Accessor () height width Small Small
-> Accessor () height width Small Big
-> Accessor () height width Big Small
-> Accessor () height width Big Big
-> Accessor () height width vertical horizontal
forall vert horiz (f :: * -> * -> *).
(C vert, C horiz) =>
f Small Small
-> f Small Big -> f Big Small -> f Big Big -> f vert horiz
switchTagPair
((Extent Small Small height width -> ())
-> Accessor () height width Small Small
forall a height width vert horiz.
(Extent vert horiz height width -> a)
-> Accessor a height width vert horiz
Accessor ((Extent Small Small height width -> ())
-> Accessor () height width Small Small)
-> (Extent Small Small height width -> ())
-> Accessor () height width Small Small
forall a b. (a -> b) -> a -> b
$ \(Square s) -> height -> ()
forall a. NFData a => a -> ()
rnf height
s)
((Extent Small Big height width -> ())
-> Accessor () height width Small Big
forall a height width vert horiz.
(Extent vert horiz height width -> a)
-> Accessor a height width vert horiz
Accessor ((Extent Small Big height width -> ())
-> Accessor () height width Small Big)
-> (Extent Small Big height width -> ())
-> Accessor () height width Small Big
forall a b. (a -> b) -> a -> b
$ \(Wide h w) -> (height, width) -> ()
forall a. NFData a => a -> ()
rnf (height
h,width
w))
((Extent Big Small height width -> ())
-> Accessor () height width Big Small
forall a height width vert horiz.
(Extent vert horiz height width -> a)
-> Accessor a height width vert horiz
Accessor ((Extent Big Small height width -> ())
-> Accessor () height width Big Small)
-> (Extent Big Small height width -> ())
-> Accessor () height width Big Small
forall a b. (a -> b) -> a -> b
$ \(Tall h w) -> (height, width) -> ()
forall a. NFData a => a -> ()
rnf (height
h,width
w))
((Extent Big Big height width -> ())
-> Accessor () height width Big Big
forall a height width vert horiz.
(Extent vert horiz height width -> a)
-> Accessor a height width vert horiz
Accessor ((Extent Big Big height width -> ())
-> Accessor () height width Big Big)
-> (Extent Big Big height width -> ())
-> Accessor () height width Big Big
forall a b. (a -> b) -> a -> b
$ \(General h w) -> (height, width) -> ()
forall a. NFData a => a -> ()
rnf (height
h,width
w))
data Big = Big deriving (Big -> Big -> Bool
(Big -> Big -> Bool) -> (Big -> Big -> Bool) -> Eq Big
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Big -> Big -> Bool
$c/= :: Big -> Big -> Bool
== :: Big -> Big -> Bool
$c== :: Big -> Big -> Bool
Eq,Int -> Big -> ShowS
[Big] -> ShowS
Big -> String
(Int -> Big -> ShowS)
-> (Big -> String) -> ([Big] -> ShowS) -> Show Big
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Big] -> ShowS
$cshowList :: [Big] -> ShowS
show :: Big -> String
$cshow :: Big -> String
showsPrec :: Int -> Big -> ShowS
$cshowsPrec :: Int -> Big -> ShowS
Show)
data Small = Small deriving (Small -> Small -> Bool
(Small -> Small -> Bool) -> (Small -> Small -> Bool) -> Eq Small
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Small -> Small -> Bool
$c/= :: Small -> Small -> Bool
== :: Small -> Small -> Bool
$c== :: Small -> Small -> Bool
Eq,Int -> Small -> ShowS
[Small] -> ShowS
Small -> String
(Int -> Small -> ShowS)
-> (Small -> String) -> ([Small] -> ShowS) -> Show Small
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Small] -> ShowS
$cshowList :: [Small] -> ShowS
show :: Small -> String
$cshow :: Small -> String
showsPrec :: Int -> Small -> ShowS
$cshowsPrec :: Int -> Small -> ShowS
Show)
instance NFData Big where rnf :: Big -> ()
rnf Big
Big = ()
instance NFData Small where rnf :: Small -> ()
rnf Small
Small = ()
type General = Extent Big Big
type Tall = Extent Big Small
type Wide = Extent Small Big
type Square sh = Extent Small Small sh sh
data instance Extent Big Big height width =
General {
Extent Big Big height width -> height
generalHeight :: height,
Extent Big Big height width -> width
generalWidth :: width
}
data instance Extent Big Small height width =
Tall {
Extent Big Small height width -> height
tallHeight :: height,
Extent Big Small height width -> width
tallWidth :: width
}
data instance Extent Small Big height width =
Wide {
Extent Small Big height width -> height
wideHeight :: height,
Extent Small Big height width -> width
wideWidth :: width
}
data instance Extent Small Small height width =
(height ~ width) =>
Square {
Extent Small Small height width -> height
squareSize :: height
}
general :: height -> width -> General height width
general :: height -> width -> General height width
general = height -> width -> General height width
forall height width. height -> width -> Extent Big Big height width
General
tall :: height -> width -> Tall height width
tall :: height -> width -> Tall height width
tall = height -> width -> Tall height width
forall height width.
height -> width -> Extent Big Small height width
Tall
wide :: height -> width -> Wide height width
wide :: height -> width -> Wide height width
wide = height -> width -> Wide height width
forall height width.
height -> width -> Extent Small Big height width
Wide
square :: sh -> Square sh
square :: sh -> Square sh
square = sh -> Square sh
forall height width.
(height ~ width) =>
height -> Extent Small Small height width
Square
newtype Map vertA horizA vertB horizB height width =
Map {
Map vertA horizA vertB horizB height width
-> Extent vertA horizA height width
-> Extent vertB horizB height width
apply ::
Extent vertA horizA height width ->
Extent vertB horizB height width
}
class C tag where switchTag :: f Small -> f Big -> f tag
instance C Small where switchTag :: f Small -> f Big -> f Small
switchTag f Small
f f Big
_ = f Small
f
instance C Big where switchTag :: f Small -> f Big -> f Big
switchTag f Small
_ f Big
f = f Big
f
switchTagPair ::
(C vert, C horiz) =>
f Small Small -> f Small Big -> f Big Small -> f Big Big -> f vert horiz
switchTagPair :: f Small Small
-> f Small Big -> f Big Small -> f Big Big -> f vert horiz
switchTagPair f Small Small
fSquare f Small Big
fWide f Big Small
fTall f Big Big
fGeneral =
Flip f horiz vert -> f vert horiz
forall (f :: * -> * -> *) b a. Flip f b a -> f a b
getFlip (Flip f horiz vert -> f vert horiz)
-> Flip f horiz vert -> f vert horiz
forall a b. (a -> b) -> a -> b
$
Flip f horiz Small -> Flip f horiz Big -> Flip f horiz vert
forall tag (f :: * -> *). C tag => f Small -> f Big -> f tag
switchTag
(f Small horiz -> Flip f horiz Small
forall (f :: * -> * -> *) b a. f a b -> Flip f b a
Flip (f Small horiz -> Flip f horiz Small)
-> f Small horiz -> Flip f horiz Small
forall a b. (a -> b) -> a -> b
$ f Small Small -> f Small Big -> f Small horiz
forall tag (f :: * -> *). C tag => f Small -> f Big -> f tag
switchTag f Small Small
fSquare f Small Big
fWide)
(f Big horiz -> Flip f horiz Big
forall (f :: * -> * -> *) b a. f a b -> Flip f b a
Flip (f Big horiz -> Flip f horiz Big)
-> f Big horiz -> Flip f horiz Big
forall a b. (a -> b) -> a -> b
$ f Big Small -> f Big Big -> f Big horiz
forall tag (f :: * -> *). C tag => f Small -> f Big -> f tag
switchTag f Big Small
fTall f Big Big
fGeneral)
newtype CaseTallWide height width vert horiz =
CaseTallWide {
CaseTallWide height width vert horiz
-> Extent vert horiz height width
-> Either (Tall height width) (Wide height width)
getCaseTallWide ::
Extent vert horiz height width ->
Either (Tall height width) (Wide height width)
}
caseTallWide ::
(C vert, C horiz) =>
(height -> width -> Bool) ->
Extent vert horiz height width ->
Either (Tall height width) (Wide height width)
caseTallWide :: (height -> width -> Bool)
-> Extent vert horiz height width
-> Either (Tall height width) (Wide height width)
caseTallWide height -> width -> Bool
ge =
CaseTallWide height width vert horiz
-> Extent vert horiz height width
-> Either (Tall height width) (Wide height width)
forall height width vert horiz.
CaseTallWide height width vert horiz
-> Extent vert horiz height width
-> Either (Tall height width) (Wide height width)
getCaseTallWide (CaseTallWide height width vert horiz
-> Extent vert horiz height width
-> Either (Tall height width) (Wide height width))
-> CaseTallWide height width vert horiz
-> Extent vert horiz height width
-> Either (Tall height width) (Wide height width)
forall a b. (a -> b) -> a -> b
$
CaseTallWide height width Small Small
-> CaseTallWide height width Small Big
-> CaseTallWide height width Big Small
-> CaseTallWide height width Big Big
-> CaseTallWide height width vert horiz
forall vert horiz (f :: * -> * -> *).
(C vert, C horiz) =>
f Small Small
-> f Small Big -> f Big Small -> f Big Big -> f vert horiz
switchTagPair
((Extent Small Small height width
-> Either (Tall height width) (Wide height width))
-> CaseTallWide height width Small Small
forall height width vert horiz.
(Extent vert horiz height width
-> Either (Tall height width) (Wide height width))
-> CaseTallWide height width vert horiz
CaseTallWide ((Extent Small Small height width
-> Either (Tall height width) (Wide height width))
-> CaseTallWide height width Small Small)
-> (Extent Small Small height width
-> Either (Tall height width) (Wide height width))
-> CaseTallWide height width Small Small
forall a b. (a -> b) -> a -> b
$ \(Square sh) -> Tall height height
-> Either (Tall height height) (Wide height width)
forall a b. a -> Either a b
Left (Tall height height
-> Either (Tall height height) (Wide height width))
-> Tall height height
-> Either (Tall height height) (Wide height width)
forall a b. (a -> b) -> a -> b
$ height -> height -> Tall height height
forall height width.
height -> width -> Extent Big Small height width
tall height
sh height
sh)
((Wide height width
-> Either (Tall height width) (Wide height width))
-> CaseTallWide height width Small Big
forall height width vert horiz.
(Extent vert horiz height width
-> Either (Tall height width) (Wide height width))
-> CaseTallWide height width vert horiz
CaseTallWide Wide height width -> Either (Tall height width) (Wide height width)
forall a b. b -> Either a b
Right)
((Tall height width
-> Either (Tall height width) (Wide height width))
-> CaseTallWide height width Big Small
forall height width vert horiz.
(Extent vert horiz height width
-> Either (Tall height width) (Wide height width))
-> CaseTallWide height width vert horiz
CaseTallWide Tall height width -> Either (Tall height width) (Wide height width)
forall a b. a -> Either a b
Left)
((Extent Big Big height width
-> Either (Tall height width) (Wide height width))
-> CaseTallWide height width Big Big
forall height width vert horiz.
(Extent vert horiz height width
-> Either (Tall height width) (Wide height width))
-> CaseTallWide height width vert horiz
CaseTallWide ((Extent Big Big height width
-> Either (Tall height width) (Wide height width))
-> CaseTallWide height width Big Big)
-> (Extent Big Big height width
-> Either (Tall height width) (Wide height width))
-> CaseTallWide height width Big Big
forall a b. (a -> b) -> a -> b
$ \(General h w) ->
if height -> width -> Bool
ge height
h width
w
then Tall height width -> Either (Tall height width) (Wide height width)
forall a b. a -> Either a b
Left (Tall height width
-> Either (Tall height width) (Wide height width))
-> Tall height width
-> Either (Tall height width) (Wide height width)
forall a b. (a -> b) -> a -> b
$ height -> width -> Tall height width
forall height width.
height -> width -> Extent Big Small height width
tall height
h width
w
else Wide height width -> Either (Tall height width) (Wide height width)
forall a b. b -> Either a b
Right (Wide height width
-> Either (Tall height width) (Wide height width))
-> Wide height width
-> Either (Tall height width) (Wide height width)
forall a b. (a -> b) -> a -> b
$ height -> width -> Wide height width
forall height width.
height -> width -> Extent Small Big height width
wide height
h width
w)
newtype GenSquare sh vert horiz =
GenSquare {GenSquare sh vert horiz -> sh -> Extent vert horiz sh sh
getGenSquare :: sh -> Extent vert horiz sh sh}
genSquare :: (C vert, C horiz) => sh -> Extent vert horiz sh sh
genSquare :: sh -> Extent vert horiz sh sh
genSquare =
GenSquare sh vert horiz -> sh -> Extent vert horiz sh sh
forall sh vert horiz.
GenSquare sh vert horiz -> sh -> Extent vert horiz sh sh
getGenSquare (GenSquare sh vert horiz -> sh -> Extent vert horiz sh sh)
-> GenSquare sh vert horiz -> sh -> Extent vert horiz sh sh
forall a b. (a -> b) -> a -> b
$
GenSquare sh Small Small
-> GenSquare sh Small Big
-> GenSquare sh Big Small
-> GenSquare sh Big Big
-> GenSquare sh vert horiz
forall vert horiz (f :: * -> * -> *).
(C vert, C horiz) =>
f Small Small
-> f Small Big -> f Big Small -> f Big Big -> f vert horiz
switchTagPair
((sh -> Extent Small Small sh sh) -> GenSquare sh Small Small
forall sh vert horiz.
(sh -> Extent vert horiz sh sh) -> GenSquare sh vert horiz
GenSquare sh -> Extent Small Small sh sh
forall sh. sh -> Square sh
square)
((sh -> Extent Small Big sh sh) -> GenSquare sh Small Big
forall sh vert horiz.
(sh -> Extent vert horiz sh sh) -> GenSquare sh vert horiz
GenSquare (\sh
sh -> sh -> sh -> Extent Small Big sh sh
forall height width.
height -> width -> Extent Small Big height width
wide sh
sh sh
sh))
((sh -> Extent Big Small sh sh) -> GenSquare sh Big Small
forall sh vert horiz.
(sh -> Extent vert horiz sh sh) -> GenSquare sh vert horiz
GenSquare (\sh
sh -> sh -> sh -> Extent Big Small sh sh
forall height width.
height -> width -> Extent Big Small height width
tall sh
sh sh
sh))
((sh -> Extent Big Big sh sh) -> GenSquare sh Big Big
forall sh vert horiz.
(sh -> Extent vert horiz sh sh) -> GenSquare sh vert horiz
GenSquare (\sh
sh -> sh -> sh -> Extent Big Big sh sh
forall height width. height -> width -> Extent Big Big height width
general sh
sh sh
sh))
newtype GenTall height width vert horiz =
GenTall {
GenTall height width vert horiz
-> Extent vert Small height width -> Extent vert horiz height width
getGenTall ::
Extent vert Small height width -> Extent vert horiz height width
}
generalizeTall :: (C vert, C horiz) =>
Extent vert Small height width -> Extent vert horiz height width
generalizeTall :: Extent vert Small height width -> Extent vert horiz height width
generalizeTall =
GenTall height width vert horiz
-> Extent vert Small height width -> Extent vert horiz height width
forall height width vert horiz.
GenTall height width vert horiz
-> Extent vert Small height width -> Extent vert horiz height width
getGenTall (GenTall height width vert horiz
-> Extent vert Small height width
-> Extent vert horiz height width)
-> GenTall height width vert horiz
-> Extent vert Small height width
-> Extent vert horiz height width
forall a b. (a -> b) -> a -> b
$
GenTall height width Small Small
-> GenTall height width Small Big
-> GenTall height width Big Small
-> GenTall height width Big Big
-> GenTall height width vert horiz
forall vert horiz (f :: * -> * -> *).
(C vert, C horiz) =>
f Small Small
-> f Small Big -> f Big Small -> f Big Big -> f vert horiz
switchTagPair
((Extent Small Small height width
-> Extent Small Small height width)
-> GenTall height width Small Small
forall height width vert horiz.
(Extent vert Small height width -> Extent vert horiz height width)
-> GenTall height width vert horiz
GenTall Extent Small Small height width -> Extent Small Small height width
forall a. a -> a
id) ((Extent Small Small height width -> Extent Small Big height width)
-> GenTall height width Small Big
forall height width vert horiz.
(Extent vert Small height width -> Extent vert horiz height width)
-> GenTall height width vert horiz
GenTall ((Extent Small Small height width -> Extent Small Big height width)
-> GenTall height width Small Big)
-> (Extent Small Small height width
-> Extent Small Big height width)
-> GenTall height width Small Big
forall a b. (a -> b) -> a -> b
$ \(Square s) -> height -> height -> Wide height height
forall height width.
height -> width -> Extent Small Big height width
wide height
s height
s)
((Extent Big Small height width -> Extent Big Small height width)
-> GenTall height width Big Small
forall height width vert horiz.
(Extent vert Small height width -> Extent vert horiz height width)
-> GenTall height width vert horiz
GenTall Extent Big Small height width -> Extent Big Small height width
forall a. a -> a
id) ((Extent Big Small height width -> Extent Big Big height width)
-> GenTall height width Big Big
forall height width vert horiz.
(Extent vert Small height width -> Extent vert horiz height width)
-> GenTall height width vert horiz
GenTall ((Extent Big Small height width -> Extent Big Big height width)
-> GenTall height width Big Big)
-> (Extent Big Small height width -> Extent Big Big height width)
-> GenTall height width Big Big
forall a b. (a -> b) -> a -> b
$ \(Tall h w) -> height -> width -> Extent Big Big height width
forall height width. height -> width -> Extent Big Big height width
general height
h width
w)
newtype GenWide height width vert horiz =
GenWide {
GenWide height width vert horiz
-> Extent Small horiz height width
-> Extent vert horiz height width
getGenWide ::
Extent Small horiz height width -> Extent vert horiz height width
}
generalizeWide :: (C vert, C horiz) =>
Extent Small horiz height width -> Extent vert horiz height width
generalizeWide :: Extent Small horiz height width -> Extent vert horiz height width
generalizeWide =
GenWide height width vert horiz
-> Extent Small horiz height width
-> Extent vert horiz height width
forall height width vert horiz.
GenWide height width vert horiz
-> Extent Small horiz height width
-> Extent vert horiz height width
getGenWide (GenWide height width vert horiz
-> Extent Small horiz height width
-> Extent vert horiz height width)
-> GenWide height width vert horiz
-> Extent Small horiz height width
-> Extent vert horiz height width
forall a b. (a -> b) -> a -> b
$
GenWide height width Small Small
-> GenWide height width Small Big
-> GenWide height width Big Small
-> GenWide height width Big Big
-> GenWide height width vert horiz
forall vert horiz (f :: * -> * -> *).
(C vert, C horiz) =>
f Small Small
-> f Small Big -> f Big Small -> f Big Big -> f vert horiz
switchTagPair
((Extent Small Small height width
-> Extent Small Small height width)
-> GenWide height width Small Small
forall height width vert horiz.
(Extent Small horiz height width -> Extent vert horiz height width)
-> GenWide height width vert horiz
GenWide Extent Small Small height width -> Extent Small Small height width
forall a. a -> a
id)
((Extent Small Big height width -> Extent Small Big height width)
-> GenWide height width Small Big
forall height width vert horiz.
(Extent Small horiz height width -> Extent vert horiz height width)
-> GenWide height width vert horiz
GenWide Extent Small Big height width -> Extent Small Big height width
forall a. a -> a
id)
((Extent Small Small height width -> Extent Big Small height width)
-> GenWide height width Big Small
forall height width vert horiz.
(Extent Small horiz height width -> Extent vert horiz height width)
-> GenWide height width vert horiz
GenWide ((Extent Small Small height width -> Extent Big Small height width)
-> GenWide height width Big Small)
-> (Extent Small Small height width
-> Extent Big Small height width)
-> GenWide height width Big Small
forall a b. (a -> b) -> a -> b
$ \(Square s) -> height -> height -> Tall height height
forall height width.
height -> width -> Extent Big Small height width
tall height
s height
s)
((Extent Small Big height width -> Extent Big Big height width)
-> GenWide height width Big Big
forall height width vert horiz.
(Extent Small horiz height width -> Extent vert horiz height width)
-> GenWide height width vert horiz
GenWide ((Extent Small Big height width -> Extent Big Big height width)
-> GenWide height width Big Big)
-> (Extent Small Big height width -> Extent Big Big height width)
-> GenWide height width Big Big
forall a b. (a -> b) -> a -> b
$ \(Wide h w) -> height -> width -> Extent Big Big height width
forall height width. height -> width -> Extent Big Big height width
general height
h width
w)
newtype GenToTall height width vert horiz =
GenToTall {
GenToTall height width vert horiz
-> Extent vert horiz height width -> Extent Big horiz height width
getGenToTall ::
Extent vert horiz height width -> Extent Big horiz height width
}
genToTall :: (C vert, C horiz) =>
Extent vert horiz height width -> Extent Big horiz height width
genToTall :: Extent vert horiz height width -> Extent Big horiz height width
genToTall =
GenToTall height width vert horiz
-> Extent vert horiz height width -> Extent Big horiz height width
forall height width vert horiz.
GenToTall height width vert horiz
-> Extent vert horiz height width -> Extent Big horiz height width
getGenToTall (GenToTall height width vert horiz
-> Extent vert horiz height width -> Extent Big horiz height width)
-> GenToTall height width vert horiz
-> Extent vert horiz height width
-> Extent Big horiz height width
forall a b. (a -> b) -> a -> b
$
GenToTall height width Small Small
-> GenToTall height width Small Big
-> GenToTall height width Big Small
-> GenToTall height width Big Big
-> GenToTall height width vert horiz
forall vert horiz (f :: * -> * -> *).
(C vert, C horiz) =>
f Small Small
-> f Small Big -> f Big Small -> f Big Big -> f vert horiz
switchTagPair
((Extent Small Small height width -> Extent Big Small height width)
-> GenToTall height width Small Small
forall height width vert horiz.
(Extent vert horiz height width -> Extent Big horiz height width)
-> GenToTall height width vert horiz
GenToTall ((Extent Small Small height width -> Extent Big Small height width)
-> GenToTall height width Small Small)
-> (Extent Small Small height width
-> Extent Big Small height width)
-> GenToTall height width Small Small
forall a b. (a -> b) -> a -> b
$ \(Square s) -> height -> height -> Tall height height
forall height width.
height -> width -> Extent Big Small height width
tall height
s height
s)
((Extent Small Big height width -> Extent Big Big height width)
-> GenToTall height width Small Big
forall height width vert horiz.
(Extent vert horiz height width -> Extent Big horiz height width)
-> GenToTall height width vert horiz
GenToTall ((Extent Small Big height width -> Extent Big Big height width)
-> GenToTall height width Small Big)
-> (Extent Small Big height width -> Extent Big Big height width)
-> GenToTall height width Small Big
forall a b. (a -> b) -> a -> b
$ \(Wide h w) -> height -> width -> Extent Big Big height width
forall height width. height -> width -> Extent Big Big height width
general height
h width
w)
((Extent Big Small height width -> Extent Big Small height width)
-> GenToTall height width Big Small
forall height width vert horiz.
(Extent vert horiz height width -> Extent Big horiz height width)
-> GenToTall height width vert horiz
GenToTall Extent Big Small height width -> Extent Big Small height width
forall a. a -> a
id)
((Extent Big Big height width -> Extent Big Big height width)
-> GenToTall height width Big Big
forall height width vert horiz.
(Extent vert horiz height width -> Extent Big horiz height width)
-> GenToTall height width vert horiz
GenToTall Extent Big Big height width -> Extent Big Big height width
forall a. a -> a
id)
newtype GenToWide height width vert horiz =
GenToWide {
GenToWide height width vert horiz
-> Extent vert horiz height width -> Extent vert Big height width
getGenToWide ::
Extent vert horiz height width -> Extent vert Big height width
}
genToWide :: (C vert, C horiz) =>
Extent vert horiz height width -> Extent vert Big height width
genToWide :: Extent vert horiz height width -> Extent vert Big height width
genToWide =
GenToWide height width vert horiz
-> Extent vert horiz height width -> Extent vert Big height width
forall height width vert horiz.
GenToWide height width vert horiz
-> Extent vert horiz height width -> Extent vert Big height width
getGenToWide (GenToWide height width vert horiz
-> Extent vert horiz height width -> Extent vert Big height width)
-> GenToWide height width vert horiz
-> Extent vert horiz height width
-> Extent vert Big height width
forall a b. (a -> b) -> a -> b
$
GenToWide height width Small Small
-> GenToWide height width Small Big
-> GenToWide height width Big Small
-> GenToWide height width Big Big
-> GenToWide height width vert horiz
forall vert horiz (f :: * -> * -> *).
(C vert, C horiz) =>
f Small Small
-> f Small Big -> f Big Small -> f Big Big -> f vert horiz
switchTagPair
((Extent Small Small height width -> Extent Small Big height width)
-> GenToWide height width Small Small
forall height width vert horiz.
(Extent vert horiz height width -> Extent vert Big height width)
-> GenToWide height width vert horiz
GenToWide ((Extent Small Small height width -> Extent Small Big height width)
-> GenToWide height width Small Small)
-> (Extent Small Small height width
-> Extent Small Big height width)
-> GenToWide height width Small Small
forall a b. (a -> b) -> a -> b
$ \(Square s) -> height -> height -> Wide height height
forall height width.
height -> width -> Extent Small Big height width
wide height
s height
s)
((Extent Small Big height width -> Extent Small Big height width)
-> GenToWide height width Small Big
forall height width vert horiz.
(Extent vert horiz height width -> Extent vert Big height width)
-> GenToWide height width vert horiz
GenToWide Extent Small Big height width -> Extent Small Big height width
forall a. a -> a
id)
((Extent Big Small height width -> Extent Big Big height width)
-> GenToWide height width Big Small
forall height width vert horiz.
(Extent vert horiz height width -> Extent vert Big height width)
-> GenToWide height width vert horiz
GenToWide ((Extent Big Small height width -> Extent Big Big height width)
-> GenToWide height width Big Small)
-> (Extent Big Small height width -> Extent Big Big height width)
-> GenToWide height width Big Small
forall a b. (a -> b) -> a -> b
$ \(Tall h w) -> height -> width -> Extent Big Big height width
forall height width. height -> width -> Extent Big Big height width
general height
h width
w)
((Extent Big Big height width -> Extent Big Big height width)
-> GenToWide height width Big Big
forall height width vert horiz.
(Extent vert horiz height width -> Extent vert Big height width)
-> GenToWide height width vert horiz
GenToWide Extent Big Big height width -> Extent Big Big height width
forall a. a -> a
id)
newtype Accessor a height width vert horiz =
Accessor {Accessor a height width vert horiz
-> Extent vert horiz height width -> a
getAccessor :: Extent vert horiz height width -> a}
height :: (C vert, C horiz) => Extent vert horiz height width -> height
height :: Extent vert horiz height width -> height
height =
Accessor height height width vert horiz
-> Extent vert horiz height width -> height
forall a height width vert horiz.
Accessor a height width vert horiz
-> Extent vert horiz height width -> a
getAccessor (Accessor height height width vert horiz
-> Extent vert horiz height width -> height)
-> Accessor height height width vert horiz
-> Extent vert horiz height width
-> height
forall a b. (a -> b) -> a -> b
$
Accessor height height width Small Small
-> Accessor height height width Small Big
-> Accessor height height width Big Small
-> Accessor height height width Big Big
-> Accessor height height width vert horiz
forall vert horiz (f :: * -> * -> *).
(C vert, C horiz) =>
f Small Small
-> f Small Big -> f Big Small -> f Big Big -> f vert horiz
switchTagPair
((Extent Small Small height width -> height)
-> Accessor height height width Small Small
forall a height width vert horiz.
(Extent vert horiz height width -> a)
-> Accessor a height width vert horiz
Accessor Extent Small Small height width -> height
forall height width. Extent Small Small height width -> height
squareSize)
((Extent Small Big height width -> height)
-> Accessor height height width Small Big
forall a height width vert horiz.
(Extent vert horiz height width -> a)
-> Accessor a height width vert horiz
Accessor Extent Small Big height width -> height
forall height width. Extent Small Big height width -> height
wideHeight)
((Extent Big Small height width -> height)
-> Accessor height height width Big Small
forall a height width vert horiz.
(Extent vert horiz height width -> a)
-> Accessor a height width vert horiz
Accessor Extent Big Small height width -> height
forall height width. Extent Big Small height width -> height
tallHeight)
((Extent Big Big height width -> height)
-> Accessor height height width Big Big
forall a height width vert horiz.
(Extent vert horiz height width -> a)
-> Accessor a height width vert horiz
Accessor Extent Big Big height width -> height
forall height width. Extent Big Big height width -> height
generalHeight)
width :: (C vert, C horiz) => Extent vert horiz height width -> width
width :: Extent vert horiz height width -> width
width =
Accessor width height width vert horiz
-> Extent vert horiz height width -> width
forall a height width vert horiz.
Accessor a height width vert horiz
-> Extent vert horiz height width -> a
getAccessor (Accessor width height width vert horiz
-> Extent vert horiz height width -> width)
-> Accessor width height width vert horiz
-> Extent vert horiz height width
-> width
forall a b. (a -> b) -> a -> b
$
Accessor width height width Small Small
-> Accessor width height width Small Big
-> Accessor width height width Big Small
-> Accessor width height width Big Big
-> Accessor width height width vert horiz
forall vert horiz (f :: * -> * -> *).
(C vert, C horiz) =>
f Small Small
-> f Small Big -> f Big Small -> f Big Big -> f vert horiz
switchTagPair
((Extent Small Small height width -> width)
-> Accessor width height width Small Small
forall a height width vert horiz.
(Extent vert horiz height width -> a)
-> Accessor a height width vert horiz
Accessor (\(Square s) -> height
width
s))
((Extent Small Big height width -> width)
-> Accessor width height width Small Big
forall a height width vert horiz.
(Extent vert horiz height width -> a)
-> Accessor a height width vert horiz
Accessor Extent Small Big height width -> width
forall height width. Extent Small Big height width -> width
wideWidth)
((Extent Big Small height width -> width)
-> Accessor width height width Big Small
forall a height width vert horiz.
(Extent vert horiz height width -> a)
-> Accessor a height width vert horiz
Accessor Extent Big Small height width -> width
forall height width. Extent Big Small height width -> width
tallWidth)
((Extent Big Big height width -> width)
-> Accessor width height width Big Big
forall a height width vert horiz.
(Extent vert horiz height width -> a)
-> Accessor a height width vert horiz
Accessor Extent Big Big height width -> width
forall height width. Extent Big Big height width -> width
generalWidth)
dimensions ::
(C vert, C horiz) => Extent vert horiz height width -> (height,width)
dimensions :: Extent vert horiz height width -> (height, width)
dimensions Extent vert horiz height width
x = (Extent vert horiz height width -> height
forall vert horiz height width.
(C vert, C horiz) =>
Extent vert horiz height width -> height
height Extent vert horiz height width
x, Extent vert horiz height width -> width
forall vert horiz height width.
(C vert, C horiz) =>
Extent vert horiz height width -> width
width Extent vert horiz height width
x)
toGeneral ::
(C vert, C horiz) => Extent vert horiz height width -> General height width
toGeneral :: Extent vert horiz height width -> General height width
toGeneral Extent vert horiz height width
x = height -> width -> General height width
forall height width. height -> width -> Extent Big Big height width
general (Extent vert horiz height width -> height
forall vert horiz height width.
(C vert, C horiz) =>
Extent vert horiz height width -> height
height Extent vert horiz height width
x) (Extent vert horiz height width -> width
forall vert horiz height width.
(C vert, C horiz) =>
Extent vert horiz height width -> width
width Extent vert horiz height width
x)
fromSquare :: (C vert, C horiz) => Square size -> Extent vert horiz size size
fromSquare :: Square size -> Extent vert horiz size size
fromSquare = size -> Extent vert horiz size size
forall vert horiz sh.
(C vert, C horiz) =>
sh -> Extent vert horiz sh sh
genSquare (size -> Extent vert horiz size size)
-> (Square size -> size)
-> Square size
-> Extent vert horiz size size
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Square size -> size
forall height width. Extent Small Small height width -> height
squareSize
fromSquareLiberal :: (C vert, C horiz) =>
Extent Small Small height width -> Extent vert horiz height width
fromSquareLiberal :: Extent Small Small height width -> Extent vert horiz height width
fromSquareLiberal (Square s) = height -> Extent vert horiz height height
forall vert horiz sh.
(C vert, C horiz) =>
sh -> Extent vert horiz sh sh
genSquare height
s
squareFromGeneral ::
(C vert, C horiz, Eq size) =>
Extent vert horiz size size -> Square size
squareFromGeneral :: Extent vert horiz size size -> Square size
squareFromGeneral Extent vert horiz size size
x =
let size :: size
size = Extent vert horiz size size -> size
forall vert horiz height width.
(C vert, C horiz) =>
Extent vert horiz height width -> height
height Extent vert horiz size size
x
in if size
size size -> size -> Bool
forall a. Eq a => a -> a -> Bool
== Extent vert horiz size size -> size
forall vert horiz height width.
(C vert, C horiz) =>
Extent vert horiz height width -> width
width Extent vert horiz size size
x
then size -> Square size
forall sh. sh -> Square sh
square size
size
else String -> Square size
forall a. HasCallStack => String -> a
error String
"Extent.squareFromGeneral: no square shape"
newtype Transpose height width vert horiz =
Transpose {
Transpose height width vert horiz
-> Extent vert horiz height width -> Extent horiz vert width height
getTranspose ::
Extent vert horiz height width ->
Extent horiz vert width height
}
transpose ::
(C vert, C horiz) =>
Extent vert horiz height width ->
Extent horiz vert width height
transpose :: Extent vert horiz height width -> Extent horiz vert width height
transpose =
Transpose height width vert horiz
-> Extent vert horiz height width -> Extent horiz vert width height
forall height width vert horiz.
Transpose height width vert horiz
-> Extent vert horiz height width -> Extent horiz vert width height
getTranspose (Transpose height width vert horiz
-> Extent vert horiz height width
-> Extent horiz vert width height)
-> Transpose height width vert horiz
-> Extent vert horiz height width
-> Extent horiz vert width height
forall a b. (a -> b) -> a -> b
$
Transpose height width Small Small
-> Transpose height width Small Big
-> Transpose height width Big Small
-> Transpose height width Big Big
-> Transpose height width vert horiz
forall vert horiz (f :: * -> * -> *).
(C vert, C horiz) =>
f Small Small
-> f Small Big -> f Big Small -> f Big Big -> f vert horiz
switchTagPair
((Extent Small Small height width
-> Extent Small Small width height)
-> Transpose height width Small Small
forall height width vert horiz.
(Extent vert horiz height width -> Extent horiz vert width height)
-> Transpose height width vert horiz
Transpose ((Extent Small Small height width
-> Extent Small Small width height)
-> Transpose height width Small Small)
-> (Extent Small Small height width
-> Extent Small Small width height)
-> Transpose height width Small Small
forall a b. (a -> b) -> a -> b
$ \(Square s) -> height -> Extent Small Small height height
forall height width.
(height ~ width) =>
height -> Extent Small Small height width
Square height
s)
((Extent Small Big height width -> Extent Big Small width height)
-> Transpose height width Small Big
forall height width vert horiz.
(Extent vert horiz height width -> Extent horiz vert width height)
-> Transpose height width vert horiz
Transpose ((Extent Small Big height width -> Extent Big Small width height)
-> Transpose height width Small Big)
-> (Extent Small Big height width -> Extent Big Small width height)
-> Transpose height width Small Big
forall a b. (a -> b) -> a -> b
$ \(Wide h w) -> width -> height -> Extent Big Small width height
forall height width.
height -> width -> Extent Big Small height width
Tall width
w height
h)
((Extent Big Small height width -> Extent Small Big width height)
-> Transpose height width Big Small
forall height width vert horiz.
(Extent vert horiz height width -> Extent horiz vert width height)
-> Transpose height width vert horiz
Transpose ((Extent Big Small height width -> Extent Small Big width height)
-> Transpose height width Big Small)
-> (Extent Big Small height width -> Extent Small Big width height)
-> Transpose height width Big Small
forall a b. (a -> b) -> a -> b
$ \(Tall h w) -> width -> height -> Extent Small Big width height
forall height width.
height -> width -> Extent Small Big height width
Wide width
w height
h)
((Extent Big Big height width -> Extent Big Big width height)
-> Transpose height width Big Big
forall height width vert horiz.
(Extent vert horiz height width -> Extent horiz vert width height)
-> Transpose height width vert horiz
Transpose ((Extent Big Big height width -> Extent Big Big width height)
-> Transpose height width Big Big)
-> (Extent Big Big height width -> Extent Big Big width height)
-> Transpose height width Big Big
forall a b. (a -> b) -> a -> b
$ \(General h w) -> width -> height -> Extent Big Big width height
forall height width. height -> width -> Extent Big Big height width
General width
w height
h)
newtype Equal height width vert horiz =
Equal {
Equal height width vert horiz
-> Extent vert horiz height width
-> Extent vert horiz height width
-> Bool
getEqual ::
Extent vert horiz height width ->
Extent vert horiz height width -> Bool
}
instance
(C vert, C horiz, Eq height, Eq width) =>
Eq (Extent vert horiz height width) where
== :: Extent vert horiz height width
-> Extent vert horiz height width -> Bool
(==) =
Equal height width vert horiz
-> Extent vert horiz height width
-> Extent vert horiz height width
-> Bool
forall height width vert horiz.
Equal height width vert horiz
-> Extent vert horiz height width
-> Extent vert horiz height width
-> Bool
getEqual (Equal height width vert horiz
-> Extent vert horiz height width
-> Extent vert horiz height width
-> Bool)
-> Equal height width vert horiz
-> Extent vert horiz height width
-> Extent vert horiz height width
-> Bool
forall a b. (a -> b) -> a -> b
$
Equal height width Small Small
-> Equal height width Small Big
-> Equal height width Big Small
-> Equal height width Big Big
-> Equal height width vert horiz
forall vert horiz (f :: * -> * -> *).
(C vert, C horiz) =>
f Small Small
-> f Small Big -> f Big Small -> f Big Big -> f vert horiz
switchTagPair
((Extent Small Small height width
-> Extent Small Small height width -> Bool)
-> Equal height width Small Small
forall height width vert horiz.
(Extent vert horiz height width
-> Extent vert horiz height width -> Bool)
-> Equal height width vert horiz
Equal ((Extent Small Small height width
-> Extent Small Small height width -> Bool)
-> Equal height width Small Small)
-> (Extent Small Small height width
-> Extent Small Small height width -> Bool)
-> Equal height width Small Small
forall a b. (a -> b) -> a -> b
$ \(Square a) (Square b) -> height
aheight -> height -> Bool
forall a. Eq a => a -> a -> Bool
==height
b)
((Extent Small Big height width
-> Extent Small Big height width -> Bool)
-> Equal height width Small Big
forall height width vert horiz.
(Extent vert horiz height width
-> Extent vert horiz height width -> Bool)
-> Equal height width vert horiz
Equal ((Extent Small Big height width
-> Extent Small Big height width -> Bool)
-> Equal height width Small Big)
-> (Extent Small Big height width
-> Extent Small Big height width -> Bool)
-> Equal height width Small Big
forall a b. (a -> b) -> a -> b
$ \Extent Small Big height width
a Extent Small Big height width
b -> (Extent Small Big height width -> height)
-> Extent Small Big height width
-> Extent Small Big height width
-> Bool
forall b a. Eq b => (a -> b) -> a -> a -> Bool
equating Extent Small Big height width -> height
forall height width. Extent Small Big height width -> height
wideHeight Extent Small Big height width
a Extent Small Big height width
b Bool -> Bool -> Bool
&& (Extent Small Big height width -> width)
-> Extent Small Big height width
-> Extent Small Big height width
-> Bool
forall b a. Eq b => (a -> b) -> a -> a -> Bool
equating Extent Small Big height width -> width
forall height width. Extent Small Big height width -> width
wideWidth Extent Small Big height width
a Extent Small Big height width
b)
((Extent Big Small height width
-> Extent Big Small height width -> Bool)
-> Equal height width Big Small
forall height width vert horiz.
(Extent vert horiz height width
-> Extent vert horiz height width -> Bool)
-> Equal height width vert horiz
Equal ((Extent Big Small height width
-> Extent Big Small height width -> Bool)
-> Equal height width Big Small)
-> (Extent Big Small height width
-> Extent Big Small height width -> Bool)
-> Equal height width Big Small
forall a b. (a -> b) -> a -> b
$ \Extent Big Small height width
a Extent Big Small height width
b -> (Extent Big Small height width -> height)
-> Extent Big Small height width
-> Extent Big Small height width
-> Bool
forall b a. Eq b => (a -> b) -> a -> a -> Bool
equating Extent Big Small height width -> height
forall height width. Extent Big Small height width -> height
tallHeight Extent Big Small height width
a Extent Big Small height width
b Bool -> Bool -> Bool
&& (Extent Big Small height width -> width)
-> Extent Big Small height width
-> Extent Big Small height width
-> Bool
forall b a. Eq b => (a -> b) -> a -> a -> Bool
equating Extent Big Small height width -> width
forall height width. Extent Big Small height width -> width
tallWidth Extent Big Small height width
a Extent Big Small height width
b)
((Extent Big Big height width
-> Extent Big Big height width -> Bool)
-> Equal height width Big Big
forall height width vert horiz.
(Extent vert horiz height width
-> Extent vert horiz height width -> Bool)
-> Equal height width vert horiz
Equal ((Extent Big Big height width
-> Extent Big Big height width -> Bool)
-> Equal height width Big Big)
-> (Extent Big Big height width
-> Extent Big Big height width -> Bool)
-> Equal height width Big Big
forall a b. (a -> b) -> a -> b
$ \Extent Big Big height width
a Extent Big Big height width
b ->
(Extent Big Big height width -> height)
-> Extent Big Big height width
-> Extent Big Big height width
-> Bool
forall b a. Eq b => (a -> b) -> a -> a -> Bool
equating Extent Big Big height width -> height
forall height width. Extent Big Big height width -> height
generalHeight Extent Big Big height width
a Extent Big Big height width
b Bool -> Bool -> Bool
&& (Extent Big Big height width -> width)
-> Extent Big Big height width
-> Extent Big Big height width
-> Bool
forall b a. Eq b => (a -> b) -> a -> a -> Bool
equating Extent Big Big height width -> width
forall height width. Extent Big Big height width -> width
generalWidth Extent Big Big height width
a Extent Big Big height width
b)
instance
(C vert, C horiz, Show height, Show width) =>
Show (Extent vert horiz height width) where
showsPrec :: Int -> Extent vert horiz height width -> ShowS
showsPrec Int
prec =
Accessor ShowS height width vert horiz
-> Extent vert horiz height width -> ShowS
forall a height width vert horiz.
Accessor a height width vert horiz
-> Extent vert horiz height width -> a
getAccessor (Accessor ShowS height width vert horiz
-> Extent vert horiz height width -> ShowS)
-> Accessor ShowS height width vert horiz
-> Extent vert horiz height width
-> ShowS
forall a b. (a -> b) -> a -> b
$
Accessor ShowS height width Small Small
-> Accessor ShowS height width Small Big
-> Accessor ShowS height width Big Small
-> Accessor ShowS height width Big Big
-> Accessor ShowS height width vert horiz
forall vert horiz (f :: * -> * -> *).
(C vert, C horiz) =>
f Small Small
-> f Small Big -> f Big Small -> f Big Big -> f vert horiz
switchTagPair
((Extent Small Small height width -> ShowS)
-> Accessor ShowS height width Small Small
forall a height width vert horiz.
(Extent vert horiz height width -> a)
-> Accessor a height width vert horiz
Accessor ((Extent Small Small height width -> ShowS)
-> Accessor ShowS height width Small Small)
-> (Extent Small Small height width -> ShowS)
-> Accessor ShowS height width Small Small
forall a b. (a -> b) -> a -> b
$ Int -> Extent Small Small height width -> ShowS
forall height width.
Show height =>
Int -> Extent Small Small height width -> ShowS
showsPrecSquare Int
prec)
((Extent Small Big height width -> ShowS)
-> Accessor ShowS height width Small Big
forall a height width vert horiz.
(Extent vert horiz height width -> a)
-> Accessor a height width vert horiz
Accessor ((Extent Small Big height width -> ShowS)
-> Accessor ShowS height width Small Big)
-> (Extent Small Big height width -> ShowS)
-> Accessor ShowS height width Small Big
forall a b. (a -> b) -> a -> b
$ String -> Int -> Extent Small Big height width -> ShowS
forall vert horiz height width.
(C vert, C horiz, Show height, Show width) =>
String -> Int -> Extent vert horiz height width -> ShowS
showsPrecAny String
"Extent.wide" Int
prec)
((Extent Big Small height width -> ShowS)
-> Accessor ShowS height width Big Small
forall a height width vert horiz.
(Extent vert horiz height width -> a)
-> Accessor a height width vert horiz
Accessor ((Extent Big Small height width -> ShowS)
-> Accessor ShowS height width Big Small)
-> (Extent Big Small height width -> ShowS)
-> Accessor ShowS height width Big Small
forall a b. (a -> b) -> a -> b
$ String -> Int -> Extent Big Small height width -> ShowS
forall vert horiz height width.
(C vert, C horiz, Show height, Show width) =>
String -> Int -> Extent vert horiz height width -> ShowS
showsPrecAny String
"Extent.tall" Int
prec)
((Extent Big Big height width -> ShowS)
-> Accessor ShowS height width Big Big
forall a height width vert horiz.
(Extent vert horiz height width -> a)
-> Accessor a height width vert horiz
Accessor ((Extent Big Big height width -> ShowS)
-> Accessor ShowS height width Big Big)
-> (Extent Big Big height width -> ShowS)
-> Accessor ShowS height width Big Big
forall a b. (a -> b) -> a -> b
$ String -> Int -> Extent Big Big height width -> ShowS
forall vert horiz height width.
(C vert, C horiz, Show height, Show width) =>
String -> Int -> Extent vert horiz height width -> ShowS
showsPrecAny String
"Extent.general" Int
prec)
showsPrecSquare ::
(Show height) =>
Int -> Extent Small Small height width -> ShowS
showsPrecSquare :: Int -> Extent Small Small height width -> ShowS
showsPrecSquare Int
p Extent Small Small height width
x =
Bool -> ShowS -> ShowS
showParen (Int
pInt -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>Int
10) (ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$
String -> ShowS
showString String
"Extent.square " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> height -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 (Extent Small Small height width -> height
forall vert horiz height width.
(C vert, C horiz) =>
Extent vert horiz height width -> height
height Extent Small Small height width
x)
showsPrecAny ::
(C vert, C horiz, Show height, Show width) =>
String -> Int -> Extent vert horiz height width -> ShowS
showsPrecAny :: String -> Int -> Extent vert horiz height width -> ShowS
showsPrecAny String
name Int
p Extent vert horiz height width
x =
Bool -> ShowS -> ShowS
showParen (Int
pInt -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>Int
10) (ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$
String -> ShowS
showString String
name ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
String -> ShowS
showString String
" " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> height -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 (Extent vert horiz height width -> height
forall vert horiz height width.
(C vert, C horiz) =>
Extent vert horiz height width -> height
height Extent vert horiz height width
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
String -> ShowS
showString String
" " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> width -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 (Extent vert horiz height width -> width
forall vert horiz height width.
(C vert, C horiz) =>
Extent vert horiz height width -> width
width Extent vert horiz height width
x)
newtype Widen heightA widthA heightB widthB vert =
Widen {
Widen heightA widthA heightB widthB vert
-> Extent vert Big heightA widthA -> Extent vert Big heightB widthB
getWiden ::
Extent vert Big heightA widthA ->
Extent vert Big heightB widthB
}
widen ::
(C vert) =>
widthB -> Extent vert Big height widthA -> Extent vert Big height widthB
widen :: widthB
-> Extent vert Big height widthA -> Extent vert Big height widthB
widen widthB
w =
Widen height widthA height widthB vert
-> Extent vert Big height widthA -> Extent vert Big height widthB
forall heightA widthA heightB widthB vert.
Widen heightA widthA heightB widthB vert
-> Extent vert Big heightA widthA -> Extent vert Big heightB widthB
getWiden (Widen height widthA height widthB vert
-> Extent vert Big height widthA -> Extent vert Big height widthB)
-> Widen height widthA height widthB vert
-> Extent vert Big height widthA
-> Extent vert Big height widthB
forall a b. (a -> b) -> a -> b
$
Widen height widthA height widthB Small
-> Widen height widthA height widthB Big
-> Widen height widthA height widthB vert
forall tag (f :: * -> *). C tag => f Small -> f Big -> f tag
switchTag
((Extent Small Big height widthA -> Extent Small Big height widthB)
-> Widen height widthA height widthB Small
forall heightA widthA heightB widthB vert.
(Extent vert Big heightA widthA -> Extent vert Big heightB widthB)
-> Widen heightA widthA heightB widthB vert
Widen (\Extent Small Big height widthA
x -> Extent Small Big height widthA
R:ExtentSmallBigheightwidth height widthA
x{wideWidth :: widthB
wideWidth = widthB
w}))
((Extent Big Big height widthA -> Extent Big Big height widthB)
-> Widen height widthA height widthB Big
forall heightA widthA heightB widthB vert.
(Extent vert Big heightA widthA -> Extent vert Big heightB widthB)
-> Widen heightA widthA heightB widthB vert
Widen (\Extent Big Big height widthA
x -> Extent Big Big height widthA
R:ExtentBigBigheightwidth height widthA
x{generalWidth :: widthB
generalWidth = widthB
w}))
reduceWideHeight ::
(C vert) =>
heightB -> Extent vert Big heightA width -> Extent vert Big heightB width
reduceWideHeight :: heightB
-> Extent vert Big heightA width -> Extent vert Big heightB width
reduceWideHeight heightB
h =
Widen heightA width heightB width vert
-> Extent vert Big heightA width -> Extent vert Big heightB width
forall heightA widthA heightB widthB vert.
Widen heightA widthA heightB widthB vert
-> Extent vert Big heightA widthA -> Extent vert Big heightB widthB
getWiden (Widen heightA width heightB width vert
-> Extent vert Big heightA width -> Extent vert Big heightB width)
-> Widen heightA width heightB width vert
-> Extent vert Big heightA width
-> Extent vert Big heightB width
forall a b. (a -> b) -> a -> b
$
Widen heightA width heightB width Small
-> Widen heightA width heightB width Big
-> Widen heightA width heightB width vert
forall tag (f :: * -> *). C tag => f Small -> f Big -> f tag
switchTag
((Extent Small Big heightA width -> Extent Small Big heightB width)
-> Widen heightA width heightB width Small
forall heightA widthA heightB widthB vert.
(Extent vert Big heightA widthA -> Extent vert Big heightB widthB)
-> Widen heightA widthA heightB widthB vert
Widen (\Extent Small Big heightA width
x -> Extent Small Big heightA width
R:ExtentSmallBigheightwidth heightA width
x{wideHeight :: heightB
wideHeight = heightB
h}))
((Extent Big Big heightA width -> Extent Big Big heightB width)
-> Widen heightA width heightB width Big
forall heightA widthA heightB widthB vert.
(Extent vert Big heightA widthA -> Extent vert Big heightB widthB)
-> Widen heightA widthA heightB widthB vert
Widen (\Extent Big Big heightA width
x -> Extent Big Big heightA width
R:ExtentBigBigheightwidth heightA width
x{generalHeight :: heightB
generalHeight = heightB
h}))
newtype Adapt heightA widthA heightB widthB vert horiz =
Adapt {
Adapt heightA widthA heightB widthB vert horiz
-> Extent vert horiz heightA widthA
-> Extent vert horiz heightB widthB
getAdapt ::
Extent vert horiz heightA widthA ->
Extent vert horiz heightB widthB
}
reduceConsistent ::
(C vert, C horiz) =>
height -> width ->
Extent vert horiz height width -> Extent vert horiz height width
reduceConsistent :: height
-> width
-> Extent vert horiz height width
-> Extent vert horiz height width
reduceConsistent height
h width
w =
Adapt height width height width vert horiz
-> Extent vert horiz height width -> Extent vert horiz height width
forall heightA widthA heightB widthB vert horiz.
Adapt heightA widthA heightB widthB vert horiz
-> Extent vert horiz heightA widthA
-> Extent vert horiz heightB widthB
getAdapt (Adapt height width height width vert horiz
-> Extent vert horiz height width
-> Extent vert horiz height width)
-> Adapt height width height width vert horiz
-> Extent vert horiz height width
-> Extent vert horiz height width
forall a b. (a -> b) -> a -> b
$
Adapt height width height width Small Small
-> Adapt height width height width Small Big
-> Adapt height width height width Big Small
-> Adapt height width height width Big Big
-> Adapt height width height width vert horiz
forall vert horiz (f :: * -> * -> *).
(C vert, C horiz) =>
f Small Small
-> f Small Big -> f Big Small -> f Big Big -> f vert horiz
switchTagPair
((Extent Small Small height width
-> Extent Small Small height width)
-> Adapt height width height width Small Small
forall heightA widthA heightB widthB vert horiz.
(Extent vert horiz heightA widthA
-> Extent vert horiz heightB widthB)
-> Adapt heightA widthA heightB widthB vert horiz
Adapt ((Extent Small Small height width
-> Extent Small Small height width)
-> Adapt height width height width Small Small)
-> (Extent Small Small height width
-> Extent Small Small height width)
-> Adapt height width height width Small Small
forall a b. (a -> b) -> a -> b
$ \(Square _) -> height -> Extent Small Small height width
forall height width.
(height ~ width) =>
height -> Extent Small Small height width
Square height
h)
((Extent Small Big height width -> Extent Small Big height width)
-> Adapt height width height width Small Big
forall heightA widthA heightB widthB vert horiz.
(Extent vert horiz heightA widthA
-> Extent vert horiz heightB widthB)
-> Adapt heightA widthA heightB widthB vert horiz
Adapt ((Extent Small Big height width -> Extent Small Big height width)
-> Adapt height width height width Small Big)
-> (Extent Small Big height width -> Extent Small Big height width)
-> Adapt height width height width Small Big
forall a b. (a -> b) -> a -> b
$ \(Wide _ _) -> height -> width -> Extent Small Big height width
forall height width.
height -> width -> Extent Small Big height width
Wide height
h width
w)
((Extent Big Small height width -> Extent Big Small height width)
-> Adapt height width height width Big Small
forall heightA widthA heightB widthB vert horiz.
(Extent vert horiz heightA widthA
-> Extent vert horiz heightB widthB)
-> Adapt heightA widthA heightB widthB vert horiz
Adapt ((Extent Big Small height width -> Extent Big Small height width)
-> Adapt height width height width Big Small)
-> (Extent Big Small height width -> Extent Big Small height width)
-> Adapt height width height width Big Small
forall a b. (a -> b) -> a -> b
$ \(Tall _ _) -> height -> width -> Extent Big Small height width
forall height width.
height -> width -> Extent Big Small height width
Tall height
h width
w)
((Extent Big Big height width -> Extent Big Big height width)
-> Adapt height width height width Big Big
forall heightA widthA heightB widthB vert horiz.
(Extent vert horiz heightA widthA
-> Extent vert horiz heightB widthB)
-> Adapt heightA widthA heightB widthB vert horiz
Adapt ((Extent Big Big height width -> Extent Big Big height width)
-> Adapt height width height width Big Big)
-> (Extent Big Big height width -> Extent Big Big height width)
-> Adapt height width height width Big Big
forall a b. (a -> b) -> a -> b
$ \(General _ _) -> height -> width -> Extent Big Big height width
forall height width. height -> width -> Extent Big Big height width
General height
h width
w)
class (C vert, C horiz) => GeneralTallWide vert horiz where
switchTagGTW :: f Small Big -> f Big Small -> f Big Big -> f vert horiz
instance GeneralTallWide Small Big where switchTagGTW :: f Small Big -> f Big Small -> f Big Big -> f Small Big
switchTagGTW f Small Big
f f Big Small
_ f Big Big
_ = f Small Big
f
instance GeneralTallWide Big Small where switchTagGTW :: f Small Big -> f Big Small -> f Big Big -> f Big Small
switchTagGTW f Small Big
_ f Big Small
f f Big Big
_ = f Big Small
f
instance GeneralTallWide Big Big where switchTagGTW :: f Small Big -> f Big Small -> f Big Big -> f Big Big
switchTagGTW f Small Big
_ f Big Small
_ f Big Big
f = f Big Big
f
mapHeight ::
(GeneralTallWide vert horiz) =>
(heightA -> heightB) ->
Extent vert horiz heightA width -> Extent vert horiz heightB width
mapHeight :: (heightA -> heightB)
-> Extent vert horiz heightA width
-> Extent vert horiz heightB width
mapHeight heightA -> heightB
f =
Adapt heightA width heightB width vert horiz
-> Extent vert horiz heightA width
-> Extent vert horiz heightB width
forall heightA widthA heightB widthB vert horiz.
Adapt heightA widthA heightB widthB vert horiz
-> Extent vert horiz heightA widthA
-> Extent vert horiz heightB widthB
getAdapt (Adapt heightA width heightB width vert horiz
-> Extent vert horiz heightA width
-> Extent vert horiz heightB width)
-> Adapt heightA width heightB width vert horiz
-> Extent vert horiz heightA width
-> Extent vert horiz heightB width
forall a b. (a -> b) -> a -> b
$
Adapt heightA width heightB width Small Big
-> Adapt heightA width heightB width Big Small
-> Adapt heightA width heightB width Big Big
-> Adapt heightA width heightB width vert horiz
forall vert horiz (f :: * -> * -> *).
GeneralTallWide vert horiz =>
f Small Big -> f Big Small -> f Big Big -> f vert horiz
switchTagGTW
((Extent Small Big heightA width -> Extent Small Big heightB width)
-> Adapt heightA width heightB width Small Big
forall heightA widthA heightB widthB vert horiz.
(Extent vert horiz heightA widthA
-> Extent vert horiz heightB widthB)
-> Adapt heightA widthA heightB widthB vert horiz
Adapt ((Extent Small Big heightA width -> Extent Small Big heightB width)
-> Adapt heightA width heightB width Small Big)
-> (Extent Small Big heightA width
-> Extent Small Big heightB width)
-> Adapt heightA width heightB width Small Big
forall a b. (a -> b) -> a -> b
$ \(Wide h w) -> heightB -> width -> Extent Small Big heightB width
forall height width.
height -> width -> Extent Small Big height width
Wide (heightA -> heightB
f heightA
h) width
w)
((Extent Big Small heightA width -> Extent Big Small heightB width)
-> Adapt heightA width heightB width Big Small
forall heightA widthA heightB widthB vert horiz.
(Extent vert horiz heightA widthA
-> Extent vert horiz heightB widthB)
-> Adapt heightA widthA heightB widthB vert horiz
Adapt ((Extent Big Small heightA width -> Extent Big Small heightB width)
-> Adapt heightA width heightB width Big Small)
-> (Extent Big Small heightA width
-> Extent Big Small heightB width)
-> Adapt heightA width heightB width Big Small
forall a b. (a -> b) -> a -> b
$ \(Tall h w) -> heightB -> width -> Extent Big Small heightB width
forall height width.
height -> width -> Extent Big Small height width
Tall (heightA -> heightB
f heightA
h) width
w)
((Extent Big Big heightA width -> Extent Big Big heightB width)
-> Adapt heightA width heightB width Big Big
forall heightA widthA heightB widthB vert horiz.
(Extent vert horiz heightA widthA
-> Extent vert horiz heightB widthB)
-> Adapt heightA widthA heightB widthB vert horiz
Adapt ((Extent Big Big heightA width -> Extent Big Big heightB width)
-> Adapt heightA width heightB width Big Big)
-> (Extent Big Big heightA width -> Extent Big Big heightB width)
-> Adapt heightA width heightB width Big Big
forall a b. (a -> b) -> a -> b
$ \(General h w) -> heightB -> width -> Extent Big Big heightB width
forall height width. height -> width -> Extent Big Big height width
General (heightA -> heightB
f heightA
h) width
w)
mapWidth ::
(GeneralTallWide vert horiz) =>
(widthA -> widthB) ->
Extent vert horiz height widthA -> Extent vert horiz height widthB
mapWidth :: (widthA -> widthB)
-> Extent vert horiz height widthA
-> Extent vert horiz height widthB
mapWidth widthA -> widthB
f =
Adapt height widthA height widthB vert horiz
-> Extent vert horiz height widthA
-> Extent vert horiz height widthB
forall heightA widthA heightB widthB vert horiz.
Adapt heightA widthA heightB widthB vert horiz
-> Extent vert horiz heightA widthA
-> Extent vert horiz heightB widthB
getAdapt (Adapt height widthA height widthB vert horiz
-> Extent vert horiz height widthA
-> Extent vert horiz height widthB)
-> Adapt height widthA height widthB vert horiz
-> Extent vert horiz height widthA
-> Extent vert horiz height widthB
forall a b. (a -> b) -> a -> b
$
Adapt height widthA height widthB Small Big
-> Adapt height widthA height widthB Big Small
-> Adapt height widthA height widthB Big Big
-> Adapt height widthA height widthB vert horiz
forall vert horiz (f :: * -> * -> *).
GeneralTallWide vert horiz =>
f Small Big -> f Big Small -> f Big Big -> f vert horiz
switchTagGTW
((Extent Small Big height widthA -> Extent Small Big height widthB)
-> Adapt height widthA height widthB Small Big
forall heightA widthA heightB widthB vert horiz.
(Extent vert horiz heightA widthA
-> Extent vert horiz heightB widthB)
-> Adapt heightA widthA heightB widthB vert horiz
Adapt ((Extent Small Big height widthA -> Extent Small Big height widthB)
-> Adapt height widthA height widthB Small Big)
-> (Extent Small Big height widthA
-> Extent Small Big height widthB)
-> Adapt height widthA height widthB Small Big
forall a b. (a -> b) -> a -> b
$ \(Wide h w) -> height -> widthB -> Extent Small Big height widthB
forall height width.
height -> width -> Extent Small Big height width
Wide height
h (widthA -> widthB
f widthA
w))
((Extent Big Small height widthA -> Extent Big Small height widthB)
-> Adapt height widthA height widthB Big Small
forall heightA widthA heightB widthB vert horiz.
(Extent vert horiz heightA widthA
-> Extent vert horiz heightB widthB)
-> Adapt heightA widthA heightB widthB vert horiz
Adapt ((Extent Big Small height widthA -> Extent Big Small height widthB)
-> Adapt height widthA height widthB Big Small)
-> (Extent Big Small height widthA
-> Extent Big Small height widthB)
-> Adapt height widthA height widthB Big Small
forall a b. (a -> b) -> a -> b
$ \(Tall h w) -> height -> widthB -> Extent Big Small height widthB
forall height width.
height -> width -> Extent Big Small height width
Tall height
h (widthA -> widthB
f widthA
w))
((Extent Big Big height widthA -> Extent Big Big height widthB)
-> Adapt height widthA height widthB Big Big
forall heightA widthA heightB widthB vert horiz.
(Extent vert horiz heightA widthA
-> Extent vert horiz heightB widthB)
-> Adapt heightA widthA heightB widthB vert horiz
Adapt ((Extent Big Big height widthA -> Extent Big Big height widthB)
-> Adapt height widthA height widthB Big Big)
-> (Extent Big Big height widthA -> Extent Big Big height widthB)
-> Adapt height widthA height widthB Big Big
forall a b. (a -> b) -> a -> b
$ \(General h w) -> height -> widthB -> Extent Big Big height widthB
forall height width. height -> width -> Extent Big Big height width
General height
h (widthA -> widthB
f widthA
w))
mapSquareSize :: (shA -> shB) -> Square shA -> Square shB
mapSquareSize :: (shA -> shB) -> Square shA -> Square shB
mapSquareSize shA -> shB
f (Square s) = shB -> Square shB
forall height width.
(height ~ width) =>
height -> Extent Small Small height width
Square (shA -> shB
f shA
s)
mapWrap ::
(C vert, C horiz) =>
(height -> f height) ->
(width -> f width) ->
Extent vert horiz height width ->
Extent vert horiz (f height) (f width)
mapWrap :: (height -> f height)
-> (width -> f width)
-> Extent vert horiz height width
-> Extent vert horiz (f height) (f width)
mapWrap height -> f height
fh width -> f width
fw =
Adapt height width (f height) (f width) vert horiz
-> Extent vert horiz height width
-> Extent vert horiz (f height) (f width)
forall heightA widthA heightB widthB vert horiz.
Adapt heightA widthA heightB widthB vert horiz
-> Extent vert horiz heightA widthA
-> Extent vert horiz heightB widthB
getAdapt (Adapt height width (f height) (f width) vert horiz
-> Extent vert horiz height width
-> Extent vert horiz (f height) (f width))
-> Adapt height width (f height) (f width) vert horiz
-> Extent vert horiz height width
-> Extent vert horiz (f height) (f width)
forall a b. (a -> b) -> a -> b
$
Adapt height width (f height) (f width) Small Small
-> Adapt height width (f height) (f width) Small Big
-> Adapt height width (f height) (f width) Big Small
-> Adapt height width (f height) (f width) Big Big
-> Adapt height width (f height) (f width) vert horiz
forall vert horiz (f :: * -> * -> *).
(C vert, C horiz) =>
f Small Small
-> f Small Big -> f Big Small -> f Big Big -> f vert horiz
switchTagPair
((Extent Small Small height width
-> Extent Small Small (f height) (f width))
-> Adapt height width (f height) (f width) Small Small
forall heightA widthA heightB widthB vert horiz.
(Extent vert horiz heightA widthA
-> Extent vert horiz heightB widthB)
-> Adapt heightA widthA heightB widthB vert horiz
Adapt ((Extent Small Small height width
-> Extent Small Small (f height) (f width))
-> Adapt height width (f height) (f width) Small Small)
-> (Extent Small Small height width
-> Extent Small Small (f height) (f width))
-> Adapt height width (f height) (f width) Small Small
forall a b. (a -> b) -> a -> b
$ \(Square h) -> f height -> Extent Small Small (f height) (f width)
forall height width.
(height ~ width) =>
height -> Extent Small Small height width
Square (height -> f height
fh height
h))
((Extent Small Big height width
-> Extent Small Big (f height) (f width))
-> Adapt height width (f height) (f width) Small Big
forall heightA widthA heightB widthB vert horiz.
(Extent vert horiz heightA widthA
-> Extent vert horiz heightB widthB)
-> Adapt heightA widthA heightB widthB vert horiz
Adapt ((Extent Small Big height width
-> Extent Small Big (f height) (f width))
-> Adapt height width (f height) (f width) Small Big)
-> (Extent Small Big height width
-> Extent Small Big (f height) (f width))
-> Adapt height width (f height) (f width) Small Big
forall a b. (a -> b) -> a -> b
$ \(Wide h w) -> f height -> f width -> Extent Small Big (f height) (f width)
forall height width.
height -> width -> Extent Small Big height width
Wide (height -> f height
fh height
h) (width -> f width
fw width
w))
((Extent Big Small height width
-> Extent Big Small (f height) (f width))
-> Adapt height width (f height) (f width) Big Small
forall heightA widthA heightB widthB vert horiz.
(Extent vert horiz heightA widthA
-> Extent vert horiz heightB widthB)
-> Adapt heightA widthA heightB widthB vert horiz
Adapt ((Extent Big Small height width
-> Extent Big Small (f height) (f width))
-> Adapt height width (f height) (f width) Big Small)
-> (Extent Big Small height width
-> Extent Big Small (f height) (f width))
-> Adapt height width (f height) (f width) Big Small
forall a b. (a -> b) -> a -> b
$ \(Tall h w) -> f height -> f width -> Extent Big Small (f height) (f width)
forall height width.
height -> width -> Extent Big Small height width
Tall (height -> f height
fh height
h) (width -> f width
fw width
w))
((Extent Big Big height width
-> Extent Big Big (f height) (f width))
-> Adapt height width (f height) (f width) Big Big
forall heightA widthA heightB widthB vert horiz.
(Extent vert horiz heightA widthA
-> Extent vert horiz heightB widthB)
-> Adapt heightA widthA heightB widthB vert horiz
Adapt ((Extent Big Big height width
-> Extent Big Big (f height) (f width))
-> Adapt height width (f height) (f width) Big Big)
-> (Extent Big Big height width
-> Extent Big Big (f height) (f width))
-> Adapt height width (f height) (f width) Big Big
forall a b. (a -> b) -> a -> b
$ \(General h w) -> f height -> f width -> Extent Big Big (f height) (f width)
forall height width. height -> width -> Extent Big Big height width
General (height -> f height
fh height
h) (width -> f width
fw width
w))
recheck ::
(C vert, C horiz) =>
Extent vert horiz (Unchecked height) (Unchecked width) ->
Extent vert horiz height width
recheck :: Extent vert horiz (Unchecked height) (Unchecked width)
-> Extent vert horiz height width
recheck =
Adapt (Unchecked height) (Unchecked width) height width vert horiz
-> Extent vert horiz (Unchecked height) (Unchecked width)
-> Extent vert horiz height width
forall heightA widthA heightB widthB vert horiz.
Adapt heightA widthA heightB widthB vert horiz
-> Extent vert horiz heightA widthA
-> Extent vert horiz heightB widthB
getAdapt (Adapt (Unchecked height) (Unchecked width) height width vert horiz
-> Extent vert horiz (Unchecked height) (Unchecked width)
-> Extent vert horiz height width)
-> Adapt
(Unchecked height) (Unchecked width) height width vert horiz
-> Extent vert horiz (Unchecked height) (Unchecked width)
-> Extent vert horiz height width
forall a b. (a -> b) -> a -> b
$
Adapt (Unchecked height) (Unchecked width) height width Small Small
-> Adapt
(Unchecked height) (Unchecked width) height width Small Big
-> Adapt
(Unchecked height) (Unchecked width) height width Big Small
-> Adapt (Unchecked height) (Unchecked width) height width Big Big
-> Adapt
(Unchecked height) (Unchecked width) height width vert horiz
forall vert horiz (f :: * -> * -> *).
(C vert, C horiz) =>
f Small Small
-> f Small Big -> f Big Small -> f Big Big -> f vert horiz
switchTagPair
((Extent Small Small (Unchecked height) (Unchecked width)
-> Extent Small Small height width)
-> Adapt
(Unchecked height) (Unchecked width) height width Small Small
forall heightA widthA heightB widthB vert horiz.
(Extent vert horiz heightA widthA
-> Extent vert horiz heightB widthB)
-> Adapt heightA widthA heightB widthB vert horiz
Adapt ((Extent Small Small (Unchecked height) (Unchecked width)
-> Extent Small Small height width)
-> Adapt
(Unchecked height) (Unchecked width) height width Small Small)
-> (Extent Small Small (Unchecked height) (Unchecked width)
-> Extent Small Small height width)
-> Adapt
(Unchecked height) (Unchecked width) height width Small Small
forall a b. (a -> b) -> a -> b
$ \(Square h) -> height -> Extent Small Small height width
forall height width.
(height ~ width) =>
height -> Extent Small Small height width
Square (Unchecked height -> height
forall sh. Unchecked sh -> sh
deconsUnchecked Unchecked height
h))
((Extent Small Big (Unchecked height) (Unchecked width)
-> Extent Small Big height width)
-> Adapt
(Unchecked height) (Unchecked width) height width Small Big
forall heightA widthA heightB widthB vert horiz.
(Extent vert horiz heightA widthA
-> Extent vert horiz heightB widthB)
-> Adapt heightA widthA heightB widthB vert horiz
Adapt ((Extent Small Big (Unchecked height) (Unchecked width)
-> Extent Small Big height width)
-> Adapt
(Unchecked height) (Unchecked width) height width Small Big)
-> (Extent Small Big (Unchecked height) (Unchecked width)
-> Extent Small Big height width)
-> Adapt
(Unchecked height) (Unchecked width) height width Small Big
forall a b. (a -> b) -> a -> b
$ \(Wide h w) -> height -> width -> Extent Small Big height width
forall height width.
height -> width -> Extent Small Big height width
Wide (Unchecked height -> height
forall sh. Unchecked sh -> sh
deconsUnchecked Unchecked height
h) (Unchecked width -> width
forall sh. Unchecked sh -> sh
deconsUnchecked Unchecked width
w))
((Extent Big Small (Unchecked height) (Unchecked width)
-> Extent Big Small height width)
-> Adapt
(Unchecked height) (Unchecked width) height width Big Small
forall heightA widthA heightB widthB vert horiz.
(Extent vert horiz heightA widthA
-> Extent vert horiz heightB widthB)
-> Adapt heightA widthA heightB widthB vert horiz
Adapt ((Extent Big Small (Unchecked height) (Unchecked width)
-> Extent Big Small height width)
-> Adapt
(Unchecked height) (Unchecked width) height width Big Small)
-> (Extent Big Small (Unchecked height) (Unchecked width)
-> Extent Big Small height width)
-> Adapt
(Unchecked height) (Unchecked width) height width Big Small
forall a b. (a -> b) -> a -> b
$ \(Tall h w) -> height -> width -> Extent Big Small height width
forall height width.
height -> width -> Extent Big Small height width
Tall (Unchecked height -> height
forall sh. Unchecked sh -> sh
deconsUnchecked Unchecked height
h) (Unchecked width -> width
forall sh. Unchecked sh -> sh
deconsUnchecked Unchecked width
w))
((Extent Big Big (Unchecked height) (Unchecked width)
-> Extent Big Big height width)
-> Adapt (Unchecked height) (Unchecked width) height width Big Big
forall heightA widthA heightB widthB vert horiz.
(Extent vert horiz heightA widthA
-> Extent vert horiz heightB widthB)
-> Adapt heightA widthA heightB widthB vert horiz
Adapt ((Extent Big Big (Unchecked height) (Unchecked width)
-> Extent Big Big height width)
-> Adapt (Unchecked height) (Unchecked width) height width Big Big)
-> (Extent Big Big (Unchecked height) (Unchecked width)
-> Extent Big Big height width)
-> Adapt (Unchecked height) (Unchecked width) height width Big Big
forall a b. (a -> b) -> a -> b
$ \(General h w) ->
height -> width -> Extent Big Big height width
forall height width. height -> width -> Extent Big Big height width
General (Unchecked height -> height
forall sh. Unchecked sh -> sh
deconsUnchecked Unchecked height
h) (Unchecked width -> width
forall sh. Unchecked sh -> sh
deconsUnchecked Unchecked width
w))
newtype Fuse height fuse width vert horiz =
Fuse {
Fuse height fuse width vert horiz
-> Extent vert horiz height fuse
-> Extent vert horiz fuse width
-> Maybe (Extent vert horiz height width)
getFuse ::
Extent vert horiz height fuse ->
Extent vert horiz fuse width ->
Maybe (Extent vert horiz height width)
}
fuse ::
(C vert, C horiz, Eq fuse) =>
Extent vert horiz height fuse ->
Extent vert horiz fuse width ->
Maybe (Extent vert horiz height width)
fuse :: Extent vert horiz height fuse
-> Extent vert horiz fuse width
-> Maybe (Extent vert horiz height width)
fuse =
Fuse height fuse width vert horiz
-> Extent vert horiz height fuse
-> Extent vert horiz fuse width
-> Maybe (Extent vert horiz height width)
forall height fuse width vert horiz.
Fuse height fuse width vert horiz
-> Extent vert horiz height fuse
-> Extent vert horiz fuse width
-> Maybe (Extent vert horiz height width)
getFuse (Fuse height fuse width vert horiz
-> Extent vert horiz height fuse
-> Extent vert horiz fuse width
-> Maybe (Extent vert horiz height width))
-> Fuse height fuse width vert horiz
-> Extent vert horiz height fuse
-> Extent vert horiz fuse width
-> Maybe (Extent vert horiz height width)
forall a b. (a -> b) -> a -> b
$
Fuse height fuse width Small Small
-> Fuse height fuse width Small Big
-> Fuse height fuse width Big Small
-> Fuse height fuse width Big Big
-> Fuse height fuse width vert horiz
forall vert horiz (f :: * -> * -> *).
(C vert, C horiz) =>
f Small Small
-> f Small Big -> f Big Small -> f Big Big -> f vert horiz
switchTagPair
((Extent Small Small height fuse
-> Extent Small Small fuse width
-> Maybe (Extent Small Small height width))
-> Fuse height fuse width Small Small
forall height fuse width vert horiz.
(Extent vert horiz height fuse
-> Extent vert horiz fuse width
-> Maybe (Extent vert horiz height width))
-> Fuse height fuse width vert horiz
Fuse ((Extent Small Small height fuse
-> Extent Small Small fuse width
-> Maybe (Extent Small Small height width))
-> Fuse height fuse width Small Small)
-> (Extent Small Small height fuse
-> Extent Small Small fuse width
-> Maybe (Extent Small Small height width))
-> Fuse height fuse width Small Small
forall a b. (a -> b) -> a -> b
$ \(Square s0) (Square s1) -> Bool
-> Extent Small Small height width
-> Maybe (Extent Small Small height width)
forall a. Bool -> a -> Maybe a
toMaybe (height
s0height -> height -> Bool
forall a. Eq a => a -> a -> Bool
==fuse
height
s1) (Extent Small Small height width
-> Maybe (Extent Small Small height width))
-> Extent Small Small height width
-> Maybe (Extent Small Small height width)
forall a b. (a -> b) -> a -> b
$ height -> Extent Small Small height width
forall height width.
(height ~ width) =>
height -> Extent Small Small height width
Square height
s0)
((Extent Small Big height fuse
-> Extent Small Big fuse width
-> Maybe (Extent Small Big height width))
-> Fuse height fuse width Small Big
forall height fuse width vert horiz.
(Extent vert horiz height fuse
-> Extent vert horiz fuse width
-> Maybe (Extent vert horiz height width))
-> Fuse height fuse width vert horiz
Fuse ((Extent Small Big height fuse
-> Extent Small Big fuse width
-> Maybe (Extent Small Big height width))
-> Fuse height fuse width Small Big)
-> (Extent Small Big height fuse
-> Extent Small Big fuse width
-> Maybe (Extent Small Big height width))
-> Fuse height fuse width Small Big
forall a b. (a -> b) -> a -> b
$ \(Wide h f0) (Wide f1 w) -> Bool
-> Extent Small Big height width
-> Maybe (Extent Small Big height width)
forall a. Bool -> a -> Maybe a
toMaybe (fuse
f0fuse -> fuse -> Bool
forall a. Eq a => a -> a -> Bool
==fuse
f1) (Extent Small Big height width
-> Maybe (Extent Small Big height width))
-> Extent Small Big height width
-> Maybe (Extent Small Big height width)
forall a b. (a -> b) -> a -> b
$ height -> width -> Extent Small Big height width
forall height width.
height -> width -> Extent Small Big height width
Wide height
h width
w)
((Extent Big Small height fuse
-> Extent Big Small fuse width
-> Maybe (Extent Big Small height width))
-> Fuse height fuse width Big Small
forall height fuse width vert horiz.
(Extent vert horiz height fuse
-> Extent vert horiz fuse width
-> Maybe (Extent vert horiz height width))
-> Fuse height fuse width vert horiz
Fuse ((Extent Big Small height fuse
-> Extent Big Small fuse width
-> Maybe (Extent Big Small height width))
-> Fuse height fuse width Big Small)
-> (Extent Big Small height fuse
-> Extent Big Small fuse width
-> Maybe (Extent Big Small height width))
-> Fuse height fuse width Big Small
forall a b. (a -> b) -> a -> b
$ \(Tall h f0) (Tall f1 w) -> Bool
-> Extent Big Small height width
-> Maybe (Extent Big Small height width)
forall a. Bool -> a -> Maybe a
toMaybe (fuse
f0fuse -> fuse -> Bool
forall a. Eq a => a -> a -> Bool
==fuse
f1) (Extent Big Small height width
-> Maybe (Extent Big Small height width))
-> Extent Big Small height width
-> Maybe (Extent Big Small height width)
forall a b. (a -> b) -> a -> b
$ height -> width -> Extent Big Small height width
forall height width.
height -> width -> Extent Big Small height width
Tall height
h width
w)
((Extent Big Big height fuse
-> Extent Big Big fuse width
-> Maybe (Extent Big Big height width))
-> Fuse height fuse width Big Big
forall height fuse width vert horiz.
(Extent vert horiz height fuse
-> Extent vert horiz fuse width
-> Maybe (Extent vert horiz height width))
-> Fuse height fuse width vert horiz
Fuse ((Extent Big Big height fuse
-> Extent Big Big fuse width
-> Maybe (Extent Big Big height width))
-> Fuse height fuse width Big Big)
-> (Extent Big Big height fuse
-> Extent Big Big fuse width
-> Maybe (Extent Big Big height width))
-> Fuse height fuse width Big Big
forall a b. (a -> b) -> a -> b
$ \(General h f0) (General f1 w) -> Bool
-> Extent Big Big height width
-> Maybe (Extent Big Big height width)
forall a. Bool -> a -> Maybe a
toMaybe (fuse
f0fuse -> fuse -> Bool
forall a. Eq a => a -> a -> Bool
==fuse
f1) (Extent Big Big height width
-> Maybe (Extent Big Big height width))
-> Extent Big Big height width
-> Maybe (Extent Big Big height width)
forall a b. (a -> b) -> a -> b
$ height -> width -> Extent Big Big height width
forall height width. height -> width -> Extent Big Big height width
General height
h width
w)
kronecker ::
(C vert, C horiz) =>
Extent vert horiz heightA widthA ->
Extent vert horiz heightB widthB ->
Extent vert horiz (heightA,heightB) (widthA,widthB)
kronecker :: Extent vert horiz heightA widthA
-> Extent vert horiz heightB widthB
-> Extent vert horiz (heightA, heightB) (widthA, widthB)
kronecker = (heightA -> heightB -> (heightA, heightB))
-> (widthA -> widthB -> (widthA, widthB))
-> Extent vert horiz heightA widthA
-> Extent vert horiz heightB widthB
-> Extent vert horiz (heightA, heightB) (widthA, widthB)
forall vert horiz heightA heightB (f :: * -> * -> *) widthA widthB.
(C vert, C horiz) =>
(heightA -> heightB -> f heightA heightB)
-> (widthA -> widthB -> f widthA widthB)
-> Extent vert horiz heightA widthA
-> Extent vert horiz heightB widthB
-> Extent vert horiz (f heightA heightB) (f widthA widthB)
stackGen (,) (,)
newtype AppendMode vertA vertB vertC height widthA widthB =
AppendMode (
Extent vertA Big height widthA ->
Extent vertB Big height widthB ->
Extent vertC Big height (widthA:+:widthB)
)
appendLeftAux ::
(C vertA, C vertB) => AppendMode vertA vertB vertA height widthA widthB
appendLeftAux :: AppendMode vertA vertB vertA height widthA widthB
appendLeftAux =
(Extent vertA Big height widthA
-> Extent vertB Big height widthB
-> Extent vertA Big height (widthA :+: widthB))
-> AppendMode vertA vertB vertA height widthA widthB
forall vertA vertB vertC height widthA widthB.
(Extent vertA Big height widthA
-> Extent vertB Big height widthB
-> Extent vertC Big height (widthA :+: widthB))
-> AppendMode vertA vertB vertC height widthA widthB
AppendMode ((Extent vertA Big height widthA
-> Extent vertB Big height widthB
-> Extent vertA Big height (widthA :+: widthB))
-> AppendMode vertA vertB vertA height widthA widthB)
-> (Extent vertA Big height widthA
-> Extent vertB Big height widthB
-> Extent vertA Big height (widthA :+: widthB))
-> AppendMode vertA vertB vertA height widthA widthB
forall a b. (a -> b) -> a -> b
$ \Extent vertA Big height widthA
extentA Extent vertB Big height widthB
extentB ->
(widthA :+: widthB)
-> Extent vertA Big height widthA
-> Extent vertA Big height (widthA :+: widthB)
forall vert widthB height widthA.
C vert =>
widthB
-> Extent vert Big height widthA -> Extent vert Big height widthB
widen (Extent vertA Big height widthA -> widthA
forall vert horiz height width.
(C vert, C horiz) =>
Extent vert horiz height width -> width
width Extent vertA Big height widthA
extentA widthA -> widthB -> widthA :+: widthB
forall sh0 sh1. sh0 -> sh1 -> sh0 :+: sh1
:+: Extent vertB Big height widthB -> widthB
forall vert horiz height width.
(C vert, C horiz) =>
Extent vert horiz height width -> width
width Extent vertB Big height widthB
extentB) Extent vertA Big height widthA
extentA
appendSame :: (C vert) => AppendMode vert vert vert height widthA widthB
appendSame :: AppendMode vert vert vert height widthA widthB
appendSame = AppendMode vert vert vert height widthA widthB
forall vertA vertB height widthA widthB.
(C vertA, C vertB) =>
AppendMode vertA vertB vertA height widthA widthB
appendLeftAux
appendLeft :: (C vert) => AppendMode vert Big vert height widthA widthB
appendLeft :: AppendMode vert Big vert height widthA widthB
appendLeft = AppendMode vert Big vert height widthA widthB
forall vertA vertB height widthA widthB.
(C vertA, C vertB) =>
AppendMode vertA vertB vertA height widthA widthB
appendLeftAux
appendRight :: (C vert) => AppendMode Big vert vert height widthA widthB
appendRight :: AppendMode Big vert vert height widthA widthB
appendRight =
(Extent Big Big height widthA
-> Extent vert Big height widthB
-> Extent vert Big height (widthA :+: widthB))
-> AppendMode Big vert vert height widthA widthB
forall vertA vertB vertC height widthA widthB.
(Extent vertA Big height widthA
-> Extent vertB Big height widthB
-> Extent vertC Big height (widthA :+: widthB))
-> AppendMode vertA vertB vertC height widthA widthB
AppendMode ((Extent Big Big height widthA
-> Extent vert Big height widthB
-> Extent vert Big height (widthA :+: widthB))
-> AppendMode Big vert vert height widthA widthB)
-> (Extent Big Big height widthA
-> Extent vert Big height widthB
-> Extent vert Big height (widthA :+: widthB))
-> AppendMode Big vert vert height widthA widthB
forall a b. (a -> b) -> a -> b
$ \Extent Big Big height widthA
extentA Extent vert Big height widthB
extentB ->
(widthA :+: widthB)
-> Extent vert Big height widthB
-> Extent vert Big height (widthA :+: widthB)
forall vert widthB height widthA.
C vert =>
widthB
-> Extent vert Big height widthA -> Extent vert Big height widthB
widen (Extent Big Big height widthA -> widthA
forall vert horiz height width.
(C vert, C horiz) =>
Extent vert horiz height width -> width
width Extent Big Big height widthA
extentA widthA -> widthB -> widthA :+: widthB
forall sh0 sh1. sh0 -> sh1 -> sh0 :+: sh1
:+: Extent vert Big height widthB -> widthB
forall vert horiz height width.
(C vert, C horiz) =>
Extent vert horiz height width -> width
width Extent vert Big height widthB
extentB) Extent vert Big height widthB
extentB
type family Append a b
type instance Append Small b = Small
type instance Append Big b = b
newtype
AppendAny vertB height widthA widthB vertA =
AppendAny {
AppendAny vertB height widthA widthB vertA
-> AppendMode vertA vertB (Append vertA vertB) height widthA widthB
getAppendAny ::
AppendMode vertA vertB (Append vertA vertB) height widthA widthB
}
appendAny ::
(C vertA, C vertB) =>
AppendMode vertA vertB (Append vertA vertB) height widthA widthB
appendAny :: AppendMode vertA vertB (Append vertA vertB) height widthA widthB
appendAny =
AppendAny vertB height widthA widthB vertA
-> AppendMode vertA vertB (Append vertA vertB) height widthA widthB
forall vertB height widthA widthB vertA.
AppendAny vertB height widthA widthB vertA
-> AppendMode vertA vertB (Append vertA vertB) height widthA widthB
getAppendAny (AppendAny vertB height widthA widthB vertA
-> AppendMode
vertA vertB (Append vertA vertB) height widthA widthB)
-> AppendAny vertB height widthA widthB vertA
-> AppendMode vertA vertB (Append vertA vertB) height widthA widthB
forall a b. (a -> b) -> a -> b
$ AppendAny vertB height widthA widthB Small
-> AppendAny vertB height widthA widthB Big
-> AppendAny vertB height widthA widthB vertA
forall tag (f :: * -> *). C tag => f Small -> f Big -> f tag
switchTag (AppendMode Small vertB (Append Small vertB) height widthA widthB
-> AppendAny vertB height widthA widthB Small
forall vertB height widthA widthB vertA.
AppendMode vertA vertB (Append vertA vertB) height widthA widthB
-> AppendAny vertB height widthA widthB vertA
AppendAny AppendMode Small vertB (Append Small vertB) height widthA widthB
forall vertA vertB height widthA widthB.
(C vertA, C vertB) =>
AppendMode vertA vertB vertA height widthA widthB
appendLeftAux) (AppendMode Big vertB (Append Big vertB) height widthA widthB
-> AppendAny vertB height widthA widthB Big
forall vertB height widthA widthB vertA.
AppendMode vertA vertB (Append vertA vertB) height widthA widthB
-> AppendAny vertB height widthA widthB vertA
AppendAny AppendMode Big vertB (Append Big vertB) height widthA widthB
forall vert height widthA widthB.
C vert =>
AppendMode Big vert vert height widthA widthB
appendRight)
stack ::
(C vert, C horiz) =>
Extent vert horiz heightA widthA ->
Extent vert horiz heightB widthB ->
Extent vert horiz (heightA:+:heightB) (widthA:+:widthB)
stack :: Extent vert horiz heightA widthA
-> Extent vert horiz heightB widthB
-> Extent vert horiz (heightA :+: heightB) (widthA :+: widthB)
stack = (heightA -> heightB -> heightA :+: heightB)
-> (widthA -> widthB -> widthA :+: widthB)
-> Extent vert horiz heightA widthA
-> Extent vert horiz heightB widthB
-> Extent vert horiz (heightA :+: heightB) (widthA :+: widthB)
forall vert horiz heightA heightB (f :: * -> * -> *) widthA widthB.
(C vert, C horiz) =>
(heightA -> heightB -> f heightA heightB)
-> (widthA -> widthB -> f widthA widthB)
-> Extent vert horiz heightA widthA
-> Extent vert horiz heightB widthB
-> Extent vert horiz (f heightA heightB) (f widthA widthB)
stackGen heightA -> heightB -> heightA :+: heightB
forall sh0 sh1. sh0 -> sh1 -> sh0 :+: sh1
(:+:) widthA -> widthB -> widthA :+: widthB
forall sh0 sh1. sh0 -> sh1 -> sh0 :+: sh1
(:+:)
newtype Stack f heightA widthA heightB widthB vert horiz =
Stack {
Stack f heightA widthA heightB widthB vert horiz
-> Extent vert horiz heightA widthA
-> Extent vert horiz heightB widthB
-> Extent vert horiz (f heightA heightB) (f widthA widthB)
getStack ::
Extent vert horiz heightA widthA ->
Extent vert horiz heightB widthB ->
Extent vert horiz (f heightA heightB) (f widthA widthB)
}
stackGen ::
(C vert, C horiz) =>
(heightA -> heightB -> f heightA heightB) ->
(widthA -> widthB -> f widthA widthB) ->
Extent vert horiz heightA widthA ->
Extent vert horiz heightB widthB ->
Extent vert horiz (f heightA heightB) (f widthA widthB)
stackGen :: (heightA -> heightB -> f heightA heightB)
-> (widthA -> widthB -> f widthA widthB)
-> Extent vert horiz heightA widthA
-> Extent vert horiz heightB widthB
-> Extent vert horiz (f heightA heightB) (f widthA widthB)
stackGen heightA -> heightB -> f heightA heightB
fh widthA -> widthB -> f widthA widthB
fw =
Stack f heightA widthA heightB widthB vert horiz
-> Extent vert horiz heightA widthA
-> Extent vert horiz heightB widthB
-> Extent vert horiz (f heightA heightB) (f widthA widthB)
forall (f :: * -> * -> *) heightA widthA heightB widthB vert horiz.
Stack f heightA widthA heightB widthB vert horiz
-> Extent vert horiz heightA widthA
-> Extent vert horiz heightB widthB
-> Extent vert horiz (f heightA heightB) (f widthA widthB)
getStack (Stack f heightA widthA heightB widthB vert horiz
-> Extent vert horiz heightA widthA
-> Extent vert horiz heightB widthB
-> Extent vert horiz (f heightA heightB) (f widthA widthB))
-> Stack f heightA widthA heightB widthB vert horiz
-> Extent vert horiz heightA widthA
-> Extent vert horiz heightB widthB
-> Extent vert horiz (f heightA heightB) (f widthA widthB)
forall a b. (a -> b) -> a -> b
$
Stack f heightA widthA heightB widthB Small Small
-> Stack f heightA widthA heightB widthB Small Big
-> Stack f heightA widthA heightB widthB Big Small
-> Stack f heightA widthA heightB widthB Big Big
-> Stack f heightA widthA heightB widthB vert horiz
forall vert horiz (f :: * -> * -> *).
(C vert, C horiz) =>
f Small Small
-> f Small Big -> f Big Small -> f Big Big -> f vert horiz
switchTagPair
((Extent Small Small heightA widthA
-> Extent Small Small heightB widthB
-> Extent Small Small (f heightA heightB) (f widthA widthB))
-> Stack f heightA widthA heightB widthB Small Small
forall (f :: * -> * -> *) heightA widthA heightB widthB vert horiz.
(Extent vert horiz heightA widthA
-> Extent vert horiz heightB widthB
-> Extent vert horiz (f heightA heightB) (f widthA widthB))
-> Stack f heightA widthA heightB widthB vert horiz
Stack ((Extent Small Small heightA widthA
-> Extent Small Small heightB widthB
-> Extent Small Small (f heightA heightB) (f widthA widthB))
-> Stack f heightA widthA heightB widthB Small Small)
-> (Extent Small Small heightA widthA
-> Extent Small Small heightB widthB
-> Extent Small Small (f heightA heightB) (f widthA widthB))
-> Stack f heightA widthA heightB widthB Small Small
forall a b. (a -> b) -> a -> b
$ \(Square sa) (Square sb) ->
f heightA heightB
-> Extent Small Small (f heightA heightB) (f widthA widthB)
forall height width.
(height ~ width) =>
height -> Extent Small Small height width
Square (heightA -> heightB -> f heightA heightB
fh heightA
sa heightB
sb))
((Extent Small Big heightA widthA
-> Extent Small Big heightB widthB
-> Extent Small Big (f heightA heightB) (f widthA widthB))
-> Stack f heightA widthA heightB widthB Small Big
forall (f :: * -> * -> *) heightA widthA heightB widthB vert horiz.
(Extent vert horiz heightA widthA
-> Extent vert horiz heightB widthB
-> Extent vert horiz (f heightA heightB) (f widthA widthB))
-> Stack f heightA widthA heightB widthB vert horiz
Stack ((Extent Small Big heightA widthA
-> Extent Small Big heightB widthB
-> Extent Small Big (f heightA heightB) (f widthA widthB))
-> Stack f heightA widthA heightB widthB Small Big)
-> (Extent Small Big heightA widthA
-> Extent Small Big heightB widthB
-> Extent Small Big (f heightA heightB) (f widthA widthB))
-> Stack f heightA widthA heightB widthB Small Big
forall a b. (a -> b) -> a -> b
$ \(Wide ha wa) (Wide hb wb) ->
f heightA heightB
-> f widthA widthB
-> Extent Small Big (f heightA heightB) (f widthA widthB)
forall height width.
height -> width -> Extent Small Big height width
Wide (heightA -> heightB -> f heightA heightB
fh heightA
ha heightB
hb) (widthA -> widthB -> f widthA widthB
fw widthA
wa widthB
wb))
((Extent Big Small heightA widthA
-> Extent Big Small heightB widthB
-> Extent Big Small (f heightA heightB) (f widthA widthB))
-> Stack f heightA widthA heightB widthB Big Small
forall (f :: * -> * -> *) heightA widthA heightB widthB vert horiz.
(Extent vert horiz heightA widthA
-> Extent vert horiz heightB widthB
-> Extent vert horiz (f heightA heightB) (f widthA widthB))
-> Stack f heightA widthA heightB widthB vert horiz
Stack ((Extent Big Small heightA widthA
-> Extent Big Small heightB widthB
-> Extent Big Small (f heightA heightB) (f widthA widthB))
-> Stack f heightA widthA heightB widthB Big Small)
-> (Extent Big Small heightA widthA
-> Extent Big Small heightB widthB
-> Extent Big Small (f heightA heightB) (f widthA widthB))
-> Stack f heightA widthA heightB widthB Big Small
forall a b. (a -> b) -> a -> b
$ \(Tall ha wa) (Tall hb wb) ->
f heightA heightB
-> f widthA widthB
-> Extent Big Small (f heightA heightB) (f widthA widthB)
forall height width.
height -> width -> Extent Big Small height width
Tall (heightA -> heightB -> f heightA heightB
fh heightA
ha heightB
hb) (widthA -> widthB -> f widthA widthB
fw widthA
wa widthB
wb))
((Extent Big Big heightA widthA
-> Extent Big Big heightB widthB
-> Extent Big Big (f heightA heightB) (f widthA widthB))
-> Stack f heightA widthA heightB widthB Big Big
forall (f :: * -> * -> *) heightA widthA heightB widthB vert horiz.
(Extent vert horiz heightA widthA
-> Extent vert horiz heightB widthB
-> Extent vert horiz (f heightA heightB) (f widthA widthB))
-> Stack f heightA widthA heightB widthB vert horiz
Stack ((Extent Big Big heightA widthA
-> Extent Big Big heightB widthB
-> Extent Big Big (f heightA heightB) (f widthA widthB))
-> Stack f heightA widthA heightB widthB Big Big)
-> (Extent Big Big heightA widthA
-> Extent Big Big heightB widthB
-> Extent Big Big (f heightA heightB) (f widthA widthB))
-> Stack f heightA widthA heightB widthB Big Big
forall a b. (a -> b) -> a -> b
$ \(General ha wa) (General hb wb) ->
f heightA heightB
-> f widthA widthB
-> Extent Big Big (f heightA heightB) (f widthA widthB)
forall height width. height -> width -> Extent Big Big height width
General (heightA -> heightB -> f heightA heightB
fh heightA
ha heightB
hb) (widthA -> widthB -> f widthA widthB
fw widthA
wa widthB
wb))
type family Multiply a b
type instance Multiply Small b = b
type instance Multiply Big b = Big
data TagFact a = C a => TagFact
newtype MultiplyTagLaw b a =
MultiplyTagLaw {
MultiplyTagLaw b a
-> TagFact a -> TagFact b -> TagFact (Multiply a b)
getMultiplyTagLaw :: TagFact a -> TagFact b -> TagFact (Multiply a b)
}
multiplyTagLaw :: TagFact a -> TagFact b -> TagFact (Multiply a b)
multiplyTagLaw :: TagFact a -> TagFact b -> TagFact (Multiply a b)
multiplyTagLaw a :: TagFact a
a@TagFact a
TagFact =
((TagFact a -> TagFact b -> TagFact (Multiply a b))
-> TagFact a -> TagFact b -> TagFact (Multiply a b)
forall a b. (a -> b) -> a -> b
$TagFact a
a) ((TagFact a -> TagFact b -> TagFact (Multiply a b))
-> TagFact b -> TagFact (Multiply a b))
-> (TagFact a -> TagFact b -> TagFact (Multiply a b))
-> TagFact b
-> TagFact (Multiply a b)
forall a b. (a -> b) -> a -> b
$ MultiplyTagLaw b a
-> TagFact a -> TagFact b -> TagFact (Multiply a b)
forall b a.
MultiplyTagLaw b a
-> TagFact a -> TagFact b -> TagFact (Multiply a b)
getMultiplyTagLaw (MultiplyTagLaw b a
-> TagFact a -> TagFact b -> TagFact (Multiply a b))
-> MultiplyTagLaw b a
-> TagFact a
-> TagFact b
-> TagFact (Multiply a b)
forall a b. (a -> b) -> a -> b
$
MultiplyTagLaw b Small
-> MultiplyTagLaw b Big -> MultiplyTagLaw b a
forall tag (f :: * -> *). C tag => f Small -> f Big -> f tag
switchTag
((TagFact Small -> TagFact b -> TagFact (Multiply Small b))
-> MultiplyTagLaw b Small
forall b a.
(TagFact a -> TagFact b -> TagFact (Multiply a b))
-> MultiplyTagLaw b a
MultiplyTagLaw ((TagFact Small -> TagFact b -> TagFact (Multiply Small b))
-> MultiplyTagLaw b Small)
-> (TagFact Small -> TagFact b -> TagFact (Multiply Small b))
-> MultiplyTagLaw b Small
forall a b. (a -> b) -> a -> b
$ (TagFact b -> TagFact Small -> TagFact b)
-> TagFact Small -> TagFact b -> TagFact b
forall a b c. (a -> b -> c) -> b -> a -> c
flip TagFact b -> TagFact Small -> TagFact b
forall a b. a -> b -> a
const)
((TagFact Big -> TagFact b -> TagFact (Multiply Big b))
-> MultiplyTagLaw b Big
forall b a.
(TagFact a -> TagFact b -> TagFact (Multiply a b))
-> MultiplyTagLaw b a
MultiplyTagLaw TagFact Big -> TagFact b -> TagFact (Multiply Big b)
forall a b. a -> b -> a
const)
heightFact :: (C vert) => Extent vert horiz height width -> TagFact vert
heightFact :: Extent vert horiz height width -> TagFact vert
heightFact Extent vert horiz height width
_ = TagFact vert
forall a. C a => TagFact a
TagFact
widthFact :: (C horiz) => Extent vert horiz height width -> TagFact horiz
widthFact :: Extent vert horiz height width -> TagFact horiz
widthFact Extent vert horiz height width
_ = TagFact horiz
forall a. C a => TagFact a
TagFact
newtype Unify height fuse width heightC widthC vertB horizB vertA horizA =
Unify {
Unify height fuse width heightC widthC vertB horizB vertA horizA
-> Extent vertA horizA height fuse
-> Extent vertB horizB fuse width
-> Extent
(Multiply vertA vertB) (Multiply horizA horizB) heightC widthC
getUnify ::
Extent vertA horizA height fuse ->
Extent vertB horizB fuse width ->
Extent (Multiply vertA vertB) (Multiply horizA horizB) heightC widthC
}
unifyLeft ::
(C vertA, C horizA, C vertB, C horizB) =>
Extent vertA horizA height fuse ->
Extent vertB horizB fuse width ->
Extent (Multiply vertA vertB) (Multiply horizA horizB) height fuse
unifyLeft :: Extent vertA horizA height fuse
-> Extent vertB horizB fuse width
-> Extent
(Multiply vertA vertB) (Multiply horizA horizB) height fuse
unifyLeft =
Unify height fuse width height fuse vertB horizB vertA horizA
-> Extent vertA horizA height fuse
-> Extent vertB horizB fuse width
-> Extent
(Multiply vertA vertB) (Multiply horizA horizB) height fuse
forall height fuse width heightC widthC vertB horizB vertA horizA.
Unify height fuse width heightC widthC vertB horizB vertA horizA
-> Extent vertA horizA height fuse
-> Extent vertB horizB fuse width
-> Extent
(Multiply vertA vertB) (Multiply horizA horizB) heightC widthC
getUnify (Unify height fuse width height fuse vertB horizB vertA horizA
-> Extent vertA horizA height fuse
-> Extent vertB horizB fuse width
-> Extent
(Multiply vertA vertB) (Multiply horizA horizB) height fuse)
-> Unify height fuse width height fuse vertB horizB vertA horizA
-> Extent vertA horizA height fuse
-> Extent vertB horizB fuse width
-> Extent
(Multiply vertA vertB) (Multiply horizA horizB) height fuse
forall a b. (a -> b) -> a -> b
$
Unify height fuse width height fuse vertB horizB Small Small
-> Unify height fuse width height fuse vertB horizB Small Big
-> Unify height fuse width height fuse vertB horizB Big Small
-> Unify height fuse width height fuse vertB horizB Big Big
-> Unify height fuse width height fuse vertB horizB vertA horizA
forall vert horiz (f :: * -> * -> *).
(C vert, C horiz) =>
f Small Small
-> f Small Big -> f Big Small -> f Big Big -> f vert horiz
switchTagPair
((Extent Small Small height fuse
-> Extent vertB horizB fuse width
-> Extent
(Multiply Small vertB) (Multiply Small horizB) height fuse)
-> Unify height fuse width height fuse vertB horizB Small Small
forall height fuse width heightC widthC vertB horizB vertA horizA.
(Extent vertA horizA height fuse
-> Extent vertB horizB fuse width
-> Extent
(Multiply vertA vertB) (Multiply horizA horizB) heightC widthC)
-> Unify height fuse width heightC widthC vertB horizB vertA horizA
Unify ((Extent Small Small height fuse
-> Extent vertB horizB fuse width
-> Extent
(Multiply Small vertB) (Multiply Small horizB) height fuse)
-> Unify height fuse width height fuse vertB horizB Small Small)
-> (Extent Small Small height fuse
-> Extent vertB horizB fuse width
-> Extent
(Multiply Small vertB) (Multiply Small horizB) height fuse)
-> Unify height fuse width height fuse vertB horizB Small Small
forall a b. (a -> b) -> a -> b
$ Extent vertB horizB height fuse
-> Extent vertB horizB fuse width
-> Extent vertB horizB height fuse
forall a b. a -> b -> a
const (Extent vertB horizB height fuse
-> Extent vertB horizB fuse width
-> Extent vertB horizB height fuse)
-> (Extent Small Small height fuse
-> Extent vertB horizB height fuse)
-> Extent Small Small height fuse
-> Extent vertB horizB fuse width
-> Extent vertB horizB height fuse
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Extent Small Small height fuse -> Extent vertB horizB height fuse
forall vert horiz height width.
(C vert, C horiz) =>
Extent Small Small height width -> Extent vert horiz height width
fromSquareLiberal)
((Extent Small Big height fuse
-> Extent vertB horizB fuse width
-> Extent (Multiply Small vertB) (Multiply Big horizB) height fuse)
-> Unify height fuse width height fuse vertB horizB Small Big
forall height fuse width heightC widthC vertB horizB vertA horizA.
(Extent vertA horizA height fuse
-> Extent vertB horizB fuse width
-> Extent
(Multiply vertA vertB) (Multiply horizA horizB) heightC widthC)
-> Unify height fuse width heightC widthC vertB horizB vertA horizA
Unify ((Extent Small Big height fuse
-> Extent vertB horizB fuse width
-> Extent (Multiply Small vertB) (Multiply Big horizB) height fuse)
-> Unify height fuse width height fuse vertB horizB Small Big)
-> (Extent Small Big height fuse
-> Extent vertB horizB fuse width
-> Extent (Multiply Small vertB) (Multiply Big horizB) height fuse)
-> Unify height fuse width height fuse vertB horizB Small Big
forall a b. (a -> b) -> a -> b
$ Extent vertB Big height fuse
-> Extent vertB horizB fuse width -> Extent vertB Big height fuse
forall a b. a -> b -> a
const (Extent vertB Big height fuse
-> Extent vertB horizB fuse width -> Extent vertB Big height fuse)
-> (Extent Small Big height fuse -> Extent vertB Big height fuse)
-> Extent Small Big height fuse
-> Extent vertB horizB fuse width
-> Extent vertB Big height fuse
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Extent Small Big height fuse -> Extent vertB Big height fuse
forall vert horiz height width.
(C vert, C horiz) =>
Extent Small horiz height width -> Extent vert horiz height width
generalizeWide)
((Extent Big Small height fuse
-> Extent vertB horizB fuse width
-> Extent (Multiply Big vertB) (Multiply Small horizB) height fuse)
-> Unify height fuse width height fuse vertB horizB Big Small
forall height fuse width heightC widthC vertB horizB vertA horizA.
(Extent vertA horizA height fuse
-> Extent vertB horizB fuse width
-> Extent
(Multiply vertA vertB) (Multiply horizA horizB) heightC widthC)
-> Unify height fuse width heightC widthC vertB horizB vertA horizA
Unify ((Extent Big Small height fuse
-> Extent vertB horizB fuse width
-> Extent (Multiply Big vertB) (Multiply Small horizB) height fuse)
-> Unify height fuse width height fuse vertB horizB Big Small)
-> (Extent Big Small height fuse
-> Extent vertB horizB fuse width
-> Extent (Multiply Big vertB) (Multiply Small horizB) height fuse)
-> Unify height fuse width height fuse vertB horizB Big Small
forall a b. (a -> b) -> a -> b
$ Extent Big horizB height fuse
-> Extent vertB horizB fuse width -> Extent Big horizB height fuse
forall a b. a -> b -> a
const (Extent Big horizB height fuse
-> Extent vertB horizB fuse width -> Extent Big horizB height fuse)
-> (Extent Big Small height fuse -> Extent Big horizB height fuse)
-> Extent Big Small height fuse
-> Extent vertB horizB fuse width
-> Extent Big horizB height fuse
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Extent Big Small height fuse -> Extent Big horizB height fuse
forall vert horiz height width.
(C vert, C horiz) =>
Extent vert Small height width -> Extent vert horiz height width
generalizeTall)
((Extent Big Big height fuse
-> Extent vertB horizB fuse width
-> Extent (Multiply Big vertB) (Multiply Big horizB) height fuse)
-> Unify height fuse width height fuse vertB horizB Big Big
forall height fuse width heightC widthC vertB horizB vertA horizA.
(Extent vertA horizA height fuse
-> Extent vertB horizB fuse width
-> Extent
(Multiply vertA vertB) (Multiply horizA horizB) heightC widthC)
-> Unify height fuse width heightC widthC vertB horizB vertA horizA
Unify ((Extent Big Big height fuse
-> Extent vertB horizB fuse width
-> Extent (Multiply Big vertB) (Multiply Big horizB) height fuse)
-> Unify height fuse width height fuse vertB horizB Big Big)
-> (Extent Big Big height fuse
-> Extent vertB horizB fuse width
-> Extent (Multiply Big vertB) (Multiply Big horizB) height fuse)
-> Unify height fuse width height fuse vertB horizB Big Big
forall a b. (a -> b) -> a -> b
$ Extent Big Big height fuse
-> Extent vertB horizB fuse width -> Extent Big Big height fuse
forall a b. a -> b -> a
const (Extent Big Big height fuse
-> Extent vertB horizB fuse width -> Extent Big Big height fuse)
-> (Extent Big Big height fuse -> Extent Big Big height fuse)
-> Extent Big Big height fuse
-> Extent vertB horizB fuse width
-> Extent Big Big height fuse
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Extent Big Big height fuse -> Extent Big Big height fuse
forall vert horiz height width.
(C vert, C horiz) =>
Extent vert horiz height width -> General height width
toGeneral)
unifyRight ::
(C vertA, C horizA, C vertB, C horizB) =>
Extent vertA horizA height fuse ->
Extent vertB horizB fuse width ->
Extent (Multiply vertA vertB) (Multiply horizA horizB) fuse width
unifyRight :: Extent vertA horizA height fuse
-> Extent vertB horizB fuse width
-> Extent
(Multiply vertA vertB) (Multiply horizA horizB) fuse width
unifyRight =
Unify height fuse width fuse width vertB horizB vertA horizA
-> Extent vertA horizA height fuse
-> Extent vertB horizB fuse width
-> Extent
(Multiply vertA vertB) (Multiply horizA horizB) fuse width
forall height fuse width heightC widthC vertB horizB vertA horizA.
Unify height fuse width heightC widthC vertB horizB vertA horizA
-> Extent vertA horizA height fuse
-> Extent vertB horizB fuse width
-> Extent
(Multiply vertA vertB) (Multiply horizA horizB) heightC widthC
getUnify (Unify height fuse width fuse width vertB horizB vertA horizA
-> Extent vertA horizA height fuse
-> Extent vertB horizB fuse width
-> Extent
(Multiply vertA vertB) (Multiply horizA horizB) fuse width)
-> Unify height fuse width fuse width vertB horizB vertA horizA
-> Extent vertA horizA height fuse
-> Extent vertB horizB fuse width
-> Extent
(Multiply vertA vertB) (Multiply horizA horizB) fuse width
forall a b. (a -> b) -> a -> b
$
Unify height fuse width fuse width vertB horizB Small Small
-> Unify height fuse width fuse width vertB horizB Small Big
-> Unify height fuse width fuse width vertB horizB Big Small
-> Unify height fuse width fuse width vertB horizB Big Big
-> Unify height fuse width fuse width vertB horizB vertA horizA
forall vert horiz (f :: * -> * -> *).
(C vert, C horiz) =>
f Small Small
-> f Small Big -> f Big Small -> f Big Big -> f vert horiz
switchTagPair
((Extent Small Small height fuse
-> Extent vertB horizB fuse width
-> Extent
(Multiply Small vertB) (Multiply Small horizB) fuse width)
-> Unify height fuse width fuse width vertB horizB Small Small
forall height fuse width heightC widthC vertB horizB vertA horizA.
(Extent vertA horizA height fuse
-> Extent vertB horizB fuse width
-> Extent
(Multiply vertA vertB) (Multiply horizA horizB) heightC widthC)
-> Unify height fuse width heightC widthC vertB horizB vertA horizA
Unify ((Extent Small Small height fuse
-> Extent vertB horizB fuse width
-> Extent
(Multiply Small vertB) (Multiply Small horizB) fuse width)
-> Unify height fuse width fuse width vertB horizB Small Small)
-> (Extent Small Small height fuse
-> Extent vertB horizB fuse width
-> Extent
(Multiply Small vertB) (Multiply Small horizB) fuse width)
-> Unify height fuse width fuse width vertB horizB Small Small
forall a b. (a -> b) -> a -> b
$ (Extent vertB horizB fuse width -> Extent vertB horizB fuse width)
-> Extent Small Small height fuse
-> Extent vertB horizB fuse width
-> Extent vertB horizB fuse width
forall a b. a -> b -> a
const Extent vertB horizB fuse width -> Extent vertB horizB fuse width
forall a. a -> a
id)
((Extent Small Big height fuse
-> Extent vertB horizB fuse width
-> Extent (Multiply Small vertB) (Multiply Big horizB) fuse width)
-> Unify height fuse width fuse width vertB horizB Small Big
forall height fuse width heightC widthC vertB horizB vertA horizA.
(Extent vertA horizA height fuse
-> Extent vertB horizB fuse width
-> Extent
(Multiply vertA vertB) (Multiply horizA horizB) heightC widthC)
-> Unify height fuse width heightC widthC vertB horizB vertA horizA
Unify ((Extent Small Big height fuse
-> Extent vertB horizB fuse width
-> Extent (Multiply Small vertB) (Multiply Big horizB) fuse width)
-> Unify height fuse width fuse width vertB horizB Small Big)
-> (Extent Small Big height fuse
-> Extent vertB horizB fuse width
-> Extent (Multiply Small vertB) (Multiply Big horizB) fuse width)
-> Unify height fuse width fuse width vertB horizB Small Big
forall a b. (a -> b) -> a -> b
$ (Extent vertB horizB fuse width -> Extent vertB Big fuse width)
-> Extent Small Big height fuse
-> Extent vertB horizB fuse width
-> Extent vertB Big fuse width
forall a b. a -> b -> a
const Extent vertB horizB fuse width -> Extent vertB Big fuse width
forall vert horiz height width.
(C vert, C horiz) =>
Extent vert horiz height width -> Extent vert Big height width
genToWide)
((Extent Big Small height fuse
-> Extent vertB horizB fuse width
-> Extent (Multiply Big vertB) (Multiply Small horizB) fuse width)
-> Unify height fuse width fuse width vertB horizB Big Small
forall height fuse width heightC widthC vertB horizB vertA horizA.
(Extent vertA horizA height fuse
-> Extent vertB horizB fuse width
-> Extent
(Multiply vertA vertB) (Multiply horizA horizB) heightC widthC)
-> Unify height fuse width heightC widthC vertB horizB vertA horizA
Unify ((Extent Big Small height fuse
-> Extent vertB horizB fuse width
-> Extent (Multiply Big vertB) (Multiply Small horizB) fuse width)
-> Unify height fuse width fuse width vertB horizB Big Small)
-> (Extent Big Small height fuse
-> Extent vertB horizB fuse width
-> Extent (Multiply Big vertB) (Multiply Small horizB) fuse width)
-> Unify height fuse width fuse width vertB horizB Big Small
forall a b. (a -> b) -> a -> b
$ (Extent vertB horizB fuse width -> Extent Big horizB fuse width)
-> Extent Big Small height fuse
-> Extent vertB horizB fuse width
-> Extent Big horizB fuse width
forall a b. a -> b -> a
const Extent vertB horizB fuse width -> Extent Big horizB fuse width
forall vert horiz height width.
(C vert, C horiz) =>
Extent vert horiz height width -> Extent Big horiz height width
genToTall)
((Extent Big Big height fuse
-> Extent vertB horizB fuse width
-> Extent (Multiply Big vertB) (Multiply Big horizB) fuse width)
-> Unify height fuse width fuse width vertB horizB Big Big
forall height fuse width heightC widthC vertB horizB vertA horizA.
(Extent vertA horizA height fuse
-> Extent vertB horizB fuse width
-> Extent
(Multiply vertA vertB) (Multiply horizA horizB) heightC widthC)
-> Unify height fuse width heightC widthC vertB horizB vertA horizA
Unify ((Extent Big Big height fuse
-> Extent vertB horizB fuse width
-> Extent (Multiply Big vertB) (Multiply Big horizB) fuse width)
-> Unify height fuse width fuse width vertB horizB Big Big)
-> (Extent Big Big height fuse
-> Extent vertB horizB fuse width
-> Extent (Multiply Big vertB) (Multiply Big horizB) fuse width)
-> Unify height fuse width fuse width vertB horizB Big Big
forall a b. (a -> b) -> a -> b
$ (Extent vertB horizB fuse width -> General fuse width)
-> Extent Big Big height fuse
-> Extent vertB horizB fuse width
-> General fuse width
forall a b. a -> b -> a
const Extent vertB horizB fuse width -> General fuse width
forall vert horiz height width.
(C vert, C horiz) =>
Extent vert horiz height width -> General height width
toGeneral)