{-# LANGUAGE GADTs, EmptyDataDecls, NoMonomorphismRestriction, TypeFamilies, ScopedTypeVariables, FlexibleInstances, RankNTypes, MultiParamTypeClasses, FlexibleContexts, OverloadedStrings, ViewPatterns, RecordWildCards #-}
module Graphics.GPipe.Internal.Expr where
import Prelude hiding ((.), id, (<*))
import Control.Category
import Control.Monad (void, when)
import Control.Monad.Trans.Writer
import Control.Monad.Trans.State
import Control.Monad.Trans.Reader
import Data.Maybe
import Data.Monoid (mconcat, mappend)
import qualified Control.Monad.Trans.Class as T (lift)
import Data.SNMap
import qualified Data.IntMap as Map
import Data.Boolean
import Data.List (intercalate)
import Control.Applicative (liftA, liftA2, liftA3)
import Linear.V4
import Linear.V3
import Linear.V2
import Linear.V1
import Linear.V0
import Linear.Affine
import Linear.Metric
import Linear.Matrix
import Linear.Vector
import Linear.Conjugate
import Data.Foldable (Foldable(toList))
import Data.Int
import Data.Word
import Data.Bits
type NextTempVar = Int
type NextGlobal = Int
data SType = STypeFloat | STypeInt | STypeBool | STypeUInt | STypeDyn String | STypeMat Int Int | STypeVec Int | STypeIVec Int | STypeUVec Int | STypeGenerativeGeometry
stypeName :: SType -> String
stypeName :: SType -> String
stypeName SType
STypeFloat = String
"float"
stypeName SType
STypeInt = String
"int"
stypeName SType
STypeBool = String
"bool"
stypeName SType
STypeUInt = String
"uint"
stypeName (STypeDyn String
s) = String
s
stypeName (STypeMat Int
r Int
c) = String
"mat" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
c String -> String -> String
forall a. [a] -> [a] -> [a]
++ Char
'x' Char -> String -> String
forall a. a -> [a] -> [a]
: Int -> String
forall a. Show a => a -> String
show Int
r
stypeName (STypeVec Int
n) = String
"vec" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
n
stypeName (STypeIVec Int
n) = String
"ivec" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
n
stypeName (STypeUVec Int
n) = String
"uvec" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
n
stypeName SType
STypeGenerativeGeometry = String
"bool"
stypeSize :: SType -> Int
stypeSize :: SType -> Int
stypeSize (STypeVec Int
n) = Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
4
stypeSize (STypeIVec Int
n) = Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
4
stypeSize (STypeUVec Int
n) = Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
4
stypeSize SType
_ = Int
4
type ExprM = SNMapReaderT
[String]
(StateT
ExprState
(WriterT
String
(StateT
NextTempVar
IO
)
)
)
type GlobDeclM = Writer String
data ExprState = ExprState
{ ExprState -> IntMap (GlobDeclM ())
shaderUsedUniformBlocks :: Map.IntMap (GlobDeclM ())
, ExprState -> IntMap (GlobDeclM ())
shaderUsedSamplers :: Map.IntMap (GlobDeclM ())
, ExprState -> IntMap (GlobDeclM (), (ExprM (), GlobDeclM ()))
shaderUsedInput :: Map.IntMap
( GlobDeclM ()
, ( ExprM ()
, GlobDeclM ()
)
)
, ExprState -> Maybe (GlobDeclM ())
shaderGeometry :: Maybe (GlobDeclM ())
}
data ExprResult = ExprResult
{ ExprResult -> String
finalSource :: String
, ExprResult -> [Int]
unis :: [Int]
, ExprResult -> [Int]
samps :: [Int]
, ExprResult -> [Int]
inps :: [Int]
, ExprResult -> GlobDeclM ()
prevDecls :: GlobDeclM ()
, ExprResult -> ExprM ()
prevSs :: ExprM ()
}
runExprM
:: GlobDeclM ()
-> ExprM ()
-> IO ExprResult
runExprM :: GlobDeclM () -> ExprM () -> IO ExprResult
runExprM GlobDeclM ()
d ExprM ()
m = do
(ExprState
st, String
body) <- StateT Int IO (ExprState, String) -> Int -> IO (ExprState, String)
forall (m :: * -> *) s a. Monad m => StateT s m a -> s -> m a
evalStateT (WriterT String (StateT Int IO) ExprState
-> StateT Int IO (ExprState, String)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
runWriterT (StateT ExprState (WriterT String (StateT Int IO)) ()
-> ExprState -> WriterT String (StateT Int IO) ExprState
forall (m :: * -> *) s a. Monad m => StateT s m a -> s -> m s
execStateT (ExprM () -> StateT ExprState (WriterT String (StateT Int IO)) ()
forall (m :: * -> *) a b. MonadIO m => SNMapReaderT a m b -> m b
runSNMapReaderT ExprM ()
m) (IntMap (GlobDeclM ())
-> IntMap (GlobDeclM ())
-> IntMap (GlobDeclM (), (ExprM (), GlobDeclM ()))
-> Maybe (GlobDeclM ())
-> ExprState
ExprState IntMap (GlobDeclM ())
forall a. IntMap a
Map.empty IntMap (GlobDeclM ())
forall a. IntMap a
Map.empty IntMap (GlobDeclM (), (ExprM (), GlobDeclM ()))
forall a. IntMap a
Map.empty Maybe (GlobDeclM ())
forall a. Maybe a
Nothing))) Int
0
let ([Int]
unis, [GlobDeclM ()]
uniDecls) = [(Int, GlobDeclM ())] -> ([Int], [GlobDeclM ()])
forall a b. [(a, b)] -> ([a], [b])
unzip ([(Int, GlobDeclM ())] -> ([Int], [GlobDeclM ()]))
-> [(Int, GlobDeclM ())] -> ([Int], [GlobDeclM ()])
forall a b. (a -> b) -> a -> b
$ IntMap (GlobDeclM ()) -> [(Int, GlobDeclM ())]
forall a. IntMap a -> [(Int, a)]
Map.toAscList (ExprState -> IntMap (GlobDeclM ())
shaderUsedUniformBlocks ExprState
st)
([Int]
samps, [GlobDeclM ()]
sampDecls) = [(Int, GlobDeclM ())] -> ([Int], [GlobDeclM ()])
forall a b. [(a, b)] -> ([a], [b])
unzip ([(Int, GlobDeclM ())] -> ([Int], [GlobDeclM ()]))
-> [(Int, GlobDeclM ())] -> ([Int], [GlobDeclM ()])
forall a b. (a -> b) -> a -> b
$ IntMap (GlobDeclM ()) -> [(Int, GlobDeclM ())]
forall a. IntMap a -> [(Int, a)]
Map.toAscList (ExprState -> IntMap (GlobDeclM ())
shaderUsedSamplers ExprState
st)
([Int]
inps, [(GlobDeclM (), (ExprM (), GlobDeclM ()))]
inpDescs) = [(Int, (GlobDeclM (), (ExprM (), GlobDeclM ())))]
-> ([Int], [(GlobDeclM (), (ExprM (), GlobDeclM ()))])
forall a b. [(a, b)] -> ([a], [b])
unzip ([(Int, (GlobDeclM (), (ExprM (), GlobDeclM ())))]
-> ([Int], [(GlobDeclM (), (ExprM (), GlobDeclM ()))]))
-> [(Int, (GlobDeclM (), (ExprM (), GlobDeclM ())))]
-> ([Int], [(GlobDeclM (), (ExprM (), GlobDeclM ()))])
forall a b. (a -> b) -> a -> b
$ IntMap (GlobDeclM (), (ExprM (), GlobDeclM ()))
-> [(Int, (GlobDeclM (), (ExprM (), GlobDeclM ())))]
forall a. IntMap a -> [(Int, a)]
Map.toAscList (ExprState -> IntMap (GlobDeclM (), (ExprM (), GlobDeclM ()))
shaderUsedInput ExprState
st)
geoDescs :: Maybe (GlobDeclM ())
geoDescs = ExprState -> Maybe (GlobDeclM ())
shaderGeometry ExprState
st
([GlobDeclM ()]
inpDecls, [(ExprM (), GlobDeclM ())]
prevDesc) = [(GlobDeclM (), (ExprM (), GlobDeclM ()))]
-> ([GlobDeclM ()], [(ExprM (), GlobDeclM ())])
forall a b. [(a, b)] -> ([a], [b])
unzip [(GlobDeclM (), (ExprM (), GlobDeclM ()))]
inpDescs
([ExprM ()] -> ExprM ()
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, Monad m) =>
t (m a) -> m ()
sequence_ -> ExprM ()
prevSs, [GlobDeclM ()] -> GlobDeclM ()
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, Monad m) =>
t (m a) -> m ()
sequence_ -> GlobDeclM ()
prevDecls) = [(ExprM (), GlobDeclM ())] -> ([ExprM ()], [GlobDeclM ()])
forall a b. [(a, b)] -> ([a], [b])
unzip [(ExprM (), GlobDeclM ())]
prevDesc
decls :: GlobDeclM ()
decls = do
GlobDeclM ()
d
Bool -> GlobDeclM () -> GlobDeclM ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Maybe (GlobDeclM ()) -> Bool
forall a. Maybe a -> Bool
isJust Maybe (GlobDeclM ())
geoDescs) (Maybe (GlobDeclM ()) -> GlobDeclM ()
forall a. HasCallStack => Maybe a -> a
fromJust Maybe (GlobDeclM ())
geoDescs)
[GlobDeclM ()] -> GlobDeclM ()
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, Monad m) =>
t (m a) -> m ()
sequence_ [GlobDeclM ()]
uniDecls
[GlobDeclM ()] -> GlobDeclM ()
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, Monad m) =>
t (m a) -> m ()
sequence_ [GlobDeclM ()]
sampDecls
[GlobDeclM ()] -> GlobDeclM ()
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, Monad m) =>
t (m a) -> m ()
sequence_ [GlobDeclM ()]
inpDecls
finalSource :: String
finalSource = [String] -> String
forall a. Monoid a => [a] -> a
mconcat
[ String
"#version 450\n"
, GlobDeclM () -> String
forall w a. Writer w a -> w
execWriter GlobDeclM ()
decls
, String
"void main() {\n"
, String
body
, String
"}\n"
]
ExprResult -> IO ExprResult
forall (m :: * -> *) a. Monad m => a -> m a
return ExprResult :: String
-> [Int]
-> [Int]
-> [Int]
-> GlobDeclM ()
-> ExprM ()
-> ExprResult
ExprResult{String
[Int]
GlobDeclM ()
ExprM ()
finalSource :: String
prevDecls :: GlobDeclM ()
prevSs :: ExprM ()
inps :: [Int]
samps :: [Int]
unis :: [Int]
prevSs :: ExprM ()
prevDecls :: GlobDeclM ()
inps :: [Int]
samps :: [Int]
unis :: [Int]
finalSource :: String
..}
data ShaderStageInput = ShaderStageInput
{
ShaderStageInput -> GlobDeclM ()
outputDeclarations :: GlobDeclM ()
, ShaderStageInput -> ExprM ()
expression :: ExprM ()
}
data ShaderStageOutput = ShaderStageOutput
{ ShaderStageOutput -> String
source :: String
, ShaderStageOutput -> [Int]
uniforms :: [Int]
, ShaderStageOutput -> [Int]
samplers :: [Int]
, ShaderStageOutput -> [Int]
inputs :: [Int]
, ShaderStageOutput -> GlobDeclM ()
previousDeclarations :: GlobDeclM ()
, ShaderStageOutput -> ExprM ()
prevExpression :: ExprM ()
}
evaluateExpression :: [ExprM ()] -> ExprM () -> GlobDeclM () -> IO ShaderStageOutput
evaluateExpression :: [ExprM ()] -> ExprM () -> GlobDeclM () -> IO ShaderStageOutput
evaluateExpression [ExprM ()]
staticExpressions ExprM ()
expression GlobDeclM ()
requiredOutputDeclarations = do
ExprResult String
s [Int]
u [Int]
ss [Int]
is GlobDeclM ()
pds ExprM ()
pe <- GlobDeclM () -> ExprM () -> IO ExprResult
runExprM GlobDeclM ()
requiredOutputDeclarations ExprM ()
expression
case [ExprM ()]
staticExpressions of
(ExprM ()
se:[ExprM ()]
ses) -> [ExprM ()] -> ExprM () -> GlobDeclM () -> IO ShaderStageOutput
evaluateExpression [ExprM ()]
ses (ExprM ()
pe ExprM () -> ExprM () -> ExprM ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ExprM ()
se) GlobDeclM ()
pds
[] -> ShaderStageOutput -> IO ShaderStageOutput
forall (m :: * -> *) a. Monad m => a -> m a
return (ShaderStageOutput -> IO ShaderStageOutput)
-> ShaderStageOutput -> IO ShaderStageOutput
forall a b. (a -> b) -> a -> b
$ String
-> [Int]
-> [Int]
-> [Int]
-> GlobDeclM ()
-> ExprM ()
-> ShaderStageOutput
ShaderStageOutput String
s [Int]
u [Int]
ss [Int]
is GlobDeclM ()
pds ExprM ()
pe
newtype S x a = S { S x a -> ExprM String
unS :: ExprM String }
scalarS :: SType -> ExprM RValue -> S c a
scalarS :: SType -> ExprM String -> S c a
scalarS SType
typ = ExprM String -> S c a
forall x a. ExprM String -> S x a
S (ExprM String -> S c a)
-> (ExprM String -> ExprM String) -> ExprM String -> S c a
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. SType -> ExprM String -> ExprM String
tellAssignment SType
typ
vec2S :: SType -> ExprM RValue -> V2 (S c a)
vec2S :: SType -> ExprM String -> V2 (S c a)
vec2S SType
typ ExprM String
s =
let V4 S c a
x S c a
y S c a
_z S c a
_w = SType -> ExprM String -> V4 (S c a)
forall c a. SType -> ExprM String -> V4 (S c a)
vec4S SType
typ ExprM String
s
in S c a -> S c a -> V2 (S c a)
forall a. a -> a -> V2 a
V2 S c a
x S c a
y
vec3S :: SType -> ExprM RValue -> V3 (S c a)
vec3S :: SType -> ExprM String -> V3 (S c a)
vec3S SType
typ ExprM String
s =
let V4 S c a
x S c a
y S c a
z S c a
_w = SType -> ExprM String -> V4 (S c a)
forall c a. SType -> ExprM String -> V4 (S c a)
vec4S SType
typ ExprM String
s
in S c a -> S c a -> S c a -> V3 (S c a)
forall a. a -> a -> a -> V3 a
V3 S c a
x S c a
y S c a
z
vec4S :: SType -> ExprM RValue -> V4 (S c a)
vec4S :: SType -> ExprM String -> V4 (S c a)
vec4S SType
typ ExprM String
s =
let m :: ExprM String
m = SType -> ExprM String -> ExprM String
tellAssignment SType
typ ExprM String
s
f :: String -> S c a
f String
p = ExprM String -> S c a
forall x a. ExprM String -> S x a
S (ExprM String -> S c a) -> ExprM String -> S c a
forall a b. (a -> b) -> a -> b
$ (String -> String) -> ExprM String -> ExprM String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
p) ExprM String
m
in S c a -> S c a -> S c a -> S c a -> V4 (S c a)
forall a. a -> a -> a -> a -> V4 a
V4 (String -> S c a
f String
".x") (String -> S c a
f String
".y") (String -> S c a
f String
".z") (String -> S c a
f String
".w")
scalarS' :: RValue -> S c a
scalarS' :: String -> S c a
scalarS' = ExprM String -> S c a
forall x a. ExprM String -> S x a
S (ExprM String -> S c a)
-> (String -> ExprM String) -> String -> S c a
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. String -> ExprM String
forall (m :: * -> *) a. Monad m => a -> m a
return
vec2S' :: RValue -> V2 (S c a)
vec2S' :: String -> V2 (S c a)
vec2S' = S c a -> V2 (S c a)
forall c a. S c a -> V2 (S c a)
vec2S'' (S c a -> V2 (S c a)) -> (String -> S c a) -> String -> V2 (S c a)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ExprM String -> S c a
forall x a. ExprM String -> S x a
S (ExprM String -> S c a)
-> (String -> ExprM String) -> String -> S c a
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. String -> ExprM String
forall (m :: * -> *) a. Monad m => a -> m a
return
vec3S' :: RValue -> V3 (S c a)
vec3S' :: String -> V3 (S c a)
vec3S' = S c a -> V3 (S c a)
forall c a. S c a -> V3 (S c a)
vec3S'' (S c a -> V3 (S c a)) -> (String -> S c a) -> String -> V3 (S c a)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ExprM String -> S c a
forall x a. ExprM String -> S x a
S (ExprM String -> S c a)
-> (String -> ExprM String) -> String -> S c a
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. String -> ExprM String
forall (m :: * -> *) a. Monad m => a -> m a
return
vec4S' :: RValue -> V4 (S c a)
vec4S' :: String -> V4 (S c a)
vec4S' = S c a -> V4 (S c a)
forall c a. S c a -> V4 (S c a)
vec4S'' (S c a -> V4 (S c a)) -> (String -> S c a) -> String -> V4 (S c a)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ExprM String -> S c a
forall x a. ExprM String -> S x a
S (ExprM String -> S c a)
-> (String -> ExprM String) -> String -> S c a
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. String -> ExprM String
forall (m :: * -> *) a. Monad m => a -> m a
return
vec2S'' :: S c a -> V2 (S c a)
vec2S'' :: S c a -> V2 (S c a)
vec2S'' S c a
s =
let V4 S c a
x S c a
y S c a
_z S c a
_w = S c a -> V4 (S c a)
forall c a. S c a -> V4 (S c a)
vec4S'' S c a
s
in S c a -> S c a -> V2 (S c a)
forall a. a -> a -> V2 a
V2 S c a
x S c a
y
vec3S'' :: S c a -> V3 (S c a)
vec3S'' :: S c a -> V3 (S c a)
vec3S'' S c a
s =
let V4 S c a
x S c a
y S c a
z S c a
_w = S c a -> V4 (S c a)
forall c a. S c a -> V4 (S c a)
vec4S'' S c a
s
in S c a -> S c a -> S c a -> V3 (S c a)
forall a. a -> a -> a -> V3 a
V3 S c a
x S c a
y S c a
z
vec4S'' :: S c a -> V4 (S c a)
vec4S'' :: S c a -> V4 (S c a)
vec4S'' S c a
s =
let f :: Int -> S c a
f Int
p = ExprM String -> S c a
forall x a. ExprM String -> S x a
S (ExprM String -> S c a) -> ExprM String -> S c a
forall a b. (a -> b) -> a -> b
$ (String -> String) -> ExprM String -> ExprM String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (String -> String -> String
forall a. [a] -> [a] -> [a]
++ (Char
'['Char -> String -> String
forall a. a -> [a] -> [a]
: Int -> String
forall a. Show a => a -> String
show (Int
p :: Int) String -> String -> String
forall a. [a] -> [a] -> [a]
++String
"]")) (S c a -> ExprM String
forall x a. S x a -> ExprM String
unS S c a
s)
in S c a -> S c a -> S c a -> S c a -> V4 (S c a)
forall a. a -> a -> a -> a -> V4 a
V4 (Int -> S c a
f Int
0) (Int -> S c a
f Int
1) (Int -> S c a
f Int
2) (Int -> S c a
f Int
3)
data V
data F
type G = V
newtype GenerativeGeometry p a = GenerativeGeometry a
type VFloat = S V Float
type VInt = S V Int
type VWord = S V Word
type VBool = S V Bool
type GGenerativeGeometry p a = S G (GenerativeGeometry p a)
type FFloat = S F Float
type FInt = S F Int
type FWord = S F Word
type FBool = S F Bool
useVInput :: SType -> Int -> ExprM String
useVInput :: SType -> Int -> ExprM String
useVInput SType
stype Int
i = do
ExprState
s <- StateT ExprState (WriterT String (StateT Int IO)) ExprState
-> SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
ExprState
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
T.lift StateT ExprState (WriterT String (StateT Int IO)) ExprState
forall (m :: * -> *) s. Monad m => StateT s m s
get
StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
T.lift (StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ())
-> StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ()
forall a b. (a -> b) -> a -> b
$ ExprState -> StateT ExprState (WriterT String (StateT Int IO)) ()
forall (m :: * -> *) s. Monad m => s -> StateT s m ()
put (ExprState -> StateT ExprState (WriterT String (StateT Int IO)) ())
-> ExprState
-> StateT ExprState (WriterT String (StateT Int IO)) ()
forall a b. (a -> b) -> a -> b
$ ExprState
s { shaderUsedInput :: IntMap (GlobDeclM (), (ExprM (), GlobDeclM ()))
shaderUsedInput = Int
-> (GlobDeclM (), (ExprM (), GlobDeclM ()))
-> IntMap (GlobDeclM (), (ExprM (), GlobDeclM ()))
-> IntMap (GlobDeclM (), (ExprM (), GlobDeclM ()))
forall a. Int -> a -> IntMap a -> IntMap a
Map.insert Int
i (GlobDeclM ()
gDeclInput, (ExprM (), GlobDeclM ())
forall a. HasCallStack => a
undefined) (IntMap (GlobDeclM (), (ExprM (), GlobDeclM ()))
-> IntMap (GlobDeclM (), (ExprM (), GlobDeclM ())))
-> IntMap (GlobDeclM (), (ExprM (), GlobDeclM ()))
-> IntMap (GlobDeclM (), (ExprM (), GlobDeclM ()))
forall a b. (a -> b) -> a -> b
$ ExprState -> IntMap (GlobDeclM (), (ExprM (), GlobDeclM ()))
shaderUsedInput ExprState
s }
String -> ExprM String
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> ExprM String) -> String -> ExprM String
forall a b. (a -> b) -> a -> b
$ String
"in" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
i
where
gDeclInput :: GlobDeclM ()
gDeclInput = do
String -> GlobDeclM ()
tellGlobal String
"in "
String -> GlobDeclM ()
tellGlobal (String -> GlobDeclM ()) -> String -> GlobDeclM ()
forall a b. (a -> b) -> a -> b
$ SType -> String
stypeName SType
stype
String -> GlobDeclM ()
tellGlobal String
" in"
String -> GlobDeclM ()
tellGlobalLn (String -> GlobDeclM ()) -> String -> GlobDeclM ()
forall a b. (a -> b) -> a -> b
$ Int -> String
forall a. Show a => a -> String
show Int
i
useGInput :: String -> SType -> Int -> Int -> ExprM String -> ExprM String
useGInput :: String -> SType -> Int -> Int -> ExprM String -> ExprM String
useGInput String
qual SType
stype Int
i Int
n ExprM String
v = do
ExprState
s <- StateT ExprState (WriterT String (StateT Int IO)) ExprState
-> SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
ExprState
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
T.lift StateT ExprState (WriterT String (StateT Int IO)) ExprState
forall (m :: * -> *) s. Monad m => StateT s m s
get
StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
T.lift (StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ())
-> StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ()
forall a b. (a -> b) -> a -> b
$ ExprState -> StateT ExprState (WriterT String (StateT Int IO)) ()
forall (m :: * -> *) s. Monad m => s -> StateT s m ()
put (ExprState -> StateT ExprState (WriterT String (StateT Int IO)) ())
-> ExprState
-> StateT ExprState (WriterT String (StateT Int IO)) ()
forall a b. (a -> b) -> a -> b
$ ExprState
s { shaderUsedInput :: IntMap (GlobDeclM (), (ExprM (), GlobDeclM ()))
shaderUsedInput = Int
-> (GlobDeclM (), (ExprM (), GlobDeclM ()))
-> IntMap (GlobDeclM (), (ExprM (), GlobDeclM ()))
-> IntMap (GlobDeclM (), (ExprM (), GlobDeclM ()))
forall a. Int -> a -> IntMap a -> IntMap a
Map.insert Int
n (GlobDeclM ()
gDeclIn, (ExprM ()
assignOutput, GlobDeclM ()
gDeclOut)) (IntMap (GlobDeclM (), (ExprM (), GlobDeclM ()))
-> IntMap (GlobDeclM (), (ExprM (), GlobDeclM ())))
-> IntMap (GlobDeclM (), (ExprM (), GlobDeclM ()))
-> IntMap (GlobDeclM (), (ExprM (), GlobDeclM ()))
forall a b. (a -> b) -> a -> b
$ ExprState -> IntMap (GlobDeclM (), (ExprM (), GlobDeclM ()))
shaderUsedInput ExprState
s }
String -> ExprM String
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> ExprM String) -> String -> ExprM String
forall a b. (a -> b) -> a -> b
$ String
forall p. IsString p => p
prefix String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
n String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"[" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
i String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"]"
where
prefix :: p
prefix = p
"vg"
assignOutput :: ExprM ()
assignOutput = do
String
val <- ExprM String
v
let name :: String
name = String
forall p. IsString p => p
prefix String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
n
String -> String -> ExprM ()
tellAssignment' String
name String
val
gDeclOut :: GlobDeclM ()
gDeclOut = do
String -> GlobDeclM ()
tellGlobal (String -> GlobDeclM ()) -> String -> GlobDeclM ()
forall a b. (a -> b) -> a -> b
$ String
qual String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" out "
String -> GlobDeclM ()
tellGlobal (String -> GlobDeclM ()) -> String -> GlobDeclM ()
forall a b. (a -> b) -> a -> b
$ SType -> String
stypeName SType
stype
String -> GlobDeclM ()
tellGlobal (String -> GlobDeclM ()) -> String -> GlobDeclM ()
forall a b. (a -> b) -> a -> b
$ Char
' 'Char -> String -> String
forall a. a -> [a] -> [a]
:String
forall p. IsString p => p
prefix
String -> GlobDeclM ()
tellGlobalLn (String -> GlobDeclM ()) -> String -> GlobDeclM ()
forall a b. (a -> b) -> a -> b
$ Int -> String
forall a. Show a => a -> String
show Int
n
gDeclIn :: GlobDeclM ()
gDeclIn = do
String -> GlobDeclM ()
tellGlobal (String -> GlobDeclM ()) -> String -> GlobDeclM ()
forall a b. (a -> b) -> a -> b
$ String
qual String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" in "
String -> GlobDeclM ()
tellGlobal (String -> GlobDeclM ()) -> String -> GlobDeclM ()
forall a b. (a -> b) -> a -> b
$ SType -> String
stypeName SType
stype
String -> GlobDeclM ()
tellGlobal (String -> GlobDeclM ()) -> String -> GlobDeclM ()
forall a b. (a -> b) -> a -> b
$ Char
' 'Char -> String -> String
forall a. a -> [a] -> [a]
:String
forall p. IsString p => p
prefix
String -> GlobDeclM ()
tellGlobal (String -> GlobDeclM ()) -> String -> GlobDeclM ()
forall a b. (a -> b) -> a -> b
$ Int -> String
forall a. Show a => a -> String
show Int
n
String -> GlobDeclM ()
tellGlobalLn (String -> GlobDeclM ()) -> String -> GlobDeclM ()
forall a b. (a -> b) -> a -> b
$ String
"[]"
useFInputFromG :: String -> SType -> Int -> ExprM String -> ExprM String
useFInputFromG :: String -> SType -> Int -> ExprM String -> ExprM String
useFInputFromG String
qual SType
stype Int
i ExprM String
v = do
ExprState
s <- StateT ExprState (WriterT String (StateT Int IO)) ExprState
-> SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
ExprState
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
T.lift StateT ExprState (WriterT String (StateT Int IO)) ExprState
forall (m :: * -> *) s. Monad m => StateT s m s
get
Int
val :: Int <- String -> Int
forall a. Read a => String -> a
read (String -> Int)
-> ExprM String
-> SNMapReaderT
[String] (StateT ExprState (WriterT String (StateT Int IO))) Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ExprM String
v
StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
T.lift (StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ())
-> StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ()
forall a b. (a -> b) -> a -> b
$ ExprState -> StateT ExprState (WriterT String (StateT Int IO)) ()
forall (m :: * -> *) s. Monad m => s -> StateT s m ()
put (ExprState -> StateT ExprState (WriterT String (StateT Int IO)) ())
-> ExprState
-> StateT ExprState (WriterT String (StateT Int IO)) ()
forall a b. (a -> b) -> a -> b
$ ExprState
s { shaderUsedInput :: IntMap (GlobDeclM (), (ExprM (), GlobDeclM ()))
shaderUsedInput = Int
-> (GlobDeclM (), (ExprM (), GlobDeclM ()))
-> IntMap (GlobDeclM (), (ExprM (), GlobDeclM ()))
-> IntMap (GlobDeclM (), (ExprM (), GlobDeclM ()))
forall a. Int -> a -> IntMap a -> IntMap a
Map.insert Int
i (Int -> String -> GlobDeclM ()
gDecl Int
val (String
qual String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" in "), (() -> ExprM ()
forall (m :: * -> *) a. Monad m => a -> m a
return (), Int -> String -> GlobDeclM ()
gDecl Int
val (String
qual String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" out "))) (IntMap (GlobDeclM (), (ExprM (), GlobDeclM ()))
-> IntMap (GlobDeclM (), (ExprM (), GlobDeclM ())))
-> IntMap (GlobDeclM (), (ExprM (), GlobDeclM ()))
-> IntMap (GlobDeclM (), (ExprM (), GlobDeclM ()))
forall a b. (a -> b) -> a -> b
$ ExprState -> IntMap (GlobDeclM (), (ExprM (), GlobDeclM ()))
shaderUsedInput ExprState
s }
String -> ExprM String
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> ExprM String) -> String -> ExprM String
forall a b. (a -> b) -> a -> b
$ String
forall p. IsString p => p
prefix String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
val
where
prefix :: p
prefix = p
"vgf"
gDecl :: Int -> String -> GlobDeclM ()
gDecl Int
val String
s = do
String -> GlobDeclM ()
tellGlobal String
s
String -> GlobDeclM ()
tellGlobal (String -> GlobDeclM ()) -> String -> GlobDeclM ()
forall a b. (a -> b) -> a -> b
$ SType -> String
stypeName SType
stype
String -> GlobDeclM ()
tellGlobal (String -> GlobDeclM ()) -> String -> GlobDeclM ()
forall a b. (a -> b) -> a -> b
$ Char
' 'Char -> String -> String
forall a. a -> [a] -> [a]
:String
forall p. IsString p => p
prefix
String -> GlobDeclM ()
tellGlobalLn (String -> GlobDeclM ()) -> String -> GlobDeclM ()
forall a b. (a -> b) -> a -> b
$ Int -> String
forall a. Show a => a -> String
show Int
val
useFInput :: String -> String -> SType -> Int -> ExprM String -> ExprM String
useFInput :: String -> String -> SType -> Int -> ExprM String -> ExprM String
useFInput String
qual String
prefix SType
stype Int
i ExprM String
v = do
ExprState
s <- StateT ExprState (WriterT String (StateT Int IO)) ExprState
-> SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
ExprState
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
T.lift StateT ExprState (WriterT String (StateT Int IO)) ExprState
forall (m :: * -> *) s. Monad m => StateT s m s
get
StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
T.lift (StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ())
-> StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ()
forall a b. (a -> b) -> a -> b
$ ExprState -> StateT ExprState (WriterT String (StateT Int IO)) ()
forall (m :: * -> *) s. Monad m => s -> StateT s m ()
put (ExprState -> StateT ExprState (WriterT String (StateT Int IO)) ())
-> ExprState
-> StateT ExprState (WriterT String (StateT Int IO)) ()
forall a b. (a -> b) -> a -> b
$ ExprState
s { shaderUsedInput :: IntMap (GlobDeclM (), (ExprM (), GlobDeclM ()))
shaderUsedInput = Int
-> (GlobDeclM (), (ExprM (), GlobDeclM ()))
-> IntMap (GlobDeclM (), (ExprM (), GlobDeclM ()))
-> IntMap (GlobDeclM (), (ExprM (), GlobDeclM ()))
forall a. Int -> a -> IntMap a -> IntMap a
Map.insert Int
i (String -> GlobDeclM ()
gDecl (String
qual String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" in "), (ExprM ()
assignOutput, String -> GlobDeclM ()
gDecl (String
qual String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" out "))) (IntMap (GlobDeclM (), (ExprM (), GlobDeclM ()))
-> IntMap (GlobDeclM (), (ExprM (), GlobDeclM ())))
-> IntMap (GlobDeclM (), (ExprM (), GlobDeclM ()))
-> IntMap (GlobDeclM (), (ExprM (), GlobDeclM ()))
forall a b. (a -> b) -> a -> b
$ ExprState -> IntMap (GlobDeclM (), (ExprM (), GlobDeclM ()))
shaderUsedInput ExprState
s }
String -> ExprM String
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> ExprM String) -> String -> ExprM String
forall a b. (a -> b) -> a -> b
$ String
prefix String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
i
where
assignOutput :: ExprM ()
assignOutput = do
String
val <- ExprM String
v
let name :: String
name = String
prefix String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
i
String -> String -> ExprM ()
tellAssignment' String
name String
val
gDecl :: String -> GlobDeclM ()
gDecl String
s = do
String -> GlobDeclM ()
tellGlobal String
s
String -> GlobDeclM ()
tellGlobal (String -> GlobDeclM ()) -> String -> GlobDeclM ()
forall a b. (a -> b) -> a -> b
$ SType -> String
stypeName SType
stype
String -> GlobDeclM ()
tellGlobal (String -> GlobDeclM ()) -> String -> GlobDeclM ()
forall a b. (a -> b) -> a -> b
$ Char
' 'Char -> String -> String
forall a. a -> [a] -> [a]
:String
prefix
String -> GlobDeclM ()
tellGlobalLn (String -> GlobDeclM ()) -> String -> GlobDeclM ()
forall a b. (a -> b) -> a -> b
$ Int -> String
forall a. Show a => a -> String
show Int
i
declareGeometryLayout :: String -> String -> Int -> ExprM ()
declareGeometryLayout :: String -> String -> Int -> ExprM ()
declareGeometryLayout String
inputPrimitive String
outputPrimitive Int
maxVertices = StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
T.lift (StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ())
-> StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ()
forall a b. (a -> b) -> a -> b
$ (ExprState -> ExprState)
-> StateT ExprState (WriterT String (StateT Int IO)) ()
forall (m :: * -> *) s. Monad m => (s -> s) -> StateT s m ()
modify ((ExprState -> ExprState)
-> StateT ExprState (WriterT String (StateT Int IO)) ())
-> (ExprState -> ExprState)
-> StateT ExprState (WriterT String (StateT Int IO)) ()
forall a b. (a -> b) -> a -> b
$ \ ExprState
s -> ExprState
s { shaderGeometry :: Maybe (GlobDeclM ())
shaderGeometry = GlobDeclM () -> Maybe (GlobDeclM ())
forall a. a -> Maybe a
Just GlobDeclM ()
gDeclBlock }
where
gDeclBlock :: GlobDeclM ()
gDeclBlock = do
String -> GlobDeclM ()
tellGlobalLn (String -> GlobDeclM ()) -> String -> GlobDeclM ()
forall a b. (a -> b) -> a -> b
$ String
"layout(" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
inputPrimitive String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
") in"
String -> GlobDeclM ()
tellGlobalLn (String -> GlobDeclM ()) -> String -> GlobDeclM ()
forall a b. (a -> b) -> a -> b
$ String
"layout(" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
outputPrimitive String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
", max_vertices = " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
maxVertices String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
") out"
useUniform :: GlobDeclM () -> Int -> Int -> ExprM String
useUniform :: GlobDeclM () -> Int -> Int -> ExprM String
useUniform GlobDeclM ()
decls Int
blockI Int
offset = do
StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
T.lift (StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ())
-> StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ()
forall a b. (a -> b) -> a -> b
$ (ExprState -> ExprState)
-> StateT ExprState (WriterT String (StateT Int IO)) ()
forall (m :: * -> *) s. Monad m => (s -> s) -> StateT s m ()
modify ((ExprState -> ExprState)
-> StateT ExprState (WriterT String (StateT Int IO)) ())
-> (ExprState -> ExprState)
-> StateT ExprState (WriterT String (StateT Int IO)) ()
forall a b. (a -> b) -> a -> b
$ \ ExprState
s -> ExprState
s { shaderUsedUniformBlocks :: IntMap (GlobDeclM ())
shaderUsedUniformBlocks = Int
-> GlobDeclM () -> IntMap (GlobDeclM ()) -> IntMap (GlobDeclM ())
forall a. Int -> a -> IntMap a -> IntMap a
Map.insert Int
blockI GlobDeclM ()
gDeclUniformBlock (IntMap (GlobDeclM ()) -> IntMap (GlobDeclM ()))
-> IntMap (GlobDeclM ()) -> IntMap (GlobDeclM ())
forall a b. (a -> b) -> a -> b
$ ExprState -> IntMap (GlobDeclM ())
shaderUsedUniformBlocks ExprState
s }
String -> ExprM String
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> ExprM String) -> String -> ExprM String
forall a b. (a -> b) -> a -> b
$ Char
'u'Char -> String -> String
forall a. a -> [a] -> [a]
:Int -> String
forall a. Show a => a -> String
show Int
blockI String -> String -> String
forall a. [a] -> [a] -> [a]
++ Char
'.'Char -> String -> String
forall a. a -> [a] -> [a]
:Char
'u'Char -> String -> String
forall a. a -> [a] -> [a]
: Int -> String
forall a. Show a => a -> String
show Int
offset
where
gDeclUniformBlock :: GlobDeclM ()
gDeclUniformBlock = do
let blockStr :: String
blockStr = Int -> String
forall a. Show a => a -> String
show Int
blockI
String -> GlobDeclM ()
tellGlobal String
"layout(std140) uniform uBlock"
String -> GlobDeclM ()
tellGlobal String
blockStr
String -> GlobDeclM ()
tellGlobal String
" {\n"
GlobDeclM ()
decls
String -> GlobDeclM ()
tellGlobal String
"} u"
String -> GlobDeclM ()
tellGlobalLn String
blockStr
useSampler :: String -> String -> Int -> ExprM String
useSampler :: String -> String -> Int -> ExprM String
useSampler String
prefix String
str Int
name = do
StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
T.lift (StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ())
-> StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ()
forall a b. (a -> b) -> a -> b
$ (ExprState -> ExprState)
-> StateT ExprState (WriterT String (StateT Int IO)) ()
forall (m :: * -> *) s. Monad m => (s -> s) -> StateT s m ()
modify ((ExprState -> ExprState)
-> StateT ExprState (WriterT String (StateT Int IO)) ())
-> (ExprState -> ExprState)
-> StateT ExprState (WriterT String (StateT Int IO)) ()
forall a b. (a -> b) -> a -> b
$ \ ExprState
s -> ExprState
s { shaderUsedSamplers :: IntMap (GlobDeclM ())
shaderUsedSamplers = Int
-> GlobDeclM () -> IntMap (GlobDeclM ()) -> IntMap (GlobDeclM ())
forall a. Int -> a -> IntMap a -> IntMap a
Map.insert Int
name GlobDeclM ()
gDeclSampler (IntMap (GlobDeclM ()) -> IntMap (GlobDeclM ()))
-> IntMap (GlobDeclM ()) -> IntMap (GlobDeclM ())
forall a b. (a -> b) -> a -> b
$ ExprState -> IntMap (GlobDeclM ())
shaderUsedSamplers ExprState
s }
String -> ExprM String
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> ExprM String) -> String -> ExprM String
forall a b. (a -> b) -> a -> b
$ Char
's'Char -> String -> String
forall a. a -> [a] -> [a]
:Int -> String
forall a. Show a => a -> String
show Int
name
where
gDeclSampler :: GlobDeclM ()
gDeclSampler = do
String -> GlobDeclM ()
tellGlobal String
"uniform "
String -> GlobDeclM ()
tellGlobal String
prefix
String -> GlobDeclM ()
tellGlobal String
"sampler"
String -> GlobDeclM ()
tellGlobal String
str
String -> GlobDeclM ()
tellGlobal String
" s"
String -> GlobDeclM ()
tellGlobalLn (String -> GlobDeclM ()) -> String -> GlobDeclM ()
forall a b. (a -> b) -> a -> b
$ Int -> String
forall a. Show a => a -> String
show Int
name
getNext :: Monad m => StateT Int m Int
getNext :: StateT Int m Int
getNext = do
Int
s <- StateT Int m Int
forall (m :: * -> *) s. Monad m => StateT s m s
get
Int -> StateT Int m ()
forall (m :: * -> *) s. Monad m => s -> StateT s m ()
put (Int -> StateT Int m ()) -> Int -> StateT Int m ()
forall a b. (a -> b) -> a -> b
$ Int
s Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
Int -> StateT Int m Int
forall (m :: * -> *) a. Monad m => a -> m a
return Int
s
type RValue = String
tellAssignment :: SType -> ExprM RValue -> ExprM String
tellAssignment :: SType -> ExprM String -> ExprM String
tellAssignment SType
typ ExprM String
m = ([String] -> String)
-> SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String]
-> ExprM String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [String] -> String
forall a. [a] -> a
head (SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String]
-> ExprM String)
-> (SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String]
-> SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
-> SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String]
-> ExprM String
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String]
-> SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String]
forall (m :: * -> *) a.
MonadIO m =>
SNMapReaderT a m a -> SNMapReaderT a m a
memoizeM (SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String]
-> ExprM String)
-> SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String]
-> ExprM String
forall a b. (a -> b) -> a -> b
$ do
String
val <- ExprM String
m
Int
var <- StateT ExprState (WriterT String (StateT Int IO)) Int
-> SNMapReaderT
[String] (StateT ExprState (WriterT String (StateT Int IO))) Int
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
T.lift (StateT ExprState (WriterT String (StateT Int IO)) Int
-> SNMapReaderT
[String] (StateT ExprState (WriterT String (StateT Int IO))) Int)
-> StateT ExprState (WriterT String (StateT Int IO)) Int
-> SNMapReaderT
[String] (StateT ExprState (WriterT String (StateT Int IO))) Int
forall a b. (a -> b) -> a -> b
$ WriterT String (StateT Int IO) Int
-> StateT ExprState (WriterT String (StateT Int IO)) Int
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
T.lift (WriterT String (StateT Int IO) Int
-> StateT ExprState (WriterT String (StateT Int IO)) Int)
-> WriterT String (StateT Int IO) Int
-> StateT ExprState (WriterT String (StateT Int IO)) Int
forall a b. (a -> b) -> a -> b
$ StateT Int IO Int -> WriterT String (StateT Int IO) Int
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
T.lift StateT Int IO Int
forall (m :: * -> *). Monad m => StateT Int m Int
getNext
let name :: String
name = Char
't' Char -> String -> String
forall a. a -> [a] -> [a]
: Int -> String
forall a. Show a => a -> String
show Int
var
StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
T.lift (StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ())
-> StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ()
forall a b. (a -> b) -> a -> b
$ WriterT String (StateT Int IO) ()
-> StateT ExprState (WriterT String (StateT Int IO)) ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
T.lift (WriterT String (StateT Int IO) ()
-> StateT ExprState (WriterT String (StateT Int IO)) ())
-> WriterT String (StateT Int IO) ()
-> StateT ExprState (WriterT String (StateT Int IO)) ()
forall a b. (a -> b) -> a -> b
$ String -> WriterT String (StateT Int IO) ()
forall (m :: * -> *) w. Monad m => w -> WriterT w m ()
tell (SType -> String
stypeName SType
typ String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" ")
String -> String -> ExprM ()
tellAssignment' String
name String
val
[String]
-> SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String]
forall (m :: * -> *) a. Monad m => a -> m a
return [String
name]
tellAssignment' :: String -> RValue -> ExprM ()
tellAssignment' :: String -> String -> ExprM ()
tellAssignment' String
name String
string = StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
T.lift (StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ())
-> StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ()
forall a b. (a -> b) -> a -> b
$ WriterT String (StateT Int IO) ()
-> StateT ExprState (WriterT String (StateT Int IO)) ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
T.lift (WriterT String (StateT Int IO) ()
-> StateT ExprState (WriterT String (StateT Int IO)) ())
-> WriterT String (StateT Int IO) ()
-> StateT ExprState (WriterT String (StateT Int IO)) ()
forall a b. (a -> b) -> a -> b
$ String -> WriterT String (StateT Int IO) ()
forall (m :: * -> *) w. Monad m => w -> WriterT w m ()
tell (String -> WriterT String (StateT Int IO) ())
-> String -> WriterT String (StateT Int IO) ()
forall a b. (a -> b) -> a -> b
$ [String] -> String
forall a. Monoid a => [a] -> a
mconcat [String
name, String
" = ", String
string, String
";\n"]
discard :: FBool -> ExprM ()
discard :: FBool -> ExprM ()
discard (S ExprM String
m) = do
String
b <- ExprM String
m
Bool -> ExprM () -> ExprM ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (String
b String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/= String
"true") (ExprM () -> ExprM ()) -> ExprM () -> ExprM ()
forall a b. (a -> b) -> a -> b
$ StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
T.lift (StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ())
-> StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ()
forall a b. (a -> b) -> a -> b
$ WriterT String (StateT Int IO) ()
-> StateT ExprState (WriterT String (StateT Int IO)) ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
T.lift (WriterT String (StateT Int IO) ()
-> StateT ExprState (WriterT String (StateT Int IO)) ())
-> WriterT String (StateT Int IO) ()
-> StateT ExprState (WriterT String (StateT Int IO)) ()
forall a b. (a -> b) -> a -> b
$ String -> WriterT String (StateT Int IO) ()
forall (m :: * -> *) w. Monad m => w -> WriterT w m ()
tell (String -> WriterT String (StateT Int IO) ())
-> String -> WriterT String (StateT Int IO) ()
forall a b. (a -> b) -> a -> b
$ [String] -> String
forall a. Monoid a => [a] -> a
mconcat [String
"if (!(", String
b, String
")) discard;\n"]
tellGlobalLn :: String -> GlobDeclM ()
tellGlobalLn :: String -> GlobDeclM ()
tellGlobalLn String
string = String -> GlobDeclM ()
forall (m :: * -> *) w. Monad m => w -> WriterT w m ()
tell (String -> GlobDeclM ()) -> String -> GlobDeclM ()
forall a b. (a -> b) -> a -> b
$ String
string String -> String -> String
forall a. Monoid a => a -> a -> a
`mappend` String
";\n"
tellGlobal :: String -> GlobDeclM ()
tellGlobal :: String -> GlobDeclM ()
tellGlobal = String -> GlobDeclM ()
forall (m :: * -> *) w. Monad m => w -> WriterT w m ()
tell
data ShaderBase a x where
ShaderBaseFloat :: S x Float -> ShaderBase (S x Float) x
ShaderBaseInt :: S x Int -> ShaderBase (S x Int) x
ShaderBaseWord :: S x Word -> ShaderBase (S x Word) x
ShaderBaseBool :: S x Bool -> ShaderBase (S x Bool) x
ShaderBaseUnit :: ShaderBase () x
ShaderBaseProd :: ShaderBase a x -> ShaderBase b x -> ShaderBase (a,b) x
ShaderBaseGenerativeGeometry :: S x (GenerativeGeometry p a) -> ShaderBase (S x (GenerativeGeometry p a)) x
shaderbaseDeclare :: ShaderBase a x -> WriterT [String] ExprM (ShaderBase a x)
shaderbaseAssign :: ShaderBase a x -> StateT [String] ExprM ()
shaderbaseReturn :: ShaderBase a x -> ReaderT (ExprM [String]) (State Int) (ShaderBase a x)
shaderbaseDeclare :: ShaderBase a x -> WriterT [String] ExprM (ShaderBase a x)
shaderbaseDeclare (ShaderBaseFloat S x Float
_) = S x Float -> ShaderBase (S x Float) x
forall x. S x Float -> ShaderBase (S x Float) x
ShaderBaseFloat (S x Float -> ShaderBase (S x Float) x)
-> WriterT [String] ExprM (S x Float)
-> WriterT [String] ExprM (ShaderBase (S x Float) x)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SType -> WriterT [String] ExprM (S x Float)
forall x a. SType -> WriterT [String] ExprM (S x a)
shaderbaseDeclareDef SType
STypeFloat
shaderbaseDeclare (ShaderBaseInt S x Int
_) = S x Int -> ShaderBase (S x Int) x
forall x. S x Int -> ShaderBase (S x Int) x
ShaderBaseInt (S x Int -> ShaderBase (S x Int) x)
-> WriterT [String] ExprM (S x Int)
-> WriterT [String] ExprM (ShaderBase (S x Int) x)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SType -> WriterT [String] ExprM (S x Int)
forall x a. SType -> WriterT [String] ExprM (S x a)
shaderbaseDeclareDef SType
STypeInt
shaderbaseDeclare (ShaderBaseWord S x Word
_) = S x Word -> ShaderBase (S x Word) x
forall x. S x Word -> ShaderBase (S x Word) x
ShaderBaseWord (S x Word -> ShaderBase (S x Word) x)
-> WriterT [String] ExprM (S x Word)
-> WriterT [String] ExprM (ShaderBase (S x Word) x)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SType -> WriterT [String] ExprM (S x Word)
forall x a. SType -> WriterT [String] ExprM (S x a)
shaderbaseDeclareDef SType
STypeUInt
shaderbaseDeclare (ShaderBaseBool S x Bool
_) = S x Bool -> ShaderBase (S x Bool) x
forall x. S x Bool -> ShaderBase (S x Bool) x
ShaderBaseBool (S x Bool -> ShaderBase (S x Bool) x)
-> WriterT [String] ExprM (S x Bool)
-> WriterT [String] ExprM (ShaderBase (S x Bool) x)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SType -> WriterT [String] ExprM (S x Bool)
forall x a. SType -> WriterT [String] ExprM (S x a)
shaderbaseDeclareDef SType
STypeBool
shaderbaseDeclare ShaderBase a x
ShaderBaseUnit = ShaderBase () x -> WriterT [String] ExprM (ShaderBase () x)
forall (m :: * -> *) a. Monad m => a -> m a
return ShaderBase () x
forall x. ShaderBase () x
ShaderBaseUnit
shaderbaseDeclare (ShaderBaseProd ShaderBase a x
a ShaderBase b x
b) = do
ShaderBase a x
a' <- ShaderBase a x -> WriterT [String] ExprM (ShaderBase a x)
forall a x.
ShaderBase a x -> WriterT [String] ExprM (ShaderBase a x)
shaderbaseDeclare ShaderBase a x
a
ShaderBase b x
b' <- ShaderBase b x -> WriterT [String] ExprM (ShaderBase b x)
forall a x.
ShaderBase a x -> WriterT [String] ExprM (ShaderBase a x)
shaderbaseDeclare ShaderBase b x
b
ShaderBase (a, b) x -> WriterT [String] ExprM (ShaderBase (a, b) x)
forall (m :: * -> *) a. Monad m => a -> m a
return (ShaderBase (a, b) x
-> WriterT [String] ExprM (ShaderBase (a, b) x))
-> ShaderBase (a, b) x
-> WriterT [String] ExprM (ShaderBase (a, b) x)
forall a b. (a -> b) -> a -> b
$ ShaderBase a x -> ShaderBase b x -> ShaderBase (a, b) x
forall a x b.
ShaderBase a x -> ShaderBase b x -> ShaderBase (a, b) x
ShaderBaseProd ShaderBase a x
a' ShaderBase b x
b'
shaderbaseDeclare (ShaderBaseGenerativeGeometry S x (GenerativeGeometry p a)
_) = S x (GenerativeGeometry p a)
-> ShaderBase (S x (GenerativeGeometry p a)) x
forall x p a.
S x (GenerativeGeometry p a)
-> ShaderBase (S x (GenerativeGeometry p a)) x
ShaderBaseGenerativeGeometry (S x (GenerativeGeometry p a)
-> ShaderBase (S x (GenerativeGeometry p a)) x)
-> WriterT [String] ExprM (S x (GenerativeGeometry p a))
-> WriterT
[String] ExprM (ShaderBase (S x (GenerativeGeometry p a)) x)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SType -> WriterT [String] ExprM (S x (GenerativeGeometry p a))
forall x a. SType -> WriterT [String] ExprM (S x a)
shaderbaseDeclareDef SType
STypeGenerativeGeometry
shaderbaseAssign :: ShaderBase a x -> StateT [String] ExprM ()
shaderbaseAssign (ShaderBaseFloat S x Float
a) = S x Float -> StateT [String] ExprM ()
forall x a. S x a -> StateT [String] ExprM ()
shaderbaseAssignDef S x Float
a
shaderbaseAssign (ShaderBaseInt S x Int
a) = S x Int -> StateT [String] ExprM ()
forall x a. S x a -> StateT [String] ExprM ()
shaderbaseAssignDef S x Int
a
shaderbaseAssign (ShaderBaseWord S x Word
a) = S x Word -> StateT [String] ExprM ()
forall x a. S x a -> StateT [String] ExprM ()
shaderbaseAssignDef S x Word
a
shaderbaseAssign (ShaderBaseBool S x Bool
a) = S x Bool -> StateT [String] ExprM ()
forall x a. S x a -> StateT [String] ExprM ()
shaderbaseAssignDef S x Bool
a
shaderbaseAssign ShaderBase a x
ShaderBaseUnit = () -> StateT [String] ExprM ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
shaderbaseAssign (ShaderBaseProd ShaderBase a x
a ShaderBase b x
b) = do
ShaderBase a x -> StateT [String] ExprM ()
forall a x. ShaderBase a x -> StateT [String] ExprM ()
shaderbaseAssign ShaderBase a x
a
ShaderBase b x -> StateT [String] ExprM ()
forall a x. ShaderBase a x -> StateT [String] ExprM ()
shaderbaseAssign ShaderBase b x
b
shaderbaseAssign (ShaderBaseGenerativeGeometry S x (GenerativeGeometry p a)
a) = S x (GenerativeGeometry p a) -> StateT [String] ExprM ()
forall x a. S x a -> StateT [String] ExprM ()
shaderbaseAssignDef S x (GenerativeGeometry p a)
a
shaderbaseReturn :: ShaderBase a x
-> ReaderT
(SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
(State Int)
(ShaderBase a x)
shaderbaseReturn (ShaderBaseFloat S x Float
_) = S x Float -> ShaderBase (S x Float) x
forall x. S x Float -> ShaderBase (S x Float) x
ShaderBaseFloat (S x Float -> ShaderBase (S x Float) x)
-> ReaderT
(SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
(State Int)
(S x Float)
-> ReaderT
(SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
(State Int)
(ShaderBase (S x Float) x)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT
(SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
(State Int)
(S x Float)
forall x a.
ReaderT
(SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
(State Int)
(S x a)
shaderbaseReturnDef
shaderbaseReturn (ShaderBaseInt S x Int
_) = S x Int -> ShaderBase (S x Int) x
forall x. S x Int -> ShaderBase (S x Int) x
ShaderBaseInt (S x Int -> ShaderBase (S x Int) x)
-> ReaderT
(SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
(State Int)
(S x Int)
-> ReaderT
(SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
(State Int)
(ShaderBase (S x Int) x)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT
(SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
(State Int)
(S x Int)
forall x a.
ReaderT
(SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
(State Int)
(S x a)
shaderbaseReturnDef
shaderbaseReturn (ShaderBaseWord S x Word
_) = S x Word -> ShaderBase (S x Word) x
forall x. S x Word -> ShaderBase (S x Word) x
ShaderBaseWord (S x Word -> ShaderBase (S x Word) x)
-> ReaderT
(SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
(State Int)
(S x Word)
-> ReaderT
(SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
(State Int)
(ShaderBase (S x Word) x)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT
(SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
(State Int)
(S x Word)
forall x a.
ReaderT
(SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
(State Int)
(S x a)
shaderbaseReturnDef
shaderbaseReturn (ShaderBaseBool S x Bool
_) = S x Bool -> ShaderBase (S x Bool) x
forall x. S x Bool -> ShaderBase (S x Bool) x
ShaderBaseBool (S x Bool -> ShaderBase (S x Bool) x)
-> ReaderT
(SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
(State Int)
(S x Bool)
-> ReaderT
(SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
(State Int)
(ShaderBase (S x Bool) x)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT
(SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
(State Int)
(S x Bool)
forall x a.
ReaderT
(SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
(State Int)
(S x a)
shaderbaseReturnDef
shaderbaseReturn ShaderBase a x
ShaderBaseUnit = ShaderBase () x
-> ReaderT
(SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
(State Int)
(ShaderBase () x)
forall (m :: * -> *) a. Monad m => a -> m a
return ShaderBase () x
forall x. ShaderBase () x
ShaderBaseUnit
shaderbaseReturn (ShaderBaseProd ShaderBase a x
a ShaderBase b x
b) = do
ShaderBase a x
a' <- ShaderBase a x
-> ReaderT
(SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
(State Int)
(ShaderBase a x)
forall a x.
ShaderBase a x
-> ReaderT
(SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
(State Int)
(ShaderBase a x)
shaderbaseReturn ShaderBase a x
a
ShaderBase b x
b' <- ShaderBase b x
-> ReaderT
(SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
(State Int)
(ShaderBase b x)
forall a x.
ShaderBase a x
-> ReaderT
(SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
(State Int)
(ShaderBase a x)
shaderbaseReturn ShaderBase b x
b
ShaderBase (a, b) x
-> ReaderT
(SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
(State Int)
(ShaderBase (a, b) x)
forall (m :: * -> *) a. Monad m => a -> m a
return (ShaderBase (a, b) x
-> ReaderT
(SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
(State Int)
(ShaderBase (a, b) x))
-> ShaderBase (a, b) x
-> ReaderT
(SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
(State Int)
(ShaderBase (a, b) x)
forall a b. (a -> b) -> a -> b
$ ShaderBase a x -> ShaderBase b x -> ShaderBase (a, b) x
forall a x b.
ShaderBase a x -> ShaderBase b x -> ShaderBase (a, b) x
ShaderBaseProd ShaderBase a x
a' ShaderBase b x
b'
shaderbaseReturn (ShaderBaseGenerativeGeometry S x (GenerativeGeometry p a)
_) = S x (GenerativeGeometry p a)
-> ShaderBase (S x (GenerativeGeometry p a)) x
forall x p a.
S x (GenerativeGeometry p a)
-> ShaderBase (S x (GenerativeGeometry p a)) x
ShaderBaseGenerativeGeometry (S x (GenerativeGeometry p a)
-> ShaderBase (S x (GenerativeGeometry p a)) x)
-> ReaderT
(SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
(State Int)
(S x (GenerativeGeometry p a))
-> ReaderT
(SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
(State Int)
(ShaderBase (S x (GenerativeGeometry p a)) x)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT
(SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
(State Int)
(S x (GenerativeGeometry p a))
forall x a.
ReaderT
(SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
(State Int)
(S x a)
shaderbaseReturnDef
shaderbaseDeclareDef :: SType -> WriterT [String] ExprM (S x a)
shaderbaseDeclareDef :: SType -> WriterT [String] ExprM (S x a)
shaderbaseDeclareDef SType
styp = do
Int
var <- SNMapReaderT
[String] (StateT ExprState (WriterT String (StateT Int IO))) Int
-> WriterT [String] ExprM Int
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
T.lift (SNMapReaderT
[String] (StateT ExprState (WriterT String (StateT Int IO))) Int
-> WriterT [String] ExprM Int)
-> SNMapReaderT
[String] (StateT ExprState (WriterT String (StateT Int IO))) Int
-> WriterT [String] ExprM Int
forall a b. (a -> b) -> a -> b
$ StateT ExprState (WriterT String (StateT Int IO)) Int
-> SNMapReaderT
[String] (StateT ExprState (WriterT String (StateT Int IO))) Int
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
T.lift (StateT ExprState (WriterT String (StateT Int IO)) Int
-> SNMapReaderT
[String] (StateT ExprState (WriterT String (StateT Int IO))) Int)
-> StateT ExprState (WriterT String (StateT Int IO)) Int
-> SNMapReaderT
[String] (StateT ExprState (WriterT String (StateT Int IO))) Int
forall a b. (a -> b) -> a -> b
$ WriterT String (StateT Int IO) Int
-> StateT ExprState (WriterT String (StateT Int IO)) Int
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
T.lift (WriterT String (StateT Int IO) Int
-> StateT ExprState (WriterT String (StateT Int IO)) Int)
-> WriterT String (StateT Int IO) Int
-> StateT ExprState (WriterT String (StateT Int IO)) Int
forall a b. (a -> b) -> a -> b
$ StateT Int IO Int -> WriterT String (StateT Int IO) Int
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
T.lift StateT Int IO Int
forall (m :: * -> *). Monad m => StateT Int m Int
getNext
let root :: String
root = Char
't' Char -> String -> String
forall a. a -> [a] -> [a]
: Int -> String
forall a. Show a => a -> String
show Int
var
ExprM () -> WriterT [String] ExprM ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
T.lift (ExprM () -> WriterT [String] ExprM ())
-> ExprM () -> WriterT [String] ExprM ()
forall a b. (a -> b) -> a -> b
$ StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
T.lift (StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ())
-> StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ()
forall a b. (a -> b) -> a -> b
$ WriterT String (StateT Int IO) ()
-> StateT ExprState (WriterT String (StateT Int IO)) ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
T.lift (WriterT String (StateT Int IO) ()
-> StateT ExprState (WriterT String (StateT Int IO)) ())
-> WriterT String (StateT Int IO) ()
-> StateT ExprState (WriterT String (StateT Int IO)) ()
forall a b. (a -> b) -> a -> b
$ String -> WriterT String (StateT Int IO) ()
forall (m :: * -> *) w. Monad m => w -> WriterT w m ()
tell (String -> WriterT String (StateT Int IO) ())
-> String -> WriterT String (StateT Int IO) ()
forall a b. (a -> b) -> a -> b
$ [String] -> String
forall a. Monoid a => [a] -> a
mconcat [SType -> String
stypeName SType
styp, Char
' 'Char -> String -> String
forall a. a -> [a] -> [a]
:String
root, String
";\n"]
[String] -> WriterT [String] ExprM ()
forall (m :: * -> *) w. Monad m => w -> WriterT w m ()
tell [String
root]
S x a -> WriterT [String] ExprM (S x a)
forall (m :: * -> *) a. Monad m => a -> m a
return (S x a -> WriterT [String] ExprM (S x a))
-> S x a -> WriterT [String] ExprM (S x a)
forall a b. (a -> b) -> a -> b
$ ExprM String -> S x a
forall x a. ExprM String -> S x a
S (ExprM String -> S x a) -> ExprM String -> S x a
forall a b. (a -> b) -> a -> b
$ String -> ExprM String
forall (m :: * -> *) a. Monad m => a -> m a
return String
root
shaderbaseAssignDef :: (S x a) -> StateT [String] ExprM ()
shaderbaseAssignDef :: S x a -> StateT [String] ExprM ()
shaderbaseAssignDef (S ExprM String
shaderM) = do
String
ul <- ExprM String -> StateT [String] ExprM String
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
T.lift ExprM String
shaderM
[String]
xs <- StateT [String] ExprM [String]
forall (m :: * -> *) s. Monad m => StateT s m s
get
[String] -> StateT [String] ExprM ()
forall (m :: * -> *) s. Monad m => s -> StateT s m ()
put ([String] -> StateT [String] ExprM ())
-> [String] -> StateT [String] ExprM ()
forall a b. (a -> b) -> a -> b
$ [String] -> [String]
forall a. [a] -> [a]
tail [String]
xs
ExprM () -> StateT [String] ExprM ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
T.lift (ExprM () -> StateT [String] ExprM ())
-> ExprM () -> StateT [String] ExprM ()
forall a b. (a -> b) -> a -> b
$ String -> String -> ExprM ()
tellAssignment' ([String] -> String
forall a. [a] -> a
head [String]
xs) String
ul
() -> StateT [String] ExprM ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
shaderbaseReturnDef :: ReaderT (ExprM [String]) (State Int) (S x a)
shaderbaseReturnDef :: ReaderT
(SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
(State Int)
(S x a)
shaderbaseReturnDef = do
Int
i <- StateT Int Identity Int
-> ReaderT
(SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
(State Int)
Int
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
T.lift StateT Int Identity Int
forall (m :: * -> *). Monad m => StateT Int m Int
getNext
SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String]
m <- ReaderT
(SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
(State Int)
(SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
forall (m :: * -> *) r. Monad m => ReaderT r m r
ask
S x a
-> ReaderT
(SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
(State Int)
(S x a)
forall (m :: * -> *) a. Monad m => a -> m a
return (S x a
-> ReaderT
(SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
(State Int)
(S x a))
-> S x a
-> ReaderT
(SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
(State Int)
(S x a)
forall a b. (a -> b) -> a -> b
$ ExprM String -> S x a
forall x a. ExprM String -> S x a
S (ExprM String -> S x a) -> ExprM String -> S x a
forall a b. (a -> b) -> a -> b
$ ([String] -> String)
-> SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String]
-> ExprM String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([String] -> Int -> String
forall a. [a] -> Int -> a
!!Int
i) SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String]
m
class ShaderType a x where
type ShaderBaseType a
toBase :: x -> a -> ShaderBase (ShaderBaseType a) x
fromBase :: x -> ShaderBase (ShaderBaseType a) x -> a
instance ShaderType (S x Float) x where
type ShaderBaseType (S x Float) = (S x Float)
toBase :: x -> S x Float -> ShaderBase (ShaderBaseType (S x Float)) x
toBase x
_ = S x Float -> ShaderBase (ShaderBaseType (S x Float)) x
forall x. S x Float -> ShaderBase (S x Float) x
ShaderBaseFloat
fromBase :: x -> ShaderBase (ShaderBaseType (S x Float)) x -> S x Float
fromBase x
_ (ShaderBaseFloat S x Float
a) = S x Float
a
instance ShaderType (S x Int) x where
type ShaderBaseType (S x Int) = (S x Int)
toBase :: x -> S x Int -> ShaderBase (ShaderBaseType (S x Int)) x
toBase x
_ = S x Int -> ShaderBase (ShaderBaseType (S x Int)) x
forall x. S x Int -> ShaderBase (S x Int) x
ShaderBaseInt
fromBase :: x -> ShaderBase (ShaderBaseType (S x Int)) x -> S x Int
fromBase x
_ (ShaderBaseInt S x Int
a) = S x Int
a
instance ShaderType (S x Word) x where
type ShaderBaseType (S x Word) = (S x Word)
toBase :: x -> S x Word -> ShaderBase (ShaderBaseType (S x Word)) x
toBase x
_ = S x Word -> ShaderBase (ShaderBaseType (S x Word)) x
forall x. S x Word -> ShaderBase (S x Word) x
ShaderBaseWord
fromBase :: x -> ShaderBase (ShaderBaseType (S x Word)) x -> S x Word
fromBase x
_ (ShaderBaseWord S x Word
a) = S x Word
a
instance ShaderType (S x Bool) x where
type ShaderBaseType (S x Bool) = (S x Bool)
toBase :: x -> S x Bool -> ShaderBase (ShaderBaseType (S x Bool)) x
toBase x
_ = S x Bool -> ShaderBase (ShaderBaseType (S x Bool)) x
forall x. S x Bool -> ShaderBase (S x Bool) x
ShaderBaseBool
fromBase :: x -> ShaderBase (ShaderBaseType (S x Bool)) x -> S x Bool
fromBase x
_ (ShaderBaseBool S x Bool
a) = S x Bool
a
instance ShaderType () x where
type ShaderBaseType () = ()
toBase :: x -> () -> ShaderBase (ShaderBaseType ()) x
toBase x
_ ()
_ = ShaderBase (ShaderBaseType ()) x
forall x. ShaderBase () x
ShaderBaseUnit
fromBase :: x -> ShaderBase (ShaderBaseType ()) x -> ()
fromBase x
_ ShaderBase (ShaderBaseType ()) x
ShaderBaseUnit = ()
instance ShaderType (S x (GenerativeGeometry p a)) x where
type ShaderBaseType (S x (GenerativeGeometry p a)) = (S x (GenerativeGeometry p a))
toBase :: x
-> S x (GenerativeGeometry p a)
-> ShaderBase (ShaderBaseType (S x (GenerativeGeometry p a))) x
toBase x
_ = S x (GenerativeGeometry p a)
-> ShaderBase (ShaderBaseType (S x (GenerativeGeometry p a))) x
forall x p a.
S x (GenerativeGeometry p a)
-> ShaderBase (S x (GenerativeGeometry p a)) x
ShaderBaseGenerativeGeometry
fromBase :: x
-> ShaderBase (ShaderBaseType (S x (GenerativeGeometry p a))) x
-> S x (GenerativeGeometry p a)
fromBase x
_ (ShaderBaseGenerativeGeometry S x (GenerativeGeometry p a)
a) = S x (GenerativeGeometry p a)
S x (GenerativeGeometry p a)
a
instance ShaderType a x => ShaderType (V0 a) x where
type ShaderBaseType (V0 a) = ()
toBase :: x -> V0 a -> ShaderBase (ShaderBaseType (V0 a)) x
toBase x
_ V0 a
V0 = ShaderBase (ShaderBaseType (V0 a)) x
forall x. ShaderBase () x
ShaderBaseUnit
fromBase :: x -> ShaderBase (ShaderBaseType (V0 a)) x -> V0 a
fromBase x
_ ShaderBase (ShaderBaseType (V0 a)) x
ShaderBaseUnit = V0 a
forall a. V0 a
V0
instance ShaderType a x => ShaderType (V1 a) x where
type ShaderBaseType (V1 a) = ShaderBaseType a
toBase :: x -> V1 a -> ShaderBase (ShaderBaseType (V1 a)) x
toBase x
x ~(V1 a
a) = x -> a -> ShaderBase (ShaderBaseType a) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x a
a
fromBase :: x -> ShaderBase (ShaderBaseType (V1 a)) x -> V1 a
fromBase x
x ShaderBase (ShaderBaseType (V1 a)) x
a = a -> V1 a
forall a. a -> V1 a
V1 (x -> ShaderBase (ShaderBaseType a) x -> a
forall a x.
ShaderType a x =>
x -> ShaderBase (ShaderBaseType a) x -> a
fromBase x
x ShaderBase (ShaderBaseType a) x
ShaderBase (ShaderBaseType (V1 a)) x
a)
instance ShaderType a x => ShaderType (V2 a) x where
type ShaderBaseType (V2 a) = (ShaderBaseType a, ShaderBaseType a)
toBase :: x -> V2 a -> ShaderBase (ShaderBaseType (V2 a)) x
toBase x
x ~(V2 a
a a
b) = ShaderBase (ShaderBaseType a) x
-> ShaderBase (ShaderBaseType a) x
-> ShaderBase (ShaderBaseType a, ShaderBaseType a) x
forall a x b.
ShaderBase a x -> ShaderBase b x -> ShaderBase (a, b) x
ShaderBaseProd (x -> a -> ShaderBase (ShaderBaseType a) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x a
a) (x -> a -> ShaderBase (ShaderBaseType a) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x a
b)
fromBase :: x -> ShaderBase (ShaderBaseType (V2 a)) x -> V2 a
fromBase x
x (ShaderBaseProd ShaderBase a x
a ShaderBase b x
b) = a -> a -> V2 a
forall a. a -> a -> V2 a
V2 (x -> ShaderBase (ShaderBaseType a) x -> a
forall a x.
ShaderType a x =>
x -> ShaderBase (ShaderBaseType a) x -> a
fromBase x
x ShaderBase a x
ShaderBase (ShaderBaseType a) x
a) (x -> ShaderBase (ShaderBaseType a) x -> a
forall a x.
ShaderType a x =>
x -> ShaderBase (ShaderBaseType a) x -> a
fromBase x
x ShaderBase b x
ShaderBase (ShaderBaseType a) x
b)
instance ShaderType a x => ShaderType (V3 a) x where
type ShaderBaseType (V3 a) = (ShaderBaseType a, (ShaderBaseType a, ShaderBaseType a))
toBase :: x -> V3 a -> ShaderBase (ShaderBaseType (V3 a)) x
toBase x
x ~(V3 a
a a
b a
c) = ShaderBase (ShaderBaseType a) x
-> ShaderBase (ShaderBaseType a, ShaderBaseType a) x
-> ShaderBase
(ShaderBaseType a, (ShaderBaseType a, ShaderBaseType a)) x
forall a x b.
ShaderBase a x -> ShaderBase b x -> ShaderBase (a, b) x
ShaderBaseProd (x -> a -> ShaderBase (ShaderBaseType a) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x a
a) (ShaderBase (ShaderBaseType a) x
-> ShaderBase (ShaderBaseType a) x
-> ShaderBase (ShaderBaseType a, ShaderBaseType a) x
forall a x b.
ShaderBase a x -> ShaderBase b x -> ShaderBase (a, b) x
ShaderBaseProd (x -> a -> ShaderBase (ShaderBaseType a) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x a
b) (x -> a -> ShaderBase (ShaderBaseType a) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x a
c))
fromBase :: x -> ShaderBase (ShaderBaseType (V3 a)) x -> V3 a
fromBase x
x (ShaderBaseProd ShaderBase a x
a (ShaderBaseProd ShaderBase a x
b ShaderBase b x
c)) = a -> a -> a -> V3 a
forall a. a -> a -> a -> V3 a
V3 (x -> ShaderBase (ShaderBaseType a) x -> a
forall a x.
ShaderType a x =>
x -> ShaderBase (ShaderBaseType a) x -> a
fromBase x
x ShaderBase a x
ShaderBase (ShaderBaseType a) x
a) (x -> ShaderBase (ShaderBaseType a) x -> a
forall a x.
ShaderType a x =>
x -> ShaderBase (ShaderBaseType a) x -> a
fromBase x
x ShaderBase a x
ShaderBase (ShaderBaseType a) x
b) (x -> ShaderBase (ShaderBaseType a) x -> a
forall a x.
ShaderType a x =>
x -> ShaderBase (ShaderBaseType a) x -> a
fromBase x
x ShaderBase b x
ShaderBase (ShaderBaseType a) x
c)
instance ShaderType a x => ShaderType (V4 a) x where
type ShaderBaseType (V4 a) = (ShaderBaseType a, (ShaderBaseType a, (ShaderBaseType a, ShaderBaseType a)))
toBase :: x -> V4 a -> ShaderBase (ShaderBaseType (V4 a)) x
toBase x
x ~(V4 a
a a
b a
c a
d) = ShaderBase (ShaderBaseType a) x
-> ShaderBase
(ShaderBaseType a, (ShaderBaseType a, ShaderBaseType a)) x
-> ShaderBase
(ShaderBaseType a,
(ShaderBaseType a, (ShaderBaseType a, ShaderBaseType a)))
x
forall a x b.
ShaderBase a x -> ShaderBase b x -> ShaderBase (a, b) x
ShaderBaseProd (x -> a -> ShaderBase (ShaderBaseType a) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x a
a) (ShaderBase (ShaderBaseType a) x
-> ShaderBase (ShaderBaseType a, ShaderBaseType a) x
-> ShaderBase
(ShaderBaseType a, (ShaderBaseType a, ShaderBaseType a)) x
forall a x b.
ShaderBase a x -> ShaderBase b x -> ShaderBase (a, b) x
ShaderBaseProd (x -> a -> ShaderBase (ShaderBaseType a) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x a
b) (ShaderBase (ShaderBaseType a) x
-> ShaderBase (ShaderBaseType a) x
-> ShaderBase (ShaderBaseType a, ShaderBaseType a) x
forall a x b.
ShaderBase a x -> ShaderBase b x -> ShaderBase (a, b) x
ShaderBaseProd (x -> a -> ShaderBase (ShaderBaseType a) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x a
c) (x -> a -> ShaderBase (ShaderBaseType a) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x a
d)))
fromBase :: x -> ShaderBase (ShaderBaseType (V4 a)) x -> V4 a
fromBase x
x (ShaderBaseProd ShaderBase a x
a (ShaderBaseProd ShaderBase a x
b (ShaderBaseProd ShaderBase a x
c ShaderBase b x
d))) = a -> a -> a -> a -> V4 a
forall a. a -> a -> a -> a -> V4 a
V4 (x -> ShaderBase (ShaderBaseType a) x -> a
forall a x.
ShaderType a x =>
x -> ShaderBase (ShaderBaseType a) x -> a
fromBase x
x ShaderBase a x
ShaderBase (ShaderBaseType a) x
a) (x -> ShaderBase (ShaderBaseType a) x -> a
forall a x.
ShaderType a x =>
x -> ShaderBase (ShaderBaseType a) x -> a
fromBase x
x ShaderBase a x
ShaderBase (ShaderBaseType a) x
b) (x -> ShaderBase (ShaderBaseType a) x -> a
forall a x.
ShaderType a x =>
x -> ShaderBase (ShaderBaseType a) x -> a
fromBase x
x ShaderBase a x
ShaderBase (ShaderBaseType a) x
c) (x -> ShaderBase (ShaderBaseType a) x -> a
forall a x.
ShaderType a x =>
x -> ShaderBase (ShaderBaseType a) x -> a
fromBase x
x ShaderBase b x
ShaderBase (ShaderBaseType a) x
d)
instance (ShaderType a x, ShaderType b x) => ShaderType (a,b) x where
type ShaderBaseType (a,b) = (ShaderBaseType a, ShaderBaseType b)
toBase :: x -> (a, b) -> ShaderBase (ShaderBaseType (a, b)) x
toBase x
x ~(a
a,b
b) = ShaderBase (ShaderBaseType a) x
-> ShaderBase (ShaderBaseType b) x
-> ShaderBase (ShaderBaseType a, ShaderBaseType b) x
forall a x b.
ShaderBase a x -> ShaderBase b x -> ShaderBase (a, b) x
ShaderBaseProd (x -> a -> ShaderBase (ShaderBaseType a) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x a
a) (x -> b -> ShaderBase (ShaderBaseType b) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x b
b)
fromBase :: x -> ShaderBase (ShaderBaseType (a, b)) x -> (a, b)
fromBase x
x (ShaderBaseProd ShaderBase a x
a ShaderBase b x
b) = (x -> ShaderBase (ShaderBaseType a) x -> a
forall a x.
ShaderType a x =>
x -> ShaderBase (ShaderBaseType a) x -> a
fromBase x
x ShaderBase a x
ShaderBase (ShaderBaseType a) x
a, x -> ShaderBase (ShaderBaseType b) x -> b
forall a x.
ShaderType a x =>
x -> ShaderBase (ShaderBaseType a) x -> a
fromBase x
x ShaderBase b x
ShaderBase (ShaderBaseType b) x
b)
instance (ShaderType a x, ShaderType b x, ShaderType c x) => ShaderType (a,b,c) x where
type ShaderBaseType (a,b,c) = (ShaderBaseType a, (ShaderBaseType b, ShaderBaseType c))
toBase :: x -> (a, b, c) -> ShaderBase (ShaderBaseType (a, b, c)) x
toBase x
x ~(a
a,b
b,c
c) = ShaderBase (ShaderBaseType a) x
-> ShaderBase (ShaderBaseType b, ShaderBaseType c) x
-> ShaderBase
(ShaderBaseType a, (ShaderBaseType b, ShaderBaseType c)) x
forall a x b.
ShaderBase a x -> ShaderBase b x -> ShaderBase (a, b) x
ShaderBaseProd (x -> a -> ShaderBase (ShaderBaseType a) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x a
a) (ShaderBase (ShaderBaseType b) x
-> ShaderBase (ShaderBaseType c) x
-> ShaderBase (ShaderBaseType b, ShaderBaseType c) x
forall a x b.
ShaderBase a x -> ShaderBase b x -> ShaderBase (a, b) x
ShaderBaseProd (x -> b -> ShaderBase (ShaderBaseType b) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x b
b) (x -> c -> ShaderBase (ShaderBaseType c) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x c
c))
fromBase :: x -> ShaderBase (ShaderBaseType (a, b, c)) x -> (a, b, c)
fromBase x
x (ShaderBaseProd ShaderBase a x
a (ShaderBaseProd ShaderBase a x
b ShaderBase b x
c)) = (x -> ShaderBase (ShaderBaseType a) x -> a
forall a x.
ShaderType a x =>
x -> ShaderBase (ShaderBaseType a) x -> a
fromBase x
x ShaderBase a x
ShaderBase (ShaderBaseType a) x
a, x -> ShaderBase (ShaderBaseType b) x -> b
forall a x.
ShaderType a x =>
x -> ShaderBase (ShaderBaseType a) x -> a
fromBase x
x ShaderBase a x
ShaderBase (ShaderBaseType b) x
b, x -> ShaderBase (ShaderBaseType c) x -> c
forall a x.
ShaderType a x =>
x -> ShaderBase (ShaderBaseType a) x -> a
fromBase x
x ShaderBase b x
ShaderBase (ShaderBaseType c) x
c)
instance (ShaderType a x, ShaderType b x, ShaderType c x, ShaderType d x) => ShaderType (a,b,c,d) x where
type ShaderBaseType (a,b,c,d) = (ShaderBaseType a, (ShaderBaseType b, (ShaderBaseType c, ShaderBaseType d)))
toBase :: x -> (a, b, c, d) -> ShaderBase (ShaderBaseType (a, b, c, d)) x
toBase x
x ~(a
a,b
b,c
c,d
d) = ShaderBase (ShaderBaseType a) x
-> ShaderBase
(ShaderBaseType b, (ShaderBaseType c, ShaderBaseType d)) x
-> ShaderBase
(ShaderBaseType a,
(ShaderBaseType b, (ShaderBaseType c, ShaderBaseType d)))
x
forall a x b.
ShaderBase a x -> ShaderBase b x -> ShaderBase (a, b) x
ShaderBaseProd (x -> a -> ShaderBase (ShaderBaseType a) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x a
a) (ShaderBase (ShaderBaseType b) x
-> ShaderBase (ShaderBaseType c, ShaderBaseType d) x
-> ShaderBase
(ShaderBaseType b, (ShaderBaseType c, ShaderBaseType d)) x
forall a x b.
ShaderBase a x -> ShaderBase b x -> ShaderBase (a, b) x
ShaderBaseProd (x -> b -> ShaderBase (ShaderBaseType b) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x b
b) (ShaderBase (ShaderBaseType c) x
-> ShaderBase (ShaderBaseType d) x
-> ShaderBase (ShaderBaseType c, ShaderBaseType d) x
forall a x b.
ShaderBase a x -> ShaderBase b x -> ShaderBase (a, b) x
ShaderBaseProd (x -> c -> ShaderBase (ShaderBaseType c) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x c
c) (x -> d -> ShaderBase (ShaderBaseType d) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x d
d)))
fromBase :: x -> ShaderBase (ShaderBaseType (a, b, c, d)) x -> (a, b, c, d)
fromBase x
x (ShaderBaseProd ShaderBase a x
a (ShaderBaseProd ShaderBase a x
b (ShaderBaseProd ShaderBase a x
c ShaderBase b x
d))) = (x -> ShaderBase (ShaderBaseType a) x -> a
forall a x.
ShaderType a x =>
x -> ShaderBase (ShaderBaseType a) x -> a
fromBase x
x ShaderBase a x
ShaderBase (ShaderBaseType a) x
a, x -> ShaderBase (ShaderBaseType b) x -> b
forall a x.
ShaderType a x =>
x -> ShaderBase (ShaderBaseType a) x -> a
fromBase x
x ShaderBase a x
ShaderBase (ShaderBaseType b) x
b, x -> ShaderBase (ShaderBaseType c) x -> c
forall a x.
ShaderType a x =>
x -> ShaderBase (ShaderBaseType a) x -> a
fromBase x
x ShaderBase a x
ShaderBase (ShaderBaseType c) x
c, x -> ShaderBase (ShaderBaseType d) x -> d
forall a x.
ShaderType a x =>
x -> ShaderBase (ShaderBaseType a) x -> a
fromBase x
x ShaderBase b x
ShaderBase (ShaderBaseType d) x
d)
instance (ShaderType a x, ShaderType b x, ShaderType c x, ShaderType d x, ShaderType e x) => ShaderType (a,b,c,d,e) x where
type ShaderBaseType (a,b,c,d,e) = (ShaderBaseType a, (ShaderBaseType b, (ShaderBaseType c, (ShaderBaseType d, ShaderBaseType e))))
toBase :: x
-> (a, b, c, d, e) -> ShaderBase (ShaderBaseType (a, b, c, d, e)) x
toBase x
x ~(a
a,b
b,c
c,d
d,e
e) = ShaderBase (ShaderBaseType a) x
-> ShaderBase
(ShaderBaseType b,
(ShaderBaseType c, (ShaderBaseType d, ShaderBaseType e)))
x
-> ShaderBase
(ShaderBaseType a,
(ShaderBaseType b,
(ShaderBaseType c, (ShaderBaseType d, ShaderBaseType e))))
x
forall a x b.
ShaderBase a x -> ShaderBase b x -> ShaderBase (a, b) x
ShaderBaseProd (x -> a -> ShaderBase (ShaderBaseType a) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x a
a) (ShaderBase (ShaderBaseType b) x
-> ShaderBase
(ShaderBaseType c, (ShaderBaseType d, ShaderBaseType e)) x
-> ShaderBase
(ShaderBaseType b,
(ShaderBaseType c, (ShaderBaseType d, ShaderBaseType e)))
x
forall a x b.
ShaderBase a x -> ShaderBase b x -> ShaderBase (a, b) x
ShaderBaseProd (x -> b -> ShaderBase (ShaderBaseType b) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x b
b) (ShaderBase (ShaderBaseType c) x
-> ShaderBase (ShaderBaseType d, ShaderBaseType e) x
-> ShaderBase
(ShaderBaseType c, (ShaderBaseType d, ShaderBaseType e)) x
forall a x b.
ShaderBase a x -> ShaderBase b x -> ShaderBase (a, b) x
ShaderBaseProd (x -> c -> ShaderBase (ShaderBaseType c) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x c
c) (ShaderBase (ShaderBaseType d) x
-> ShaderBase (ShaderBaseType e) x
-> ShaderBase (ShaderBaseType d, ShaderBaseType e) x
forall a x b.
ShaderBase a x -> ShaderBase b x -> ShaderBase (a, b) x
ShaderBaseProd (x -> d -> ShaderBase (ShaderBaseType d) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x d
d) (x -> e -> ShaderBase (ShaderBaseType e) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x e
e))))
fromBase :: x
-> ShaderBase (ShaderBaseType (a, b, c, d, e)) x -> (a, b, c, d, e)
fromBase x
x (ShaderBaseProd ShaderBase a x
a (ShaderBaseProd ShaderBase a x
b (ShaderBaseProd ShaderBase a x
c (ShaderBaseProd ShaderBase a x
d ShaderBase b x
e)))) = (x -> ShaderBase (ShaderBaseType a) x -> a
forall a x.
ShaderType a x =>
x -> ShaderBase (ShaderBaseType a) x -> a
fromBase x
x ShaderBase a x
ShaderBase (ShaderBaseType a) x
a, x -> ShaderBase (ShaderBaseType b) x -> b
forall a x.
ShaderType a x =>
x -> ShaderBase (ShaderBaseType a) x -> a
fromBase x
x ShaderBase a x
ShaderBase (ShaderBaseType b) x
b, x -> ShaderBase (ShaderBaseType c) x -> c
forall a x.
ShaderType a x =>
x -> ShaderBase (ShaderBaseType a) x -> a
fromBase x
x ShaderBase a x
ShaderBase (ShaderBaseType c) x
c, x -> ShaderBase (ShaderBaseType d) x -> d
forall a x.
ShaderType a x =>
x -> ShaderBase (ShaderBaseType a) x -> a
fromBase x
x ShaderBase a x
ShaderBase (ShaderBaseType d) x
d, x -> ShaderBase (ShaderBaseType e) x -> e
forall a x.
ShaderType a x =>
x -> ShaderBase (ShaderBaseType a) x -> a
fromBase x
x ShaderBase b x
ShaderBase (ShaderBaseType e) x
e)
instance (ShaderType a x, ShaderType b x, ShaderType c x, ShaderType d x, ShaderType e x, ShaderType f x) => ShaderType (a,b,c,d,e,f) x where
type ShaderBaseType (a,b,c,d,e,f) = (ShaderBaseType a, (ShaderBaseType b, (ShaderBaseType c, (ShaderBaseType d, (ShaderBaseType e, ShaderBaseType f)))))
toBase :: x
-> (a, b, c, d, e, f)
-> ShaderBase (ShaderBaseType (a, b, c, d, e, f)) x
toBase x
x ~(a
a,b
b,c
c,d
d,e
e,f
f) = ShaderBase (ShaderBaseType a) x
-> ShaderBase
(ShaderBaseType b,
(ShaderBaseType c,
(ShaderBaseType d, (ShaderBaseType e, ShaderBaseType f))))
x
-> ShaderBase
(ShaderBaseType a,
(ShaderBaseType b,
(ShaderBaseType c,
(ShaderBaseType d, (ShaderBaseType e, ShaderBaseType f)))))
x
forall a x b.
ShaderBase a x -> ShaderBase b x -> ShaderBase (a, b) x
ShaderBaseProd (x -> a -> ShaderBase (ShaderBaseType a) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x a
a) (ShaderBase (ShaderBaseType b) x
-> ShaderBase
(ShaderBaseType c,
(ShaderBaseType d, (ShaderBaseType e, ShaderBaseType f)))
x
-> ShaderBase
(ShaderBaseType b,
(ShaderBaseType c,
(ShaderBaseType d, (ShaderBaseType e, ShaderBaseType f))))
x
forall a x b.
ShaderBase a x -> ShaderBase b x -> ShaderBase (a, b) x
ShaderBaseProd (x -> b -> ShaderBase (ShaderBaseType b) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x b
b) (ShaderBase (ShaderBaseType c) x
-> ShaderBase
(ShaderBaseType d, (ShaderBaseType e, ShaderBaseType f)) x
-> ShaderBase
(ShaderBaseType c,
(ShaderBaseType d, (ShaderBaseType e, ShaderBaseType f)))
x
forall a x b.
ShaderBase a x -> ShaderBase b x -> ShaderBase (a, b) x
ShaderBaseProd (x -> c -> ShaderBase (ShaderBaseType c) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x c
c) (ShaderBase (ShaderBaseType d) x
-> ShaderBase (ShaderBaseType e, ShaderBaseType f) x
-> ShaderBase
(ShaderBaseType d, (ShaderBaseType e, ShaderBaseType f)) x
forall a x b.
ShaderBase a x -> ShaderBase b x -> ShaderBase (a, b) x
ShaderBaseProd (x -> d -> ShaderBase (ShaderBaseType d) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x d
d) (ShaderBase (ShaderBaseType e) x
-> ShaderBase (ShaderBaseType f) x
-> ShaderBase (ShaderBaseType e, ShaderBaseType f) x
forall a x b.
ShaderBase a x -> ShaderBase b x -> ShaderBase (a, b) x
ShaderBaseProd (x -> e -> ShaderBase (ShaderBaseType e) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x e
e) (x -> f -> ShaderBase (ShaderBaseType f) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x f
f)))))
fromBase :: x
-> ShaderBase (ShaderBaseType (a, b, c, d, e, f)) x
-> (a, b, c, d, e, f)
fromBase x
x (ShaderBaseProd ShaderBase a x
a (ShaderBaseProd ShaderBase a x
b (ShaderBaseProd ShaderBase a x
c (ShaderBaseProd ShaderBase a x
d (ShaderBaseProd ShaderBase a x
e ShaderBase b x
f))))) = (x -> ShaderBase (ShaderBaseType a) x -> a
forall a x.
ShaderType a x =>
x -> ShaderBase (ShaderBaseType a) x -> a
fromBase x
x ShaderBase a x
ShaderBase (ShaderBaseType a) x
a, x -> ShaderBase (ShaderBaseType b) x -> b
forall a x.
ShaderType a x =>
x -> ShaderBase (ShaderBaseType a) x -> a
fromBase x
x ShaderBase a x
ShaderBase (ShaderBaseType b) x
b, x -> ShaderBase (ShaderBaseType c) x -> c
forall a x.
ShaderType a x =>
x -> ShaderBase (ShaderBaseType a) x -> a
fromBase x
x ShaderBase a x
ShaderBase (ShaderBaseType c) x
c, x -> ShaderBase (ShaderBaseType d) x -> d
forall a x.
ShaderType a x =>
x -> ShaderBase (ShaderBaseType a) x -> a
fromBase x
x ShaderBase a x
ShaderBase (ShaderBaseType d) x
d, x -> ShaderBase (ShaderBaseType e) x -> e
forall a x.
ShaderType a x =>
x -> ShaderBase (ShaderBaseType a) x -> a
fromBase x
x ShaderBase a x
ShaderBase (ShaderBaseType e) x
e, x -> ShaderBase (ShaderBaseType f) x -> f
forall a x.
ShaderType a x =>
x -> ShaderBase (ShaderBaseType a) x -> a
fromBase x
x ShaderBase b x
ShaderBase (ShaderBaseType f) x
f)
instance (ShaderType a x, ShaderType b x, ShaderType c x, ShaderType d x, ShaderType e x, ShaderType f x, ShaderType g x) => ShaderType (a,b,c,d,e,f,g) x where
type ShaderBaseType (a,b,c,d,e,f,g) = (ShaderBaseType a, (ShaderBaseType b, (ShaderBaseType c, (ShaderBaseType d, (ShaderBaseType e, (ShaderBaseType f, ShaderBaseType g))))))
toBase :: x
-> (a, b, c, d, e, f, g)
-> ShaderBase (ShaderBaseType (a, b, c, d, e, f, g)) x
toBase x
x ~(a
a,b
b,c
c,d
d,e
e,f
f,g
g) = ShaderBase (ShaderBaseType a) x
-> ShaderBase
(ShaderBaseType b,
(ShaderBaseType c,
(ShaderBaseType d,
(ShaderBaseType e, (ShaderBaseType f, ShaderBaseType g)))))
x
-> ShaderBase
(ShaderBaseType a,
(ShaderBaseType b,
(ShaderBaseType c,
(ShaderBaseType d,
(ShaderBaseType e, (ShaderBaseType f, ShaderBaseType g))))))
x
forall a x b.
ShaderBase a x -> ShaderBase b x -> ShaderBase (a, b) x
ShaderBaseProd (x -> a -> ShaderBase (ShaderBaseType a) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x a
a) (ShaderBase (ShaderBaseType b) x
-> ShaderBase
(ShaderBaseType c,
(ShaderBaseType d,
(ShaderBaseType e, (ShaderBaseType f, ShaderBaseType g))))
x
-> ShaderBase
(ShaderBaseType b,
(ShaderBaseType c,
(ShaderBaseType d,
(ShaderBaseType e, (ShaderBaseType f, ShaderBaseType g)))))
x
forall a x b.
ShaderBase a x -> ShaderBase b x -> ShaderBase (a, b) x
ShaderBaseProd (x -> b -> ShaderBase (ShaderBaseType b) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x b
b) (ShaderBase (ShaderBaseType c) x
-> ShaderBase
(ShaderBaseType d,
(ShaderBaseType e, (ShaderBaseType f, ShaderBaseType g)))
x
-> ShaderBase
(ShaderBaseType c,
(ShaderBaseType d,
(ShaderBaseType e, (ShaderBaseType f, ShaderBaseType g))))
x
forall a x b.
ShaderBase a x -> ShaderBase b x -> ShaderBase (a, b) x
ShaderBaseProd (x -> c -> ShaderBase (ShaderBaseType c) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x c
c) (ShaderBase (ShaderBaseType d) x
-> ShaderBase
(ShaderBaseType e, (ShaderBaseType f, ShaderBaseType g)) x
-> ShaderBase
(ShaderBaseType d,
(ShaderBaseType e, (ShaderBaseType f, ShaderBaseType g)))
x
forall a x b.
ShaderBase a x -> ShaderBase b x -> ShaderBase (a, b) x
ShaderBaseProd (x -> d -> ShaderBase (ShaderBaseType d) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x d
d) (ShaderBase (ShaderBaseType e) x
-> ShaderBase (ShaderBaseType f, ShaderBaseType g) x
-> ShaderBase
(ShaderBaseType e, (ShaderBaseType f, ShaderBaseType g)) x
forall a x b.
ShaderBase a x -> ShaderBase b x -> ShaderBase (a, b) x
ShaderBaseProd (x -> e -> ShaderBase (ShaderBaseType e) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x e
e) (ShaderBase (ShaderBaseType f) x
-> ShaderBase (ShaderBaseType g) x
-> ShaderBase (ShaderBaseType f, ShaderBaseType g) x
forall a x b.
ShaderBase a x -> ShaderBase b x -> ShaderBase (a, b) x
ShaderBaseProd (x -> f -> ShaderBase (ShaderBaseType f) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x f
f) (x -> g -> ShaderBase (ShaderBaseType g) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x g
g))))))
fromBase :: x
-> ShaderBase (ShaderBaseType (a, b, c, d, e, f, g)) x
-> (a, b, c, d, e, f, g)
fromBase x
x (ShaderBaseProd ShaderBase a x
a (ShaderBaseProd ShaderBase a x
b (ShaderBaseProd ShaderBase a x
c (ShaderBaseProd ShaderBase a x
d (ShaderBaseProd ShaderBase a x
e (ShaderBaseProd ShaderBase a x
f ShaderBase b x
g)))))) = (x -> ShaderBase (ShaderBaseType a) x -> a
forall a x.
ShaderType a x =>
x -> ShaderBase (ShaderBaseType a) x -> a
fromBase x
x ShaderBase a x
ShaderBase (ShaderBaseType a) x
a, x -> ShaderBase (ShaderBaseType b) x -> b
forall a x.
ShaderType a x =>
x -> ShaderBase (ShaderBaseType a) x -> a
fromBase x
x ShaderBase a x
ShaderBase (ShaderBaseType b) x
b, x -> ShaderBase (ShaderBaseType c) x -> c
forall a x.
ShaderType a x =>
x -> ShaderBase (ShaderBaseType a) x -> a
fromBase x
x ShaderBase a x
ShaderBase (ShaderBaseType c) x
c, x -> ShaderBase (ShaderBaseType d) x -> d
forall a x.
ShaderType a x =>
x -> ShaderBase (ShaderBaseType a) x -> a
fromBase x
x ShaderBase a x
ShaderBase (ShaderBaseType d) x
d, x -> ShaderBase (ShaderBaseType e) x -> e
forall a x.
ShaderType a x =>
x -> ShaderBase (ShaderBaseType a) x -> a
fromBase x
x ShaderBase a x
ShaderBase (ShaderBaseType e) x
e, x -> ShaderBase (ShaderBaseType f) x -> f
forall a x.
ShaderType a x =>
x -> ShaderBase (ShaderBaseType a) x -> a
fromBase x
x ShaderBase a x
ShaderBase (ShaderBaseType f) x
f, x -> ShaderBase (ShaderBaseType g) x -> g
forall a x.
ShaderType a x =>
x -> ShaderBase (ShaderBaseType a) x -> a
fromBase x
x ShaderBase b x
ShaderBase (ShaderBaseType g) x
g)
ifThenElse' :: forall a x. (ShaderType a x) => S x Bool -> a -> a -> a
ifThenElse' :: S x Bool -> a -> a -> a
ifThenElse' S x Bool
b a
t a
e = S x Bool -> (() -> a) -> (() -> a) -> () -> a
forall a b x.
(ShaderType a x, ShaderType b x) =>
S x Bool -> (a -> b) -> (a -> b) -> a -> b
ifThenElse S x Bool
b (a -> () -> a
forall a b. a -> b -> a
const a
t) (a -> () -> a
forall a b. a -> b -> a
const a
e) ()
ifThenElse :: forall a b x. (ShaderType a x, ShaderType b x) => S x Bool -> (a -> b) -> (a -> b) -> a -> b
ifThenElse :: S x Bool -> (a -> b) -> (a -> b) -> a -> b
ifThenElse S x Bool
c a -> b
t a -> b
e a
i = x -> ShaderBase (ShaderBaseType b) x -> b
forall a x.
ShaderType a x =>
x -> ShaderBase (ShaderBaseType a) x -> a
fromBase x
x (ShaderBase (ShaderBaseType b) x -> b)
-> ShaderBase (ShaderBaseType b) x -> b
forall a b. (a -> b) -> a -> b
$ S x Bool
-> (ShaderBase (ShaderBaseType a) x
-> ShaderBase (ShaderBaseType b) x)
-> (ShaderBase (ShaderBaseType a) x
-> ShaderBase (ShaderBaseType b) x)
-> ShaderBase (ShaderBaseType a) x
-> ShaderBase (ShaderBaseType b) x
ifThenElse_ S x Bool
c (x -> b -> ShaderBase (ShaderBaseType b) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x (b -> ShaderBase (ShaderBaseType b) x)
-> (ShaderBase (ShaderBaseType a) x -> b)
-> ShaderBase (ShaderBaseType a) x
-> ShaderBase (ShaderBaseType b) x
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. a -> b
t (a -> b)
-> (ShaderBase (ShaderBaseType a) x -> a)
-> ShaderBase (ShaderBaseType a) x
-> b
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. x -> ShaderBase (ShaderBaseType a) x -> a
forall a x.
ShaderType a x =>
x -> ShaderBase (ShaderBaseType a) x -> a
fromBase x
x) (x -> b -> ShaderBase (ShaderBaseType b) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x (b -> ShaderBase (ShaderBaseType b) x)
-> (ShaderBase (ShaderBaseType a) x -> b)
-> ShaderBase (ShaderBaseType a) x
-> ShaderBase (ShaderBaseType b) x
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. a -> b
e (a -> b)
-> (ShaderBase (ShaderBaseType a) x -> a)
-> ShaderBase (ShaderBaseType a) x
-> b
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. x -> ShaderBase (ShaderBaseType a) x -> a
forall a x.
ShaderType a x =>
x -> ShaderBase (ShaderBaseType a) x -> a
fromBase x
x) (x -> a -> ShaderBase (ShaderBaseType a) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x a
i)
where
x :: x
x = x
forall a. HasCallStack => a
undefined :: x
ifThenElse_
:: S x Bool
-> (ShaderBase (ShaderBaseType a) x -> ShaderBase (ShaderBaseType b) x)
-> (ShaderBase (ShaderBaseType a) x -> ShaderBase (ShaderBaseType b) x)
-> ShaderBase (ShaderBaseType a) x -> ShaderBase (ShaderBaseType b) x
ifThenElse_ :: S x Bool
-> (ShaderBase (ShaderBaseType a) x
-> ShaderBase (ShaderBaseType b) x)
-> (ShaderBase (ShaderBaseType a) x
-> ShaderBase (ShaderBaseType b) x)
-> ShaderBase (ShaderBaseType a) x
-> ShaderBase (ShaderBaseType b) x
ifThenElse_ S x Bool
bool ShaderBase (ShaderBaseType a) x -> ShaderBase (ShaderBaseType b) x
thn ShaderBase (ShaderBaseType a) x -> ShaderBase (ShaderBaseType b) x
els ShaderBase (ShaderBaseType a) x
a =
let ifM :: ExprM [String]
ifM :: SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String]
ifM = SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String]
-> SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String]
forall (m :: * -> *) a.
MonadIO m =>
SNMapReaderT a m a -> SNMapReaderT a m a
memoizeM (SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String]
-> SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
-> SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String]
-> SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String]
forall a b. (a -> b) -> a -> b
$ do
String
boolStr <- S x Bool -> ExprM String
forall x a. S x a -> ExprM String
unS S x Bool
bool
(ShaderBase (ShaderBaseType a) x
lifted, [String]
aDecls) <- WriterT [String] ExprM (ShaderBase (ShaderBaseType a) x)
-> ExprM (ShaderBase (ShaderBaseType a) x, [String])
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
runWriterT (WriterT [String] ExprM (ShaderBase (ShaderBaseType a) x)
-> ExprM (ShaderBase (ShaderBaseType a) x, [String]))
-> WriterT [String] ExprM (ShaderBase (ShaderBaseType a) x)
-> ExprM (ShaderBase (ShaderBaseType a) x, [String])
forall a b. (a -> b) -> a -> b
$ ShaderBase (ShaderBaseType a) x
-> WriterT [String] ExprM (ShaderBase (ShaderBaseType a) x)
forall a x.
ShaderBase a x -> WriterT [String] ExprM (ShaderBase a x)
shaderbaseDeclare (x -> a -> ShaderBase (ShaderBaseType a) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x (a
forall a. a
errShaderType :: a))
ExprM () -> ExprM ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (ExprM () -> ExprM ()) -> ExprM () -> ExprM ()
forall a b. (a -> b) -> a -> b
$ StateT [String] ExprM () -> [String] -> ExprM ()
forall (m :: * -> *) s a. Monad m => StateT s m a -> s -> m a
evalStateT (ShaderBase (ShaderBaseType a) x -> StateT [String] ExprM ()
forall a x. ShaderBase a x -> StateT [String] ExprM ()
shaderbaseAssign ShaderBase (ShaderBaseType a) x
a) [String]
aDecls
[String]
decls <- WriterT [String] ExprM (ShaderBase (ShaderBaseType b) x)
-> SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String]
forall (m :: * -> *) w a. Monad m => WriterT w m a -> m w
execWriterT (WriterT [String] ExprM (ShaderBase (ShaderBaseType b) x)
-> SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
-> WriterT [String] ExprM (ShaderBase (ShaderBaseType b) x)
-> SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String]
forall a b. (a -> b) -> a -> b
$ ShaderBase (ShaderBaseType b) x
-> WriterT [String] ExprM (ShaderBase (ShaderBaseType b) x)
forall a x.
ShaderBase a x -> WriterT [String] ExprM (ShaderBase a x)
shaderbaseDeclare (x -> b -> ShaderBase (ShaderBaseType b) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x (b
forall a. a
errShaderType :: b))
String -> ExprM ()
tellIf String
boolStr
ExprM () -> ExprM ()
forall (m :: * -> *) a x.
MonadIO m =>
SNMapReaderT a m x -> SNMapReaderT a m x
scopedM (ExprM () -> ExprM ()) -> ExprM () -> ExprM ()
forall a b. (a -> b) -> a -> b
$ ExprM () -> ExprM ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (ExprM () -> ExprM ()) -> ExprM () -> ExprM ()
forall a b. (a -> b) -> a -> b
$ StateT [String] ExprM () -> [String] -> ExprM ()
forall (m :: * -> *) s a. Monad m => StateT s m a -> s -> m a
evalStateT (ShaderBase (ShaderBaseType b) x -> StateT [String] ExprM ()
forall a x. ShaderBase a x -> StateT [String] ExprM ()
shaderbaseAssign (ShaderBase (ShaderBaseType b) x -> StateT [String] ExprM ())
-> ShaderBase (ShaderBaseType b) x -> StateT [String] ExprM ()
forall a b. (a -> b) -> a -> b
$ ShaderBase (ShaderBaseType a) x -> ShaderBase (ShaderBaseType b) x
thn ShaderBase (ShaderBaseType a) x
lifted) [String]
decls
StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
T.lift (StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ())
-> StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ()
forall a b. (a -> b) -> a -> b
$ WriterT String (StateT Int IO) ()
-> StateT ExprState (WriterT String (StateT Int IO)) ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
T.lift (WriterT String (StateT Int IO) ()
-> StateT ExprState (WriterT String (StateT Int IO)) ())
-> WriterT String (StateT Int IO) ()
-> StateT ExprState (WriterT String (StateT Int IO)) ()
forall a b. (a -> b) -> a -> b
$ String -> WriterT String (StateT Int IO) ()
forall (m :: * -> *) w. Monad m => w -> WriterT w m ()
tell String
"} else {\n"
ExprM () -> ExprM ()
forall (m :: * -> *) a x.
MonadIO m =>
SNMapReaderT a m x -> SNMapReaderT a m x
scopedM (ExprM () -> ExprM ()) -> ExprM () -> ExprM ()
forall a b. (a -> b) -> a -> b
$ ExprM () -> ExprM ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (ExprM () -> ExprM ()) -> ExprM () -> ExprM ()
forall a b. (a -> b) -> a -> b
$ StateT [String] ExprM () -> [String] -> ExprM ()
forall (m :: * -> *) s a. Monad m => StateT s m a -> s -> m a
evalStateT (ShaderBase (ShaderBaseType b) x -> StateT [String] ExprM ()
forall a x. ShaderBase a x -> StateT [String] ExprM ()
shaderbaseAssign (ShaderBase (ShaderBaseType b) x -> StateT [String] ExprM ())
-> ShaderBase (ShaderBaseType b) x -> StateT [String] ExprM ()
forall a b. (a -> b) -> a -> b
$ ShaderBase (ShaderBaseType a) x -> ShaderBase (ShaderBaseType b) x
els ShaderBase (ShaderBaseType a) x
lifted) [String]
decls
StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
T.lift (StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ())
-> StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ()
forall a b. (a -> b) -> a -> b
$ WriterT String (StateT Int IO) ()
-> StateT ExprState (WriterT String (StateT Int IO)) ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
T.lift (WriterT String (StateT Int IO) ()
-> StateT ExprState (WriterT String (StateT Int IO)) ())
-> WriterT String (StateT Int IO) ()
-> StateT ExprState (WriterT String (StateT Int IO)) ()
forall a b. (a -> b) -> a -> b
$ String -> WriterT String (StateT Int IO) ()
forall (m :: * -> *) w. Monad m => w -> WriterT w m ()
tell String
"}\n"
[String]
-> SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String]
forall (m :: * -> *) a. Monad m => a -> m a
return [String]
decls
in State Int (ShaderBase (ShaderBaseType b) x)
-> Int -> ShaderBase (ShaderBaseType b) x
forall s a. State s a -> s -> a
evalState (ReaderT
(SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
(State Int)
(ShaderBase (ShaderBaseType b) x)
-> SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String]
-> State Int (ShaderBase (ShaderBaseType b) x)
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT (ShaderBase (ShaderBaseType b) x
-> ReaderT
(SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
(State Int)
(ShaderBase (ShaderBaseType b) x)
forall a x.
ShaderBase a x
-> ReaderT
(SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
(State Int)
(ShaderBase a x)
shaderbaseReturn (x -> b -> ShaderBase (ShaderBaseType b) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x (b
forall a. a
errShaderType :: b))) SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String]
ifM) Int
0
ifThen :: forall a x. (ShaderType a x) => S x Bool -> (a -> a) -> a -> a
ifThen :: S x Bool -> (a -> a) -> a -> a
ifThen S x Bool
c a -> a
t a
i = x -> ShaderBase (ShaderBaseType a) x -> a
forall a x.
ShaderType a x =>
x -> ShaderBase (ShaderBaseType a) x -> a
fromBase x
x (ShaderBase (ShaderBaseType a) x -> a)
-> ShaderBase (ShaderBaseType a) x -> a
forall a b. (a -> b) -> a -> b
$ S x Bool
-> (ShaderBase (ShaderBaseType a) x
-> ShaderBase (ShaderBaseType a) x)
-> ShaderBase (ShaderBaseType a) x
-> ShaderBase (ShaderBaseType a) x
ifThen_ S x Bool
c (x -> a -> ShaderBase (ShaderBaseType a) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x (a -> ShaderBase (ShaderBaseType a) x)
-> (ShaderBase (ShaderBaseType a) x -> a)
-> ShaderBase (ShaderBaseType a) x
-> ShaderBase (ShaderBaseType a) x
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. a -> a
t (a -> a)
-> (ShaderBase (ShaderBaseType a) x -> a)
-> ShaderBase (ShaderBaseType a) x
-> a
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. x -> ShaderBase (ShaderBaseType a) x -> a
forall a x.
ShaderType a x =>
x -> ShaderBase (ShaderBaseType a) x -> a
fromBase x
x) (x -> a -> ShaderBase (ShaderBaseType a) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x a
i)
where
x :: x
x = x
forall a. HasCallStack => a
undefined :: x
ifThen_ :: S x Bool -> (ShaderBase (ShaderBaseType a) x -> ShaderBase (ShaderBaseType a) x) -> ShaderBase (ShaderBaseType a) x -> ShaderBase (ShaderBaseType a) x
ifThen_ :: S x Bool
-> (ShaderBase (ShaderBaseType a) x
-> ShaderBase (ShaderBaseType a) x)
-> ShaderBase (ShaderBaseType a) x
-> ShaderBase (ShaderBaseType a) x
ifThen_ S x Bool
bool ShaderBase (ShaderBaseType a) x -> ShaderBase (ShaderBaseType a) x
thn ShaderBase (ShaderBaseType a) x
a =
let ifM :: SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String]
ifM = SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String]
-> SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String]
forall (m :: * -> *) a.
MonadIO m =>
SNMapReaderT a m a -> SNMapReaderT a m a
memoizeM (SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String]
-> SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
-> SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String]
-> SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String]
forall a b. (a -> b) -> a -> b
$ do
String
boolStr <- S x Bool -> ExprM String
forall x a. S x a -> ExprM String
unS S x Bool
bool
(ShaderBase (ShaderBaseType a) x
lifted, [String]
decls) <- WriterT [String] ExprM (ShaderBase (ShaderBaseType a) x)
-> ExprM (ShaderBase (ShaderBaseType a) x, [String])
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
runWriterT (WriterT [String] ExprM (ShaderBase (ShaderBaseType a) x)
-> ExprM (ShaderBase (ShaderBaseType a) x, [String]))
-> WriterT [String] ExprM (ShaderBase (ShaderBaseType a) x)
-> ExprM (ShaderBase (ShaderBaseType a) x, [String])
forall a b. (a -> b) -> a -> b
$ ShaderBase (ShaderBaseType a) x
-> WriterT [String] ExprM (ShaderBase (ShaderBaseType a) x)
forall a x.
ShaderBase a x -> WriterT [String] ExprM (ShaderBase a x)
shaderbaseDeclare (x -> a -> ShaderBase (ShaderBaseType a) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x (a
forall a. a
errShaderType :: a))
ExprM () -> ExprM ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (ExprM () -> ExprM ()) -> ExprM () -> ExprM ()
forall a b. (a -> b) -> a -> b
$ StateT [String] ExprM () -> [String] -> ExprM ()
forall (m :: * -> *) s a. Monad m => StateT s m a -> s -> m a
evalStateT (ShaderBase (ShaderBaseType a) x -> StateT [String] ExprM ()
forall a x. ShaderBase a x -> StateT [String] ExprM ()
shaderbaseAssign ShaderBase (ShaderBaseType a) x
a) [String]
decls
String -> ExprM ()
tellIf String
boolStr
ExprM () -> ExprM ()
forall (m :: * -> *) a x.
MonadIO m =>
SNMapReaderT a m x -> SNMapReaderT a m x
scopedM (ExprM () -> ExprM ()) -> ExprM () -> ExprM ()
forall a b. (a -> b) -> a -> b
$ ExprM () -> ExprM ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (ExprM () -> ExprM ()) -> ExprM () -> ExprM ()
forall a b. (a -> b) -> a -> b
$ StateT [String] ExprM () -> [String] -> ExprM ()
forall (m :: * -> *) s a. Monad m => StateT s m a -> s -> m a
evalStateT (ShaderBase (ShaderBaseType a) x -> StateT [String] ExprM ()
forall a x. ShaderBase a x -> StateT [String] ExprM ()
shaderbaseAssign (ShaderBase (ShaderBaseType a) x -> StateT [String] ExprM ())
-> ShaderBase (ShaderBaseType a) x -> StateT [String] ExprM ()
forall a b. (a -> b) -> a -> b
$ ShaderBase (ShaderBaseType a) x -> ShaderBase (ShaderBaseType a) x
thn ShaderBase (ShaderBaseType a) x
lifted) [String]
decls
StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
T.lift (StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ())
-> StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ()
forall a b. (a -> b) -> a -> b
$ WriterT String (StateT Int IO) ()
-> StateT ExprState (WriterT String (StateT Int IO)) ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
T.lift (WriterT String (StateT Int IO) ()
-> StateT ExprState (WriterT String (StateT Int IO)) ())
-> WriterT String (StateT Int IO) ()
-> StateT ExprState (WriterT String (StateT Int IO)) ()
forall a b. (a -> b) -> a -> b
$ String -> WriterT String (StateT Int IO) ()
forall (m :: * -> *) w. Monad m => w -> WriterT w m ()
tell String
"}\n"
[String]
-> SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String]
forall (m :: * -> *) a. Monad m => a -> m a
return [String]
decls
in State Int (ShaderBase (ShaderBaseType a) x)
-> Int -> ShaderBase (ShaderBaseType a) x
forall s a. State s a -> s -> a
evalState (ReaderT
(SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
(State Int)
(ShaderBase (ShaderBaseType a) x)
-> SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String]
-> State Int (ShaderBase (ShaderBaseType a) x)
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT (ShaderBase (ShaderBaseType a) x
-> ReaderT
(SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
(State Int)
(ShaderBase (ShaderBaseType a) x)
forall a x.
ShaderBase a x
-> ReaderT
(SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
(State Int)
(ShaderBase a x)
shaderbaseReturn (x -> a -> ShaderBase (ShaderBaseType a) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x (a
forall a. a
errShaderType :: a))) SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String]
ifM) Int
0
tellIf :: RValue -> ExprM ()
tellIf :: String -> ExprM ()
tellIf String
boolStr = StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
T.lift (StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ())
-> StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ()
forall a b. (a -> b) -> a -> b
$ WriterT String (StateT Int IO) ()
-> StateT ExprState (WriterT String (StateT Int IO)) ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
T.lift (WriterT String (StateT Int IO) ()
-> StateT ExprState (WriterT String (StateT Int IO)) ())
-> WriterT String (StateT Int IO) ()
-> StateT ExprState (WriterT String (StateT Int IO)) ()
forall a b. (a -> b) -> a -> b
$ String -> WriterT String (StateT Int IO) ()
forall (m :: * -> *) w. Monad m => w -> WriterT w m ()
tell (String -> WriterT String (StateT Int IO) ())
-> String -> WriterT String (StateT Int IO) ()
forall a b. (a -> b) -> a -> b
$ [String] -> String
forall a. Monoid a => [a] -> a
mconcat [String
"if(", String
boolStr, String
"){\n" ]
while :: forall a x. (ShaderType a x) => (a -> S x Bool) -> (a -> a) -> a -> a
while :: (a -> S x Bool) -> (a -> a) -> a -> a
while a -> S x Bool
c a -> a
f a
i = x -> ShaderBase (ShaderBaseType a) x -> a
forall a x.
ShaderType a x =>
x -> ShaderBase (ShaderBaseType a) x -> a
fromBase x
x (ShaderBase (ShaderBaseType a) x -> a)
-> ShaderBase (ShaderBaseType a) x -> a
forall a b. (a -> b) -> a -> b
$ (ShaderBase (ShaderBaseType a) x -> S x Bool)
-> (ShaderBase (ShaderBaseType a) x
-> ShaderBase (ShaderBaseType a) x)
-> ShaderBase (ShaderBaseType a) x
-> ShaderBase (ShaderBaseType a) x
while_ (a -> S x Bool
c (a -> S x Bool)
-> (ShaderBase (ShaderBaseType a) x -> a)
-> ShaderBase (ShaderBaseType a) x
-> S x Bool
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. x -> ShaderBase (ShaderBaseType a) x -> a
forall a x.
ShaderType a x =>
x -> ShaderBase (ShaderBaseType a) x -> a
fromBase x
x) (x -> a -> ShaderBase (ShaderBaseType a) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x (a -> ShaderBase (ShaderBaseType a) x)
-> (ShaderBase (ShaderBaseType a) x -> a)
-> ShaderBase (ShaderBaseType a) x
-> ShaderBase (ShaderBaseType a) x
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. a -> a
f (a -> a)
-> (ShaderBase (ShaderBaseType a) x -> a)
-> ShaderBase (ShaderBaseType a) x
-> a
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. x -> ShaderBase (ShaderBaseType a) x -> a
forall a x.
ShaderType a x =>
x -> ShaderBase (ShaderBaseType a) x -> a
fromBase x
x) (x -> a -> ShaderBase (ShaderBaseType a) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x a
i)
where
x :: x
x = x
forall a. HasCallStack => a
undefined :: x
while_ :: (ShaderBase (ShaderBaseType a) x -> S x Bool) -> (ShaderBase (ShaderBaseType a) x -> ShaderBase (ShaderBaseType a) x) -> ShaderBase (ShaderBaseType a) x -> ShaderBase (ShaderBaseType a) x
while_ :: (ShaderBase (ShaderBaseType a) x -> S x Bool)
-> (ShaderBase (ShaderBaseType a) x
-> ShaderBase (ShaderBaseType a) x)
-> ShaderBase (ShaderBaseType a) x
-> ShaderBase (ShaderBaseType a) x
while_ ShaderBase (ShaderBaseType a) x -> S x Bool
bool ShaderBase (ShaderBaseType a) x -> ShaderBase (ShaderBaseType a) x
loopF ShaderBase (ShaderBaseType a) x
a =
let whileM :: SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String]
whileM = SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String]
-> SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String]
forall (m :: * -> *) a.
MonadIO m =>
SNMapReaderT a m a -> SNMapReaderT a m a
memoizeM (SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String]
-> SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
-> SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String]
-> SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String]
forall a b. (a -> b) -> a -> b
$ do
(ShaderBase (ShaderBaseType a) x
lifted, [String]
decls) <- WriterT [String] ExprM (ShaderBase (ShaderBaseType a) x)
-> ExprM (ShaderBase (ShaderBaseType a) x, [String])
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
runWriterT (WriterT [String] ExprM (ShaderBase (ShaderBaseType a) x)
-> ExprM (ShaderBase (ShaderBaseType a) x, [String]))
-> WriterT [String] ExprM (ShaderBase (ShaderBaseType a) x)
-> ExprM (ShaderBase (ShaderBaseType a) x, [String])
forall a b. (a -> b) -> a -> b
$ ShaderBase (ShaderBaseType a) x
-> WriterT [String] ExprM (ShaderBase (ShaderBaseType a) x)
forall a x.
ShaderBase a x -> WriterT [String] ExprM (ShaderBase a x)
shaderbaseDeclare (x -> a -> ShaderBase (ShaderBaseType a) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x (a
forall a. a
errShaderType :: a))
ExprM () -> ExprM ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (ExprM () -> ExprM ()) -> ExprM () -> ExprM ()
forall a b. (a -> b) -> a -> b
$ StateT [String] ExprM () -> [String] -> ExprM ()
forall (m :: * -> *) s a. Monad m => StateT s m a -> s -> m a
evalStateT (ShaderBase (ShaderBaseType a) x -> StateT [String] ExprM ()
forall a x. ShaderBase a x -> StateT [String] ExprM ()
shaderbaseAssign ShaderBase (ShaderBaseType a) x
a) [String]
decls
String
boolDecl <- SType -> ExprM String -> ExprM String
tellAssignment SType
STypeBool (S x Bool -> ExprM String
forall x a. S x a -> ExprM String
unS (S x Bool -> ExprM String) -> S x Bool -> ExprM String
forall a b. (a -> b) -> a -> b
$ ShaderBase (ShaderBaseType a) x -> S x Bool
bool ShaderBase (ShaderBaseType a) x
a)
StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
T.lift (StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ())
-> StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ()
forall a b. (a -> b) -> a -> b
$ WriterT String (StateT Int IO) ()
-> StateT ExprState (WriterT String (StateT Int IO)) ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
T.lift (WriterT String (StateT Int IO) ()
-> StateT ExprState (WriterT String (StateT Int IO)) ())
-> WriterT String (StateT Int IO) ()
-> StateT ExprState (WriterT String (StateT Int IO)) ()
forall a b. (a -> b) -> a -> b
$ String -> WriterT String (StateT Int IO) ()
forall (m :: * -> *) w. Monad m => w -> WriterT w m ()
tell (String -> WriterT String (StateT Int IO) ())
-> String -> WriterT String (StateT Int IO) ()
forall a b. (a -> b) -> a -> b
$ [String] -> String
forall a. Monoid a => [a] -> a
mconcat [String
"while(", String
boolDecl, String
"){\n" ]
let looped :: ShaderBase (ShaderBaseType a) x
looped = ShaderBase (ShaderBaseType a) x -> ShaderBase (ShaderBaseType a) x
loopF ShaderBase (ShaderBaseType a) x
lifted
ExprM () -> ExprM ()
forall (m :: * -> *) a x.
MonadIO m =>
SNMapReaderT a m x -> SNMapReaderT a m x
scopedM (ExprM () -> ExprM ()) -> ExprM () -> ExprM ()
forall a b. (a -> b) -> a -> b
$ do
ExprM () -> ExprM ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (ExprM () -> ExprM ()) -> ExprM () -> ExprM ()
forall a b. (a -> b) -> a -> b
$ StateT [String] ExprM () -> [String] -> ExprM ()
forall (m :: * -> *) s a. Monad m => StateT s m a -> s -> m a
evalStateT (ShaderBase (ShaderBaseType a) x -> StateT [String] ExprM ()
forall a x. ShaderBase a x -> StateT [String] ExprM ()
shaderbaseAssign ShaderBase (ShaderBaseType a) x
looped) [String]
decls
String
loopedBoolStr <- S x Bool -> ExprM String
forall x a. S x a -> ExprM String
unS (S x Bool -> ExprM String) -> S x Bool -> ExprM String
forall a b. (a -> b) -> a -> b
$ ShaderBase (ShaderBaseType a) x -> S x Bool
bool ShaderBase (ShaderBaseType a) x
looped
String -> String -> ExprM ()
tellAssignment' String
boolDecl String
loopedBoolStr
StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
T.lift (StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ())
-> StateT ExprState (WriterT String (StateT Int IO)) () -> ExprM ()
forall a b. (a -> b) -> a -> b
$ WriterT String (StateT Int IO) ()
-> StateT ExprState (WriterT String (StateT Int IO)) ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
T.lift (WriterT String (StateT Int IO) ()
-> StateT ExprState (WriterT String (StateT Int IO)) ())
-> WriterT String (StateT Int IO) ()
-> StateT ExprState (WriterT String (StateT Int IO)) ()
forall a b. (a -> b) -> a -> b
$ String -> WriterT String (StateT Int IO) ()
forall (m :: * -> *) w. Monad m => w -> WriterT w m ()
tell String
"}\n"
[String]
-> SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String]
forall (m :: * -> *) a. Monad m => a -> m a
return [String]
decls
in State Int (ShaderBase (ShaderBaseType a) x)
-> Int -> ShaderBase (ShaderBaseType a) x
forall s a. State s a -> s -> a
evalState (ReaderT
(SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
(State Int)
(ShaderBase (ShaderBaseType a) x)
-> SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String]
-> State Int (ShaderBase (ShaderBaseType a) x)
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT (ShaderBase (ShaderBaseType a) x
-> ReaderT
(SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
(State Int)
(ShaderBase (ShaderBaseType a) x)
forall a x.
ShaderBase a x
-> ReaderT
(SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
(State Int)
(ShaderBase a x)
shaderbaseReturn (x -> a -> ShaderBase (ShaderBaseType a) x
forall a x.
ShaderType a x =>
x -> a -> ShaderBase (ShaderBaseType a) x
toBase x
x (a
forall a. a
errShaderType :: a))) SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String]
whileM) Int
0
errShaderType :: a
errShaderType = String -> a
forall a. HasCallStack => String -> a
error String
"toBase in an instance of ShaderType is not lazy enough! Make sure you use tilde (~) for each pattern match on a data constructor."
bin :: SType -> String -> S c x -> S c y -> S c z
bin :: SType -> String -> S c x -> S c y -> S c z
bin SType
typ String
o (S ExprM String
a) (S ExprM String
b) = ExprM String -> S c z
forall x a. ExprM String -> S x a
S (ExprM String -> S c z) -> ExprM String -> S c z
forall a b. (a -> b) -> a -> b
$ SType -> ExprM String -> ExprM String
tellAssignment SType
typ (ExprM String -> ExprM String) -> ExprM String -> ExprM String
forall a b. (a -> b) -> a -> b
$ do String
a' <- ExprM String
a
String
b' <- ExprM String
b
String -> ExprM String
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> ExprM String) -> String -> ExprM String
forall a b. (a -> b) -> a -> b
$ Char
'(' Char -> String -> String
forall a. a -> [a] -> [a]
: String
a' String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
o String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
b' String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
")"
fun1 :: SType -> String -> S c x -> S c y
fun1 :: SType -> String -> S c x -> S c y
fun1 SType
typ String
f (S ExprM String
a) = ExprM String -> S c y
forall x a. ExprM String -> S x a
S (ExprM String -> S c y) -> ExprM String -> S c y
forall a b. (a -> b) -> a -> b
$ SType -> ExprM String -> ExprM String
tellAssignment SType
typ (ExprM String -> ExprM String) -> ExprM String -> ExprM String
forall a b. (a -> b) -> a -> b
$ do String
a' <- ExprM String
a
String -> ExprM String
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> ExprM String) -> String -> ExprM String
forall a b. (a -> b) -> a -> b
$ String
f String -> String -> String
forall a. [a] -> [a] -> [a]
++ Char
'(' Char -> String -> String
forall a. a -> [a] -> [a]
: String
a' String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
")"
fun2 :: SType -> String -> S c x -> S c y -> S c z
fun2 :: SType -> String -> S c x -> S c y -> S c z
fun2 SType
typ String
f (S ExprM String
a) (S ExprM String
b) = ExprM String -> S c z
forall x a. ExprM String -> S x a
S (ExprM String -> S c z) -> ExprM String -> S c z
forall a b. (a -> b) -> a -> b
$ SType -> ExprM String -> ExprM String
tellAssignment SType
typ (ExprM String -> ExprM String) -> ExprM String -> ExprM String
forall a b. (a -> b) -> a -> b
$ do String
a' <- ExprM String
a
String
b' <- ExprM String
b
String -> ExprM String
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> ExprM String) -> String -> ExprM String
forall a b. (a -> b) -> a -> b
$ String
f String -> String -> String
forall a. [a] -> [a] -> [a]
++ Char
'(' Char -> String -> String
forall a. a -> [a] -> [a]
: String
a' String -> String -> String
forall a. [a] -> [a] -> [a]
++ Char
',' Char -> String -> String
forall a. a -> [a] -> [a]
: String
b' String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
")"
fun3 :: SType -> String -> S c x -> S c y -> S c z -> S c w
fun3 :: SType -> String -> S c x -> S c y -> S c z -> S c w
fun3 SType
typ String
f (S ExprM String
a) (S ExprM String
b) (S ExprM String
c) = ExprM String -> S c w
forall x a. ExprM String -> S x a
S (ExprM String -> S c w) -> ExprM String -> S c w
forall a b. (a -> b) -> a -> b
$ SType -> ExprM String -> ExprM String
tellAssignment SType
typ (ExprM String -> ExprM String) -> ExprM String -> ExprM String
forall a b. (a -> b) -> a -> b
$ do String
a' <- ExprM String
a
String
b' <- ExprM String
b
String
c' <- ExprM String
c
String -> ExprM String
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> ExprM String) -> String -> ExprM String
forall a b. (a -> b) -> a -> b
$ String
f String -> String -> String
forall a. [a] -> [a] -> [a]
++ Char
'(' Char -> String -> String
forall a. a -> [a] -> [a]
: String
a' String -> String -> String
forall a. [a] -> [a] -> [a]
++ Char
',' Char -> String -> String
forall a. a -> [a] -> [a]
: String
b' String -> String -> String
forall a. [a] -> [a] -> [a]
++ Char
',' Char -> String -> String
forall a. a -> [a] -> [a]
: String
c' String -> String -> String
forall a. [a] -> [a] -> [a]
++String
")"
fun4 :: SType -> String -> S c x -> S c y -> S c z -> S c w -> S c r
fun4 :: SType -> String -> S c x -> S c y -> S c z -> S c w -> S c r
fun4 SType
typ String
f (S ExprM String
a) (S ExprM String
b) (S ExprM String
c) (S ExprM String
d) = ExprM String -> S c r
forall x a. ExprM String -> S x a
S (ExprM String -> S c r) -> ExprM String -> S c r
forall a b. (a -> b) -> a -> b
$ SType -> ExprM String -> ExprM String
tellAssignment SType
typ (ExprM String -> ExprM String) -> ExprM String -> ExprM String
forall a b. (a -> b) -> a -> b
$ do String
a' <- ExprM String
a
String
b' <- ExprM String
b
String
c' <- ExprM String
c
String
d' <- ExprM String
d
String -> ExprM String
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> ExprM String) -> String -> ExprM String
forall a b. (a -> b) -> a -> b
$ String
f String -> String -> String
forall a. [a] -> [a] -> [a]
++ Char
'(' Char -> String -> String
forall a. a -> [a] -> [a]
: String
a' String -> String -> String
forall a. [a] -> [a] -> [a]
++ Char
',' Char -> String -> String
forall a. a -> [a] -> [a]
: String
b' String -> String -> String
forall a. [a] -> [a] -> [a]
++ Char
',' Char -> String -> String
forall a. a -> [a] -> [a]
: String
c' String -> String -> String
forall a. [a] -> [a] -> [a]
++ Char
',' Char -> String -> String
forall a. a -> [a] -> [a]
: String
d' String -> String -> String
forall a. [a] -> [a] -> [a]
++String
")"
postop :: SType -> String -> S c x -> S c y
postop :: SType -> String -> S c x -> S c y
postop SType
typ String
f (S ExprM String
a) = ExprM String -> S c y
forall x a. ExprM String -> S x a
S (ExprM String -> S c y) -> ExprM String -> S c y
forall a b. (a -> b) -> a -> b
$ SType -> ExprM String -> ExprM String
tellAssignment SType
typ (ExprM String -> ExprM String) -> ExprM String -> ExprM String
forall a b. (a -> b) -> a -> b
$ do String
a' <- ExprM String
a
String -> ExprM String
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> ExprM String) -> String -> ExprM String
forall a b. (a -> b) -> a -> b
$ Char
'(' Char -> String -> String
forall a. a -> [a] -> [a]
: String
a' String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
f String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
")"
preop :: SType -> String -> S c x -> S c y
preop :: SType -> String -> S c x -> S c y
preop SType
typ String
f (S ExprM String
a) = ExprM String -> S c y
forall x a. ExprM String -> S x a
S (ExprM String -> S c y) -> ExprM String -> S c y
forall a b. (a -> b) -> a -> b
$ SType -> ExprM String -> ExprM String
tellAssignment SType
typ (ExprM String -> ExprM String) -> ExprM String -> ExprM String
forall a b. (a -> b) -> a -> b
$ do String
a' <- ExprM String
a
String -> ExprM String
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> ExprM String) -> String -> ExprM String
forall a b. (a -> b) -> a -> b
$ Char
'(' Char -> String -> String
forall a. a -> [a] -> [a]
: String
f String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
a' String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
")"
binf :: String -> S c x -> S c y -> S c Float
binf :: String -> S c x -> S c y -> S c Float
binf = SType -> String -> S c x -> S c y -> S c Float
forall c x y z. SType -> String -> S c x -> S c y -> S c z
bin SType
STypeFloat
fun1f :: String -> S c x -> S c Float
fun1f :: String -> S c x -> S c Float
fun1f = SType -> String -> S c x -> S c Float
forall c x y. SType -> String -> S c x -> S c y
fun1 SType
STypeFloat
fun2f :: String -> S c x -> S c y -> S c Float
fun2f :: String -> S c x -> S c y -> S c Float
fun2f = SType -> String -> S c x -> S c y -> S c Float
forall c x y z. SType -> String -> S c x -> S c y -> S c z
fun2 SType
STypeFloat
fun3f :: String -> S c x -> S c y -> S c z -> S c Float
fun3f :: String -> S c x -> S c y -> S c z -> S c Float
fun3f = SType -> String -> S c x -> S c y -> S c z -> S c Float
forall c x y z w.
SType -> String -> S c x -> S c y -> S c z -> S c w
fun3 SType
STypeFloat
preopf :: String -> S c x -> S c Float
preopf :: String -> S c x -> S c Float
preopf = SType -> String -> S c x -> S c Float
forall c x y. SType -> String -> S c x -> S c y
preop SType
STypeFloat
postopf :: String -> S c x -> S c Float
postopf :: String -> S c x -> S c Float
postopf = SType -> String -> S c x -> S c Float
forall c x y. SType -> String -> S c x -> S c y
postop SType
STypeFloat
bini :: String -> S c x -> S c y -> S c Int
bini :: String -> S c x -> S c y -> S c Int
bini = SType -> String -> S c x -> S c y -> S c Int
forall c x y z. SType -> String -> S c x -> S c y -> S c z
bin SType
STypeInt
fun1i :: String -> S c x -> S c Int
fun1i :: String -> S c x -> S c Int
fun1i = SType -> String -> S c x -> S c Int
forall c x y. SType -> String -> S c x -> S c y
fun1 SType
STypeInt
preopi :: String -> S c x -> S c Int
preopi :: String -> S c x -> S c Int
preopi = SType -> String -> S c x -> S c Int
forall c x y. SType -> String -> S c x -> S c y
preop SType
STypeInt
binu :: String -> S c x -> S c y -> S c Word
binu :: String -> S c x -> S c y -> S c Word
binu = SType -> String -> S c x -> S c y -> S c Word
forall c x y z. SType -> String -> S c x -> S c y -> S c z
bin SType
STypeUInt
fun1u :: String -> S c x -> S c Word
fun1u :: String -> S c x -> S c Word
fun1u = SType -> String -> S c x -> S c Word
forall c x y. SType -> String -> S c x -> S c y
fun1 SType
STypeUInt
preopu :: String -> S c x -> S c Word
preopu :: String -> S c x -> S c Word
preopu = SType -> String -> S c x -> S c Word
forall c x y. SType -> String -> S c x -> S c y
preop SType
STypeUInt
instance Num (S a Float) where
+ :: S a Float -> S a Float -> S a Float
(+) = String -> S a Float -> S a Float -> S a Float
forall c x y. String -> S c x -> S c y -> S c Float
binf String
"+"
(-) = String -> S a Float -> S a Float -> S a Float
forall c x y. String -> S c x -> S c y -> S c Float
binf String
"-"
abs :: S a Float -> S a Float
abs = String -> S a Float -> S a Float
forall c x. String -> S c x -> S c Float
fun1f String
"abs"
signum :: S a Float -> S a Float
signum = String -> S a Float -> S a Float
forall c x. String -> S c x -> S c Float
fun1f String
"sign"
* :: S a Float -> S a Float -> S a Float
(*) = String -> S a Float -> S a Float -> S a Float
forall c x y. String -> S c x -> S c y -> S c Float
binf String
"*"
fromInteger :: Integer -> S a Float
fromInteger = ExprM String -> S a Float
forall x a. ExprM String -> S x a
S (ExprM String -> S a Float)
-> (Integer -> ExprM String) -> Integer -> S a Float
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. String -> ExprM String
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> ExprM String)
-> (Integer -> String) -> Integer -> ExprM String
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Integer -> String
forall a. Show a => a -> String
show
negate :: S a Float -> S a Float
negate = String -> S a Float -> S a Float
forall c x. String -> S c x -> S c Float
preopf String
"-"
instance Num (S a Int) where
+ :: S a Int -> S a Int -> S a Int
(+) = String -> S a Int -> S a Int -> S a Int
forall c x y. String -> S c x -> S c y -> S c Int
bini String
"+"
(-) = String -> S a Int -> S a Int -> S a Int
forall c x y. String -> S c x -> S c y -> S c Int
bini String
"-"
abs :: S a Int -> S a Int
abs = String -> S a Int -> S a Int
forall c x. String -> S c x -> S c Int
fun1i String
"abs"
signum :: S a Int -> S a Int
signum = String -> S a Int -> S a Int
forall c x. String -> S c x -> S c Int
fun1i String
"sign"
* :: S a Int -> S a Int -> S a Int
(*) = String -> S a Int -> S a Int -> S a Int
forall c x y. String -> S c x -> S c y -> S c Int
bini String
"*"
fromInteger :: Integer -> S a Int
fromInteger = ExprM String -> S a Int
forall x a. ExprM String -> S x a
S (ExprM String -> S a Int)
-> (Integer -> ExprM String) -> Integer -> S a Int
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. String -> ExprM String
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> ExprM String)
-> (Integer -> String) -> Integer -> ExprM String
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Integer -> String
forall a. Show a => a -> String
show
negate :: S a Int -> S a Int
negate = String -> S a Int -> S a Int
forall c x. String -> S c x -> S c Int
preopi String
"-"
instance Num (S a Word) where
+ :: S a Word -> S a Word -> S a Word
(+) = String -> S a Word -> S a Word -> S a Word
forall c x y. String -> S c x -> S c y -> S c Word
binu String
"+"
(-) = String -> S a Word -> S a Word -> S a Word
forall c x y. String -> S c x -> S c y -> S c Word
binu String
"-"
abs :: S a Word -> S a Word
abs = String -> S a Word -> S a Word
forall c x. String -> S c x -> S c Word
fun1u String
"abs"
signum :: S a Word -> S a Word
signum = String -> S a Word -> S a Word
forall c x. String -> S c x -> S c Word
fun1u String
"sign"
* :: S a Word -> S a Word -> S a Word
(*) = String -> S a Word -> S a Word -> S a Word
forall c x y. String -> S c x -> S c y -> S c Word
binu String
"*"
fromInteger :: Integer -> S a Word
fromInteger Integer
x = ExprM String -> S a Word
forall x a. ExprM String -> S x a
S (ExprM String -> S a Word) -> ExprM String -> S a Word
forall a b. (a -> b) -> a -> b
$ String -> ExprM String
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> ExprM String) -> String -> ExprM String
forall a b. (a -> b) -> a -> b
$ Integer -> String
forall a. Show a => a -> String
show Integer
x String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"u"
negate :: S a Word -> S a Word
negate = String -> S a Word -> S a Word
forall c x. String -> S c x -> S c Word
preopu String
"-"
instance Fractional (S a Float) where
/ :: S a Float -> S a Float -> S a Float
(/) = String -> S a Float -> S a Float -> S a Float
forall c x y. String -> S c x -> S c y -> S c Float
binf String
"/"
fromRational :: Rational -> S a Float
fromRational = ExprM String -> S a Float
forall x a. ExprM String -> S x a
S (ExprM String -> S a Float)
-> (Rational -> ExprM String) -> Rational -> S a Float
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. String -> ExprM String
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> ExprM String)
-> (Rational -> String) -> Rational -> ExprM String
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (String
"float(" String -> String -> String
forall a. [a] -> [a] -> [a]
++) (String -> String) -> (Rational -> String) -> Rational -> String
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
")") (String -> String) -> (Rational -> String) -> Rational -> String
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Float -> String
forall a. Show a => a -> String
show (Float -> String) -> (Rational -> Float) -> Rational -> String
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (Float -> Float -> Float
forall a. a -> a -> a
`asTypeOf` (Float
forall a. HasCallStack => a
undefined :: Float)) (Float -> Float) -> (Rational -> Float) -> Rational -> Float
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Rational -> Float
forall a. Fractional a => Rational -> a
fromRational
class Integral' a where
div' :: a -> a -> a
mod' :: a -> a -> a
instance Integral' Int where
div' :: Int -> Int -> Int
div' = Int -> Int -> Int
forall a. Integral a => a -> a -> a
div
mod' :: Int -> Int -> Int
mod' = Int -> Int -> Int
forall a. Integral a => a -> a -> a
mod
instance Integral' Int32 where
div' :: Int32 -> Int32 -> Int32
div' = Int32 -> Int32 -> Int32
forall a. Integral a => a -> a -> a
div
mod' :: Int32 -> Int32 -> Int32
mod' = Int32 -> Int32 -> Int32
forall a. Integral a => a -> a -> a
mod
instance Integral' Int16 where
div' :: Int16 -> Int16 -> Int16
div' = Int16 -> Int16 -> Int16
forall a. Integral a => a -> a -> a
div
mod' :: Int16 -> Int16 -> Int16
mod' = Int16 -> Int16 -> Int16
forall a. Integral a => a -> a -> a
mod
instance Integral' Int8 where
div' :: Int8 -> Int8 -> Int8
div' = Int8 -> Int8 -> Int8
forall a. Integral a => a -> a -> a
div
mod' :: Int8 -> Int8 -> Int8
mod' = Int8 -> Int8 -> Int8
forall a. Integral a => a -> a -> a
mod
instance Integral' Word where
div' :: Word -> Word -> Word
div' = Word -> Word -> Word
forall a. Integral a => a -> a -> a
div
mod' :: Word -> Word -> Word
mod' = Word -> Word -> Word
forall a. Integral a => a -> a -> a
mod
instance Integral' Word32 where
div' :: Word32 -> Word32 -> Word32
div' = Word32 -> Word32 -> Word32
forall a. Integral a => a -> a -> a
div
mod' :: Word32 -> Word32 -> Word32
mod' = Word32 -> Word32 -> Word32
forall a. Integral a => a -> a -> a
mod
instance Integral' Word16 where
div' :: Word16 -> Word16 -> Word16
div' = Word16 -> Word16 -> Word16
forall a. Integral a => a -> a -> a
div
mod' :: Word16 -> Word16 -> Word16
mod' = Word16 -> Word16 -> Word16
forall a. Integral a => a -> a -> a
mod
instance Integral' Word8 where
div' :: Word8 -> Word8 -> Word8
div' = Word8 -> Word8 -> Word8
forall a. Integral a => a -> a -> a
div
mod' :: Word8 -> Word8 -> Word8
mod' = Word8 -> Word8 -> Word8
forall a. Integral a => a -> a -> a
mod
instance Integral' (S a Int) where
div' :: S a Int -> S a Int -> S a Int
div' = String -> S a Int -> S a Int -> S a Int
forall c x y. String -> S c x -> S c y -> S c Int
bini String
"/"
mod' :: S a Int -> S a Int -> S a Int
mod' = String -> S a Int -> S a Int -> S a Int
forall c x y. String -> S c x -> S c y -> S c Int
bini String
"%"
instance Integral' (S a Word) where
div' :: S a Word -> S a Word -> S a Word
div' = String -> S a Word -> S a Word -> S a Word
forall c x y. String -> S c x -> S c y -> S c Word
binu String
"/"
mod' :: S a Word -> S a Word -> S a Word
mod' = String -> S a Word -> S a Word -> S a Word
forall c x y. String -> S c x -> S c y -> S c Word
binu String
"%"
instance Integral' a => Integral' (V0 a) where
div' :: V0 a -> V0 a -> V0 a
div' = (a -> a -> a) -> V0 a -> V0 a -> V0 a
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> a
forall a. Integral' a => a -> a -> a
div'
mod' :: V0 a -> V0 a -> V0 a
mod' = (a -> a -> a) -> V0 a -> V0 a -> V0 a
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> a
forall a. Integral' a => a -> a -> a
mod'
instance Integral' a => Integral' (V1 a) where
div' :: V1 a -> V1 a -> V1 a
div' = (a -> a -> a) -> V1 a -> V1 a -> V1 a
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> a
forall a. Integral' a => a -> a -> a
div'
mod' :: V1 a -> V1 a -> V1 a
mod' = (a -> a -> a) -> V1 a -> V1 a -> V1 a
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> a
forall a. Integral' a => a -> a -> a
mod'
instance Integral' a => Integral' (V2 a) where
div' :: V2 a -> V2 a -> V2 a
div' = (a -> a -> a) -> V2 a -> V2 a -> V2 a
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> a
forall a. Integral' a => a -> a -> a
div'
mod' :: V2 a -> V2 a -> V2 a
mod' = (a -> a -> a) -> V2 a -> V2 a -> V2 a
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> a
forall a. Integral' a => a -> a -> a
mod'
instance Integral' a => Integral' (V3 a) where
div' :: V3 a -> V3 a -> V3 a
div' = (a -> a -> a) -> V3 a -> V3 a -> V3 a
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> a
forall a. Integral' a => a -> a -> a
div'
mod' :: V3 a -> V3 a -> V3 a
mod' = (a -> a -> a) -> V3 a -> V3 a -> V3 a
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> a
forall a. Integral' a => a -> a -> a
mod'
instance Integral' a => Integral' (V4 a) where
div' :: V4 a -> V4 a -> V4 a
div' = (a -> a -> a) -> V4 a -> V4 a -> V4 a
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> a
forall a. Integral' a => a -> a -> a
div'
mod' :: V4 a -> V4 a -> V4 a
mod' = (a -> a -> a) -> V4 a -> V4 a -> V4 a
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> a
forall a. Integral' a => a -> a -> a
mod'
class Bits' a where
and' :: a -> a -> a
or' :: a -> a -> a
xor' :: a -> a -> a
complement' :: a -> a
shiftL' :: a -> a -> a
shiftR' :: a -> a -> a
bitSize' :: a -> Int
instance Bits' (S a Int) where
and' :: S a Int -> S a Int -> S a Int
and' = String -> S a Int -> S a Int -> S a Int
forall c x y. String -> S c x -> S c y -> S c Int
bini String
"&"
or' :: S a Int -> S a Int -> S a Int
or' = String -> S a Int -> S a Int -> S a Int
forall c x y. String -> S c x -> S c y -> S c Int
bini String
"|"
xor' :: S a Int -> S a Int -> S a Int
xor' = String -> S a Int -> S a Int -> S a Int
forall c x y. String -> S c x -> S c y -> S c Int
bini String
"^"
complement' :: S a Int -> S a Int
complement' = String -> S a Int -> S a Int
forall c x. String -> S c x -> S c Int
fun1i String
"~"
shiftL' :: S a Int -> S a Int -> S a Int
shiftL' = String -> S a Int -> S a Int -> S a Int
forall c x y. String -> S c x -> S c y -> S c Int
bini String
"<<"
shiftR' :: S a Int -> S a Int -> S a Int
shiftR' = String -> S a Int -> S a Int -> S a Int
forall c x y. String -> S c x -> S c y -> S c Int
bini String
">>"
bitSize' :: S a Int -> Int
bitSize' = Int -> S a Int -> Int
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int -> Int
forall b. FiniteBits b => b -> Int
finiteBitSize (Int
forall a. HasCallStack => a
undefined :: Int))
instance Bits' (S a Word) where
and' :: S a Word -> S a Word -> S a Word
and' = String -> S a Word -> S a Word -> S a Word
forall c x y. String -> S c x -> S c y -> S c Word
binu String
"&"
or' :: S a Word -> S a Word -> S a Word
or' = String -> S a Word -> S a Word -> S a Word
forall c x y. String -> S c x -> S c y -> S c Word
binu String
"|"
xor' :: S a Word -> S a Word -> S a Word
xor' = String -> S a Word -> S a Word -> S a Word
forall c x y. String -> S c x -> S c y -> S c Word
binu String
"^"
complement' :: S a Word -> S a Word
complement' = String -> S a Word -> S a Word
forall c x. String -> S c x -> S c Word
fun1u String
"~"
shiftL' :: S a Word -> S a Word -> S a Word
shiftL' = String -> S a Word -> S a Word -> S a Word
forall c x y. String -> S c x -> S c y -> S c Word
binu String
"<<"
shiftR' :: S a Word -> S a Word -> S a Word
shiftR' = String -> S a Word -> S a Word -> S a Word
forall c x y. String -> S c x -> S c y -> S c Word
binu String
">>"
bitSize' :: S a Word -> Int
bitSize' = Int -> S a Word -> Int
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Word -> Int
forall b. FiniteBits b => b -> Int
finiteBitSize (Word
forall a. HasCallStack => a
undefined :: Word))
instance Floating (S a Float) where
pi :: S a Float
pi = ExprM String -> S a Float
forall x a. ExprM String -> S x a
S (ExprM String -> S a Float) -> ExprM String -> S a Float
forall a b. (a -> b) -> a -> b
$ String -> ExprM String
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> ExprM String) -> String -> ExprM String
forall a b. (a -> b) -> a -> b
$ Float -> String
forall a. Show a => a -> String
show (Float
forall a. Floating a => a
pi :: Float)
sqrt :: S a Float -> S a Float
sqrt = String -> S a Float -> S a Float
forall c x. String -> S c x -> S c Float
fun1f String
"sqrt"
exp :: S a Float -> S a Float
exp = String -> S a Float -> S a Float
forall c x. String -> S c x -> S c Float
fun1f String
"exp"
log :: S a Float -> S a Float
log = String -> S a Float -> S a Float
forall c x. String -> S c x -> S c Float
fun1f String
"log"
** :: S a Float -> S a Float -> S a Float
(**) = String -> S a Float -> S a Float -> S a Float
forall c x y. String -> S c x -> S c y -> S c Float
fun2f String
"pow"
sin :: S a Float -> S a Float
sin = String -> S a Float -> S a Float
forall c x. String -> S c x -> S c Float
fun1f String
"sin"
cos :: S a Float -> S a Float
cos = String -> S a Float -> S a Float
forall c x. String -> S c x -> S c Float
fun1f String
"cos"
tan :: S a Float -> S a Float
tan = String -> S a Float -> S a Float
forall c x. String -> S c x -> S c Float
fun1f String
"tan"
asin :: S a Float -> S a Float
asin = String -> S a Float -> S a Float
forall c x. String -> S c x -> S c Float
fun1f String
"asin"
acos :: S a Float -> S a Float
acos = String -> S a Float -> S a Float
forall c x. String -> S c x -> S c Float
fun1f String
"acos"
atan :: S a Float -> S a Float
atan = String -> S a Float -> S a Float
forall c x. String -> S c x -> S c Float
fun1f String
"atan"
sinh :: S a Float -> S a Float
sinh = String -> S a Float -> S a Float
forall c x. String -> S c x -> S c Float
fun1f String
"sinh"
cosh :: S a Float -> S a Float
cosh = String -> S a Float -> S a Float
forall c x. String -> S c x -> S c Float
fun1f String
"cosh"
asinh :: S a Float -> S a Float
asinh = String -> S a Float -> S a Float
forall c x. String -> S c x -> S c Float
fun1f String
"asinh"
atanh :: S a Float -> S a Float
atanh = String -> S a Float -> S a Float
forall c x. String -> S c x -> S c Float
fun1f String
"atanh"
acosh :: S a Float -> S a Float
acosh = String -> S a Float -> S a Float
forall c x. String -> S c x -> S c Float
fun1f String
"acosh"
instance Boolean (S a Bool) where
true :: S a Bool
true = ExprM String -> S a Bool
forall x a. ExprM String -> S x a
S (ExprM String -> S a Bool) -> ExprM String -> S a Bool
forall a b. (a -> b) -> a -> b
$ String -> ExprM String
forall (m :: * -> *) a. Monad m => a -> m a
return String
"true"
false :: S a Bool
false = ExprM String -> S a Bool
forall x a. ExprM String -> S x a
S (ExprM String -> S a Bool) -> ExprM String -> S a Bool
forall a b. (a -> b) -> a -> b
$ String -> ExprM String
forall (m :: * -> *) a. Monad m => a -> m a
return String
"false"
notB :: S a Bool -> S a Bool
notB = SType -> String -> S a Bool -> S a Bool
forall c x y. SType -> String -> S c x -> S c y
preop SType
STypeBool String
"!"
&&* :: S a Bool -> S a Bool -> S a Bool
(&&*) = SType -> String -> S a Bool -> S a Bool -> S a Bool
forall c x y z. SType -> String -> S c x -> S c y -> S c z
bin SType
STypeBool String
"&&"
||* :: S a Bool -> S a Bool -> S a Bool
(||*) = SType -> String -> S a Bool -> S a Bool -> S a Bool
forall c x y z. SType -> String -> S c x -> S c y -> S c z
bin SType
STypeBool String
"||"
type instance BooleanOf (S a x) = S a Bool
instance Eq x => EqB (S a x) where
==* :: S a x -> S a x -> bool
(==*) = SType -> String -> S a x -> S a x -> S a Bool
forall c x y z. SType -> String -> S c x -> S c y -> S c z
bin SType
STypeBool String
"=="
/=* :: S a x -> S a x -> bool
(/=*) = SType -> String -> S a x -> S a x -> S a Bool
forall c x y z. SType -> String -> S c x -> S c y -> S c z
bin SType
STypeBool String
"!="
instance Ord x => OrdB (S a x) where
<* :: S a x -> S a x -> bool
(<*) = SType -> String -> S a x -> S a x -> S a Bool
forall c x y z. SType -> String -> S c x -> S c y -> S c z
bin SType
STypeBool String
"<"
<=* :: S a x -> S a x -> bool
(<=*) = SType -> String -> S a x -> S a x -> S a Bool
forall c x y z. SType -> String -> S c x -> S c y -> S c z
bin SType
STypeBool String
"<="
>=* :: S a x -> S a x -> bool
(>=*) = SType -> String -> S a x -> S a x -> S a Bool
forall c x y z. SType -> String -> S c x -> S c y -> S c z
bin SType
STypeBool String
">="
>* :: S a x -> S a x -> bool
(>*) = SType -> String -> S a x -> S a x -> S a Bool
forall c x y z. SType -> String -> S c x -> S c y -> S c z
bin SType
STypeBool String
">"
instance IfB (S a Float) where ifB :: bool -> S a Float -> S a Float -> S a Float
ifB = bool -> S a Float -> S a Float -> S a Float
forall a x. ShaderType a x => S x Bool -> a -> a -> a
ifThenElse'
instance IfB (S a Int) where ifB :: bool -> S a Int -> S a Int -> S a Int
ifB = bool -> S a Int -> S a Int -> S a Int
forall a x. ShaderType a x => S x Bool -> a -> a -> a
ifThenElse'
instance IfB (S a Word) where ifB :: bool -> S a Word -> S a Word -> S a Word
ifB = bool -> S a Word -> S a Word -> S a Word
forall a x. ShaderType a x => S x Bool -> a -> a -> a
ifThenElse'
instance IfB (S a Bool) where ifB :: bool -> S a Bool -> S a Bool -> S a Bool
ifB = bool -> S a Bool -> S a Bool -> S a Bool
forall a x. ShaderType a x => S x Bool -> a -> a -> a
ifThenElse'
instance IfB (S a (GenerativeGeometry p b)) where ifB :: bool
-> S a (GenerativeGeometry p b)
-> S a (GenerativeGeometry p b)
-> S a (GenerativeGeometry p b)
ifB = bool
-> S a (GenerativeGeometry p b)
-> S a (GenerativeGeometry p b)
-> S a (GenerativeGeometry p b)
forall a x. ShaderType a x => S x Bool -> a -> a -> a
ifThenElse'
instance Conjugate (S a Float)
instance Conjugate (S a Int)
instance Conjugate (S a Word)
instance TrivialConjugate (S a Float)
instance TrivialConjugate (S a Int)
instance TrivialConjugate (S a Word)
class Floating a => Real' a where
rsqrt :: a -> a
exp2 :: a -> a
log2 :: a -> a
floor' :: a -> a
ceiling' :: a -> a
fract' :: a -> a
mod'' :: a -> a -> a
mix :: a -> a -> a-> a
atan2' :: a -> a -> a
rsqrt = (a
1a -> a -> a
forall a. Fractional a => a -> a -> a
/) (a -> a) -> (a -> a) -> a -> a
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. a -> a
forall a. Floating a => a -> a
sqrt
exp2 = (a
2a -> a -> a
forall a. Floating a => a -> a -> a
**)
log2 = a -> a -> a
forall a. Floating a => a -> a -> a
logBase a
2
mix a
x a
y a
a = a
xa -> a -> a
forall a. Num a => a -> a -> a
*(a
1a -> a -> a
forall a. Num a => a -> a -> a
-a
a)a -> a -> a
forall a. Num a => a -> a -> a
+a
ya -> a -> a
forall a. Num a => a -> a -> a
*a
a
fract' a
x = a
x a -> a -> a
forall a. Num a => a -> a -> a
- a -> a
forall a. Real' a => a -> a
floor' a
x
mod'' a
x a
y = a
x a -> a -> a
forall a. Num a => a -> a -> a
- a
ya -> a -> a
forall a. Num a => a -> a -> a
* a -> a
forall a. Real' a => a -> a
floor' (a
xa -> a -> a
forall a. Fractional a => a -> a -> a
/a
y)
floor' a
x = -a -> a
forall a. Real' a => a -> a
ceiling' (-a
x)
ceiling' a
x = -a -> a
forall a. Real' a => a -> a
floor' (-a
x)
{-# MINIMAL (floor' | ceiling') , atan2' #-}
instance Real' Float where
floor' :: Float -> Float
floor' = Integer -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Float) -> (Float -> Integer) -> Float -> Float
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Float -> Integer
forall a b. (RealFrac a, Integral b) => a -> b
floor
ceiling' :: Float -> Float
ceiling' = Integer -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Float) -> (Float -> Integer) -> Float -> Float
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Float -> Integer
forall a b. (RealFrac a, Integral b) => a -> b
ceiling
atan2' :: Float -> Float -> Float
atan2' = Float -> Float -> Float
forall a. RealFloat a => a -> a -> a
atan2
instance Real' Double where
floor' :: Double -> Double
floor' = Integer -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Double) -> (Double -> Integer) -> Double -> Double
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Double -> Integer
forall a b. (RealFrac a, Integral b) => a -> b
floor
ceiling' :: Double -> Double
ceiling' = Integer -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Double) -> (Double -> Integer) -> Double -> Double
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Double -> Integer
forall a b. (RealFrac a, Integral b) => a -> b
ceiling
atan2' :: Double -> Double -> Double
atan2' = Double -> Double -> Double
forall a. RealFloat a => a -> a -> a
atan2
instance Real' (S x Float) where
rsqrt :: S x Float -> S x Float
rsqrt = String -> S x Float -> S x Float
forall c x. String -> S c x -> S c Float
fun1f String
"inversesqrt"
exp2 :: S x Float -> S x Float
exp2 = String -> S x Float -> S x Float
forall c x. String -> S c x -> S c Float
fun1f String
"exp2"
log2 :: S x Float -> S x Float
log2 = String -> S x Float -> S x Float
forall c x. String -> S c x -> S c Float
fun1f String
"log2"
floor' :: S x Float -> S x Float
floor' = String -> S x Float -> S x Float
forall c x. String -> S c x -> S c Float
fun1f String
"floor"
ceiling' :: S x Float -> S x Float
ceiling' = String -> S x Float -> S x Float
forall c x. String -> S c x -> S c Float
fun1f String
"ceil"
fract' :: S x Float -> S x Float
fract' = String -> S x Float -> S x Float
forall c x. String -> S c x -> S c Float
fun1f String
"fract"
mod'' :: S x Float -> S x Float -> S x Float
mod'' = String -> S x Float -> S x Float -> S x Float
forall c x y. String -> S c x -> S c y -> S c Float
fun2f String
"mod"
mix :: S x Float -> S x Float -> S x Float -> S x Float
mix = String -> S x Float -> S x Float -> S x Float -> S x Float
forall c x y z. String -> S c x -> S c y -> S c z -> S c Float
fun3f String
"mix"
atan2' :: S x Float -> S x Float -> S x Float
atan2' = String -> S x Float -> S x Float -> S x Float
forall c x y. String -> S c x -> S c y -> S c Float
fun2f String
"atan"
instance (Real' a) => Real' (V0 a) where
rsqrt :: V0 a -> V0 a
rsqrt = (a -> a) -> V0 a -> V0 a
forall (f :: * -> *) a b. Applicative f => (a -> b) -> f a -> f b
liftA a -> a
forall a. Real' a => a -> a
rsqrt
exp2 :: V0 a -> V0 a
exp2 = (a -> a) -> V0 a -> V0 a
forall (f :: * -> *) a b. Applicative f => (a -> b) -> f a -> f b
liftA a -> a
forall a. Real' a => a -> a
exp2
log2 :: V0 a -> V0 a
log2 = (a -> a) -> V0 a -> V0 a
forall (f :: * -> *) a b. Applicative f => (a -> b) -> f a -> f b
liftA a -> a
forall a. Real' a => a -> a
log2
floor' :: V0 a -> V0 a
floor' = (a -> a) -> V0 a -> V0 a
forall (f :: * -> *) a b. Applicative f => (a -> b) -> f a -> f b
liftA a -> a
forall a. Real' a => a -> a
floor'
ceiling' :: V0 a -> V0 a
ceiling' = (a -> a) -> V0 a -> V0 a
forall (f :: * -> *) a b. Applicative f => (a -> b) -> f a -> f b
liftA a -> a
forall a. Real' a => a -> a
ceiling'
fract' :: V0 a -> V0 a
fract' = (a -> a) -> V0 a -> V0 a
forall (f :: * -> *) a b. Applicative f => (a -> b) -> f a -> f b
liftA a -> a
forall a. Real' a => a -> a
fract'
mod'' :: V0 a -> V0 a -> V0 a
mod'' = (a -> a -> a) -> V0 a -> V0 a -> V0 a
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> a
forall a. Real' a => a -> a -> a
mod''
mix :: V0 a -> V0 a -> V0 a -> V0 a
mix = (a -> a -> a -> a) -> V0 a -> V0 a -> V0 a -> V0 a
forall (f :: * -> *) a b c d.
Applicative f =>
(a -> b -> c -> d) -> f a -> f b -> f c -> f d
liftA3 a -> a -> a -> a
forall a. Real' a => a -> a -> a -> a
mix
atan2' :: V0 a -> V0 a -> V0 a
atan2' = (a -> a -> a) -> V0 a -> V0 a -> V0 a
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> a
forall a. Real' a => a -> a -> a
atan2'
instance (Real' a) => Real' (V1 a) where
rsqrt :: V1 a -> V1 a
rsqrt = (a -> a) -> V1 a -> V1 a
forall (f :: * -> *) a b. Applicative f => (a -> b) -> f a -> f b
liftA a -> a
forall a. Real' a => a -> a
rsqrt
exp2 :: V1 a -> V1 a
exp2 = (a -> a) -> V1 a -> V1 a
forall (f :: * -> *) a b. Applicative f => (a -> b) -> f a -> f b
liftA a -> a
forall a. Real' a => a -> a
exp2
log2 :: V1 a -> V1 a
log2 = (a -> a) -> V1 a -> V1 a
forall (f :: * -> *) a b. Applicative f => (a -> b) -> f a -> f b
liftA a -> a
forall a. Real' a => a -> a
log2
floor' :: V1 a -> V1 a
floor' = (a -> a) -> V1 a -> V1 a
forall (f :: * -> *) a b. Applicative f => (a -> b) -> f a -> f b
liftA a -> a
forall a. Real' a => a -> a
floor'
ceiling' :: V1 a -> V1 a
ceiling' = (a -> a) -> V1 a -> V1 a
forall (f :: * -> *) a b. Applicative f => (a -> b) -> f a -> f b
liftA a -> a
forall a. Real' a => a -> a
ceiling'
fract' :: V1 a -> V1 a
fract' = (a -> a) -> V1 a -> V1 a
forall (f :: * -> *) a b. Applicative f => (a -> b) -> f a -> f b
liftA a -> a
forall a. Real' a => a -> a
fract'
mod'' :: V1 a -> V1 a -> V1 a
mod'' = (a -> a -> a) -> V1 a -> V1 a -> V1 a
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> a
forall a. Real' a => a -> a -> a
mod''
mix :: V1 a -> V1 a -> V1 a -> V1 a
mix = (a -> a -> a -> a) -> V1 a -> V1 a -> V1 a -> V1 a
forall (f :: * -> *) a b c d.
Applicative f =>
(a -> b -> c -> d) -> f a -> f b -> f c -> f d
liftA3 a -> a -> a -> a
forall a. Real' a => a -> a -> a -> a
mix
atan2' :: V1 a -> V1 a -> V1 a
atan2' = (a -> a -> a) -> V1 a -> V1 a -> V1 a
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> a
forall a. Real' a => a -> a -> a
atan2'
instance (Real' a) => Real' (V2 a) where
rsqrt :: V2 a -> V2 a
rsqrt = (a -> a) -> V2 a -> V2 a
forall (f :: * -> *) a b. Applicative f => (a -> b) -> f a -> f b
liftA a -> a
forall a. Real' a => a -> a
rsqrt
exp2 :: V2 a -> V2 a
exp2 = (a -> a) -> V2 a -> V2 a
forall (f :: * -> *) a b. Applicative f => (a -> b) -> f a -> f b
liftA a -> a
forall a. Real' a => a -> a
exp2
log2 :: V2 a -> V2 a
log2 = (a -> a) -> V2 a -> V2 a
forall (f :: * -> *) a b. Applicative f => (a -> b) -> f a -> f b
liftA a -> a
forall a. Real' a => a -> a
log2
floor' :: V2 a -> V2 a
floor' = (a -> a) -> V2 a -> V2 a
forall (f :: * -> *) a b. Applicative f => (a -> b) -> f a -> f b
liftA a -> a
forall a. Real' a => a -> a
floor'
ceiling' :: V2 a -> V2 a
ceiling' = (a -> a) -> V2 a -> V2 a
forall (f :: * -> *) a b. Applicative f => (a -> b) -> f a -> f b
liftA a -> a
forall a. Real' a => a -> a
ceiling'
fract' :: V2 a -> V2 a
fract' = (a -> a) -> V2 a -> V2 a
forall (f :: * -> *) a b. Applicative f => (a -> b) -> f a -> f b
liftA a -> a
forall a. Real' a => a -> a
fract'
mod'' :: V2 a -> V2 a -> V2 a
mod'' = (a -> a -> a) -> V2 a -> V2 a -> V2 a
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> a
forall a. Real' a => a -> a -> a
mod''
mix :: V2 a -> V2 a -> V2 a -> V2 a
mix = (a -> a -> a -> a) -> V2 a -> V2 a -> V2 a -> V2 a
forall (f :: * -> *) a b c d.
Applicative f =>
(a -> b -> c -> d) -> f a -> f b -> f c -> f d
liftA3 a -> a -> a -> a
forall a. Real' a => a -> a -> a -> a
mix
atan2' :: V2 a -> V2 a -> V2 a
atan2' = (a -> a -> a) -> V2 a -> V2 a -> V2 a
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> a
forall a. Real' a => a -> a -> a
atan2'
instance (Real' a) => Real' (V3 a) where
rsqrt :: V3 a -> V3 a
rsqrt = (a -> a) -> V3 a -> V3 a
forall (f :: * -> *) a b. Applicative f => (a -> b) -> f a -> f b
liftA a -> a
forall a. Real' a => a -> a
rsqrt
exp2 :: V3 a -> V3 a
exp2 = (a -> a) -> V3 a -> V3 a
forall (f :: * -> *) a b. Applicative f => (a -> b) -> f a -> f b
liftA a -> a
forall a. Real' a => a -> a
exp2
log2 :: V3 a -> V3 a
log2 = (a -> a) -> V3 a -> V3 a
forall (f :: * -> *) a b. Applicative f => (a -> b) -> f a -> f b
liftA a -> a
forall a. Real' a => a -> a
log2
floor' :: V3 a -> V3 a
floor' = (a -> a) -> V3 a -> V3 a
forall (f :: * -> *) a b. Applicative f => (a -> b) -> f a -> f b
liftA a -> a
forall a. Real' a => a -> a
floor'
ceiling' :: V3 a -> V3 a
ceiling' = (a -> a) -> V3 a -> V3 a
forall (f :: * -> *) a b. Applicative f => (a -> b) -> f a -> f b
liftA a -> a
forall a. Real' a => a -> a
ceiling'
fract' :: V3 a -> V3 a
fract' = (a -> a) -> V3 a -> V3 a
forall (f :: * -> *) a b. Applicative f => (a -> b) -> f a -> f b
liftA a -> a
forall a. Real' a => a -> a
fract'
mod'' :: V3 a -> V3 a -> V3 a
mod'' = (a -> a -> a) -> V3 a -> V3 a -> V3 a
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> a
forall a. Real' a => a -> a -> a
mod''
mix :: V3 a -> V3 a -> V3 a -> V3 a
mix = (a -> a -> a -> a) -> V3 a -> V3 a -> V3 a -> V3 a
forall (f :: * -> *) a b c d.
Applicative f =>
(a -> b -> c -> d) -> f a -> f b -> f c -> f d
liftA3 a -> a -> a -> a
forall a. Real' a => a -> a -> a -> a
mix
atan2' :: V3 a -> V3 a -> V3 a
atan2' = (a -> a -> a) -> V3 a -> V3 a -> V3 a
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> a
forall a. Real' a => a -> a -> a
atan2'
instance (Real' a) => Real' (V4 a) where
rsqrt :: V4 a -> V4 a
rsqrt = (a -> a) -> V4 a -> V4 a
forall (f :: * -> *) a b. Applicative f => (a -> b) -> f a -> f b
liftA a -> a
forall a. Real' a => a -> a
rsqrt
exp2 :: V4 a -> V4 a
exp2 = (a -> a) -> V4 a -> V4 a
forall (f :: * -> *) a b. Applicative f => (a -> b) -> f a -> f b
liftA a -> a
forall a. Real' a => a -> a
exp2
log2 :: V4 a -> V4 a
log2 = (a -> a) -> V4 a -> V4 a
forall (f :: * -> *) a b. Applicative f => (a -> b) -> f a -> f b
liftA a -> a
forall a. Real' a => a -> a
log2
floor' :: V4 a -> V4 a
floor' = (a -> a) -> V4 a -> V4 a
forall (f :: * -> *) a b. Applicative f => (a -> b) -> f a -> f b
liftA a -> a
forall a. Real' a => a -> a
floor'
ceiling' :: V4 a -> V4 a
ceiling' = (a -> a) -> V4 a -> V4 a
forall (f :: * -> *) a b. Applicative f => (a -> b) -> f a -> f b
liftA a -> a
forall a. Real' a => a -> a
ceiling'
fract' :: V4 a -> V4 a
fract' = (a -> a) -> V4 a -> V4 a
forall (f :: * -> *) a b. Applicative f => (a -> b) -> f a -> f b
liftA a -> a
forall a. Real' a => a -> a
fract'
mod'' :: V4 a -> V4 a -> V4 a
mod'' = (a -> a -> a) -> V4 a -> V4 a -> V4 a
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> a
forall a. Real' a => a -> a -> a
mod''
mix :: V4 a -> V4 a -> V4 a -> V4 a
mix = (a -> a -> a -> a) -> V4 a -> V4 a -> V4 a -> V4 a
forall (f :: * -> *) a b c d.
Applicative f =>
(a -> b -> c -> d) -> f a -> f b -> f c -> f d
liftA3 a -> a -> a -> a
forall a. Real' a => a -> a -> a -> a
mix
atan2' :: V4 a -> V4 a -> V4 a
atan2' = (a -> a -> a) -> V4 a -> V4 a -> V4 a
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> a
forall a. Real' a => a -> a -> a
atan2'
class (IfB a, OrdB a, Floating a) => FloatingOrd a where
clamp :: a -> a -> a -> a
saturate :: a -> a
step :: a -> a -> a
smoothstep :: a -> a -> a -> a
clamp a
x a
a = a -> a -> a
forall a. (IfB a, OrdB a) => a -> a -> a
minB (a -> a -> a
forall a. (IfB a, OrdB a) => a -> a -> a
maxB a
x a
a)
saturate a
x = a -> a -> a -> a
forall a. FloatingOrd a => a -> a -> a -> a
clamp a
x a
0 a
1
step a
a a
x = BooleanOf a -> a -> a -> a
forall a bool. (IfB a, bool ~ BooleanOf a) => bool -> a -> a -> a
ifB (a
x a -> a -> BooleanOf a
forall a bool. (OrdB a, bool ~ BooleanOf a) => a -> a -> bool
<* a
a) a
0 a
1
smoothstep a
a a
b a
x = let t :: a
t = a -> a
forall a. FloatingOrd a => a -> a
saturate ((a
xa -> a -> a
forall a. Num a => a -> a -> a
-a
a) a -> a -> a
forall a. Fractional a => a -> a -> a
/ (a
ba -> a -> a
forall a. Num a => a -> a -> a
-a
a)) in a
ta -> a -> a
forall a. Num a => a -> a -> a
*a
ta -> a -> a
forall a. Num a => a -> a -> a
*(a
3a -> a -> a
forall a. Num a => a -> a -> a
-a
2a -> a -> a
forall a. Num a => a -> a -> a
*a
t)
instance FloatingOrd Float
instance FloatingOrd Double
instance FloatingOrd (S x Float) where
clamp :: S x Float -> S x Float -> S x Float -> S x Float
clamp = String -> S x Float -> S x Float -> S x Float -> S x Float
forall c x y z. String -> S c x -> S c y -> S c z -> S c Float
fun3f String
"clamp"
step :: S x Float -> S x Float -> S x Float
step = String -> S x Float -> S x Float -> S x Float
forall c x y. String -> S c x -> S c y -> S c Float
fun2f String
"step"
smoothstep :: S x Float -> S x Float -> S x Float -> S x Float
smoothstep = String -> S x Float -> S x Float -> S x Float -> S x Float
forall c x y z. String -> S c x -> S c y -> S c z -> S c Float
fun3f String
"smoothstep"
class Convert a where
type ConvertFloat a
type ConvertInt a
type ConvertWord a
toFloat :: a -> ConvertFloat a
toInt :: a -> ConvertInt a
toWord :: a -> ConvertWord a
instance Convert Float where
type ConvertFloat Float = Float
type ConvertInt Float = Int
type ConvertWord Float = Word
toFloat :: Float -> ConvertFloat Float
toFloat = Float -> ConvertFloat Float
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
toInt :: Float -> ConvertInt Float
toInt = Float -> ConvertInt Float
forall a b. (RealFrac a, Integral b) => a -> b
truncate
toWord :: Float -> ConvertWord Float
toWord = Float -> ConvertWord Float
forall a b. (RealFrac a, Integral b) => a -> b
truncate
instance Convert Int where
type ConvertFloat Int = Float
type ConvertInt Int = Int
type ConvertWord Int = Word
toFloat :: Int -> ConvertFloat Int
toFloat = Int -> ConvertFloat Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral
toInt :: Int -> ConvertInt Int
toInt = Int -> ConvertInt Int
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
toWord :: Int -> ConvertWord Int
toWord = Int -> ConvertWord Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance Convert Word where
type ConvertFloat Word = Float
type ConvertInt Word = Int
type ConvertWord Word = Word
toFloat :: Word -> ConvertFloat Word
toFloat = Word -> ConvertFloat Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral
toInt :: Word -> ConvertInt Word
toInt = Word -> ConvertInt Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral
toWord :: Word -> ConvertWord Word
toWord = Word -> ConvertWord Word
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance Convert (S x Float) where
type ConvertFloat (S x Float) = S x Float
type ConvertInt (S x Float) = S x Int
type ConvertWord (S x Float) = S x Word
toFloat :: S x Float -> ConvertFloat (S x Float)
toFloat = S x Float -> ConvertFloat (S x Float)
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
toInt :: S x Float -> ConvertInt (S x Float)
toInt = String -> S x Float -> S x Int
forall c x. String -> S c x -> S c Int
fun1i String
"int"
toWord :: S x Float -> ConvertWord (S x Float)
toWord = String -> S x Float -> S x Word
forall c x. String -> S c x -> S c Word
fun1u String
"uint"
instance Convert (S x Int) where
type ConvertFloat (S x Int) = S x Float
type ConvertInt (S x Int) = S x Int
type ConvertWord (S x Int) = S x Word
toFloat :: S x Int -> ConvertFloat (S x Int)
toFloat = String -> S x Int -> S x Float
forall c x. String -> S c x -> S c Float
fun1f String
"float"
toInt :: S x Int -> ConvertInt (S x Int)
toInt = S x Int -> ConvertInt (S x Int)
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
toWord :: S x Int -> ConvertWord (S x Int)
toWord = String -> S x Int -> S x Word
forall c x. String -> S c x -> S c Word
fun1u String
"uint"
instance Convert (S x Word) where
type ConvertFloat (S x Word) = S x Float
type ConvertInt (S x Word) = S x Int
type ConvertWord (S x Word) = S x Word
toFloat :: S x Word -> ConvertFloat (S x Word)
toFloat = String -> S x Word -> S x Float
forall c x. String -> S c x -> S c Float
fun1f String
"float"
toInt :: S x Word -> ConvertInt (S x Word)
toInt = String -> S x Word -> S x Int
forall c x. String -> S c x -> S c Int
fun1i String
"int"
toWord :: S x Word -> ConvertWord (S x Word)
toWord = S x Word -> ConvertWord (S x Word)
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
dFdx :: FFloat -> FFloat
dFdy :: FFloat -> FFloat
fwidth :: FFloat -> FFloat
dFdx :: FFloat -> FFloat
dFdx = String -> FFloat -> FFloat
forall c x. String -> S c x -> S c Float
fun1f String
"dFdx"
dFdy :: FFloat -> FFloat
dFdy = String -> FFloat -> FFloat
forall c x. String -> S c x -> S c Float
fun1f String
"dFdy"
fwidth :: FFloat -> FFloat
fwidth = String -> FFloat -> FFloat
forall c x. String -> S c x -> S c Float
fun1f String
"fwidth"
fromV :: (a -> S x a) -> String -> t a -> S x a
fromV a -> S x a
f String
s t a
v = ExprM String -> S x a
forall x a. ExprM String -> S x a
S (ExprM String -> S x a) -> ExprM String -> S x a
forall a b. (a -> b) -> a -> b
$ do [String]
params <- (a -> ExprM String)
-> [a]
-> SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (S x a -> ExprM String
forall x a. S x a -> ExprM String
unS (S x a -> ExprM String) -> (a -> S x a) -> a -> ExprM String
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. a -> S x a
f) ([a]
-> SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String])
-> [a]
-> SNMapReaderT
[String]
(StateT ExprState (WriterT String (StateT Int IO)))
[String]
forall a b. (a -> b) -> a -> b
$ t a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList t a
v
String -> ExprM String
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> ExprM String) -> String -> ExprM String
forall a b. (a -> b) -> a -> b
$ String
s String -> String -> String
forall a. [a] -> [a] -> [a]
++ Char
'(' Char -> String -> String
forall a. a -> [a] -> [a]
: String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"," [String]
params String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
")"
fromVec4 :: V4 (S x Float) -> S x (V4 Float)
fromVec4 :: V4 (S x Float) -> S x (V4 Float)
fromVec4 = (S x Float -> S x Float)
-> String -> V4 (S x Float) -> S x (V4 Float)
forall (t :: * -> *) a x a x a.
Foldable t =>
(a -> S x a) -> String -> t a -> S x a
fromV S x Float -> S x Float
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id String
"vec4"
fromVec3 :: V3 (S x Float) -> S x (V3 Float)
fromVec3 :: V3 (S x Float) -> S x (V3 Float)
fromVec3 = (S x Float -> S x Float)
-> String -> V3 (S x Float) -> S x (V3 Float)
forall (t :: * -> *) a x a x a.
Foldable t =>
(a -> S x a) -> String -> t a -> S x a
fromV S x Float -> S x Float
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id String
"vec3"
fromVec2 :: V2 (S x Float) -> S x (V2 Float)
fromVec2 :: V2 (S x Float) -> S x (V2 Float)
fromVec2 = (S x Float -> S x Float)
-> String -> V2 (S x Float) -> S x (V2 Float)
forall (t :: * -> *) a x a x a.
Foldable t =>
(a -> S x a) -> String -> t a -> S x a
fromV S x Float -> S x Float
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id String
"vec2"
fromMat22 :: V2 (V2 (S x Float)) -> S x (V2 (V2 Float))
fromMat22 :: V2 (V2 (S x Float)) -> S x (V2 (V2 Float))
fromMat22 = (V2 (S x Float) -> S x (V2 Float))
-> String -> V2 (V2 (S x Float)) -> S x (V2 (V2 Float))
forall (t :: * -> *) a x a x a.
Foldable t =>
(a -> S x a) -> String -> t a -> S x a
fromV V2 (S x Float) -> S x (V2 Float)
forall x. V2 (S x Float) -> S x (V2 Float)
fromVec2 String
"mat2x2"
fromMat23 :: V2 (V3 (S x Float)) -> S x (V2 (V3 Float))
fromMat23 :: V2 (V3 (S x Float)) -> S x (V2 (V3 Float))
fromMat23 = (V3 (S x Float) -> S x (V3 Float))
-> String -> V2 (V3 (S x Float)) -> S x (V2 (V3 Float))
forall (t :: * -> *) a x a x a.
Foldable t =>
(a -> S x a) -> String -> t a -> S x a
fromV V3 (S x Float) -> S x (V3 Float)
forall x. V3 (S x Float) -> S x (V3 Float)
fromVec3 String
"mat2x3"
fromMat24 :: V2 (V4 (S x Float)) -> S x (V2 (V4 Float))
fromMat24 :: V2 (V4 (S x Float)) -> S x (V2 (V4 Float))
fromMat24 = (V4 (S x Float) -> S x (V4 Float))
-> String -> V2 (V4 (S x Float)) -> S x (V2 (V4 Float))
forall (t :: * -> *) a x a x a.
Foldable t =>
(a -> S x a) -> String -> t a -> S x a
fromV V4 (S x Float) -> S x (V4 Float)
forall x. V4 (S x Float) -> S x (V4 Float)
fromVec4 String
"mat2x4"
fromMat32 :: V3 (V2 (S x Float)) -> S x (V3 (V2 Float))
fromMat32 :: V3 (V2 (S x Float)) -> S x (V3 (V2 Float))
fromMat32 = (V2 (S x Float) -> S x (V2 Float))
-> String -> V3 (V2 (S x Float)) -> S x (V3 (V2 Float))
forall (t :: * -> *) a x a x a.
Foldable t =>
(a -> S x a) -> String -> t a -> S x a
fromV V2 (S x Float) -> S x (V2 Float)
forall x. V2 (S x Float) -> S x (V2 Float)
fromVec2 String
"mat3x2"
fromMat33 :: V3 (V3 (S x Float)) -> S x (V3 (V3 Float))
fromMat33 :: V3 (V3 (S x Float)) -> S x (V3 (V3 Float))
fromMat33 = (V3 (S x Float) -> S x (V3 Float))
-> String -> V3 (V3 (S x Float)) -> S x (V3 (V3 Float))
forall (t :: * -> *) a x a x a.
Foldable t =>
(a -> S x a) -> String -> t a -> S x a
fromV V3 (S x Float) -> S x (V3 Float)
forall x. V3 (S x Float) -> S x (V3 Float)
fromVec3 String
"mat3x3"
fromMat34 :: V3 (V4 (S x Float)) -> S x (V3 (V4 Float))
fromMat34 :: V3 (V4 (S x Float)) -> S x (V3 (V4 Float))
fromMat34 = (V4 (S x Float) -> S x (V4 Float))
-> String -> V3 (V4 (S x Float)) -> S x (V3 (V4 Float))
forall (t :: * -> *) a x a x a.
Foldable t =>
(a -> S x a) -> String -> t a -> S x a
fromV V4 (S x Float) -> S x (V4 Float)
forall x. V4 (S x Float) -> S x (V4 Float)
fromVec4 String
"mat3x4"
fromMat42 :: V4 (V2 (S x Float)) -> S x (V4 (V2 Float))
fromMat42 :: V4 (V2 (S x Float)) -> S x (V4 (V2 Float))
fromMat42 = (V2 (S x Float) -> S x (V2 Float))
-> String -> V4 (V2 (S x Float)) -> S x (V4 (V2 Float))
forall (t :: * -> *) a x a x a.
Foldable t =>
(a -> S x a) -> String -> t a -> S x a
fromV V2 (S x Float) -> S x (V2 Float)
forall x. V2 (S x Float) -> S x (V2 Float)
fromVec2 String
"mat4x2"
fromMat43 :: V4 (V3 (S x Float)) -> S x (V4 (V3 Float))
fromMat43 :: V4 (V3 (S x Float)) -> S x (V4 (V3 Float))
fromMat43 = (V3 (S x Float) -> S x (V3 Float))
-> String -> V4 (V3 (S x Float)) -> S x (V4 (V3 Float))
forall (t :: * -> *) a x a x a.
Foldable t =>
(a -> S x a) -> String -> t a -> S x a
fromV V3 (S x Float) -> S x (V3 Float)
forall x. V3 (S x Float) -> S x (V3 Float)
fromVec3 String
"mat4x3"
fromMat44 :: V4 (V4 (S x Float)) -> S x (V4 (V4 Float))
fromMat44 :: V4 (V4 (S x Float)) -> S x (V4 (V4 Float))
fromMat44 = (V4 (S x Float) -> S x (V4 Float))
-> String -> V4 (V4 (S x Float)) -> S x (V4 (V4 Float))
forall (t :: * -> *) a x a x a.
Foldable t =>
(a -> S x a) -> String -> t a -> S x a
fromV V4 (S x Float) -> S x (V4 Float)
forall x. V4 (S x Float) -> S x (V4 Float)
fromVec4 String
"mat4x4"
mulToV4 :: S c x -> S c y -> V4 (S c a)
mulToV4 S c x
a S c y
b = S c a -> V4 (S c a)
forall c a. S c a -> V4 (S c a)
vec4S'' (S c a -> V4 (S c a)) -> S c a -> V4 (S c a)
forall a b. (a -> b) -> a -> b
$ SType -> String -> S c x -> S c y -> S c a
forall c x y z. SType -> String -> S c x -> S c y -> S c z
bin (Int -> SType
STypeVec Int
4) String
"*" S c x
a S c y
b
mulToV3 :: S c x -> S c y -> V3 (S c a)
mulToV3 S c x
a S c y
b = S c a -> V3 (S c a)
forall c a. S c a -> V3 (S c a)
vec3S'' (S c a -> V3 (S c a)) -> S c a -> V3 (S c a)
forall a b. (a -> b) -> a -> b
$ SType -> String -> S c x -> S c y -> S c a
forall c x y z. SType -> String -> S c x -> S c y -> S c z
bin (Int -> SType
STypeVec Int
3) String
"*" S c x
a S c y
b
mulToV2 :: S c x -> S c y -> V2 (S c a)
mulToV2 S c x
a S c y
b = S c a -> V2 (S c a)
forall c a. S c a -> V2 (S c a)
vec2S'' (S c a -> V2 (S c a)) -> S c a -> V2 (S c a)
forall a b. (a -> b) -> a -> b
$ SType -> String -> S c x -> S c y -> S c a
forall c x y z. SType -> String -> S c x -> S c y -> S c z
bin (Int -> SType
STypeVec Int
2) String
"*" S c x
a S c y
b
mulToM :: (Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
mulToM (Int
r,S c z -> f a
x) (Int
c,a -> b
y) S c x
a S c y
b = (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
y (f a -> f b) -> f a -> f b
forall a b. (a -> b) -> a -> b
$ S c z -> f a
x (S c z -> f a) -> S c z -> f a
forall a b. (a -> b) -> a -> b
$ SType -> String -> S c x -> S c y -> S c z
forall c x y z. SType -> String -> S c x -> S c y -> S c z
bin (Int -> Int -> SType
STypeMat Int
c Int
r) String
"*" S c x
a S c y
b
d2 :: (a, S c a -> V2 (S c a))
d2 = (a
2,S c a -> V2 (S c a)
forall c a. S c a -> V2 (S c a)
vec2S'')
d3 :: (a, S c a -> V3 (S c a))
d3 = (a
3,S c a -> V3 (S c a)
forall c a. S c a -> V3 (S c a)
vec3S'')
d4 :: (a, S c a -> V4 (S c a))
d4 = (a
4,S c a -> V4 (S c a)
forall c a. S c a -> V4 (S c a)
vec4S'')
unV1 :: V1 t -> t
unV1 :: V1 t -> t
unV1 (V1 t
x) = t
x
outerToM :: (Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
outerToM (Int
r,S c z -> f a
x) (Int
c,a -> b
y) S c x
a S c y
b = (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
y (f a -> f b) -> f a -> f b
forall a b. (a -> b) -> a -> b
$ S c z -> f a
x (S c z -> f a) -> S c z -> f a
forall a b. (a -> b) -> a -> b
$ SType -> String -> S c x -> S c y -> S c z
forall c x y z. SType -> String -> S c x -> S c y -> S c z
fun2 (Int -> Int -> SType
STypeMat Int
c Int
r) String
"outerProduct" S c x
a S c y
b
{-# RULES "norm/length4" norm = length4 #-}
{-# RULES "norm/length3" norm = length3 #-}
{-# RULES "norm/length2" norm = length2 #-}
length4 :: V4 (S x Float) -> S x Float
length4 :: V4 (S x Float) -> S x Float
length4 = String -> S x (V4 Float) -> S x Float
forall c x. String -> S c x -> S c Float
fun1f String
"length" (S x (V4 Float) -> S x Float)
-> (V4 (S x Float) -> S x (V4 Float))
-> V4 (S x Float)
-> S x Float
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. V4 (S x Float) -> S x (V4 Float)
forall x. V4 (S x Float) -> S x (V4 Float)
fromVec4
length3 :: V3 (S x Float) -> S x Float
length3 :: V3 (S x Float) -> S x Float
length3 = String -> S x (V3 Float) -> S x Float
forall c x. String -> S c x -> S c Float
fun1f String
"length" (S x (V3 Float) -> S x Float)
-> (V3 (S x Float) -> S x (V3 Float))
-> V3 (S x Float)
-> S x Float
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. V3 (S x Float) -> S x (V3 Float)
forall x. V3 (S x Float) -> S x (V3 Float)
fromVec3
length2 :: V2 (S x Float) -> S x Float
length2 :: V2 (S x Float) -> S x Float
length2 = String -> S x (V2 Float) -> S x Float
forall c x. String -> S c x -> S c Float
fun1f String
"length" (S x (V2 Float) -> S x Float)
-> (V2 (S x Float) -> S x (V2 Float))
-> V2 (S x Float)
-> S x Float
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. V2 (S x Float) -> S x (V2 Float)
forall x. V2 (S x Float) -> S x (V2 Float)
fromVec2
{-# RULES "signorm/normalize4" signorm = normalize4 #-}
{-# RULES "signorm/normalize3" signorm = normalize3 #-}
{-# RULES "signorm/normalize2" signorm = normalize2 #-}
normalize4 :: V4 (S x Float) -> V4 (S x Float)
normalize4 :: V4 (S x Float) -> V4 (S x Float)
normalize4 = S x Float -> V4 (S x Float)
forall c a. S c a -> V4 (S c a)
vec4S'' (S x Float -> V4 (S x Float))
-> (V4 (S x Float) -> S x Float)
-> V4 (S x Float)
-> V4 (S x Float)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. SType -> String -> S x (V4 Float) -> S x Float
forall c x y. SType -> String -> S c x -> S c y
fun1 (Int -> SType
STypeVec Int
4) String
"normalize" (S x (V4 Float) -> S x Float)
-> (V4 (S x Float) -> S x (V4 Float))
-> V4 (S x Float)
-> S x Float
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. V4 (S x Float) -> S x (V4 Float)
forall x. V4 (S x Float) -> S x (V4 Float)
fromVec4
normalize3 :: V3 (S x Float) -> V3 (S x Float)
normalize3 :: V3 (S x Float) -> V3 (S x Float)
normalize3 = S x Float -> V3 (S x Float)
forall c a. S c a -> V3 (S c a)
vec3S'' (S x Float -> V3 (S x Float))
-> (V3 (S x Float) -> S x Float)
-> V3 (S x Float)
-> V3 (S x Float)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. SType -> String -> S x (V3 Float) -> S x Float
forall c x y. SType -> String -> S c x -> S c y
fun1 (Int -> SType
STypeVec Int
3) String
"normalize" (S x (V3 Float) -> S x Float)
-> (V3 (S x Float) -> S x (V3 Float))
-> V3 (S x Float)
-> S x Float
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. V3 (S x Float) -> S x (V3 Float)
forall x. V3 (S x Float) -> S x (V3 Float)
fromVec3
normalize2 :: V2 (S x Float) -> V2 (S x Float)
normalize2 :: V2 (S x Float) -> V2 (S x Float)
normalize2 = S x Float -> V2 (S x Float)
forall c a. S c a -> V2 (S c a)
vec2S'' (S x Float -> V2 (S x Float))
-> (V2 (S x Float) -> S x Float)
-> V2 (S x Float)
-> V2 (S x Float)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. SType -> String -> S x (V2 Float) -> S x Float
forall c x y. SType -> String -> S c x -> S c y
fun1 (Int -> SType
STypeVec Int
2) String
"normalize" (S x (V2 Float) -> S x Float)
-> (V2 (S x Float) -> S x (V2 Float))
-> V2 (S x Float)
-> S x Float
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. V2 (S x Float) -> S x (V2 Float)
forall x. V2 (S x Float) -> S x (V2 Float)
fromVec2
{-# RULES "distanceA/dist4" distanceA = dist4 #-}
{-# RULES "distanceA/dist3" distanceA = dist3 #-}
{-# RULES "distanceA/dist2" distanceA = dist2 #-}
{-# RULES "distance/dist4" distance = dist4 #-}
{-# RULES "distance/dist3" distance = dist3 #-}
{-# RULES "distance/dist2" distance = dist2 #-}
dist4 :: V4 (S x Float) -> V4 (S x Float) -> S x Float
dist4 :: V4 (S x Float) -> V4 (S x Float) -> S x Float
dist4 V4 (S x Float)
a V4 (S x Float)
b = String -> S x (V4 Float) -> S x (V4 Float) -> S x Float
forall c x y. String -> S c x -> S c y -> S c Float
fun2f String
"distance" (V4 (S x Float) -> S x (V4 Float)
forall x. V4 (S x Float) -> S x (V4 Float)
fromVec4 V4 (S x Float)
a) (V4 (S x Float) -> S x (V4 Float)
forall x. V4 (S x Float) -> S x (V4 Float)
fromVec4 V4 (S x Float)
b)
dist3 :: V3 (S x Float) -> V3 (S x Float) -> S x Float
dist3 :: V3 (S x Float) -> V3 (S x Float) -> S x Float
dist3 V3 (S x Float)
a V3 (S x Float)
b = String -> S x (V3 Float) -> S x (V3 Float) -> S x Float
forall c x y. String -> S c x -> S c y -> S c Float
fun2f String
"distance" (V3 (S x Float) -> S x (V3 Float)
forall x. V3 (S x Float) -> S x (V3 Float)
fromVec3 V3 (S x Float)
a) (V3 (S x Float) -> S x (V3 Float)
forall x. V3 (S x Float) -> S x (V3 Float)
fromVec3 V3 (S x Float)
b)
dist2 :: V2 (S x Float) -> V2 (S x Float) -> S x Float
dist2 :: V2 (S x Float) -> V2 (S x Float) -> S x Float
dist2 V2 (S x Float)
a V2 (S x Float)
b = String -> S x (V2 Float) -> S x (V2 Float) -> S x Float
forall c x y. String -> S c x -> S c y -> S c Float
fun2f String
"distance" (V2 (S x Float) -> S x (V2 Float)
forall x. V2 (S x Float) -> S x (V2 Float)
fromVec2 V2 (S x Float)
a) (V2 (S x Float) -> S x (V2 Float)
forall x. V2 (S x Float) -> S x (V2 Float)
fromVec2 V2 (S x Float)
b)
{-# RULES "cross/S" cross = crossS #-}
crossS :: V3 (S x Float) -> V3 (S x Float) -> V3 (S x Float)
crossS :: V3 (S x Float) -> V3 (S x Float) -> V3 (S x Float)
crossS V3 (S x Float)
a V3 (S x Float)
b = S x Float -> V3 (S x Float)
forall c a. S c a -> V3 (S c a)
vec3S'' (S x Float -> V3 (S x Float)) -> S x Float -> V3 (S x Float)
forall a b. (a -> b) -> a -> b
$ SType -> String -> S x (V3 Float) -> S x (V3 Float) -> S x Float
forall c x y z. SType -> String -> S c x -> S c y -> S c z
fun2 (Int -> SType
STypeVec Int
3) String
"cross" (V3 (S x Float) -> S x (V3 Float)
forall x. V3 (S x Float) -> S x (V3 Float)
fromVec3 V3 (S x Float)
a) (V3 (S x Float) -> S x (V3 Float)
forall x. V3 (S x Float) -> S x (V3 Float)
fromVec3 V3 (S x Float)
b)
{-# RULES "minB/S" minB = minS #-}
{-# RULES "maxB/S" maxB = maxS #-}
minS :: S x Float -> S x Float -> S x Float
minS :: S x Float -> S x Float -> S x Float
minS = String -> S x Float -> S x Float -> S x Float
forall c x y. String -> S c x -> S c y -> S c Float
fun2f String
"min"
maxS :: S x Float -> S x Float -> S x Float
maxS :: S x Float -> S x Float -> S x Float
maxS = String -> S x Float -> S x Float -> S x Float
forall c x y. String -> S c x -> S c y -> S c Float
fun2f String
"max"
{-# RULES "mul_12_21vv" dot = mul_12_21vv #-}
{-# RULES "mul_13_31vv" dot = mul_13_31vv #-}
{-# RULES "mul_14_41vv" dot = mul_14_41vv #-}
mul_12_21vv :: V2 (S x Float) -> V2 (S x Float) -> S x Float
mul_12_21vv :: V2 (S x Float) -> V2 (S x Float) -> S x Float
mul_12_21vv V2 (S x Float)
a V2 (S x Float)
b = String -> S x (V2 Float) -> S x (V2 Float) -> S x Float
forall c x y. String -> S c x -> S c y -> S c Float
fun2f String
"dot" (V2 (S x Float) -> S x (V2 Float)
forall x. V2 (S x Float) -> S x (V2 Float)
fromVec2 V2 (S x Float)
a) (V2 (S x Float) -> S x (V2 Float)
forall x. V2 (S x Float) -> S x (V2 Float)
fromVec2 V2 (S x Float)
b)
mul_13_31vv :: V3 (S x Float) -> V3 (S x Float) -> S x Float
mul_13_31vv :: V3 (S x Float) -> V3 (S x Float) -> S x Float
mul_13_31vv V3 (S x Float)
a V3 (S x Float)
b = String -> S x (V3 Float) -> S x (V3 Float) -> S x Float
forall c x y. String -> S c x -> S c y -> S c Float
fun2f String
"dot" (V3 (S x Float) -> S x (V3 Float)
forall x. V3 (S x Float) -> S x (V3 Float)
fromVec3 V3 (S x Float)
a) (V3 (S x Float) -> S x (V3 Float)
forall x. V3 (S x Float) -> S x (V3 Float)
fromVec3 V3 (S x Float)
b)
mul_14_41vv :: V4 (S x Float) -> V4 (S x Float) -> S x Float
mul_14_41vv :: V4 (S x Float) -> V4 (S x Float) -> S x Float
mul_14_41vv V4 (S x Float)
a V4 (S x Float)
b = String -> S x (V4 Float) -> S x (V4 Float) -> S x Float
forall c x y. String -> S c x -> S c y -> S c Float
fun2f String
"dot" (V4 (S x Float) -> S x (V4 Float)
forall x. V4 (S x Float) -> S x (V4 Float)
fromVec4 V4 (S x Float)
a) (V4 (S x Float) -> S x (V4 Float)
forall x. V4 (S x Float) -> S x (V4 Float)
fromVec4 V4 (S x Float)
b)
{-# RULES "mul_12_21vm" (*!) = mul_12_21vm #-}
{-# RULES "mul_13_31vm" (*!) = mul_13_31vm #-}
{-# RULES "mul_14_41vm" (*!) = mul_14_41vm #-}
mul_12_21vm :: V2 (S x Float) -> V2 (V1 (S x Float)) -> V1 (S x Float)
mul_12_21vm :: V2 (S x Float) -> V2 (V1 (S x Float)) -> V1 (S x Float)
mul_12_21vm V2 (S x Float)
a V2 (V1 (S x Float))
b = S x Float -> V1 (S x Float)
forall a. a -> V1 a
V1 (S x Float -> V1 (S x Float)) -> S x Float -> V1 (S x Float)
forall a b. (a -> b) -> a -> b
$ String -> S x (V2 Float) -> S x (V2 Float) -> S x Float
forall c x y. String -> S c x -> S c y -> S c Float
fun2f String
"dot" (V2 (S x Float) -> S x (V2 Float)
forall x. V2 (S x Float) -> S x (V2 Float)
fromVec2 V2 (S x Float)
a) (V2 (S x Float) -> S x (V2 Float)
forall x. V2 (S x Float) -> S x (V2 Float)
fromVec2 (V2 (S x Float) -> S x (V2 Float))
-> V2 (S x Float) -> S x (V2 Float)
forall a b. (a -> b) -> a -> b
$ (V1 (S x Float) -> S x Float)
-> V2 (V1 (S x Float)) -> V2 (S x Float)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap V1 (S x Float) -> S x Float
forall t. V1 t -> t
unV1 V2 (V1 (S x Float))
b)
mul_13_31vm :: V3 (S x Float) -> V3 (V1 (S x Float)) -> V1 (S x Float)
mul_13_31vm :: V3 (S x Float) -> V3 (V1 (S x Float)) -> V1 (S x Float)
mul_13_31vm V3 (S x Float)
a V3 (V1 (S x Float))
b = S x Float -> V1 (S x Float)
forall a. a -> V1 a
V1 (S x Float -> V1 (S x Float)) -> S x Float -> V1 (S x Float)
forall a b. (a -> b) -> a -> b
$ String -> S x (V3 Float) -> S x (V3 Float) -> S x Float
forall c x y. String -> S c x -> S c y -> S c Float
fun2f String
"dot" (V3 (S x Float) -> S x (V3 Float)
forall x. V3 (S x Float) -> S x (V3 Float)
fromVec3 V3 (S x Float)
a) (V3 (S x Float) -> S x (V3 Float)
forall x. V3 (S x Float) -> S x (V3 Float)
fromVec3 (V3 (S x Float) -> S x (V3 Float))
-> V3 (S x Float) -> S x (V3 Float)
forall a b. (a -> b) -> a -> b
$ (V1 (S x Float) -> S x Float)
-> V3 (V1 (S x Float)) -> V3 (S x Float)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap V1 (S x Float) -> S x Float
forall t. V1 t -> t
unV1 V3 (V1 (S x Float))
b)
mul_14_41vm :: V4 (S x Float) -> V4 (V1 (S x Float)) -> V1 (S x Float)
mul_14_41vm :: V4 (S x Float) -> V4 (V1 (S x Float)) -> V1 (S x Float)
mul_14_41vm V4 (S x Float)
a V4 (V1 (S x Float))
b = S x Float -> V1 (S x Float)
forall a. a -> V1 a
V1 (S x Float -> V1 (S x Float)) -> S x Float -> V1 (S x Float)
forall a b. (a -> b) -> a -> b
$ String -> S x (V4 Float) -> S x (V4 Float) -> S x Float
forall c x y. String -> S c x -> S c y -> S c Float
fun2f String
"dot" (V4 (S x Float) -> S x (V4 Float)
forall x. V4 (S x Float) -> S x (V4 Float)
fromVec4 V4 (S x Float)
a) (V4 (S x Float) -> S x (V4 Float)
forall x. V4 (S x Float) -> S x (V4 Float)
fromVec4 (V4 (S x Float) -> S x (V4 Float))
-> V4 (S x Float) -> S x (V4 Float)
forall a b. (a -> b) -> a -> b
$ (V1 (S x Float) -> S x Float)
-> V4 (V1 (S x Float)) -> V4 (S x Float)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap V1 (S x Float) -> S x Float
forall t. V1 t -> t
unV1 V4 (V1 (S x Float))
b)
{-# RULES "mul_12_21mv" (!*) = mul_12_21mv #-}
{-# RULES "mul_13_31mv" (!*) = mul_13_31mv #-}
{-# RULES "mul_14_41mv" (!*) = mul_14_41mv #-}
mul_12_21mv :: V1 (V2 (S x Float)) -> V2 (S x Float) -> V1 (S x Float)
mul_12_21mv :: V1 (V2 (S x Float)) -> V2 (S x Float) -> V1 (S x Float)
mul_12_21mv V1 (V2 (S x Float))
a V2 (S x Float)
b = S x Float -> V1 (S x Float)
forall a. a -> V1 a
V1 (S x Float -> V1 (S x Float)) -> S x Float -> V1 (S x Float)
forall a b. (a -> b) -> a -> b
$ String -> S x (V2 Float) -> S x (V2 Float) -> S x Float
forall c x y. String -> S c x -> S c y -> S c Float
fun2f String
"dot" (V2 (S x Float) -> S x (V2 Float)
forall x. V2 (S x Float) -> S x (V2 Float)
fromVec2 (V2 (S x Float) -> S x (V2 Float))
-> V2 (S x Float) -> S x (V2 Float)
forall a b. (a -> b) -> a -> b
$ V1 (V2 (S x Float)) -> V2 (S x Float)
forall t. V1 t -> t
unV1 V1 (V2 (S x Float))
a) (V2 (S x Float) -> S x (V2 Float)
forall x. V2 (S x Float) -> S x (V2 Float)
fromVec2 V2 (S x Float)
b)
mul_13_31mv :: V1 (V3 (S x Float)) -> V3 (S x Float) -> V1 (S x Float)
mul_13_31mv :: V1 (V3 (S x Float)) -> V3 (S x Float) -> V1 (S x Float)
mul_13_31mv V1 (V3 (S x Float))
a V3 (S x Float)
b = S x Float -> V1 (S x Float)
forall a. a -> V1 a
V1 (S x Float -> V1 (S x Float)) -> S x Float -> V1 (S x Float)
forall a b. (a -> b) -> a -> b
$ String -> S x (V3 Float) -> S x (V3 Float) -> S x Float
forall c x y. String -> S c x -> S c y -> S c Float
fun2f String
"dot" (V3 (S x Float) -> S x (V3 Float)
forall x. V3 (S x Float) -> S x (V3 Float)
fromVec3 (V3 (S x Float) -> S x (V3 Float))
-> V3 (S x Float) -> S x (V3 Float)
forall a b. (a -> b) -> a -> b
$ V1 (V3 (S x Float)) -> V3 (S x Float)
forall t. V1 t -> t
unV1 V1 (V3 (S x Float))
a) (V3 (S x Float) -> S x (V3 Float)
forall x. V3 (S x Float) -> S x (V3 Float)
fromVec3 V3 (S x Float)
b)
mul_14_41mv :: V1 (V4 (S x Float)) -> V4 (S x Float) -> V1 (S x Float)
mul_14_41mv :: V1 (V4 (S x Float)) -> V4 (S x Float) -> V1 (S x Float)
mul_14_41mv V1 (V4 (S x Float))
a V4 (S x Float)
b = S x Float -> V1 (S x Float)
forall a. a -> V1 a
V1 (S x Float -> V1 (S x Float)) -> S x Float -> V1 (S x Float)
forall a b. (a -> b) -> a -> b
$ String -> S x (V4 Float) -> S x (V4 Float) -> S x Float
forall c x y. String -> S c x -> S c y -> S c Float
fun2f String
"dot" (V4 (S x Float) -> S x (V4 Float)
forall x. V4 (S x Float) -> S x (V4 Float)
fromVec4 (V4 (S x Float) -> S x (V4 Float))
-> V4 (S x Float) -> S x (V4 Float)
forall a b. (a -> b) -> a -> b
$ V1 (V4 (S x Float)) -> V4 (S x Float)
forall t. V1 t -> t
unV1 V1 (V4 (S x Float))
a) (V4 (S x Float) -> S x (V4 Float)
forall x. V4 (S x Float) -> S x (V4 Float)
fromVec4 V4 (S x Float)
b)
{-# RULES "mul_12_21mm" (!*!) = mul_12_21mm #-}
{-# RULES "mul_13_31mm" (!*!) = mul_13_31mm #-}
{-# RULES "mul_14_41mm" (!*!) = mul_14_41mm #-}
mul_12_21mm :: V1 (V2 (S x Float)) -> V2 (V1 (S x Float)) -> V1 (V1 (S x Float))
mul_12_21mm :: V1 (V2 (S x Float)) -> V2 (V1 (S x Float)) -> V1 (V1 (S x Float))
mul_12_21mm V1 (V2 (S x Float))
a V2 (V1 (S x Float))
b = V1 (S x Float) -> V1 (V1 (S x Float))
forall a. a -> V1 a
V1 (V1 (S x Float) -> V1 (V1 (S x Float)))
-> V1 (S x Float) -> V1 (V1 (S x Float))
forall a b. (a -> b) -> a -> b
$ S x Float -> V1 (S x Float)
forall a. a -> V1 a
V1 (S x Float -> V1 (S x Float)) -> S x Float -> V1 (S x Float)
forall a b. (a -> b) -> a -> b
$ String -> S x (V2 Float) -> S x (V2 Float) -> S x Float
forall c x y. String -> S c x -> S c y -> S c Float
fun2f String
"dot" (V2 (S x Float) -> S x (V2 Float)
forall x. V2 (S x Float) -> S x (V2 Float)
fromVec2 (V2 (S x Float) -> S x (V2 Float))
-> V2 (S x Float) -> S x (V2 Float)
forall a b. (a -> b) -> a -> b
$ V1 (V2 (S x Float)) -> V2 (S x Float)
forall t. V1 t -> t
unV1 V1 (V2 (S x Float))
a) (V2 (S x Float) -> S x (V2 Float)
forall x. V2 (S x Float) -> S x (V2 Float)
fromVec2 (V2 (S x Float) -> S x (V2 Float))
-> V2 (S x Float) -> S x (V2 Float)
forall a b. (a -> b) -> a -> b
$ (V1 (S x Float) -> S x Float)
-> V2 (V1 (S x Float)) -> V2 (S x Float)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap V1 (S x Float) -> S x Float
forall t. V1 t -> t
unV1 V2 (V1 (S x Float))
b)
mul_13_31mm :: V1 (V3 (S x Float)) -> V3 (V1 (S x Float)) -> V1 (V1 (S x Float))
mul_13_31mm :: V1 (V3 (S x Float)) -> V3 (V1 (S x Float)) -> V1 (V1 (S x Float))
mul_13_31mm V1 (V3 (S x Float))
a V3 (V1 (S x Float))
b = V1 (S x Float) -> V1 (V1 (S x Float))
forall a. a -> V1 a
V1 (V1 (S x Float) -> V1 (V1 (S x Float)))
-> V1 (S x Float) -> V1 (V1 (S x Float))
forall a b. (a -> b) -> a -> b
$ S x Float -> V1 (S x Float)
forall a. a -> V1 a
V1 (S x Float -> V1 (S x Float)) -> S x Float -> V1 (S x Float)
forall a b. (a -> b) -> a -> b
$ String -> S x (V3 Float) -> S x (V3 Float) -> S x Float
forall c x y. String -> S c x -> S c y -> S c Float
fun2f String
"dot" (V3 (S x Float) -> S x (V3 Float)
forall x. V3 (S x Float) -> S x (V3 Float)
fromVec3 (V3 (S x Float) -> S x (V3 Float))
-> V3 (S x Float) -> S x (V3 Float)
forall a b. (a -> b) -> a -> b
$ V1 (V3 (S x Float)) -> V3 (S x Float)
forall t. V1 t -> t
unV1 V1 (V3 (S x Float))
a) (V3 (S x Float) -> S x (V3 Float)
forall x. V3 (S x Float) -> S x (V3 Float)
fromVec3 (V3 (S x Float) -> S x (V3 Float))
-> V3 (S x Float) -> S x (V3 Float)
forall a b. (a -> b) -> a -> b
$ (V1 (S x Float) -> S x Float)
-> V3 (V1 (S x Float)) -> V3 (S x Float)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap V1 (S x Float) -> S x Float
forall t. V1 t -> t
unV1 V3 (V1 (S x Float))
b)
mul_14_41mm :: V1 (V4 (S x Float)) -> V4 (V1 (S x Float)) -> V1 (V1 (S x Float))
mul_14_41mm :: V1 (V4 (S x Float)) -> V4 (V1 (S x Float)) -> V1 (V1 (S x Float))
mul_14_41mm V1 (V4 (S x Float))
a V4 (V1 (S x Float))
b = V1 (S x Float) -> V1 (V1 (S x Float))
forall a. a -> V1 a
V1 (V1 (S x Float) -> V1 (V1 (S x Float)))
-> V1 (S x Float) -> V1 (V1 (S x Float))
forall a b. (a -> b) -> a -> b
$ S x Float -> V1 (S x Float)
forall a. a -> V1 a
V1 (S x Float -> V1 (S x Float)) -> S x Float -> V1 (S x Float)
forall a b. (a -> b) -> a -> b
$ String -> S x (V4 Float) -> S x (V4 Float) -> S x Float
forall c x y. String -> S c x -> S c y -> S c Float
fun2f String
"dot" (V4 (S x Float) -> S x (V4 Float)
forall x. V4 (S x Float) -> S x (V4 Float)
fromVec4 (V4 (S x Float) -> S x (V4 Float))
-> V4 (S x Float) -> S x (V4 Float)
forall a b. (a -> b) -> a -> b
$ V1 (V4 (S x Float)) -> V4 (S x Float)
forall t. V1 t -> t
unV1 V1 (V4 (S x Float))
a) (V4 (S x Float) -> S x (V4 Float)
forall x. V4 (S x Float) -> S x (V4 Float)
fromVec4 (V4 (S x Float) -> S x (V4 Float))
-> V4 (S x Float) -> S x (V4 Float)
forall a b. (a -> b) -> a -> b
$ (V1 (S x Float) -> S x Float)
-> V4 (V1 (S x Float)) -> V4 (S x Float)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap V1 (S x Float) -> S x Float
forall t. V1 t -> t
unV1 V4 (V1 (S x Float))
b)
{-# RULES "mul_21_12" outer = mul_21_12 #-}
{-# RULES "mul_21_13" outer = mul_21_13 #-}
{-# RULES "mul_21_14" outer = mul_21_14 #-}
{-# RULES "mul_31_12" outer = mul_31_12 #-}
{-# RULES "mul_31_13" outer = mul_31_13 #-}
{-# RULES "mul_31_14" outer = mul_31_14 #-}
{-# RULES "mul_41_12" outer = mul_41_12 #-}
{-# RULES "mul_41_13" outer = mul_41_13 #-}
{-# RULES "mul_41_14" outer = mul_41_14 #-}
mul_21_12 :: V2 (S x Float) -> V2 (S x Float) -> V2 (V2 (S x Float))
mul_21_12 :: V2 (S x Float) -> V2 (S x Float) -> V2 (V2 (S x Float))
mul_21_12 V2 (S x Float)
a V2 (S x Float)
b = (Int, S x Float -> V2 (S x Float))
-> (Int, S x Float -> V2 (S x Float))
-> S x (V2 Float)
-> S x (V2 Float)
-> V2 (V2 (S x Float))
forall (f :: * -> *) c z a b x y.
Functor f =>
(Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
outerToM (Int, S x Float -> V2 (S x Float))
forall a c a. Num a => (a, S c a -> V2 (S c a))
d2 (Int, S x Float -> V2 (S x Float))
forall a c a. Num a => (a, S c a -> V2 (S c a))
d2 (V2 (S x Float) -> S x (V2 Float)
forall x. V2 (S x Float) -> S x (V2 Float)
fromVec2 V2 (S x Float)
b) (V2 (S x Float) -> S x (V2 Float)
forall x. V2 (S x Float) -> S x (V2 Float)
fromVec2 V2 (S x Float)
a)
mul_21_13 :: V2 (S x Float) -> V3 (S x Float) -> V2 (V3 (S x Float))
mul_21_13 :: V2 (S x Float) -> V3 (S x Float) -> V2 (V3 (S x Float))
mul_21_13 V2 (S x Float)
a V3 (S x Float)
b = (Int, S x Float -> V2 (S x Float))
-> (Int, S x Float -> V3 (S x Float))
-> S x (V3 Float)
-> S x (V2 Float)
-> V2 (V3 (S x Float))
forall (f :: * -> *) c z a b x y.
Functor f =>
(Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
outerToM (Int, S x Float -> V2 (S x Float))
forall a c a. Num a => (a, S c a -> V2 (S c a))
d2 (Int, S x Float -> V3 (S x Float))
forall a c a. Num a => (a, S c a -> V3 (S c a))
d3 (V3 (S x Float) -> S x (V3 Float)
forall x. V3 (S x Float) -> S x (V3 Float)
fromVec3 V3 (S x Float)
b) (V2 (S x Float) -> S x (V2 Float)
forall x. V2 (S x Float) -> S x (V2 Float)
fromVec2 V2 (S x Float)
a)
mul_21_14 :: V2 (S x Float) -> V4 (S x Float) -> V2 (V4 (S x Float))
mul_21_14 :: V2 (S x Float) -> V4 (S x Float) -> V2 (V4 (S x Float))
mul_21_14 V2 (S x Float)
a V4 (S x Float)
b = (Int, S x Float -> V2 (S x Float))
-> (Int, S x Float -> V4 (S x Float))
-> S x (V4 Float)
-> S x (V2 Float)
-> V2 (V4 (S x Float))
forall (f :: * -> *) c z a b x y.
Functor f =>
(Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
outerToM (Int, S x Float -> V2 (S x Float))
forall a c a. Num a => (a, S c a -> V2 (S c a))
d2 (Int, S x Float -> V4 (S x Float))
forall a c a. Num a => (a, S c a -> V4 (S c a))
d4 (V4 (S x Float) -> S x (V4 Float)
forall x. V4 (S x Float) -> S x (V4 Float)
fromVec4 V4 (S x Float)
b) (V2 (S x Float) -> S x (V2 Float)
forall x. V2 (S x Float) -> S x (V2 Float)
fromVec2 V2 (S x Float)
a)
mul_31_12 :: V3 (S x Float) -> V2 (S x Float) -> V3 (V2 (S x Float))
mul_31_12 :: V3 (S x Float) -> V2 (S x Float) -> V3 (V2 (S x Float))
mul_31_12 V3 (S x Float)
a V2 (S x Float)
b = (Int, S x Float -> V3 (S x Float))
-> (Int, S x Float -> V2 (S x Float))
-> S x (V2 Float)
-> S x (V3 Float)
-> V3 (V2 (S x Float))
forall (f :: * -> *) c z a b x y.
Functor f =>
(Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
outerToM (Int, S x Float -> V3 (S x Float))
forall a c a. Num a => (a, S c a -> V3 (S c a))
d3 (Int, S x Float -> V2 (S x Float))
forall a c a. Num a => (a, S c a -> V2 (S c a))
d2 (V2 (S x Float) -> S x (V2 Float)
forall x. V2 (S x Float) -> S x (V2 Float)
fromVec2 V2 (S x Float)
b) (V3 (S x Float) -> S x (V3 Float)
forall x. V3 (S x Float) -> S x (V3 Float)
fromVec3 V3 (S x Float)
a)
mul_31_13 :: V3 (S x Float) -> V3 (S x Float) -> V3 (V3 (S x Float))
mul_31_13 :: V3 (S x Float) -> V3 (S x Float) -> V3 (V3 (S x Float))
mul_31_13 V3 (S x Float)
a V3 (S x Float)
b = (Int, S x Float -> V3 (S x Float))
-> (Int, S x Float -> V3 (S x Float))
-> S x (V3 Float)
-> S x (V3 Float)
-> V3 (V3 (S x Float))
forall (f :: * -> *) c z a b x y.
Functor f =>
(Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
outerToM (Int, S x Float -> V3 (S x Float))
forall a c a. Num a => (a, S c a -> V3 (S c a))
d3 (Int, S x Float -> V3 (S x Float))
forall a c a. Num a => (a, S c a -> V3 (S c a))
d3 (V3 (S x Float) -> S x (V3 Float)
forall x. V3 (S x Float) -> S x (V3 Float)
fromVec3 V3 (S x Float)
b) (V3 (S x Float) -> S x (V3 Float)
forall x. V3 (S x Float) -> S x (V3 Float)
fromVec3 V3 (S x Float)
a)
mul_31_14 :: V3 (S x Float) -> V4 (S x Float) -> V3 (V4 (S x Float))
mul_31_14 :: V3 (S x Float) -> V4 (S x Float) -> V3 (V4 (S x Float))
mul_31_14 V3 (S x Float)
a V4 (S x Float)
b = (Int, S x Float -> V3 (S x Float))
-> (Int, S x Float -> V4 (S x Float))
-> S x (V4 Float)
-> S x (V3 Float)
-> V3 (V4 (S x Float))
forall (f :: * -> *) c z a b x y.
Functor f =>
(Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
outerToM (Int, S x Float -> V3 (S x Float))
forall a c a. Num a => (a, S c a -> V3 (S c a))
d3 (Int, S x Float -> V4 (S x Float))
forall a c a. Num a => (a, S c a -> V4 (S c a))
d4 (V4 (S x Float) -> S x (V4 Float)
forall x. V4 (S x Float) -> S x (V4 Float)
fromVec4 V4 (S x Float)
b) (V3 (S x Float) -> S x (V3 Float)
forall x. V3 (S x Float) -> S x (V3 Float)
fromVec3 V3 (S x Float)
a)
mul_41_12 :: V4 (S x Float) -> V2 (S x Float) -> V4 (V2 (S x Float))
mul_41_12 :: V4 (S x Float) -> V2 (S x Float) -> V4 (V2 (S x Float))
mul_41_12 V4 (S x Float)
a V2 (S x Float)
b = (Int, S x Float -> V4 (S x Float))
-> (Int, S x Float -> V2 (S x Float))
-> S x (V2 Float)
-> S x (V4 Float)
-> V4 (V2 (S x Float))
forall (f :: * -> *) c z a b x y.
Functor f =>
(Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
outerToM (Int, S x Float -> V4 (S x Float))
forall a c a. Num a => (a, S c a -> V4 (S c a))
d4 (Int, S x Float -> V2 (S x Float))
forall a c a. Num a => (a, S c a -> V2 (S c a))
d2 (V2 (S x Float) -> S x (V2 Float)
forall x. V2 (S x Float) -> S x (V2 Float)
fromVec2 V2 (S x Float)
b) (V4 (S x Float) -> S x (V4 Float)
forall x. V4 (S x Float) -> S x (V4 Float)
fromVec4 V4 (S x Float)
a)
mul_41_13 :: V4 (S x Float) -> V3 (S x Float) -> V4 (V3 (S x Float))
mul_41_13 :: V4 (S x Float) -> V3 (S x Float) -> V4 (V3 (S x Float))
mul_41_13 V4 (S x Float)
a V3 (S x Float)
b = (Int, S x Float -> V4 (S x Float))
-> (Int, S x Float -> V3 (S x Float))
-> S x (V3 Float)
-> S x (V4 Float)
-> V4 (V3 (S x Float))
forall (f :: * -> *) c z a b x y.
Functor f =>
(Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
outerToM (Int, S x Float -> V4 (S x Float))
forall a c a. Num a => (a, S c a -> V4 (S c a))
d4 (Int, S x Float -> V3 (S x Float))
forall a c a. Num a => (a, S c a -> V3 (S c a))
d3 (V3 (S x Float) -> S x (V3 Float)
forall x. V3 (S x Float) -> S x (V3 Float)
fromVec3 V3 (S x Float)
b) (V4 (S x Float) -> S x (V4 Float)
forall x. V4 (S x Float) -> S x (V4 Float)
fromVec4 V4 (S x Float)
a)
mul_41_14 :: V4 (S x Float) -> V4 (S x Float) -> V4 (V4 (S x Float))
mul_41_14 :: V4 (S x Float) -> V4 (S x Float) -> V4 (V4 (S x Float))
mul_41_14 V4 (S x Float)
a V4 (S x Float)
b = (Int, S x Float -> V4 (S x Float))
-> (Int, S x Float -> V4 (S x Float))
-> S x (V4 Float)
-> S x (V4 Float)
-> V4 (V4 (S x Float))
forall (f :: * -> *) c z a b x y.
Functor f =>
(Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
outerToM (Int, S x Float -> V4 (S x Float))
forall a c a. Num a => (a, S c a -> V4 (S c a))
d4 (Int, S x Float -> V4 (S x Float))
forall a c a. Num a => (a, S c a -> V4 (S c a))
d4 (V4 (S x Float) -> S x (V4 Float)
forall x. V4 (S x Float) -> S x (V4 Float)
fromVec4 V4 (S x Float)
b) (V4 (S x Float) -> S x (V4 Float)
forall x. V4 (S x Float) -> S x (V4 Float)
fromVec4 V4 (S x Float)
a)
{-# RULES "mul_21_12m" (!*!) = mul_21_12m #-}
{-# RULES "mul_21_13m" (!*!) = mul_21_13m #-}
{-# RULES "mul_21_14m" (!*!) = mul_21_14m #-}
{-# RULES "mul_31_12m" (!*!) = mul_31_12m #-}
{-# RULES "mul_31_13m" (!*!) = mul_31_13m #-}
{-# RULES "mul_31_14m" (!*!) = mul_31_14m #-}
{-# RULES "mul_41_12m" (!*!) = mul_41_12m #-}
{-# RULES "mul_41_13m" (!*!) = mul_41_13m #-}
{-# RULES "mul_41_14m" (!*!) = mul_41_14m #-}
mul_21_12m :: V2 (V1 (S x Float)) -> V1 (V2 (S x Float)) -> V2 (V2 (S x Float))
mul_21_12m :: V2 (V1 (S x Float)) -> V1 (V2 (S x Float)) -> V2 (V2 (S x Float))
mul_21_12m V2 (V1 (S x Float))
a V1 (V2 (S x Float))
b = (Int, S x Float -> V2 (S x Float))
-> (Int, S x Float -> V2 (S x Float))
-> S x (V2 Float)
-> S x (V2 Float)
-> V2 (V2 (S x Float))
forall (f :: * -> *) c z a b x y.
Functor f =>
(Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
outerToM (Int, S x Float -> V2 (S x Float))
forall a c a. Num a => (a, S c a -> V2 (S c a))
d2 (Int, S x Float -> V2 (S x Float))
forall a c a. Num a => (a, S c a -> V2 (S c a))
d2 (V2 (S x Float) -> S x (V2 Float)
forall x. V2 (S x Float) -> S x (V2 Float)
fromVec2 (V2 (S x Float) -> S x (V2 Float))
-> V2 (S x Float) -> S x (V2 Float)
forall a b. (a -> b) -> a -> b
$ V1 (V2 (S x Float)) -> V2 (S x Float)
forall t. V1 t -> t
unV1 V1 (V2 (S x Float))
b) (V2 (S x Float) -> S x (V2 Float)
forall x. V2 (S x Float) -> S x (V2 Float)
fromVec2 (V2 (S x Float) -> S x (V2 Float))
-> V2 (S x Float) -> S x (V2 Float)
forall a b. (a -> b) -> a -> b
$ (V1 (S x Float) -> S x Float)
-> V2 (V1 (S x Float)) -> V2 (S x Float)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap V1 (S x Float) -> S x Float
forall t. V1 t -> t
unV1 V2 (V1 (S x Float))
a)
mul_21_13m :: V2 (V1 (S x Float)) -> V1 (V3 (S x Float)) -> V2 (V3 (S x Float))
mul_21_13m :: V2 (V1 (S x Float)) -> V1 (V3 (S x Float)) -> V2 (V3 (S x Float))
mul_21_13m V2 (V1 (S x Float))
a V1 (V3 (S x Float))
b = (Int, S x Float -> V2 (S x Float))
-> (Int, S x Float -> V3 (S x Float))
-> S x (V3 Float)
-> S x (V2 Float)
-> V2 (V3 (S x Float))
forall (f :: * -> *) c z a b x y.
Functor f =>
(Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
outerToM (Int, S x Float -> V2 (S x Float))
forall a c a. Num a => (a, S c a -> V2 (S c a))
d2 (Int, S x Float -> V3 (S x Float))
forall a c a. Num a => (a, S c a -> V3 (S c a))
d3 (V3 (S x Float) -> S x (V3 Float)
forall x. V3 (S x Float) -> S x (V3 Float)
fromVec3 (V3 (S x Float) -> S x (V3 Float))
-> V3 (S x Float) -> S x (V3 Float)
forall a b. (a -> b) -> a -> b
$ V1 (V3 (S x Float)) -> V3 (S x Float)
forall t. V1 t -> t
unV1 V1 (V3 (S x Float))
b) (V2 (S x Float) -> S x (V2 Float)
forall x. V2 (S x Float) -> S x (V2 Float)
fromVec2 (V2 (S x Float) -> S x (V2 Float))
-> V2 (S x Float) -> S x (V2 Float)
forall a b. (a -> b) -> a -> b
$ (V1 (S x Float) -> S x Float)
-> V2 (V1 (S x Float)) -> V2 (S x Float)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap V1 (S x Float) -> S x Float
forall t. V1 t -> t
unV1 V2 (V1 (S x Float))
a)
mul_21_14m :: V2 (V1 (S x Float)) -> V1 (V4 (S x Float)) -> V2 (V4 (S x Float))
mul_21_14m :: V2 (V1 (S x Float)) -> V1 (V4 (S x Float)) -> V2 (V4 (S x Float))
mul_21_14m V2 (V1 (S x Float))
a V1 (V4 (S x Float))
b = (Int, S x Float -> V2 (S x Float))
-> (Int, S x Float -> V4 (S x Float))
-> S x (V4 Float)
-> S x (V2 Float)
-> V2 (V4 (S x Float))
forall (f :: * -> *) c z a b x y.
Functor f =>
(Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
outerToM (Int, S x Float -> V2 (S x Float))
forall a c a. Num a => (a, S c a -> V2 (S c a))
d2 (Int, S x Float -> V4 (S x Float))
forall a c a. Num a => (a, S c a -> V4 (S c a))
d4 (V4 (S x Float) -> S x (V4 Float)
forall x. V4 (S x Float) -> S x (V4 Float)
fromVec4 (V4 (S x Float) -> S x (V4 Float))
-> V4 (S x Float) -> S x (V4 Float)
forall a b. (a -> b) -> a -> b
$ V1 (V4 (S x Float)) -> V4 (S x Float)
forall t. V1 t -> t
unV1 V1 (V4 (S x Float))
b) (V2 (S x Float) -> S x (V2 Float)
forall x. V2 (S x Float) -> S x (V2 Float)
fromVec2 (V2 (S x Float) -> S x (V2 Float))
-> V2 (S x Float) -> S x (V2 Float)
forall a b. (a -> b) -> a -> b
$ (V1 (S x Float) -> S x Float)
-> V2 (V1 (S x Float)) -> V2 (S x Float)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap V1 (S x Float) -> S x Float
forall t. V1 t -> t
unV1 V2 (V1 (S x Float))
a)
mul_31_12m :: V3 (V1 (S x Float)) -> V1 (V2 (S x Float)) -> V3 (V2 (S x Float))
mul_31_12m :: V3 (V1 (S x Float)) -> V1 (V2 (S x Float)) -> V3 (V2 (S x Float))
mul_31_12m V3 (V1 (S x Float))
a V1 (V2 (S x Float))
b = (Int, S x Float -> V3 (S x Float))
-> (Int, S x Float -> V2 (S x Float))
-> S x (V2 Float)
-> S x (V3 Float)
-> V3 (V2 (S x Float))
forall (f :: * -> *) c z a b x y.
Functor f =>
(Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
outerToM (Int, S x Float -> V3 (S x Float))
forall a c a. Num a => (a, S c a -> V3 (S c a))
d3 (Int, S x Float -> V2 (S x Float))
forall a c a. Num a => (a, S c a -> V2 (S c a))
d2 (V2 (S x Float) -> S x (V2 Float)
forall x. V2 (S x Float) -> S x (V2 Float)
fromVec2 (V2 (S x Float) -> S x (V2 Float))
-> V2 (S x Float) -> S x (V2 Float)
forall a b. (a -> b) -> a -> b
$ V1 (V2 (S x Float)) -> V2 (S x Float)
forall t. V1 t -> t
unV1 V1 (V2 (S x Float))
b) (V3 (S x Float) -> S x (V3 Float)
forall x. V3 (S x Float) -> S x (V3 Float)
fromVec3 (V3 (S x Float) -> S x (V3 Float))
-> V3 (S x Float) -> S x (V3 Float)
forall a b. (a -> b) -> a -> b
$ (V1 (S x Float) -> S x Float)
-> V3 (V1 (S x Float)) -> V3 (S x Float)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap V1 (S x Float) -> S x Float
forall t. V1 t -> t
unV1 V3 (V1 (S x Float))
a)
mul_31_13m :: V3 (V1 (S x Float)) -> V1 (V3 (S x Float)) -> V3 (V3 (S x Float))
mul_31_13m :: V3 (V1 (S x Float)) -> V1 (V3 (S x Float)) -> V3 (V3 (S x Float))
mul_31_13m V3 (V1 (S x Float))
a V1 (V3 (S x Float))
b = (Int, S x Float -> V3 (S x Float))
-> (Int, S x Float -> V3 (S x Float))
-> S x (V3 Float)
-> S x (V3 Float)
-> V3 (V3 (S x Float))
forall (f :: * -> *) c z a b x y.
Functor f =>
(Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
outerToM (Int, S x Float -> V3 (S x Float))
forall a c a. Num a => (a, S c a -> V3 (S c a))
d3 (Int, S x Float -> V3 (S x Float))
forall a c a. Num a => (a, S c a -> V3 (S c a))
d3 (V3 (S x Float) -> S x (V3 Float)
forall x. V3 (S x Float) -> S x (V3 Float)
fromVec3 (V3 (S x Float) -> S x (V3 Float))
-> V3 (S x Float) -> S x (V3 Float)
forall a b. (a -> b) -> a -> b
$ V1 (V3 (S x Float)) -> V3 (S x Float)
forall t. V1 t -> t
unV1 V1 (V3 (S x Float))
b) (V3 (S x Float) -> S x (V3 Float)
forall x. V3 (S x Float) -> S x (V3 Float)
fromVec3 (V3 (S x Float) -> S x (V3 Float))
-> V3 (S x Float) -> S x (V3 Float)
forall a b. (a -> b) -> a -> b
$ (V1 (S x Float) -> S x Float)
-> V3 (V1 (S x Float)) -> V3 (S x Float)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap V1 (S x Float) -> S x Float
forall t. V1 t -> t
unV1 V3 (V1 (S x Float))
a)
mul_31_14m :: V3 (V1 (S x Float)) -> V1 (V4 (S x Float)) -> V3 (V4 (S x Float))
mul_31_14m :: V3 (V1 (S x Float)) -> V1 (V4 (S x Float)) -> V3 (V4 (S x Float))
mul_31_14m V3 (V1 (S x Float))
a V1 (V4 (S x Float))
b = (Int, S x Float -> V3 (S x Float))
-> (Int, S x Float -> V4 (S x Float))
-> S x (V4 Float)
-> S x (V3 Float)
-> V3 (V4 (S x Float))
forall (f :: * -> *) c z a b x y.
Functor f =>
(Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
outerToM (Int, S x Float -> V3 (S x Float))
forall a c a. Num a => (a, S c a -> V3 (S c a))
d3 (Int, S x Float -> V4 (S x Float))
forall a c a. Num a => (a, S c a -> V4 (S c a))
d4 (V4 (S x Float) -> S x (V4 Float)
forall x. V4 (S x Float) -> S x (V4 Float)
fromVec4 (V4 (S x Float) -> S x (V4 Float))
-> V4 (S x Float) -> S x (V4 Float)
forall a b. (a -> b) -> a -> b
$ V1 (V4 (S x Float)) -> V4 (S x Float)
forall t. V1 t -> t
unV1 V1 (V4 (S x Float))
b) (V3 (S x Float) -> S x (V3 Float)
forall x. V3 (S x Float) -> S x (V3 Float)
fromVec3 (V3 (S x Float) -> S x (V3 Float))
-> V3 (S x Float) -> S x (V3 Float)
forall a b. (a -> b) -> a -> b
$ (V1 (S x Float) -> S x Float)
-> V3 (V1 (S x Float)) -> V3 (S x Float)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap V1 (S x Float) -> S x Float
forall t. V1 t -> t
unV1 V3 (V1 (S x Float))
a)
mul_41_12m :: V4 (V1 (S x Float)) -> V1 (V2 (S x Float)) -> V4 (V2 (S x Float))
mul_41_12m :: V4 (V1 (S x Float)) -> V1 (V2 (S x Float)) -> V4 (V2 (S x Float))
mul_41_12m V4 (V1 (S x Float))
a V1 (V2 (S x Float))
b = (Int, S x Float -> V4 (S x Float))
-> (Int, S x Float -> V2 (S x Float))
-> S x (V2 Float)
-> S x (V4 Float)
-> V4 (V2 (S x Float))
forall (f :: * -> *) c z a b x y.
Functor f =>
(Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
outerToM (Int, S x Float -> V4 (S x Float))
forall a c a. Num a => (a, S c a -> V4 (S c a))
d4 (Int, S x Float -> V2 (S x Float))
forall a c a. Num a => (a, S c a -> V2 (S c a))
d2 (V2 (S x Float) -> S x (V2 Float)
forall x. V2 (S x Float) -> S x (V2 Float)
fromVec2 (V2 (S x Float) -> S x (V2 Float))
-> V2 (S x Float) -> S x (V2 Float)
forall a b. (a -> b) -> a -> b
$ V1 (V2 (S x Float)) -> V2 (S x Float)
forall t. V1 t -> t
unV1 V1 (V2 (S x Float))
b) (V4 (S x Float) -> S x (V4 Float)
forall x. V4 (S x Float) -> S x (V4 Float)
fromVec4 (V4 (S x Float) -> S x (V4 Float))
-> V4 (S x Float) -> S x (V4 Float)
forall a b. (a -> b) -> a -> b
$ (V1 (S x Float) -> S x Float)
-> V4 (V1 (S x Float)) -> V4 (S x Float)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap V1 (S x Float) -> S x Float
forall t. V1 t -> t
unV1 V4 (V1 (S x Float))
a)
mul_41_13m :: V4 (V1 (S x Float)) -> V1 (V3 (S x Float)) -> V4 (V3 (S x Float))
mul_41_13m :: V4 (V1 (S x Float)) -> V1 (V3 (S x Float)) -> V4 (V3 (S x Float))
mul_41_13m V4 (V1 (S x Float))
a V1 (V3 (S x Float))
b = (Int, S x Float -> V4 (S x Float))
-> (Int, S x Float -> V3 (S x Float))
-> S x (V3 Float)
-> S x (V4 Float)
-> V4 (V3 (S x Float))
forall (f :: * -> *) c z a b x y.
Functor f =>
(Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
outerToM (Int, S x Float -> V4 (S x Float))
forall a c a. Num a => (a, S c a -> V4 (S c a))
d4 (Int, S x Float -> V3 (S x Float))
forall a c a. Num a => (a, S c a -> V3 (S c a))
d3 (V3 (S x Float) -> S x (V3 Float)
forall x. V3 (S x Float) -> S x (V3 Float)
fromVec3 (V3 (S x Float) -> S x (V3 Float))
-> V3 (S x Float) -> S x (V3 Float)
forall a b. (a -> b) -> a -> b
$ V1 (V3 (S x Float)) -> V3 (S x Float)
forall t. V1 t -> t
unV1 V1 (V3 (S x Float))
b) (V4 (S x Float) -> S x (V4 Float)
forall x. V4 (S x Float) -> S x (V4 Float)
fromVec4 (V4 (S x Float) -> S x (V4 Float))
-> V4 (S x Float) -> S x (V4 Float)
forall a b. (a -> b) -> a -> b
$ (V1 (S x Float) -> S x Float)
-> V4 (V1 (S x Float)) -> V4 (S x Float)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap V1 (S x Float) -> S x Float
forall t. V1 t -> t
unV1 V4 (V1 (S x Float))
a)
mul_41_14m :: V4 (V1 (S x Float)) -> V1 (V4 (S x Float)) -> V4 (V4 (S x Float))
mul_41_14m :: V4 (V1 (S x Float)) -> V1 (V4 (S x Float)) -> V4 (V4 (S x Float))
mul_41_14m V4 (V1 (S x Float))
a V1 (V4 (S x Float))
b = (Int, S x Float -> V4 (S x Float))
-> (Int, S x Float -> V4 (S x Float))
-> S x (V4 Float)
-> S x (V4 Float)
-> V4 (V4 (S x Float))
forall (f :: * -> *) c z a b x y.
Functor f =>
(Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
outerToM (Int, S x Float -> V4 (S x Float))
forall a c a. Num a => (a, S c a -> V4 (S c a))
d4 (Int, S x Float -> V4 (S x Float))
forall a c a. Num a => (a, S c a -> V4 (S c a))
d4 (V4 (S x Float) -> S x (V4 Float)
forall x. V4 (S x Float) -> S x (V4 Float)
fromVec4 (V4 (S x Float) -> S x (V4 Float))
-> V4 (S x Float) -> S x (V4 Float)
forall a b. (a -> b) -> a -> b
$ V1 (V4 (S x Float)) -> V4 (S x Float)
forall t. V1 t -> t
unV1 V1 (V4 (S x Float))
b) (V4 (S x Float) -> S x (V4 Float)
forall x. V4 (S x Float) -> S x (V4 Float)
fromVec4 (V4 (S x Float) -> S x (V4 Float))
-> V4 (S x Float) -> S x (V4 Float)
forall a b. (a -> b) -> a -> b
$ (V1 (S x Float) -> S x Float)
-> V4 (V1 (S x Float)) -> V4 (S x Float)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap V1 (S x Float) -> S x Float
forall t. V1 t -> t
unV1 V4 (V1 (S x Float))
a)
{-# RULES "mul_12_22" (*!) = mul_12_22 #-}
{-# RULES "mul_13_32" (*!) = mul_13_32 #-}
{-# RULES "mul_14_42" (*!) = mul_14_42 #-}
{-# RULES "mul_12_23" (*!) = mul_12_23 #-}
{-# RULES "mul_13_33" (*!) = mul_13_33 #-}
{-# RULES "mul_14_43" (*!) = mul_14_43 #-}
{-# RULES "mul_12_24" (*!) = mul_12_24 #-}
{-# RULES "mul_13_34" (*!) = mul_13_34 #-}
{-# RULES "mul_14_44" (*!) = mul_14_44 #-}
mul_12_22 :: V2 (S x Float) -> V2 (V2 (S x Float)) -> V2 (S x Float)
mul_12_22 :: V2 (S x Float) -> V2 (V2 (S x Float)) -> V2 (S x Float)
mul_12_22 V2 (S x Float)
v V2 (V2 (S x Float))
m = S x (V2 (V2 Float)) -> S x (V2 Float) -> V2 (S x Float)
forall c x y a. S c x -> S c y -> V2 (S c a)
mulToV2 (V2 (V2 (S x Float)) -> S x (V2 (V2 Float))
forall x. V2 (V2 (S x Float)) -> S x (V2 (V2 Float))
fromMat22 V2 (V2 (S x Float))
m) (V2 (S x Float) -> S x (V2 Float)
forall x. V2 (S x Float) -> S x (V2 Float)
fromVec2 V2 (S x Float)
v)
mul_13_32 :: V3 (S x Float) -> V3 (V2 (S x Float)) -> V2 (S x Float)
mul_13_32 :: V3 (S x Float) -> V3 (V2 (S x Float)) -> V2 (S x Float)
mul_13_32 V3 (S x Float)
v V3 (V2 (S x Float))
m = S x (V3 (V2 Float)) -> S x (V3 Float) -> V2 (S x Float)
forall c x y a. S c x -> S c y -> V2 (S c a)
mulToV2 (V3 (V2 (S x Float)) -> S x (V3 (V2 Float))
forall x. V3 (V2 (S x Float)) -> S x (V3 (V2 Float))
fromMat32 V3 (V2 (S x Float))
m) (V3 (S x Float) -> S x (V3 Float)
forall x. V3 (S x Float) -> S x (V3 Float)
fromVec3 V3 (S x Float)
v)
mul_14_42 :: V4 (S x Float) -> V4 (V2 (S x Float)) -> V2 (S x Float)
mul_14_42 :: V4 (S x Float) -> V4 (V2 (S x Float)) -> V2 (S x Float)
mul_14_42 V4 (S x Float)
v V4 (V2 (S x Float))
m = S x (V4 (V2 Float)) -> S x (V4 Float) -> V2 (S x Float)
forall c x y a. S c x -> S c y -> V2 (S c a)
mulToV2 (V4 (V2 (S x Float)) -> S x (V4 (V2 Float))
forall x. V4 (V2 (S x Float)) -> S x (V4 (V2 Float))
fromMat42 V4 (V2 (S x Float))
m) (V4 (S x Float) -> S x (V4 Float)
forall x. V4 (S x Float) -> S x (V4 Float)
fromVec4 V4 (S x Float)
v)
mul_12_23 :: V2 (S x Float) -> V2 (V3 (S x Float)) -> V3 (S x Float)
mul_12_23 :: V2 (S x Float) -> V2 (V3 (S x Float)) -> V3 (S x Float)
mul_12_23 V2 (S x Float)
v V2 (V3 (S x Float))
m = S x (V2 (V3 Float)) -> S x (V2 Float) -> V3 (S x Float)
forall c x y a. S c x -> S c y -> V3 (S c a)
mulToV3 (V2 (V3 (S x Float)) -> S x (V2 (V3 Float))
forall x. V2 (V3 (S x Float)) -> S x (V2 (V3 Float))
fromMat23 V2 (V3 (S x Float))
m) (V2 (S x Float) -> S x (V2 Float)
forall x. V2 (S x Float) -> S x (V2 Float)
fromVec2 V2 (S x Float)
v)
mul_13_33 :: V3 (S x Float) -> V3 (V3 (S x Float)) -> V3 (S x Float)
mul_13_33 :: V3 (S x Float) -> V3 (V3 (S x Float)) -> V3 (S x Float)
mul_13_33 V3 (S x Float)
v V3 (V3 (S x Float))
m = S x (V3 (V3 Float)) -> S x (V3 Float) -> V3 (S x Float)
forall c x y a. S c x -> S c y -> V3 (S c a)
mulToV3 (V3 (V3 (S x Float)) -> S x (V3 (V3 Float))
forall x. V3 (V3 (S x Float)) -> S x (V3 (V3 Float))
fromMat33 V3 (V3 (S x Float))
m) (V3 (S x Float) -> S x (V3 Float)
forall x. V3 (S x Float) -> S x (V3 Float)
fromVec3 V3 (S x Float)
v)
mul_14_43 :: V4 (S x Float) -> V4 (V3 (S x Float)) -> V3 (S x Float)
mul_14_43 :: V4 (S x Float) -> V4 (V3 (S x Float)) -> V3 (S x Float)
mul_14_43 V4 (S x Float)
v V4 (V3 (S x Float))
m = S x (V4 (V3 Float)) -> S x (V4 Float) -> V3 (S x Float)
forall c x y a. S c x -> S c y -> V3 (S c a)
mulToV3 (V4 (V3 (S x Float)) -> S x (V4 (V3 Float))
forall x. V4 (V3 (S x Float)) -> S x (V4 (V3 Float))
fromMat43 V4 (V3 (S x Float))
m) (V4 (S x Float) -> S x (V4 Float)
forall x. V4 (S x Float) -> S x (V4 Float)
fromVec4 V4 (S x Float)
v)
mul_12_24 :: V2 (S x Float) -> V2 (V4 (S x Float)) -> V4 (S x Float)
mul_12_24 :: V2 (S x Float) -> V2 (V4 (S x Float)) -> V4 (S x Float)
mul_12_24 V2 (S x Float)
v V2 (V4 (S x Float))
m = S x (V2 (V4 Float)) -> S x (V2 Float) -> V4 (S x Float)
forall c x y a. S c x -> S c y -> V4 (S c a)
mulToV4 (V2 (V4 (S x Float)) -> S x (V2 (V4 Float))
forall x. V2 (V4 (S x Float)) -> S x (V2 (V4 Float))
fromMat24 V2 (V4 (S x Float))
m) (V2 (S x Float) -> S x (V2 Float)
forall x. V2 (S x Float) -> S x (V2 Float)
fromVec2 V2 (S x Float)
v)
mul_13_34 :: V3 (S x Float) -> V3 (V4 (S x Float)) -> V4 (S x Float)
mul_13_34 :: V3 (S x Float) -> V3 (V4 (S x Float)) -> V4 (S x Float)
mul_13_34 V3 (S x Float)
v V3 (V4 (S x Float))
m = S x (V3 (V4 Float)) -> S x (V3 Float) -> V4 (S x Float)
forall c x y a. S c x -> S c y -> V4 (S c a)
mulToV4 (V3 (V4 (S x Float)) -> S x (V3 (V4 Float))
forall x. V3 (V4 (S x Float)) -> S x (V3 (V4 Float))
fromMat34 V3 (V4 (S x Float))
m) (V3 (S x Float) -> S x (V3 Float)
forall x. V3 (S x Float) -> S x (V3 Float)
fromVec3 V3 (S x Float)
v)
mul_14_44 :: V4 (S x Float) -> V4 (V4 (S x Float)) -> V4 (S x Float)
mul_14_44 :: V4 (S x Float) -> V4 (V4 (S x Float)) -> V4 (S x Float)
mul_14_44 V4 (S x Float)
v V4 (V4 (S x Float))
m = S x (V4 (V4 Float)) -> S x (V4 Float) -> V4 (S x Float)
forall c x y a. S c x -> S c y -> V4 (S c a)
mulToV4 (V4 (V4 (S x Float)) -> S x (V4 (V4 Float))
forall x. V4 (V4 (S x Float)) -> S x (V4 (V4 Float))
fromMat44 V4 (V4 (S x Float))
m) (V4 (S x Float) -> S x (V4 Float)
forall x. V4 (S x Float) -> S x (V4 Float)
fromVec4 V4 (S x Float)
v)
{-# RULES "mul_12_22m" (!*!) = mul_12_22m #-}
{-# RULES "mul_13_32m" (!*!) = mul_13_32m #-}
{-# RULES "mul_14_42m" (!*!) = mul_14_42m #-}
{-# RULES "mul_12_23m" (!*!) = mul_12_23m #-}
{-# RULES "mul_13_33m" (!*!) = mul_13_33m #-}
{-# RULES "mul_14_43m" (!*!) = mul_14_43m #-}
{-# RULES "mul_12_24m" (!*!) = mul_12_24m #-}
{-# RULES "mul_13_34m" (!*!) = mul_13_34m #-}
{-# RULES "mul_14_44m" (!*!) = mul_14_44m #-}
mul_12_22m :: V1 (V2 (S x Float)) -> V2 (V2 (S x Float)) -> V1 (V2 (S x Float))
mul_12_22m :: V1 (V2 (S x Float)) -> V2 (V2 (S x Float)) -> V1 (V2 (S x Float))
mul_12_22m V1 (V2 (S x Float))
v V2 (V2 (S x Float))
m = V2 (S x Float) -> V1 (V2 (S x Float))
forall a. a -> V1 a
V1 (V2 (S x Float) -> V1 (V2 (S x Float)))
-> V2 (S x Float) -> V1 (V2 (S x Float))
forall a b. (a -> b) -> a -> b
$ S x (V2 (V2 Float)) -> S x (V2 Float) -> V2 (S x Float)
forall c x y a. S c x -> S c y -> V2 (S c a)
mulToV2 (V2 (V2 (S x Float)) -> S x (V2 (V2 Float))
forall x. V2 (V2 (S x Float)) -> S x (V2 (V2 Float))
fromMat22 V2 (V2 (S x Float))
m) (V2 (S x Float) -> S x (V2 Float)
forall x. V2 (S x Float) -> S x (V2 Float)
fromVec2 (V2 (S x Float) -> S x (V2 Float))
-> V2 (S x Float) -> S x (V2 Float)
forall a b. (a -> b) -> a -> b
$ V1 (V2 (S x Float)) -> V2 (S x Float)
forall t. V1 t -> t
unV1 V1 (V2 (S x Float))
v)
mul_13_32m :: V1 (V3 (S x Float)) -> V3 (V2 (S x Float)) -> V1 (V2 (S x Float))
mul_13_32m :: V1 (V3 (S x Float)) -> V3 (V2 (S x Float)) -> V1 (V2 (S x Float))
mul_13_32m V1 (V3 (S x Float))
v V3 (V2 (S x Float))
m = V2 (S x Float) -> V1 (V2 (S x Float))
forall a. a -> V1 a
V1 (V2 (S x Float) -> V1 (V2 (S x Float)))
-> V2 (S x Float) -> V1 (V2 (S x Float))
forall a b. (a -> b) -> a -> b
$ S x (V3 (V2 Float)) -> S x (V3 Float) -> V2 (S x Float)
forall c x y a. S c x -> S c y -> V2 (S c a)
mulToV2 (V3 (V2 (S x Float)) -> S x (V3 (V2 Float))
forall x. V3 (V2 (S x Float)) -> S x (V3 (V2 Float))
fromMat32 V3 (V2 (S x Float))
m) (V3 (S x Float) -> S x (V3 Float)
forall x. V3 (S x Float) -> S x (V3 Float)
fromVec3 (V3 (S x Float) -> S x (V3 Float))
-> V3 (S x Float) -> S x (V3 Float)
forall a b. (a -> b) -> a -> b
$ V1 (V3 (S x Float)) -> V3 (S x Float)
forall t. V1 t -> t
unV1 V1 (V3 (S x Float))
v)
mul_14_42m :: V1 (V4 (S x Float)) -> V4 (V2 (S x Float)) -> V1 (V2 (S x Float))
mul_14_42m :: V1 (V4 (S x Float)) -> V4 (V2 (S x Float)) -> V1 (V2 (S x Float))
mul_14_42m V1 (V4 (S x Float))
v V4 (V2 (S x Float))
m = V2 (S x Float) -> V1 (V2 (S x Float))
forall a. a -> V1 a
V1 (V2 (S x Float) -> V1 (V2 (S x Float)))
-> V2 (S x Float) -> V1 (V2 (S x Float))
forall a b. (a -> b) -> a -> b
$ S x (V4 (V2 Float)) -> S x (V4 Float) -> V2 (S x Float)
forall c x y a. S c x -> S c y -> V2 (S c a)
mulToV2 (V4 (V2 (S x Float)) -> S x (V4 (V2 Float))
forall x. V4 (V2 (S x Float)) -> S x (V4 (V2 Float))
fromMat42 V4 (V2 (S x Float))
m) (V4 (S x Float) -> S x (V4 Float)
forall x. V4 (S x Float) -> S x (V4 Float)
fromVec4 (V4 (S x Float) -> S x (V4 Float))
-> V4 (S x Float) -> S x (V4 Float)
forall a b. (a -> b) -> a -> b
$ V1 (V4 (S x Float)) -> V4 (S x Float)
forall t. V1 t -> t
unV1 V1 (V4 (S x Float))
v)
mul_12_23m :: V1 (V2 (S x Float)) -> V2 (V3 (S x Float)) -> V1 (V3 (S x Float))
mul_12_23m :: V1 (V2 (S x Float)) -> V2 (V3 (S x Float)) -> V1 (V3 (S x Float))
mul_12_23m V1 (V2 (S x Float))
v V2 (V3 (S x Float))
m = V3 (S x Float) -> V1 (V3 (S x Float))
forall a. a -> V1 a
V1 (V3 (S x Float) -> V1 (V3 (S x Float)))
-> V3 (S x Float) -> V1 (V3 (S x Float))
forall a b. (a -> b) -> a -> b
$ S x (V2 (V3 Float)) -> S x (V2 Float) -> V3 (S x Float)
forall c x y a. S c x -> S c y -> V3 (S c a)
mulToV3 (V2 (V3 (S x Float)) -> S x (V2 (V3 Float))
forall x. V2 (V3 (S x Float)) -> S x (V2 (V3 Float))
fromMat23 V2 (V3 (S x Float))
m) (V2 (S x Float) -> S x (V2 Float)
forall x. V2 (S x Float) -> S x (V2 Float)
fromVec2 (V2 (S x Float) -> S x (V2 Float))
-> V2 (S x Float) -> S x (V2 Float)
forall a b. (a -> b) -> a -> b
$ V1 (V2 (S x Float)) -> V2 (S x Float)
forall t. V1 t -> t
unV1 V1 (V2 (S x Float))
v)
mul_13_33m :: V1 (V3 (S x Float)) -> V3 (V3 (S x Float)) -> V1 (V3 (S x Float))
mul_13_33m :: V1 (V3 (S x Float)) -> V3 (V3 (S x Float)) -> V1 (V3 (S x Float))
mul_13_33m V1 (V3 (S x Float))
v V3 (V3 (S x Float))
m = V3 (S x Float) -> V1 (V3 (S x Float))
forall a. a -> V1 a
V1 (V3 (S x Float) -> V1 (V3 (S x Float)))
-> V3 (S x Float) -> V1 (V3 (S x Float))
forall a b. (a -> b) -> a -> b
$ S x (V3 (V3 Float)) -> S x (V3 Float) -> V3 (S x Float)
forall c x y a. S c x -> S c y -> V3 (S c a)
mulToV3 (V3 (V3 (S x Float)) -> S x (V3 (V3 Float))
forall x. V3 (V3 (S x Float)) -> S x (V3 (V3 Float))
fromMat33 V3 (V3 (S x Float))
m) (V3 (S x Float) -> S x (V3 Float)
forall x. V3 (S x Float) -> S x (V3 Float)
fromVec3 (V3 (S x Float) -> S x (V3 Float))
-> V3 (S x Float) -> S x (V3 Float)
forall a b. (a -> b) -> a -> b
$ V1 (V3 (S x Float)) -> V3 (S x Float)
forall t. V1 t -> t
unV1 V1 (V3 (S x Float))
v)
mul_14_43m :: V1 (V4 (S x Float)) -> V4 (V3 (S x Float)) -> V1 (V3 (S x Float))
mul_14_43m :: V1 (V4 (S x Float)) -> V4 (V3 (S x Float)) -> V1 (V3 (S x Float))
mul_14_43m V1 (V4 (S x Float))
v V4 (V3 (S x Float))
m = V3 (S x Float) -> V1 (V3 (S x Float))
forall a. a -> V1 a
V1 (V3 (S x Float) -> V1 (V3 (S x Float)))
-> V3 (S x Float) -> V1 (V3 (S x Float))
forall a b. (a -> b) -> a -> b
$ S x (V4 (V3 Float)) -> S x (V4 Float) -> V3 (S x Float)
forall c x y a. S c x -> S c y -> V3 (S c a)
mulToV3 (V4 (V3 (S x Float)) -> S x (V4 (V3 Float))
forall x. V4 (V3 (S x Float)) -> S x (V4 (V3 Float))
fromMat43 V4 (V3 (S x Float))
m) (V4 (S x Float) -> S x (V4 Float)
forall x. V4 (S x Float) -> S x (V4 Float)
fromVec4 (V4 (S x Float) -> S x (V4 Float))
-> V4 (S x Float) -> S x (V4 Float)
forall a b. (a -> b) -> a -> b
$ V1 (V4 (S x Float)) -> V4 (S x Float)
forall t. V1 t -> t
unV1 V1 (V4 (S x Float))
v)
mul_12_24m :: V1 (V2 (S x Float)) -> V2 (V4 (S x Float)) -> V1 (V4 (S x Float))
mul_12_24m :: V1 (V2 (S x Float)) -> V2 (V4 (S x Float)) -> V1 (V4 (S x Float))
mul_12_24m V1 (V2 (S x Float))
v V2 (V4 (S x Float))
m = V4 (S x Float) -> V1 (V4 (S x Float))
forall a. a -> V1 a
V1 (V4 (S x Float) -> V1 (V4 (S x Float)))
-> V4 (S x Float) -> V1 (V4 (S x Float))
forall a b. (a -> b) -> a -> b
$ S x (V2 (V4 Float)) -> S x (V2 Float) -> V4 (S x Float)
forall c x y a. S c x -> S c y -> V4 (S c a)
mulToV4 (V2 (V4 (S x Float)) -> S x (V2 (V4 Float))
forall x. V2 (V4 (S x Float)) -> S x (V2 (V4 Float))
fromMat24 V2 (V4 (S x Float))
m) (V2 (S x Float) -> S x (V2 Float)
forall x. V2 (S x Float) -> S x (V2 Float)
fromVec2 (V2 (S x Float) -> S x (V2 Float))
-> V2 (S x Float) -> S x (V2 Float)
forall a b. (a -> b) -> a -> b
$ V1 (V2 (S x Float)) -> V2 (S x Float)
forall t. V1 t -> t
unV1 V1 (V2 (S x Float))
v)
mul_13_34m :: V1 (V3 (S x Float)) -> V3 (V4 (S x Float)) -> V1 (V4 (S x Float))
mul_13_34m :: V1 (V3 (S x Float)) -> V3 (V4 (S x Float)) -> V1 (V4 (S x Float))
mul_13_34m V1 (V3 (S x Float))
v V3 (V4 (S x Float))
m = V4 (S x Float) -> V1 (V4 (S x Float))
forall a. a -> V1 a
V1 (V4 (S x Float) -> V1 (V4 (S x Float)))
-> V4 (S x Float) -> V1 (V4 (S x Float))
forall a b. (a -> b) -> a -> b
$ S x (V3 (V4 Float)) -> S x (V3 Float) -> V4 (S x Float)
forall c x y a. S c x -> S c y -> V4 (S c a)
mulToV4 (V3 (V4 (S x Float)) -> S x (V3 (V4 Float))
forall x. V3 (V4 (S x Float)) -> S x (V3 (V4 Float))
fromMat34 V3 (V4 (S x Float))
m) (V3 (S x Float) -> S x (V3 Float)
forall x. V3 (S x Float) -> S x (V3 Float)
fromVec3 (V3 (S x Float) -> S x (V3 Float))
-> V3 (S x Float) -> S x (V3 Float)
forall a b. (a -> b) -> a -> b
$ V1 (V3 (S x Float)) -> V3 (S x Float)
forall t. V1 t -> t
unV1 V1 (V3 (S x Float))
v)
mul_14_44m :: V1 (V4 (S x Float)) -> V4 (V4 (S x Float)) -> V1 (V4 (S x Float))
mul_14_44m :: V1 (V4 (S x Float)) -> V4 (V4 (S x Float)) -> V1 (V4 (S x Float))
mul_14_44m V1 (V4 (S x Float))
v V4 (V4 (S x Float))
m = V4 (S x Float) -> V1 (V4 (S x Float))
forall a. a -> V1 a
V1 (V4 (S x Float) -> V1 (V4 (S x Float)))
-> V4 (S x Float) -> V1 (V4 (S x Float))
forall a b. (a -> b) -> a -> b
$ S x (V4 (V4 Float)) -> S x (V4 Float) -> V4 (S x Float)
forall c x y a. S c x -> S c y -> V4 (S c a)
mulToV4 (V4 (V4 (S x Float)) -> S x (V4 (V4 Float))
forall x. V4 (V4 (S x Float)) -> S x (V4 (V4 Float))
fromMat44 V4 (V4 (S x Float))
m) (V4 (S x Float) -> S x (V4 Float)
forall x. V4 (S x Float) -> S x (V4 Float)
fromVec4 (V4 (S x Float) -> S x (V4 Float))
-> V4 (S x Float) -> S x (V4 Float)
forall a b. (a -> b) -> a -> b
$ V1 (V4 (S x Float)) -> V4 (S x Float)
forall t. V1 t -> t
unV1 V1 (V4 (S x Float))
v)
{-# RULES "mul_22_21" (!*) = mul_22_21 #-}
{-# RULES "mul_23_31" (!*) = mul_23_31 #-}
{-# RULES "mul_24_41" (!*) = mul_24_41 #-}
{-# RULES "mul_32_21" (!*) = mul_32_21 #-}
{-# RULES "mul_33_31" (!*) = mul_33_31 #-}
{-# RULES "mul_34_41" (!*) = mul_34_41 #-}
{-# RULES "mul_42_21" (!*) = mul_42_21 #-}
{-# RULES "mul_43_31" (!*) = mul_43_31 #-}
{-# RULES "mul_44_41" (!*) = mul_44_41 #-}
mul_22_21 :: V2 (V2 (S x Float)) -> V2 (S x Float) -> V2 (S x Float)
mul_22_21 :: V2 (V2 (S x Float)) -> V2 (S x Float) -> V2 (S x Float)
mul_22_21 V2 (V2 (S x Float))
m V2 (S x Float)
v = S x (V2 Float) -> S x (V2 (V2 Float)) -> V2 (S x Float)
forall c x y a. S c x -> S c y -> V2 (S c a)
mulToV2 (V2 (S x Float) -> S x (V2 Float)
forall x. V2 (S x Float) -> S x (V2 Float)
fromVec2 V2 (S x Float)
v) (V2 (V2 (S x Float)) -> S x (V2 (V2 Float))
forall x. V2 (V2 (S x Float)) -> S x (V2 (V2 Float))
fromMat22 V2 (V2 (S x Float))
m)
mul_23_31 :: V2 (V3 (S x Float)) -> V3 (S x Float) -> V2 (S x Float)
mul_23_31 :: V2 (V3 (S x Float)) -> V3 (S x Float) -> V2 (S x Float)
mul_23_31 V2 (V3 (S x Float))
m V3 (S x Float)
v = S x (V3 Float) -> S x (V2 (V3 Float)) -> V2 (S x Float)
forall c x y a. S c x -> S c y -> V2 (S c a)
mulToV2 (V3 (S x Float) -> S x (V3 Float)
forall x. V3 (S x Float) -> S x (V3 Float)
fromVec3 V3 (S x Float)
v) (V2 (V3 (S x Float)) -> S x (V2 (V3 Float))
forall x. V2 (V3 (S x Float)) -> S x (V2 (V3 Float))
fromMat23 V2 (V3 (S x Float))
m)
mul_24_41 :: V2 (V4 (S x Float)) -> V4 (S x Float) -> V2 (S x Float)
mul_24_41 :: V2 (V4 (S x Float)) -> V4 (S x Float) -> V2 (S x Float)
mul_24_41 V2 (V4 (S x Float))
m V4 (S x Float)
v = S x (V4 Float) -> S x (V2 (V4 Float)) -> V2 (S x Float)
forall c x y a. S c x -> S c y -> V2 (S c a)
mulToV2 (V4 (S x Float) -> S x (V4 Float)
forall x. V4 (S x Float) -> S x (V4 Float)
fromVec4 V4 (S x Float)
v) (V2 (V4 (S x Float)) -> S x (V2 (V4 Float))
forall x. V2 (V4 (S x Float)) -> S x (V2 (V4 Float))
fromMat24 V2 (V4 (S x Float))
m)
mul_32_21 :: V3 (V2 (S x Float)) -> V2 (S x Float) -> V3 (S x Float)
mul_32_21 :: V3 (V2 (S x Float)) -> V2 (S x Float) -> V3 (S x Float)
mul_32_21 V3 (V2 (S x Float))
m V2 (S x Float)
v = S x (V2 Float) -> S x (V3 (V2 Float)) -> V3 (S x Float)
forall c x y a. S c x -> S c y -> V3 (S c a)
mulToV3 (V2 (S x Float) -> S x (V2 Float)
forall x. V2 (S x Float) -> S x (V2 Float)
fromVec2 V2 (S x Float)
v) (V3 (V2 (S x Float)) -> S x (V3 (V2 Float))
forall x. V3 (V2 (S x Float)) -> S x (V3 (V2 Float))
fromMat32 V3 (V2 (S x Float))
m)
mul_33_31 :: V3 (V3 (S x Float)) -> V3 (S x Float) -> V3 (S x Float)
mul_33_31 :: V3 (V3 (S x Float)) -> V3 (S x Float) -> V3 (S x Float)
mul_33_31 V3 (V3 (S x Float))
m V3 (S x Float)
v = S x (V3 Float) -> S x (V3 (V3 Float)) -> V3 (S x Float)
forall c x y a. S c x -> S c y -> V3 (S c a)
mulToV3 (V3 (S x Float) -> S x (V3 Float)
forall x. V3 (S x Float) -> S x (V3 Float)
fromVec3 V3 (S x Float)
v) (V3 (V3 (S x Float)) -> S x (V3 (V3 Float))
forall x. V3 (V3 (S x Float)) -> S x (V3 (V3 Float))
fromMat33 V3 (V3 (S x Float))
m)
mul_34_41 :: V3 (V4 (S x Float)) -> V4 (S x Float) -> V3 (S x Float)
mul_34_41 :: V3 (V4 (S x Float)) -> V4 (S x Float) -> V3 (S x Float)
mul_34_41 V3 (V4 (S x Float))
m V4 (S x Float)
v = S x (V4 Float) -> S x (V3 (V4 Float)) -> V3 (S x Float)
forall c x y a. S c x -> S c y -> V3 (S c a)
mulToV3 (V4 (S x Float) -> S x (V4 Float)
forall x. V4 (S x Float) -> S x (V4 Float)
fromVec4 V4 (S x Float)
v) (V3 (V4 (S x Float)) -> S x (V3 (V4 Float))
forall x. V3 (V4 (S x Float)) -> S x (V3 (V4 Float))
fromMat34 V3 (V4 (S x Float))
m)
mul_42_21 :: V4 (V2 (S x Float)) -> V2 (S x Float) -> V4 (S x Float)
mul_42_21 :: V4 (V2 (S x Float)) -> V2 (S x Float) -> V4 (S x Float)
mul_42_21 V4 (V2 (S x Float))
m V2 (S x Float)
v = S x (V2 Float) -> S x (V4 (V2 Float)) -> V4 (S x Float)
forall c x y a. S c x -> S c y -> V4 (S c a)
mulToV4 (V2 (S x Float) -> S x (V2 Float)
forall x. V2 (S x Float) -> S x (V2 Float)
fromVec2 V2 (S x Float)
v) (V4 (V2 (S x Float)) -> S x (V4 (V2 Float))
forall x. V4 (V2 (S x Float)) -> S x (V4 (V2 Float))
fromMat42 V4 (V2 (S x Float))
m)
mul_43_31 :: V4 (V3 (S x Float)) -> V3 (S x Float) -> V4 (S x Float)
mul_43_31 :: V4 (V3 (S x Float)) -> V3 (S x Float) -> V4 (S x Float)
mul_43_31 V4 (V3 (S x Float))
m V3 (S x Float)
v = S x (V3 Float) -> S x (V4 (V3 Float)) -> V4 (S x Float)
forall c x y a. S c x -> S c y -> V4 (S c a)
mulToV4 (V3 (S x Float) -> S x (V3 Float)
forall x. V3 (S x Float) -> S x (V3 Float)
fromVec3 V3 (S x Float)
v) (V4 (V3 (S x Float)) -> S x (V4 (V3 Float))
forall x. V4 (V3 (S x Float)) -> S x (V4 (V3 Float))
fromMat43 V4 (V3 (S x Float))
m)
mul_44_41 :: V4 (V4 (S x Float)) -> V4 (S x Float) -> V4 (S x Float)
mul_44_41 :: V4 (V4 (S x Float)) -> V4 (S x Float) -> V4 (S x Float)
mul_44_41 V4 (V4 (S x Float))
m V4 (S x Float)
v = S x (V4 Float) -> S x (V4 (V4 Float)) -> V4 (S x Float)
forall c x y a. S c x -> S c y -> V4 (S c a)
mulToV4 (V4 (S x Float) -> S x (V4 Float)
forall x. V4 (S x Float) -> S x (V4 Float)
fromVec4 V4 (S x Float)
v) (V4 (V4 (S x Float)) -> S x (V4 (V4 Float))
forall x. V4 (V4 (S x Float)) -> S x (V4 (V4 Float))
fromMat44 V4 (V4 (S x Float))
m)
{-# RULES "mul_22_21m" (!*!) = mul_22_21m #-}
{-# RULES "mul_23_31m" (!*!) = mul_23_31m #-}
{-# RULES "mul_24_41m" (!*!) = mul_24_41m #-}
{-# RULES "mul_32_21m" (!*!) = mul_32_21m #-}
{-# RULES "mul_33_31m" (!*!) = mul_33_31m #-}
{-# RULES "mul_34_41m" (!*!) = mul_34_41m #-}
{-# RULES "mul_42_21m" (!*!) = mul_42_21m #-}
{-# RULES "mul_43_31m" (!*!) = mul_43_31m #-}
{-# RULES "mul_44_41m" (!*!) = mul_44_41m #-}
mul_22_21m :: V2 (V2 (S x Float)) -> V2 (V1 (S x Float)) -> V2 (V1 (S x Float))
mul_22_21m :: V2 (V2 (S x Float)) -> V2 (V1 (S x Float)) -> V2 (V1 (S x Float))
mul_22_21m V2 (V2 (S x Float))
m V2 (V1 (S x Float))
v = S x Float -> V1 (S x Float)
forall a. a -> V1 a
V1 (S x Float -> V1 (S x Float))
-> V2 (S x Float) -> V2 (V1 (S x Float))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> S x (V2 Float) -> S x (V2 (V2 Float)) -> V2 (S x Float)
forall c x y a. S c x -> S c y -> V2 (S c a)
mulToV2 (V2 (S x Float) -> S x (V2 Float)
forall x. V2 (S x Float) -> S x (V2 Float)
fromVec2 (V2 (S x Float) -> S x (V2 Float))
-> V2 (S x Float) -> S x (V2 Float)
forall a b. (a -> b) -> a -> b
$ (V1 (S x Float) -> S x Float)
-> V2 (V1 (S x Float)) -> V2 (S x Float)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap V1 (S x Float) -> S x Float
forall t. V1 t -> t
unV1 V2 (V1 (S x Float))
v) (V2 (V2 (S x Float)) -> S x (V2 (V2 Float))
forall x. V2 (V2 (S x Float)) -> S x (V2 (V2 Float))
fromMat22 V2 (V2 (S x Float))
m)
mul_23_31m :: V2 (V3 (S x Float)) -> V3 (V1 (S x Float)) -> V2 (V1 (S x Float))
mul_23_31m :: V2 (V3 (S x Float)) -> V3 (V1 (S x Float)) -> V2 (V1 (S x Float))
mul_23_31m V2 (V3 (S x Float))
m V3 (V1 (S x Float))
v = S x Float -> V1 (S x Float)
forall a. a -> V1 a
V1 (S x Float -> V1 (S x Float))
-> V2 (S x Float) -> V2 (V1 (S x Float))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> S x (V3 Float) -> S x (V2 (V3 Float)) -> V2 (S x Float)
forall c x y a. S c x -> S c y -> V2 (S c a)
mulToV2 (V3 (S x Float) -> S x (V3 Float)
forall x. V3 (S x Float) -> S x (V3 Float)
fromVec3 (V3 (S x Float) -> S x (V3 Float))
-> V3 (S x Float) -> S x (V3 Float)
forall a b. (a -> b) -> a -> b
$ (V1 (S x Float) -> S x Float)
-> V3 (V1 (S x Float)) -> V3 (S x Float)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap V1 (S x Float) -> S x Float
forall t. V1 t -> t
unV1 V3 (V1 (S x Float))
v) (V2 (V3 (S x Float)) -> S x (V2 (V3 Float))
forall x. V2 (V3 (S x Float)) -> S x (V2 (V3 Float))
fromMat23 V2 (V3 (S x Float))
m)
mul_24_41m :: V2 (V4 (S x Float)) -> V4 (V1 (S x Float)) -> V2 (V1 (S x Float))
mul_24_41m :: V2 (V4 (S x Float)) -> V4 (V1 (S x Float)) -> V2 (V1 (S x Float))
mul_24_41m V2 (V4 (S x Float))
m V4 (V1 (S x Float))
v = S x Float -> V1 (S x Float)
forall a. a -> V1 a
V1 (S x Float -> V1 (S x Float))
-> V2 (S x Float) -> V2 (V1 (S x Float))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> S x (V4 Float) -> S x (V2 (V4 Float)) -> V2 (S x Float)
forall c x y a. S c x -> S c y -> V2 (S c a)
mulToV2 (V4 (S x Float) -> S x (V4 Float)
forall x. V4 (S x Float) -> S x (V4 Float)
fromVec4 (V4 (S x Float) -> S x (V4 Float))
-> V4 (S x Float) -> S x (V4 Float)
forall a b. (a -> b) -> a -> b
$ (V1 (S x Float) -> S x Float)
-> V4 (V1 (S x Float)) -> V4 (S x Float)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap V1 (S x Float) -> S x Float
forall t. V1 t -> t
unV1 V4 (V1 (S x Float))
v) (V2 (V4 (S x Float)) -> S x (V2 (V4 Float))
forall x. V2 (V4 (S x Float)) -> S x (V2 (V4 Float))
fromMat24 V2 (V4 (S x Float))
m)
mul_32_21m :: V3 (V2 (S x Float)) -> V2 (V1 (S x Float)) -> V3 (V1 (S x Float))
mul_32_21m :: V3 (V2 (S x Float)) -> V2 (V1 (S x Float)) -> V3 (V1 (S x Float))
mul_32_21m V3 (V2 (S x Float))
m V2 (V1 (S x Float))
v = S x Float -> V1 (S x Float)
forall a. a -> V1 a
V1 (S x Float -> V1 (S x Float))
-> V3 (S x Float) -> V3 (V1 (S x Float))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> S x (V2 Float) -> S x (V3 (V2 Float)) -> V3 (S x Float)
forall c x y a. S c x -> S c y -> V3 (S c a)
mulToV3 (V2 (S x Float) -> S x (V2 Float)
forall x. V2 (S x Float) -> S x (V2 Float)
fromVec2 (V2 (S x Float) -> S x (V2 Float))
-> V2 (S x Float) -> S x (V2 Float)
forall a b. (a -> b) -> a -> b
$ (V1 (S x Float) -> S x Float)
-> V2 (V1 (S x Float)) -> V2 (S x Float)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap V1 (S x Float) -> S x Float
forall t. V1 t -> t
unV1 V2 (V1 (S x Float))
v) (V3 (V2 (S x Float)) -> S x (V3 (V2 Float))
forall x. V3 (V2 (S x Float)) -> S x (V3 (V2 Float))
fromMat32 V3 (V2 (S x Float))
m)
mul_33_31m :: V3 (V3 (S x Float)) -> V3 (V1 (S x Float)) -> V3 (V1 (S x Float))
mul_33_31m :: V3 (V3 (S x Float)) -> V3 (V1 (S x Float)) -> V3 (V1 (S x Float))
mul_33_31m V3 (V3 (S x Float))
m V3 (V1 (S x Float))
v = S x Float -> V1 (S x Float)
forall a. a -> V1 a
V1 (S x Float -> V1 (S x Float))
-> V3 (S x Float) -> V3 (V1 (S x Float))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> S x (V3 Float) -> S x (V3 (V3 Float)) -> V3 (S x Float)
forall c x y a. S c x -> S c y -> V3 (S c a)
mulToV3 (V3 (S x Float) -> S x (V3 Float)
forall x. V3 (S x Float) -> S x (V3 Float)
fromVec3 (V3 (S x Float) -> S x (V3 Float))
-> V3 (S x Float) -> S x (V3 Float)
forall a b. (a -> b) -> a -> b
$ (V1 (S x Float) -> S x Float)
-> V3 (V1 (S x Float)) -> V3 (S x Float)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap V1 (S x Float) -> S x Float
forall t. V1 t -> t
unV1 V3 (V1 (S x Float))
v) (V3 (V3 (S x Float)) -> S x (V3 (V3 Float))
forall x. V3 (V3 (S x Float)) -> S x (V3 (V3 Float))
fromMat33 V3 (V3 (S x Float))
m)
mul_34_41m :: V3 (V4 (S x Float)) -> V4 (V1 (S x Float)) -> V3 (V1 (S x Float))
mul_34_41m :: V3 (V4 (S x Float)) -> V4 (V1 (S x Float)) -> V3 (V1 (S x Float))
mul_34_41m V3 (V4 (S x Float))
m V4 (V1 (S x Float))
v = S x Float -> V1 (S x Float)
forall a. a -> V1 a
V1 (S x Float -> V1 (S x Float))
-> V3 (S x Float) -> V3 (V1 (S x Float))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> S x (V4 Float) -> S x (V3 (V4 Float)) -> V3 (S x Float)
forall c x y a. S c x -> S c y -> V3 (S c a)
mulToV3 (V4 (S x Float) -> S x (V4 Float)
forall x. V4 (S x Float) -> S x (V4 Float)
fromVec4 (V4 (S x Float) -> S x (V4 Float))
-> V4 (S x Float) -> S x (V4 Float)
forall a b. (a -> b) -> a -> b
$ (V1 (S x Float) -> S x Float)
-> V4 (V1 (S x Float)) -> V4 (S x Float)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap V1 (S x Float) -> S x Float
forall t. V1 t -> t
unV1 V4 (V1 (S x Float))
v) (V3 (V4 (S x Float)) -> S x (V3 (V4 Float))
forall x. V3 (V4 (S x Float)) -> S x (V3 (V4 Float))
fromMat34 V3 (V4 (S x Float))
m)
mul_42_21m :: V4 (V2 (S x Float)) -> V2 (V1 (S x Float)) -> V4 (V1 (S x Float))
mul_42_21m :: V4 (V2 (S x Float)) -> V2 (V1 (S x Float)) -> V4 (V1 (S x Float))
mul_42_21m V4 (V2 (S x Float))
m V2 (V1 (S x Float))
v = S x Float -> V1 (S x Float)
forall a. a -> V1 a
V1 (S x Float -> V1 (S x Float))
-> V4 (S x Float) -> V4 (V1 (S x Float))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> S x (V2 Float) -> S x (V4 (V2 Float)) -> V4 (S x Float)
forall c x y a. S c x -> S c y -> V4 (S c a)
mulToV4 (V2 (S x Float) -> S x (V2 Float)
forall x. V2 (S x Float) -> S x (V2 Float)
fromVec2 (V2 (S x Float) -> S x (V2 Float))
-> V2 (S x Float) -> S x (V2 Float)
forall a b. (a -> b) -> a -> b
$ (V1 (S x Float) -> S x Float)
-> V2 (V1 (S x Float)) -> V2 (S x Float)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap V1 (S x Float) -> S x Float
forall t. V1 t -> t
unV1 V2 (V1 (S x Float))
v) (V4 (V2 (S x Float)) -> S x (V4 (V2 Float))
forall x. V4 (V2 (S x Float)) -> S x (V4 (V2 Float))
fromMat42 V4 (V2 (S x Float))
m)
mul_43_31m :: V4 (V3 (S x Float)) -> V3 (V1 (S x Float)) -> V4 (V1 (S x Float))
mul_43_31m :: V4 (V3 (S x Float)) -> V3 (V1 (S x Float)) -> V4 (V1 (S x Float))
mul_43_31m V4 (V3 (S x Float))
m V3 (V1 (S x Float))
v = S x Float -> V1 (S x Float)
forall a. a -> V1 a
V1 (S x Float -> V1 (S x Float))
-> V4 (S x Float) -> V4 (V1 (S x Float))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> S x (V3 Float) -> S x (V4 (V3 Float)) -> V4 (S x Float)
forall c x y a. S c x -> S c y -> V4 (S c a)
mulToV4 (V3 (S x Float) -> S x (V3 Float)
forall x. V3 (S x Float) -> S x (V3 Float)
fromVec3 (V3 (S x Float) -> S x (V3 Float))
-> V3 (S x Float) -> S x (V3 Float)
forall a b. (a -> b) -> a -> b
$ (V1 (S x Float) -> S x Float)
-> V3 (V1 (S x Float)) -> V3 (S x Float)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap V1 (S x Float) -> S x Float
forall t. V1 t -> t
unV1 V3 (V1 (S x Float))
v) (V4 (V3 (S x Float)) -> S x (V4 (V3 Float))
forall x. V4 (V3 (S x Float)) -> S x (V4 (V3 Float))
fromMat43 V4 (V3 (S x Float))
m)
mul_44_41m :: V4 (V4 (S x Float)) -> V4 (V1 (S x Float)) -> V4 (V1 (S x Float))
mul_44_41m :: V4 (V4 (S x Float)) -> V4 (V1 (S x Float)) -> V4 (V1 (S x Float))
mul_44_41m V4 (V4 (S x Float))
m V4 (V1 (S x Float))
v = S x Float -> V1 (S x Float)
forall a. a -> V1 a
V1 (S x Float -> V1 (S x Float))
-> V4 (S x Float) -> V4 (V1 (S x Float))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> S x (V4 Float) -> S x (V4 (V4 Float)) -> V4 (S x Float)
forall c x y a. S c x -> S c y -> V4 (S c a)
mulToV4 (V4 (S x Float) -> S x (V4 Float)
forall x. V4 (S x Float) -> S x (V4 Float)
fromVec4 (V4 (S x Float) -> S x (V4 Float))
-> V4 (S x Float) -> S x (V4 Float)
forall a b. (a -> b) -> a -> b
$ (V1 (S x Float) -> S x Float)
-> V4 (V1 (S x Float)) -> V4 (S x Float)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap V1 (S x Float) -> S x Float
forall t. V1 t -> t
unV1 V4 (V1 (S x Float))
v) (V4 (V4 (S x Float)) -> S x (V4 (V4 Float))
forall x. V4 (V4 (S x Float)) -> S x (V4 (V4 Float))
fromMat44 V4 (V4 (S x Float))
m)
{-# RULES "mul_22_22" (!*!) = mul_22_22 #-}
{-# RULES "mul_23_32" (!*!) = mul_23_32 #-}
{-# RULES "mul_24_42" (!*!) = mul_24_42 #-}
{-# RULES "mul_22_23" (!*!) = mul_22_23 #-}
{-# RULES "mul_23_33" (!*!) = mul_23_33 #-}
{-# RULES "mul_24_43" (!*!) = mul_24_43 #-}
{-# RULES "mul_22_24" (!*!) = mul_22_24 #-}
{-# RULES "mul_23_34" (!*!) = mul_23_34 #-}
{-# RULES "mul_24_44" (!*!) = mul_24_44 #-}
mul_22_22 :: V2 (V2 (S x Float)) -> V2 (V2 (S x Float)) -> V2 (V2 (S x Float))
mul_22_22 :: V2 (V2 (S x Float)) -> V2 (V2 (S x Float)) -> V2 (V2 (S x Float))
mul_22_22 V2 (V2 (S x Float))
a V2 (V2 (S x Float))
b = (Int, S x Float -> V2 (S x Float))
-> (Int, S x Float -> V2 (S x Float))
-> S x (V2 (V2 Float))
-> S x (V2 (V2 Float))
-> V2 (V2 (S x Float))
forall (f :: * -> *) c z a b x y.
Functor f =>
(Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
mulToM (Int, S x Float -> V2 (S x Float))
forall a c a. Num a => (a, S c a -> V2 (S c a))
d2 (Int, S x Float -> V2 (S x Float))
forall a c a. Num a => (a, S c a -> V2 (S c a))
d2 (V2 (V2 (S x Float)) -> S x (V2 (V2 Float))
forall x. V2 (V2 (S x Float)) -> S x (V2 (V2 Float))
fromMat22 V2 (V2 (S x Float))
b) (V2 (V2 (S x Float)) -> S x (V2 (V2 Float))
forall x. V2 (V2 (S x Float)) -> S x (V2 (V2 Float))
fromMat22 V2 (V2 (S x Float))
a)
mul_23_32 :: V2 (V3 (S x Float)) -> V3 (V2 (S x Float)) -> V2 (V2 (S x Float))
mul_23_32 :: V2 (V3 (S x Float)) -> V3 (V2 (S x Float)) -> V2 (V2 (S x Float))
mul_23_32 V2 (V3 (S x Float))
a V3 (V2 (S x Float))
b = (Int, S x Float -> V2 (S x Float))
-> (Int, S x Float -> V2 (S x Float))
-> S x (V3 (V2 Float))
-> S x (V2 (V3 Float))
-> V2 (V2 (S x Float))
forall (f :: * -> *) c z a b x y.
Functor f =>
(Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
mulToM (Int, S x Float -> V2 (S x Float))
forall a c a. Num a => (a, S c a -> V2 (S c a))
d2 (Int, S x Float -> V2 (S x Float))
forall a c a. Num a => (a, S c a -> V2 (S c a))
d2 (V3 (V2 (S x Float)) -> S x (V3 (V2 Float))
forall x. V3 (V2 (S x Float)) -> S x (V3 (V2 Float))
fromMat32 V3 (V2 (S x Float))
b) (V2 (V3 (S x Float)) -> S x (V2 (V3 Float))
forall x. V2 (V3 (S x Float)) -> S x (V2 (V3 Float))
fromMat23 V2 (V3 (S x Float))
a)
mul_24_42 :: V2 (V4 (S x Float)) -> V4 (V2 (S x Float)) -> V2 (V2 (S x Float))
mul_24_42 :: V2 (V4 (S x Float)) -> V4 (V2 (S x Float)) -> V2 (V2 (S x Float))
mul_24_42 V2 (V4 (S x Float))
a V4 (V2 (S x Float))
b = (Int, S x Float -> V2 (S x Float))
-> (Int, S x Float -> V2 (S x Float))
-> S x (V4 (V2 Float))
-> S x (V2 (V4 Float))
-> V2 (V2 (S x Float))
forall (f :: * -> *) c z a b x y.
Functor f =>
(Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
mulToM (Int, S x Float -> V2 (S x Float))
forall a c a. Num a => (a, S c a -> V2 (S c a))
d2 (Int, S x Float -> V2 (S x Float))
forall a c a. Num a => (a, S c a -> V2 (S c a))
d2 (V4 (V2 (S x Float)) -> S x (V4 (V2 Float))
forall x. V4 (V2 (S x Float)) -> S x (V4 (V2 Float))
fromMat42 V4 (V2 (S x Float))
b) (V2 (V4 (S x Float)) -> S x (V2 (V4 Float))
forall x. V2 (V4 (S x Float)) -> S x (V2 (V4 Float))
fromMat24 V2 (V4 (S x Float))
a)
mul_22_23 :: V2 (V2 (S x Float)) -> V2 (V3 (S x Float)) -> V2 (V3 (S x Float))
mul_22_23 :: V2 (V2 (S x Float)) -> V2 (V3 (S x Float)) -> V2 (V3 (S x Float))
mul_22_23 V2 (V2 (S x Float))
a V2 (V3 (S x Float))
b = (Int, S x Float -> V2 (S x Float))
-> (Int, S x Float -> V3 (S x Float))
-> S x (V2 (V3 Float))
-> S x (V2 (V2 Float))
-> V2 (V3 (S x Float))
forall (f :: * -> *) c z a b x y.
Functor f =>
(Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
mulToM (Int, S x Float -> V2 (S x Float))
forall a c a. Num a => (a, S c a -> V2 (S c a))
d2 (Int, S x Float -> V3 (S x Float))
forall a c a. Num a => (a, S c a -> V3 (S c a))
d3 (V2 (V3 (S x Float)) -> S x (V2 (V3 Float))
forall x. V2 (V3 (S x Float)) -> S x (V2 (V3 Float))
fromMat23 V2 (V3 (S x Float))
b) (V2 (V2 (S x Float)) -> S x (V2 (V2 Float))
forall x. V2 (V2 (S x Float)) -> S x (V2 (V2 Float))
fromMat22 V2 (V2 (S x Float))
a)
mul_23_33 :: V2 (V3 (S x Float)) -> V3 (V3 (S x Float)) -> V2 (V3 (S x Float))
mul_23_33 :: V2 (V3 (S x Float)) -> V3 (V3 (S x Float)) -> V2 (V3 (S x Float))
mul_23_33 V2 (V3 (S x Float))
a V3 (V3 (S x Float))
b = (Int, S x Float -> V2 (S x Float))
-> (Int, S x Float -> V3 (S x Float))
-> S x (V3 (V3 Float))
-> S x (V2 (V3 Float))
-> V2 (V3 (S x Float))
forall (f :: * -> *) c z a b x y.
Functor f =>
(Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
mulToM (Int, S x Float -> V2 (S x Float))
forall a c a. Num a => (a, S c a -> V2 (S c a))
d2 (Int, S x Float -> V3 (S x Float))
forall a c a. Num a => (a, S c a -> V3 (S c a))
d3 (V3 (V3 (S x Float)) -> S x (V3 (V3 Float))
forall x. V3 (V3 (S x Float)) -> S x (V3 (V3 Float))
fromMat33 V3 (V3 (S x Float))
b) (V2 (V3 (S x Float)) -> S x (V2 (V3 Float))
forall x. V2 (V3 (S x Float)) -> S x (V2 (V3 Float))
fromMat23 V2 (V3 (S x Float))
a)
mul_24_43 :: V2 (V4 (S x Float)) -> V4 (V3 (S x Float)) -> V2 (V3 (S x Float))
mul_24_43 :: V2 (V4 (S x Float)) -> V4 (V3 (S x Float)) -> V2 (V3 (S x Float))
mul_24_43 V2 (V4 (S x Float))
a V4 (V3 (S x Float))
b = (Int, S x Float -> V2 (S x Float))
-> (Int, S x Float -> V3 (S x Float))
-> S x (V4 (V3 Float))
-> S x (V2 (V4 Float))
-> V2 (V3 (S x Float))
forall (f :: * -> *) c z a b x y.
Functor f =>
(Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
mulToM (Int, S x Float -> V2 (S x Float))
forall a c a. Num a => (a, S c a -> V2 (S c a))
d2 (Int, S x Float -> V3 (S x Float))
forall a c a. Num a => (a, S c a -> V3 (S c a))
d3 (V4 (V3 (S x Float)) -> S x (V4 (V3 Float))
forall x. V4 (V3 (S x Float)) -> S x (V4 (V3 Float))
fromMat43 V4 (V3 (S x Float))
b) (V2 (V4 (S x Float)) -> S x (V2 (V4 Float))
forall x. V2 (V4 (S x Float)) -> S x (V2 (V4 Float))
fromMat24 V2 (V4 (S x Float))
a)
mul_22_24 :: V2 (V2 (S x Float)) -> V2 (V4 (S x Float)) -> V2 (V4 (S x Float))
mul_22_24 :: V2 (V2 (S x Float)) -> V2 (V4 (S x Float)) -> V2 (V4 (S x Float))
mul_22_24 V2 (V2 (S x Float))
a V2 (V4 (S x Float))
b = (Int, S x Float -> V2 (S x Float))
-> (Int, S x Float -> V4 (S x Float))
-> S x (V2 (V4 Float))
-> S x (V2 (V2 Float))
-> V2 (V4 (S x Float))
forall (f :: * -> *) c z a b x y.
Functor f =>
(Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
mulToM (Int, S x Float -> V2 (S x Float))
forall a c a. Num a => (a, S c a -> V2 (S c a))
d2 (Int, S x Float -> V4 (S x Float))
forall a c a. Num a => (a, S c a -> V4 (S c a))
d4 (V2 (V4 (S x Float)) -> S x (V2 (V4 Float))
forall x. V2 (V4 (S x Float)) -> S x (V2 (V4 Float))
fromMat24 V2 (V4 (S x Float))
b) (V2 (V2 (S x Float)) -> S x (V2 (V2 Float))
forall x. V2 (V2 (S x Float)) -> S x (V2 (V2 Float))
fromMat22 V2 (V2 (S x Float))
a)
mul_23_34 :: V2 (V3 (S x Float)) -> V3 (V4 (S x Float)) -> V2 (V4 (S x Float))
mul_23_34 :: V2 (V3 (S x Float)) -> V3 (V4 (S x Float)) -> V2 (V4 (S x Float))
mul_23_34 V2 (V3 (S x Float))
a V3 (V4 (S x Float))
b = (Int, S x Float -> V2 (S x Float))
-> (Int, S x Float -> V4 (S x Float))
-> S x (V3 (V4 Float))
-> S x (V2 (V3 Float))
-> V2 (V4 (S x Float))
forall (f :: * -> *) c z a b x y.
Functor f =>
(Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
mulToM (Int, S x Float -> V2 (S x Float))
forall a c a. Num a => (a, S c a -> V2 (S c a))
d2 (Int, S x Float -> V4 (S x Float))
forall a c a. Num a => (a, S c a -> V4 (S c a))
d4 (V3 (V4 (S x Float)) -> S x (V3 (V4 Float))
forall x. V3 (V4 (S x Float)) -> S x (V3 (V4 Float))
fromMat34 V3 (V4 (S x Float))
b) (V2 (V3 (S x Float)) -> S x (V2 (V3 Float))
forall x. V2 (V3 (S x Float)) -> S x (V2 (V3 Float))
fromMat23 V2 (V3 (S x Float))
a)
mul_24_44 :: V2 (V4 (S x Float)) -> V4 (V4 (S x Float)) -> V2 (V4 (S x Float))
mul_24_44 :: V2 (V4 (S x Float)) -> V4 (V4 (S x Float)) -> V2 (V4 (S x Float))
mul_24_44 V2 (V4 (S x Float))
a V4 (V4 (S x Float))
b = (Int, S x Float -> V2 (S x Float))
-> (Int, S x Float -> V4 (S x Float))
-> S x (V4 (V4 Float))
-> S x (V2 (V4 Float))
-> V2 (V4 (S x Float))
forall (f :: * -> *) c z a b x y.
Functor f =>
(Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
mulToM (Int, S x Float -> V2 (S x Float))
forall a c a. Num a => (a, S c a -> V2 (S c a))
d2 (Int, S x Float -> V4 (S x Float))
forall a c a. Num a => (a, S c a -> V4 (S c a))
d4 (V4 (V4 (S x Float)) -> S x (V4 (V4 Float))
forall x. V4 (V4 (S x Float)) -> S x (V4 (V4 Float))
fromMat44 V4 (V4 (S x Float))
b) (V2 (V4 (S x Float)) -> S x (V2 (V4 Float))
forall x. V2 (V4 (S x Float)) -> S x (V2 (V4 Float))
fromMat24 V2 (V4 (S x Float))
a)
{-# RULES "mul_32_22" (!*!) = mul_32_22 #-}
{-# RULES "mul_33_32" (!*!) = mul_33_32 #-}
{-# RULES "mul_34_42" (!*!) = mul_34_42 #-}
{-# RULES "mul_32_23" (!*!) = mul_32_23 #-}
{-# RULES "mul_33_33" (!*!) = mul_33_33 #-}
{-# RULES "mul_34_43" (!*!) = mul_34_43 #-}
{-# RULES "mul_32_24" (!*!) = mul_32_24 #-}
{-# RULES "mul_33_34" (!*!) = mul_33_34 #-}
{-# RULES "mul_34_44" (!*!) = mul_34_44 #-}
mul_32_22 :: V3 (V2 (S x Float)) -> V2 (V2 (S x Float)) -> V3 (V2 (S x Float))
mul_32_22 :: V3 (V2 (S x Float)) -> V2 (V2 (S x Float)) -> V3 (V2 (S x Float))
mul_32_22 V3 (V2 (S x Float))
a V2 (V2 (S x Float))
b = (Int, S x Float -> V3 (S x Float))
-> (Int, S x Float -> V2 (S x Float))
-> S x (V2 (V2 Float))
-> S x (V3 (V2 Float))
-> V3 (V2 (S x Float))
forall (f :: * -> *) c z a b x y.
Functor f =>
(Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
mulToM (Int, S x Float -> V3 (S x Float))
forall a c a. Num a => (a, S c a -> V3 (S c a))
d3 (Int, S x Float -> V2 (S x Float))
forall a c a. Num a => (a, S c a -> V2 (S c a))
d2 (V2 (V2 (S x Float)) -> S x (V2 (V2 Float))
forall x. V2 (V2 (S x Float)) -> S x (V2 (V2 Float))
fromMat22 V2 (V2 (S x Float))
b) (V3 (V2 (S x Float)) -> S x (V3 (V2 Float))
forall x. V3 (V2 (S x Float)) -> S x (V3 (V2 Float))
fromMat32 V3 (V2 (S x Float))
a)
mul_33_32 :: V3 (V3 (S x Float)) -> V3 (V2 (S x Float)) -> V3 (V2 (S x Float))
mul_33_32 :: V3 (V3 (S x Float)) -> V3 (V2 (S x Float)) -> V3 (V2 (S x Float))
mul_33_32 V3 (V3 (S x Float))
a V3 (V2 (S x Float))
b = (Int, S x Float -> V3 (S x Float))
-> (Int, S x Float -> V2 (S x Float))
-> S x (V3 (V2 Float))
-> S x (V3 (V3 Float))
-> V3 (V2 (S x Float))
forall (f :: * -> *) c z a b x y.
Functor f =>
(Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
mulToM (Int, S x Float -> V3 (S x Float))
forall a c a. Num a => (a, S c a -> V3 (S c a))
d3 (Int, S x Float -> V2 (S x Float))
forall a c a. Num a => (a, S c a -> V2 (S c a))
d2 (V3 (V2 (S x Float)) -> S x (V3 (V2 Float))
forall x. V3 (V2 (S x Float)) -> S x (V3 (V2 Float))
fromMat32 V3 (V2 (S x Float))
b) (V3 (V3 (S x Float)) -> S x (V3 (V3 Float))
forall x. V3 (V3 (S x Float)) -> S x (V3 (V3 Float))
fromMat33 V3 (V3 (S x Float))
a)
mul_34_42 :: V3 (V4 (S x Float)) -> V4 (V2 (S x Float)) -> V3 (V2 (S x Float))
mul_34_42 :: V3 (V4 (S x Float)) -> V4 (V2 (S x Float)) -> V3 (V2 (S x Float))
mul_34_42 V3 (V4 (S x Float))
a V4 (V2 (S x Float))
b = (Int, S x Float -> V3 (S x Float))
-> (Int, S x Float -> V2 (S x Float))
-> S x (V4 (V2 Float))
-> S x (V3 (V4 Float))
-> V3 (V2 (S x Float))
forall (f :: * -> *) c z a b x y.
Functor f =>
(Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
mulToM (Int, S x Float -> V3 (S x Float))
forall a c a. Num a => (a, S c a -> V3 (S c a))
d3 (Int, S x Float -> V2 (S x Float))
forall a c a. Num a => (a, S c a -> V2 (S c a))
d2 (V4 (V2 (S x Float)) -> S x (V4 (V2 Float))
forall x. V4 (V2 (S x Float)) -> S x (V4 (V2 Float))
fromMat42 V4 (V2 (S x Float))
b) (V3 (V4 (S x Float)) -> S x (V3 (V4 Float))
forall x. V3 (V4 (S x Float)) -> S x (V3 (V4 Float))
fromMat34 V3 (V4 (S x Float))
a)
mul_32_23 :: V3 (V2 (S x Float)) -> V2 (V3 (S x Float)) -> V3 (V3 (S x Float))
mul_32_23 :: V3 (V2 (S x Float)) -> V2 (V3 (S x Float)) -> V3 (V3 (S x Float))
mul_32_23 V3 (V2 (S x Float))
a V2 (V3 (S x Float))
b = (Int, S x Float -> V3 (S x Float))
-> (Int, S x Float -> V3 (S x Float))
-> S x (V2 (V3 Float))
-> S x (V3 (V2 Float))
-> V3 (V3 (S x Float))
forall (f :: * -> *) c z a b x y.
Functor f =>
(Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
mulToM (Int, S x Float -> V3 (S x Float))
forall a c a. Num a => (a, S c a -> V3 (S c a))
d3 (Int, S x Float -> V3 (S x Float))
forall a c a. Num a => (a, S c a -> V3 (S c a))
d3 (V2 (V3 (S x Float)) -> S x (V2 (V3 Float))
forall x. V2 (V3 (S x Float)) -> S x (V2 (V3 Float))
fromMat23 V2 (V3 (S x Float))
b) (V3 (V2 (S x Float)) -> S x (V3 (V2 Float))
forall x. V3 (V2 (S x Float)) -> S x (V3 (V2 Float))
fromMat32 V3 (V2 (S x Float))
a)
mul_33_33 :: V3 (V3 (S x Float)) -> V3 (V3 (S x Float)) -> V3 (V3 (S x Float))
mul_33_33 :: V3 (V3 (S x Float)) -> V3 (V3 (S x Float)) -> V3 (V3 (S x Float))
mul_33_33 V3 (V3 (S x Float))
a V3 (V3 (S x Float))
b = (Int, S x Float -> V3 (S x Float))
-> (Int, S x Float -> V3 (S x Float))
-> S x (V3 (V3 Float))
-> S x (V3 (V3 Float))
-> V3 (V3 (S x Float))
forall (f :: * -> *) c z a b x y.
Functor f =>
(Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
mulToM (Int, S x Float -> V3 (S x Float))
forall a c a. Num a => (a, S c a -> V3 (S c a))
d3 (Int, S x Float -> V3 (S x Float))
forall a c a. Num a => (a, S c a -> V3 (S c a))
d3 (V3 (V3 (S x Float)) -> S x (V3 (V3 Float))
forall x. V3 (V3 (S x Float)) -> S x (V3 (V3 Float))
fromMat33 V3 (V3 (S x Float))
b) (V3 (V3 (S x Float)) -> S x (V3 (V3 Float))
forall x. V3 (V3 (S x Float)) -> S x (V3 (V3 Float))
fromMat33 V3 (V3 (S x Float))
a)
mul_34_43 :: V3 (V4 (S x Float)) -> V4 (V3 (S x Float)) -> V3 (V3 (S x Float))
mul_34_43 :: V3 (V4 (S x Float)) -> V4 (V3 (S x Float)) -> V3 (V3 (S x Float))
mul_34_43 V3 (V4 (S x Float))
a V4 (V3 (S x Float))
b = (Int, S x Float -> V3 (S x Float))
-> (Int, S x Float -> V3 (S x Float))
-> S x (V4 (V3 Float))
-> S x (V3 (V4 Float))
-> V3 (V3 (S x Float))
forall (f :: * -> *) c z a b x y.
Functor f =>
(Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
mulToM (Int, S x Float -> V3 (S x Float))
forall a c a. Num a => (a, S c a -> V3 (S c a))
d3 (Int, S x Float -> V3 (S x Float))
forall a c a. Num a => (a, S c a -> V3 (S c a))
d3 (V4 (V3 (S x Float)) -> S x (V4 (V3 Float))
forall x. V4 (V3 (S x Float)) -> S x (V4 (V3 Float))
fromMat43 V4 (V3 (S x Float))
b) (V3 (V4 (S x Float)) -> S x (V3 (V4 Float))
forall x. V3 (V4 (S x Float)) -> S x (V3 (V4 Float))
fromMat34 V3 (V4 (S x Float))
a)
mul_32_24 :: V3 (V2 (S x Float)) -> V2 (V4 (S x Float)) -> V3 (V4 (S x Float))
mul_32_24 :: V3 (V2 (S x Float)) -> V2 (V4 (S x Float)) -> V3 (V4 (S x Float))
mul_32_24 V3 (V2 (S x Float))
a V2 (V4 (S x Float))
b = (Int, S x Float -> V3 (S x Float))
-> (Int, S x Float -> V4 (S x Float))
-> S x (V2 (V4 Float))
-> S x (V3 (V2 Float))
-> V3 (V4 (S x Float))
forall (f :: * -> *) c z a b x y.
Functor f =>
(Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
mulToM (Int, S x Float -> V3 (S x Float))
forall a c a. Num a => (a, S c a -> V3 (S c a))
d3 (Int, S x Float -> V4 (S x Float))
forall a c a. Num a => (a, S c a -> V4 (S c a))
d4 (V2 (V4 (S x Float)) -> S x (V2 (V4 Float))
forall x. V2 (V4 (S x Float)) -> S x (V2 (V4 Float))
fromMat24 V2 (V4 (S x Float))
b) (V3 (V2 (S x Float)) -> S x (V3 (V2 Float))
forall x. V3 (V2 (S x Float)) -> S x (V3 (V2 Float))
fromMat32 V3 (V2 (S x Float))
a)
mul_33_34 :: V3 (V3 (S x Float)) -> V3 (V4 (S x Float)) -> V3 (V4 (S x Float))
mul_33_34 :: V3 (V3 (S x Float)) -> V3 (V4 (S x Float)) -> V3 (V4 (S x Float))
mul_33_34 V3 (V3 (S x Float))
a V3 (V4 (S x Float))
b = (Int, S x Float -> V3 (S x Float))
-> (Int, S x Float -> V4 (S x Float))
-> S x (V3 (V4 Float))
-> S x (V3 (V3 Float))
-> V3 (V4 (S x Float))
forall (f :: * -> *) c z a b x y.
Functor f =>
(Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
mulToM (Int, S x Float -> V3 (S x Float))
forall a c a. Num a => (a, S c a -> V3 (S c a))
d3 (Int, S x Float -> V4 (S x Float))
forall a c a. Num a => (a, S c a -> V4 (S c a))
d4 (V3 (V4 (S x Float)) -> S x (V3 (V4 Float))
forall x. V3 (V4 (S x Float)) -> S x (V3 (V4 Float))
fromMat34 V3 (V4 (S x Float))
b) (V3 (V3 (S x Float)) -> S x (V3 (V3 Float))
forall x. V3 (V3 (S x Float)) -> S x (V3 (V3 Float))
fromMat33 V3 (V3 (S x Float))
a)
mul_34_44 :: V3 (V4 (S x Float)) -> V4 (V4 (S x Float)) -> V3 (V4 (S x Float))
mul_34_44 :: V3 (V4 (S x Float)) -> V4 (V4 (S x Float)) -> V3 (V4 (S x Float))
mul_34_44 V3 (V4 (S x Float))
a V4 (V4 (S x Float))
b = (Int, S x Float -> V3 (S x Float))
-> (Int, S x Float -> V4 (S x Float))
-> S x (V4 (V4 Float))
-> S x (V3 (V4 Float))
-> V3 (V4 (S x Float))
forall (f :: * -> *) c z a b x y.
Functor f =>
(Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
mulToM (Int, S x Float -> V3 (S x Float))
forall a c a. Num a => (a, S c a -> V3 (S c a))
d3 (Int, S x Float -> V4 (S x Float))
forall a c a. Num a => (a, S c a -> V4 (S c a))
d4 (V4 (V4 (S x Float)) -> S x (V4 (V4 Float))
forall x. V4 (V4 (S x Float)) -> S x (V4 (V4 Float))
fromMat44 V4 (V4 (S x Float))
b) (V3 (V4 (S x Float)) -> S x (V3 (V4 Float))
forall x. V3 (V4 (S x Float)) -> S x (V3 (V4 Float))
fromMat34 V3 (V4 (S x Float))
a)
{-# RULES "mul_42_22" (!*!) = mul_42_22 #-}
{-# RULES "mul_43_32" (!*!) = mul_43_32 #-}
{-# RULES "mul_44_42" (!*!) = mul_44_42 #-}
{-# RULES "mul_42_23" (!*!) = mul_42_23 #-}
{-# RULES "mul_43_33" (!*!) = mul_43_33 #-}
{-# RULES "mul_44_43" (!*!) = mul_44_43 #-}
{-# RULES "mul_42_24" (!*!) = mul_42_24 #-}
{-# RULES "mul_43_34" (!*!) = mul_43_34 #-}
{-# RULES "mul_44_44" (!*!) = mul_44_44 #-}
mul_42_22 :: V4 (V2 (S x Float)) -> V2 (V2 (S x Float)) -> V4 (V2 (S x Float))
mul_42_22 :: V4 (V2 (S x Float)) -> V2 (V2 (S x Float)) -> V4 (V2 (S x Float))
mul_42_22 V4 (V2 (S x Float))
a V2 (V2 (S x Float))
b = (Int, S x Float -> V4 (S x Float))
-> (Int, S x Float -> V2 (S x Float))
-> S x (V2 (V2 Float))
-> S x (V4 (V2 Float))
-> V4 (V2 (S x Float))
forall (f :: * -> *) c z a b x y.
Functor f =>
(Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
mulToM (Int, S x Float -> V4 (S x Float))
forall a c a. Num a => (a, S c a -> V4 (S c a))
d4 (Int, S x Float -> V2 (S x Float))
forall a c a. Num a => (a, S c a -> V2 (S c a))
d2 (V2 (V2 (S x Float)) -> S x (V2 (V2 Float))
forall x. V2 (V2 (S x Float)) -> S x (V2 (V2 Float))
fromMat22 V2 (V2 (S x Float))
b) (V4 (V2 (S x Float)) -> S x (V4 (V2 Float))
forall x. V4 (V2 (S x Float)) -> S x (V4 (V2 Float))
fromMat42 V4 (V2 (S x Float))
a)
mul_43_32 :: V4 (V3 (S x Float)) -> V3 (V2 (S x Float)) -> V4 (V2 (S x Float))
mul_43_32 :: V4 (V3 (S x Float)) -> V3 (V2 (S x Float)) -> V4 (V2 (S x Float))
mul_43_32 V4 (V3 (S x Float))
a V3 (V2 (S x Float))
b = (Int, S x Float -> V4 (S x Float))
-> (Int, S x Float -> V2 (S x Float))
-> S x (V3 (V2 Float))
-> S x (V4 (V3 Float))
-> V4 (V2 (S x Float))
forall (f :: * -> *) c z a b x y.
Functor f =>
(Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
mulToM (Int, S x Float -> V4 (S x Float))
forall a c a. Num a => (a, S c a -> V4 (S c a))
d4 (Int, S x Float -> V2 (S x Float))
forall a c a. Num a => (a, S c a -> V2 (S c a))
d2 (V3 (V2 (S x Float)) -> S x (V3 (V2 Float))
forall x. V3 (V2 (S x Float)) -> S x (V3 (V2 Float))
fromMat32 V3 (V2 (S x Float))
b) (V4 (V3 (S x Float)) -> S x (V4 (V3 Float))
forall x. V4 (V3 (S x Float)) -> S x (V4 (V3 Float))
fromMat43 V4 (V3 (S x Float))
a)
mul_44_42 :: V4 (V4 (S x Float)) -> V4 (V2 (S x Float)) -> V4 (V2 (S x Float))
mul_44_42 :: V4 (V4 (S x Float)) -> V4 (V2 (S x Float)) -> V4 (V2 (S x Float))
mul_44_42 V4 (V4 (S x Float))
a V4 (V2 (S x Float))
b = (Int, S x Float -> V4 (S x Float))
-> (Int, S x Float -> V2 (S x Float))
-> S x (V4 (V2 Float))
-> S x (V4 (V4 Float))
-> V4 (V2 (S x Float))
forall (f :: * -> *) c z a b x y.
Functor f =>
(Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
mulToM (Int, S x Float -> V4 (S x Float))
forall a c a. Num a => (a, S c a -> V4 (S c a))
d4 (Int, S x Float -> V2 (S x Float))
forall a c a. Num a => (a, S c a -> V2 (S c a))
d2 (V4 (V2 (S x Float)) -> S x (V4 (V2 Float))
forall x. V4 (V2 (S x Float)) -> S x (V4 (V2 Float))
fromMat42 V4 (V2 (S x Float))
b) (V4 (V4 (S x Float)) -> S x (V4 (V4 Float))
forall x. V4 (V4 (S x Float)) -> S x (V4 (V4 Float))
fromMat44 V4 (V4 (S x Float))
a)
mul_42_23 :: V4 (V2 (S x Float)) -> V2 (V3 (S x Float)) -> V4 (V3 (S x Float))
mul_42_23 :: V4 (V2 (S x Float)) -> V2 (V3 (S x Float)) -> V4 (V3 (S x Float))
mul_42_23 V4 (V2 (S x Float))
a V2 (V3 (S x Float))
b = (Int, S x Float -> V4 (S x Float))
-> (Int, S x Float -> V3 (S x Float))
-> S x (V2 (V3 Float))
-> S x (V4 (V2 Float))
-> V4 (V3 (S x Float))
forall (f :: * -> *) c z a b x y.
Functor f =>
(Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
mulToM (Int, S x Float -> V4 (S x Float))
forall a c a. Num a => (a, S c a -> V4 (S c a))
d4 (Int, S x Float -> V3 (S x Float))
forall a c a. Num a => (a, S c a -> V3 (S c a))
d3 (V2 (V3 (S x Float)) -> S x (V2 (V3 Float))
forall x. V2 (V3 (S x Float)) -> S x (V2 (V3 Float))
fromMat23 V2 (V3 (S x Float))
b) (V4 (V2 (S x Float)) -> S x (V4 (V2 Float))
forall x. V4 (V2 (S x Float)) -> S x (V4 (V2 Float))
fromMat42 V4 (V2 (S x Float))
a)
mul_43_33 :: V4 (V3 (S x Float)) -> V3 (V3 (S x Float)) -> V4 (V3 (S x Float))
mul_43_33 :: V4 (V3 (S x Float)) -> V3 (V3 (S x Float)) -> V4 (V3 (S x Float))
mul_43_33 V4 (V3 (S x Float))
a V3 (V3 (S x Float))
b = (Int, S x Float -> V4 (S x Float))
-> (Int, S x Float -> V3 (S x Float))
-> S x (V3 (V3 Float))
-> S x (V4 (V3 Float))
-> V4 (V3 (S x Float))
forall (f :: * -> *) c z a b x y.
Functor f =>
(Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
mulToM (Int, S x Float -> V4 (S x Float))
forall a c a. Num a => (a, S c a -> V4 (S c a))
d4 (Int, S x Float -> V3 (S x Float))
forall a c a. Num a => (a, S c a -> V3 (S c a))
d3 (V3 (V3 (S x Float)) -> S x (V3 (V3 Float))
forall x. V3 (V3 (S x Float)) -> S x (V3 (V3 Float))
fromMat33 V3 (V3 (S x Float))
b) (V4 (V3 (S x Float)) -> S x (V4 (V3 Float))
forall x. V4 (V3 (S x Float)) -> S x (V4 (V3 Float))
fromMat43 V4 (V3 (S x Float))
a)
mul_44_43 :: V4 (V4 (S x Float)) -> V4 (V3 (S x Float)) -> V4 (V3 (S x Float))
mul_44_43 :: V4 (V4 (S x Float)) -> V4 (V3 (S x Float)) -> V4 (V3 (S x Float))
mul_44_43 V4 (V4 (S x Float))
a V4 (V3 (S x Float))
b = (Int, S x Float -> V4 (S x Float))
-> (Int, S x Float -> V3 (S x Float))
-> S x (V4 (V3 Float))
-> S x (V4 (V4 Float))
-> V4 (V3 (S x Float))
forall (f :: * -> *) c z a b x y.
Functor f =>
(Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
mulToM (Int, S x Float -> V4 (S x Float))
forall a c a. Num a => (a, S c a -> V4 (S c a))
d4 (Int, S x Float -> V3 (S x Float))
forall a c a. Num a => (a, S c a -> V3 (S c a))
d3 (V4 (V3 (S x Float)) -> S x (V4 (V3 Float))
forall x. V4 (V3 (S x Float)) -> S x (V4 (V3 Float))
fromMat43 V4 (V3 (S x Float))
b) (V4 (V4 (S x Float)) -> S x (V4 (V4 Float))
forall x. V4 (V4 (S x Float)) -> S x (V4 (V4 Float))
fromMat44 V4 (V4 (S x Float))
a)
mul_42_24 :: V4 (V2 (S x Float)) -> V2 (V4 (S x Float)) -> V4 (V4 (S x Float))
mul_42_24 :: V4 (V2 (S x Float)) -> V2 (V4 (S x Float)) -> V4 (V4 (S x Float))
mul_42_24 V4 (V2 (S x Float))
a V2 (V4 (S x Float))
b = (Int, S x Float -> V4 (S x Float))
-> (Int, S x Float -> V4 (S x Float))
-> S x (V2 (V4 Float))
-> S x (V4 (V2 Float))
-> V4 (V4 (S x Float))
forall (f :: * -> *) c z a b x y.
Functor f =>
(Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
mulToM (Int, S x Float -> V4 (S x Float))
forall a c a. Num a => (a, S c a -> V4 (S c a))
d4 (Int, S x Float -> V4 (S x Float))
forall a c a. Num a => (a, S c a -> V4 (S c a))
d4 (V2 (V4 (S x Float)) -> S x (V2 (V4 Float))
forall x. V2 (V4 (S x Float)) -> S x (V2 (V4 Float))
fromMat24 V2 (V4 (S x Float))
b) (V4 (V2 (S x Float)) -> S x (V4 (V2 Float))
forall x. V4 (V2 (S x Float)) -> S x (V4 (V2 Float))
fromMat42 V4 (V2 (S x Float))
a)
mul_43_34 :: V4 (V3 (S x Float)) -> V3 (V4 (S x Float)) -> V4 (V4 (S x Float))
mul_43_34 :: V4 (V3 (S x Float)) -> V3 (V4 (S x Float)) -> V4 (V4 (S x Float))
mul_43_34 V4 (V3 (S x Float))
a V3 (V4 (S x Float))
b = (Int, S x Float -> V4 (S x Float))
-> (Int, S x Float -> V4 (S x Float))
-> S x (V3 (V4 Float))
-> S x (V4 (V3 Float))
-> V4 (V4 (S x Float))
forall (f :: * -> *) c z a b x y.
Functor f =>
(Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
mulToM (Int, S x Float -> V4 (S x Float))
forall a c a. Num a => (a, S c a -> V4 (S c a))
d4 (Int, S x Float -> V4 (S x Float))
forall a c a. Num a => (a, S c a -> V4 (S c a))
d4 (V3 (V4 (S x Float)) -> S x (V3 (V4 Float))
forall x. V3 (V4 (S x Float)) -> S x (V3 (V4 Float))
fromMat34 V3 (V4 (S x Float))
b) (V4 (V3 (S x Float)) -> S x (V4 (V3 Float))
forall x. V4 (V3 (S x Float)) -> S x (V4 (V3 Float))
fromMat43 V4 (V3 (S x Float))
a)
mul_44_44 :: V4 (V4 (S x Float)) -> V4 (V4 (S x Float)) -> V4 (V4 (S x Float))
mul_44_44 :: V4 (V4 (S x Float)) -> V4 (V4 (S x Float)) -> V4 (V4 (S x Float))
mul_44_44 V4 (V4 (S x Float))
a V4 (V4 (S x Float))
b = (Int, S x Float -> V4 (S x Float))
-> (Int, S x Float -> V4 (S x Float))
-> S x (V4 (V4 Float))
-> S x (V4 (V4 Float))
-> V4 (V4 (S x Float))
forall (f :: * -> *) c z a b x y.
Functor f =>
(Int, S c z -> f a) -> (Int, a -> b) -> S c x -> S c y -> f b
mulToM (Int, S x Float -> V4 (S x Float))
forall a c a. Num a => (a, S c a -> V4 (S c a))
d4 (Int, S x Float -> V4 (S x Float))
forall a c a. Num a => (a, S c a -> V4 (S c a))
d4 (V4 (V4 (S x Float)) -> S x (V4 (V4 Float))
forall x. V4 (V4 (S x Float)) -> S x (V4 (V4 Float))
fromMat44 V4 (V4 (S x Float))
b) (V4 (V4 (S x Float)) -> S x (V4 (V4 Float))
forall x. V4 (V4 (S x Float)) -> S x (V4 (V4 Float))
fromMat44 V4 (V4 (S x Float))
a)