summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--TODO6
-rw-r--r--src/LambdaCube/Compiler/CoreToIR.hs98
-rw-r--r--src/LambdaCube/Compiler/Infer.hs79
-rw-r--r--src/LambdaCube/Compiler/Parser.hs35
-rw-r--r--test/runTests.hs2
-rw-r--r--testdata/Graphics.out114
-rw-r--r--testdata/HyperbolicParaboloic.out10
-rw-r--r--testdata/Hyperboloid.lc4
-rw-r--r--testdata/Hyperboloid.out21
-rw-r--r--testdata/Spiral.out5
-rw-r--r--testdata/editor-examples/Heartbeat.out12
-rw-r--r--testdata/fetcharrays01.out8
-rw-r--r--testdata/gfx03.out19
-rw-r--r--testdata/gfx04.out3
-rw-r--r--testdata/gfx05.out19
-rw-r--r--testdata/heartbeat01.out12
-rw-r--r--testdata/language-features/recursion/simplerec02.lc (renamed from testdata/language-features/recursion/simplerec02.wip.lc)0
-rw-r--r--testdata/language-features/recursion/simplerec02.out9
-rw-r--r--testdata/language-features/recursion/simplerec03.lc (renamed from testdata/language-features/recursion/simplerec03.wip.lc)0
-rw-r--r--testdata/language-features/recursion/simplerec03.out9
-rw-r--r--testdata/line01.out8
-rw-r--r--testdata/simple02.out3
-rw-r--r--testdata/simple03.out6
23 files changed, 315 insertions, 167 deletions
diff --git a/TODO b/TODO
index eafb3252..4faa9de5 100644
--- a/TODO
+++ b/TODO
@@ -85,14 +85,16 @@ done:
85- don't overnormalize (String => [Char]) 85- don't overnormalize (String => [Char])
86- compiler: support function recognition 86- compiler: support function recognition
87- backend: generate functions in shaders 87- backend: generate functions in shaders
88 88- backend: remove duplicate programs
89next:
90- support local pattern matching functions 89- support local pattern matching functions
91- support recursive local definitions 90- support recursive local definitions
91
92next:
92- mutual recursion (inference & reduction) 93- mutual recursion (inference & reduction)
93- compiler optimization: irrelevance + erasure 94- compiler optimization: irrelevance + erasure
94- re-enable ambiguity checks 95- re-enable ambiguity checks
95- show desugared source code on a tab in the editor 96- show desugared source code on a tab in the editor
97- names should have unique identifiers
96 98
97- testenv: performance benchmarks (time and memory consumption) 99- testenv: performance benchmarks (time and memory consumption)
98 done - create benchmark test set (pipeline codegen and error report) 100 done - create benchmark test set (pipeline codegen and error report)
diff --git a/src/LambdaCube/Compiler/CoreToIR.hs b/src/LambdaCube/Compiler/CoreToIR.hs
index 42d7f3d3..80bc07cc 100644
--- a/src/LambdaCube/Compiler/CoreToIR.hs
+++ b/src/LambdaCube/Compiler/CoreToIR.hs
@@ -6,6 +6,7 @@
6{-# LANGUAGE TypeSynonymInstances #-} 6{-# LANGUAGE TypeSynonymInstances #-}
7{-# LANGUAGE MultiParamTypeClasses #-} 7{-# LANGUAGE MultiParamTypeClasses #-}
8{-# LANGUAGE RecursiveDo #-} 8{-# LANGUAGE RecursiveDo #-}
9{-# LANGUAGE TupleSections #-}
9{-# OPTIONS_GHC -fno-warn-unused-binds #-} -- TODO: remove 10{-# OPTIONS_GHC -fno-warn-unused-binds #-} -- TODO: remove
10module LambdaCube.Compiler.CoreToIR 11module LambdaCube.Compiler.CoreToIR
11 ( compilePipeline 12 ( compilePipeline
@@ -53,20 +54,21 @@ compilePipeline backend exp = IR.Pipeline
53 } 54 }
54 where 55 where
55 ((subCmds,cmds), (streams, programs, targets, slots, textures)) 56 ((subCmds,cmds), (streams, programs, targets, slots, textures))
56 = flip runState ((0, mempty), mempty, (0, mempty), mempty, (0, mempty)) 57 = flip runState ((0, mempty), mempty, (0, mempty), mempty, (0, mempty)) $ case toExp exp of
57 $ getCommands backend $ toExp exp 58 A1 "ScreenOut" a -> addTarget backend a [IR.TargetItem s $ Just $ IR.Framebuffer s | s <- getSemantics a]
59 x -> error $ "ScreenOut expected inststead of " ++ ppShow x
58 60
59type CG = State (List IR.StreamData, Map IR.Program Int, List IR.RenderTarget, Map String (Int, IR.Slot), List IR.TextureDescriptor) 61type CG = State (List IR.StreamData, Map IR.Program Int, List IR.RenderTarget, Map String (Int, IR.Slot), List IR.TextureDescriptor)
60 62
61type List a = (Int, [a]) 63type List a = (Int, [a])
62 64
63streamLens = (\(a,b,c,d,e) -> a, \x (a,b,c,d,e) -> (x,b,c,d,e)) 65streamLens f (a,b,c,d,e) = f (,b,c,d,e) a
64programLens = (\(a,b,c,d,e) -> b, \x (a,b,c,d,e) -> (a,x,c,d,e)) 66programLens f (a,b,c,d,e) = f (a,,c,d,e) b
65targetLens = (\(a,b,c,d,e) -> c, \x (a,b,c,d,e) -> (a,b,x,d,e)) 67targetLens f (a,b,c,d,e) = f (a,b,,d,e) c
66slotLens = (\(a,b,c,d,e) -> d, \x (a,b,c,d,e) -> (a,b,c,x,e)) 68slotLens f (a,b,c,d,e) = f (a,b,c,,e) d
67textureLens = (\(a,b,c,d,e) -> e, \x (a,b,c,d,e) -> (a,b,c,d,x)) 69textureLens f (a,b,c,d,e) = f (a,b,c,d,) e
68 70
69modL (g, s) f = state $ \st -> second (`s` st) $ f (g st) 71modL gs f = state $ gs $ \fx -> second fx . f
70 72
71addL' l p f x = modL l $ \sv -> maybe (length sv, Map.insert p (length sv, x) sv) (\(i, x') -> (i, Map.insert p (i, f x x') sv)) $ Map.lookup p sv 73addL' l p f x = modL l $ \sv -> maybe (length sv, Map.insert p (length sv, x) sv) (\(i, x') -> (i, Map.insert p (i, f x x') sv)) $ Map.lookup p sv
72addL l x = modL l $ \(i, sv) -> (i, (i+1, x: sv)) 74addL l x = modL l $ \(i, sv) -> (i, (i+1, x: sv))
@@ -74,14 +76,18 @@ addLEq l x = modL l $ \sv -> maybe (let i = length sv in i `seq` (i, Map.insert
74 76
75--------------------------------------------------------- 77---------------------------------------------------------
76 78
77getCommands :: Backend -> ExpTV -> CG ([IR.Command],[IR.Command]) 79addTarget backend a tl = do
80 rt <- addL targetLens $ IR.RenderTarget $ Vector.fromList tl
81 second (IR.SetRenderTarget rt:) <$> getCommands backend a
82
83getCommands :: Backend -> ExpTV{-FrameBuffer-} -> CG ([IR.Command],[IR.Command])
78getCommands backend e = case e of 84getCommands backend e = case e of
79 85
80 A1 "ScreenOut" a -> addTarget a [IR.TargetItem s $ Just $ IR.Framebuffer s | s <- getSemantics a] 86 A1 "FrameBuffer" a -> return ([], [IR.ClearRenderTarget $ Vector.fromList $ map compFrameBuffer $ eTuple a])
81 87
82 A1 "FrameBuffer" a -> return ([], [IR.ClearRenderTarget $ Vector.fromList $ map (uncurry IR.ClearImage) $ compFrameBuffer a]) 88 A3 "Accumulate" actx (getFragmentShader -> (frag, getFragFilter -> (ffilter, x1))) fbuf -> case x1 of
83 89
84 A3 "Accumulate" actx (getFragmentShader -> (frag, getFragFilter -> (ffilter, A3 "foldr" (A0 "++") (A0 "Nil") (A2 "map" (EtaPrim3 "rasterizePrimitive" ints rctx) (getVertexShader -> (vert, input_)))))) fbuf -> mdo 90 A3 "foldr" (A0 "++") (A0 "Nil") (A2 "map" (EtaPrim3 "rasterizePrimitive" ints rctx) (getVertexShader -> (vert, input_))) -> mdo
85 91
86 let 92 let
87 (vertexInput, pUniforms, vertSrc, fragSrc) = genGLSLs backend (compRC' rctx) ints vert frag ffilter 93 (vertexInput, pUniforms, vertSrc, fragSrc) = genGLSLs backend (compRC' rctx) ints vert frag ffilter
@@ -148,7 +154,8 @@ getCommands backend e = case e of
148 154
149 (<> (txtCmds, cmds)) <$> getCommands backend fbuf 155 (<> (txtCmds, cmds)) <$> getCommands backend fbuf
150 156
151 x -> error $ "getCommands " ++ ppShow x 157 x -> error $ "getCommands': " ++ ppShow x
158 x -> error $ "getCommands: " ++ ppShow x
152 where 159 where
153 getRenderTextureCommands :: String -> Uniform -> CG ([SamplerBinding],[IR.Command]) 160 getRenderTextureCommands :: String -> Uniform -> CG ([SamplerBinding],[IR.Command])
154 getRenderTextureCommands n = \case 161 getRenderTextureCommands n = \case
@@ -178,15 +185,11 @@ getCommands backend e = case e of
178 , IR.textureMaxLevel = 0 185 , IR.textureMaxLevel = 0
179 } 186 }
180 return $ IR.TargetItem semantic $ Just $ IR.TextureImage texture 0 Nothing 187 return $ IR.TargetItem semantic $ Just $ IR.TextureImage texture 0 Nothing
181 (subCmds, cmds) <- addTarget a tl 188 (subCmds, cmds) <- addTarget backend a tl
182 let (IR.TargetItem IR.Color (Just tx)) = tf tl 189 let (IR.TargetItem IR.Color (Just tx)) = tf tl
183 return ([(n, tx)], subCmds ++ cmds) 190 return ([(n, tx)], subCmds ++ cmds)
184 _ -> return mempty 191 _ -> return mempty
185 192
186 addTarget a tl = do
187 rt <- addL targetLens $ IR.RenderTarget $ Vector.fromList tl
188 second (IR.SetRenderTarget rt: ) <$> getCommands backend a
189
190type SamplerBinding = (IR.UniformName,IR.ImageRef) 193type SamplerBinding = (IR.UniformName,IR.ImageRef)
191 194
192---------------------------------------------------------------- 195----------------------------------------------------------------
@@ -200,9 +203,13 @@ getFragFilter (A2 "map" (EtaPrim2 "filterFragment" p) x) = (Just p, x)
200getFragFilter x = (Nothing, x) 203getFragFilter x = (Nothing, x)
201 204
202getVertexShader (A2 "map" (EtaPrim2 "mapPrimitive" f@(etaRed -> Just (_, o))) x) = ((Just f, tyOf o), x) 205getVertexShader (A2 "map" (EtaPrim2 "mapPrimitive" f@(etaRed -> Just (_, o))) x) = ((Just f, tyOf o), x)
206--getVertexShader (A2 "map" (EtaPrim2 "mapPrimitive" f) x) = error $ "gff: " ++ show (case f of ExpTV x _ _ -> x) --ppShow (mapVal unFunc' f)
207--getVertexShader x = error $ "gf: " ++ ppShow x
203getVertexShader x = ((Nothing, getPrim' $ tyOf x), x) 208getVertexShader x = ((Nothing, getPrim' $ tyOf x), x)
204 209
205getFragmentShader (A2 "map" (EtaPrim2 "mapFragment" f@(etaRed -> Just (_, frago))) x) = ((Just f, tyOf frago), x) 210getFragmentShader (A2 "map" (EtaPrim2 "mapFragment" f@(etaRed -> Just (_, o))) x) = ((Just f, tyOf o), x)
211--getFragmentShader (A2 "map" (EtaPrim2 "mapFragment" f) x) = error $ "gff: " ++ ppShow f
212--getFragmentShader x = error $ "gf: " ++ ppShow x
206getFragmentShader x = ((Nothing, getPrim'' $ tyOf x), x) 213getFragmentShader x = ((Nothing, getPrim'' $ tyOf x), x)
207 214
208getPrim (A1 "List" (A2 "Primitive" _ p)) = p 215getPrim (A1 "List" (A2 "Primitive" _ p)) = p
@@ -210,18 +217,17 @@ getPrim' (A1 "List" (A2 "Primitive" a _)) = a
210getPrim'' (A1 "List" (A2 "Vector" _ (A1 "Maybe" (A1 "SimpleFragment" a)))) = a 217getPrim'' (A1 "List" (A2 "Vector" _ (A1 "Maybe" (A1 "SimpleFragment" a)))) = a
211getPrim'' x = error $ "getPrim'':" ++ ppShow x 218getPrim'' x = error $ "getPrim'':" ++ ppShow x
212 219
213compFrameBuffer x = case x of 220compFrameBuffer = \case
214 ETuple a -> concatMap compFrameBuffer a 221 A1 "DepthImage" a -> IR.ClearImage IR.Depth $ compValue a
215 A1 "DepthImage" a -> [(IR.Depth, compValue a)] 222 A1 "ColorImage" a -> IR.ClearImage IR.Color $ compValue a
216 A1 "ColorImage" a -> [(IR.Color, compValue a)]
217 x -> error $ "compFrameBuffer " ++ ppShow x 223 x -> error $ "compFrameBuffer " ++ ppShow x
218 224
219compSemantics x = case x of 225compSemantics = \case
220 A2 "Cons" a b -> compSemantic a: compSemantics b 226 A2 "Cons" a b -> compSemantic a: compSemantics b
221 A0 "Nil" -> [] 227 A0 "Nil" -> []
222 x -> error $ "compSemantics: " ++ ppShow x 228 x -> error $ "compSemantics: " ++ ppShow x
223 229
224compSemantic x = case x of 230compSemantic = \case
225 A1 "Depth" _ -> IR.Depth 231 A1 "Depth" _ -> IR.Depth
226 A1 "Stencil" _ -> IR.Stencil 232 A1 "Stencil" _ -> IR.Stencil
227 A1 "Color" _ -> IR.Color 233 A1 "Color" _ -> IR.Color
@@ -553,6 +559,7 @@ genGLSLs backend
553 vertOutNamesWithPosition = "gl_Position": vertOutNames 559 vertOutNamesWithPosition = "gl_Position": vertOutNames
554 560
555 red (etaRed -> Just (ps, o)) = (ps, o) 561 red (etaRed -> Just (ps, o)) = (ps, o)
562 red x = error $ "red: " ++ ppShow x
556 genGLSL' vertOuts (ps, o) 563 genGLSL' vertOuts (ps, o)
557 | length ps == length vertOuts = genGLSL (reverse vertOuts) o 564 | length ps == length vertOuts = genGLSL (reverse vertOuts) o
558 | otherwise = error $ "makeSubst illegal input " ++ show ps ++ "\n" ++ show vertOuts 565 | otherwise = error $ "makeSubst illegal input " ++ show ps ++ "\n" ++ show vertOuts
@@ -741,6 +748,7 @@ genGLSL dns e = case e of
741 n | n `elem` ["primIntToWord", "primIntToFloat", "primCompareInt", "primCompareWord", "primCompareFloat"] -> error $ "WebGL 1 does not support: " ++ ppShow e 748 n | n `elem` ["primIntToWord", "primIntToFloat", "primCompareInt", "primCompareWord", "primCompareFloat"] -> error $ "WebGL 1 does not support: " ++ ppShow e
742 n | n `elem` ["M23F", "M24F", "M32F", "M34F", "M42F", "M43F"] -> error "WebGL 1 does not support matrices with this dimension" 749 n | n `elem` ["M23F", "M24F", "M32F", "M34F", "M42F", "M43F"] -> error "WebGL 1 does not support matrices with this dimension"
743 (tupName -> Just n) -> pure $ error "GLSL codegen for tuple is not supported yet" 750 (tupName -> Just n) -> pure $ error "GLSL codegen for tuple is not supported yet"
751 x -> error $ "GLSL codegen - unsupported function: " ++ ppShow x
744 752
745 x -> error $ "GLSL codegen - unsupported expression: " ++ ppShow x 753 x -> error $ "GLSL codegen - unsupported expression: " ++ ppShow x
746 where 754 where
@@ -799,14 +807,16 @@ type Ty = ExpTV
799tyOf :: ExpTV -> Ty 807tyOf :: ExpTV -> Ty
800tyOf (ExpTV _ t vs) = t .@ vs 808tyOf (ExpTV _ t vs) = t .@ vs
801 809
810mapVal f (ExpTV a b c) = ExpTV (f a) b c
811
802toExp :: ExpType -> ExpTV 812toExp :: ExpType -> ExpTV
803toExp (x, xt) = ExpTV x xt [] 813toExp (x, xt) = ExpTV x xt []
804 814
805pattern Pi h a b <- (mkPi -> Just (h, a, b)) 815pattern Pi h a b <- (mkPi . mapVal unLab' -> Just (h, a, b))
806pattern Lam h a b <- (mkLam -> Just (h, a, b)) 816pattern Lam h a b <- (mkLam . mapVal unFunc' -> Just (h, a, b))
807pattern Con h b <- (mkCon -> Just (h, b)) 817pattern Con h b <- (mkCon . mapVal unLab' -> Just (h, b))
808pattern App a b <- (mkApp -> Just (a, b)) 818pattern App a b <- (mkApp . mapVal unLab' -> Just (a, b))
809pattern Var a b <- (mkVar -> Just (a, b)) 819pattern Var a b <- (mkVar . mapVal unLab' -> Just (a, b))
810pattern ELit l <- ExpTV (I.ELit l) _ _ 820pattern ELit l <- ExpTV (I.ELit l) _ _
811pattern TType <- ExpTV (unLab' -> I.TType) _ _ 821pattern TType <- ExpTV (unLab' -> I.TType) _ _
812pattern Func fn def ty xs <- (mkFunc -> Just (fn, def, ty, xs)) 822pattern Func fn def ty xs <- (mkFunc -> Just (fn, def, ty, xs))
@@ -818,23 +828,23 @@ pattern EInt s <- ELit (LInt s)
818t .@ vs = ExpTV t I.TType vs 828t .@ vs = ExpTV t I.TType vs
819infix 1 .@ 829infix 1 .@
820 830
821mkVar (ExpTV (unLab' -> I.Var i) t vs) = Just (i, t .@ vs) 831mkVar (ExpTV (I.Var i) t vs) = Just (i, t .@ vs)
822mkVar _ = Nothing 832mkVar _ = Nothing
823 833
824mkPi (ExpTV (unLab' -> I.Pi b x y) _ vs) = Just (b, x .@ vs, y .@ addToEnv x vs) 834mkPi (ExpTV (I.Pi b x y) _ vs) = Just (b, x .@ vs, y .@ addToEnv x vs)
825mkPi _ = Nothing 835mkPi _ = Nothing
826 836
827mkLam (ExpTV (unLab' -> I.Lam y) (I.Pi b x yt) vs) = Just (b, x .@ vs, ExpTV y yt $ addToEnv x vs) 837mkLam (ExpTV (I.Lam y) (I.Pi b x yt) vs) = Just (b, x .@ vs, ExpTV y yt $ addToEnv x vs)
828mkLam _ = Nothing 838mkLam _ = Nothing
829 839
830mkCon (ExpTV (unLab' -> I.Con s n xs) et vs) = Just (untick $ show s, chain vs (conType et s) $ mkConPars n et ++ xs) 840mkCon (ExpTV (I.Con s n xs) et vs) = Just (untick $ show s, chain vs (conType et s) $ mkConPars n et ++ xs)
831mkCon (ExpTV (unLab' -> TyCon s xs) et vs) = Just (untick $ show s, chain vs (nType s) xs) 841mkCon (ExpTV (TyCon s xs) et vs) = Just (untick $ show s, chain vs (nType s) xs)
832mkCon (ExpTV (unLab' -> Neut (I.Fun s i (reverse -> xs) def)) et vs) = Just (untick $ show s, chain vs (nType s) xs) 842mkCon (ExpTV (Neut (I.Fun s i (reverse -> xs) def)) et vs) = Just (untick $ show s, chain vs (nType s) xs)
833mkCon (ExpTV (unLab' -> CaseFun s xs n) et vs) = Just (untick $ show s, chain vs (nType s) $ makeCaseFunPars' (mkEnv vs) n ++ xs ++ [Neut n]) 843mkCon (ExpTV (CaseFun s xs n) et vs) = Just (untick $ show s, chain vs (nType s) $ makeCaseFunPars' (mkEnv vs) n ++ xs ++ [Neut n])
834mkCon (ExpTV (unLab' -> TyCaseFun s [m, t, f] n) et vs) = Just (untick $ show s, chain vs (nType s) [m, t, Neut n, f]) 844mkCon (ExpTV (TyCaseFun s [m, t, f] n) et vs) = Just (untick $ show s, chain vs (nType s) [m, t, Neut n, f])
835mkCon _ = Nothing 845mkCon _ = Nothing
836 846
837mkApp (ExpTV (unLab' -> Neut (I.App_ a b)) et vs) = Just (ExpTV (Neut a) t vs, head $ chain vs t [b]) 847mkApp (ExpTV (Neut (I.App_ a b)) et vs) = Just (ExpTV (Neut a) t vs, head $ chain vs t [b])
838 where t = neutType' (mkEnv vs) a 848 where t = neutType' (mkEnv vs) a
839mkApp _ = Nothing 849mkApp _ = Nothing
840 850
@@ -854,7 +864,14 @@ chain' vs t _ = error $ "chain: " ++ show t
854 864
855mkTVar i (ExpTV t _ vs) = ExpTV (I.Var i) t vs 865mkTVar i (ExpTV t _ vs) = ExpTV (I.Var i) t vs
856 866
857unLab' = unfixlabel 867unLab' (FL x) = unLab' x
868unLab' (LabelEnd x) = unLab' x
869unLab' x = x
870
871unFunc' (FL x) = unFunc' x -- todo: remove?
872unFunc' (UFL x) = unFunc' x
873unFunc' (LabelEnd x) = unFunc' x
874unFunc' x = x
858 875
859instance Subst Exp ExpTV where 876instance Subst Exp ExpTV where
860 subst i0 x (ExpTV a at vs) = ExpTV (subst i0 x a) (subst i0 x at) (zipWith (\i -> subst (i0+i) $ up i x{-todo: review-}) [1..] vs) 877 subst i0 x (ExpTV a at vs) = ExpTV (subst i0 x a) (subst i0 x at) (zipWith (\i -> subst (i0+i) $ up i x{-todo: review-}) [1..] vs)
@@ -887,6 +904,7 @@ removeLams i (Lam Hidden _ x) = removeLams i x
887etaRed (ELam _ (App (down 0 -> Just f) (EVar 0))) = etaRed f 904etaRed (ELam _ (App (down 0 -> Just f) (EVar 0))) = etaRed f
888etaRed (ELam _ (A3 (tupCaseName -> Just k) _ (down 0 -> Just x) (EVar 0))) = Just $ getPats k x 905etaRed (ELam _ (A3 (tupCaseName -> Just k) _ (down 0 -> Just x) (EVar 0))) = Just $ getPats k x
889etaRed (ELam p i) = Just (getPVars p, i) 906etaRed (ELam p i) = Just (getPVars p, i)
907--etaRed x | Pi Visible a b <- tyOf x = Just ([mkTVar 0 a], App x $ mkTVar 0 a)
890etaRed x = Nothing 908etaRed x = Nothing
891 909
892getPVars = \case 910getPVars = \case
diff --git a/src/LambdaCube/Compiler/Infer.hs b/src/LambdaCube/Compiler/Infer.hs
index ee78422d..79a97a09 100644
--- a/src/LambdaCube/Compiler/Infer.hs
+++ b/src/LambdaCube/Compiler/Infer.hs
@@ -18,7 +18,7 @@ module LambdaCube.Compiler.Infer
18 ( Binder (..), SName, Lit(..), Visibility(..) 18 ( Binder (..), SName, Lit(..), Visibility(..)
19 , Exp (..), Neutral (..), ExpType, GlobalEnv 19 , Exp (..), Neutral (..), ExpType, GlobalEnv
20 , pattern Var, pattern CaseFun, pattern TyCaseFun, pattern App_ 20 , pattern Var, pattern CaseFun, pattern TyCaseFun, pattern App_
21 , pattern Con, pattern TyCon, pattern Pi, pattern Lam, pattern Fun, pattern ELit, pattern Func, pattern LabelEnd 21 , pattern Con, pattern TyCon, pattern Pi, pattern Lam, pattern Fun, pattern ELit, pattern Func, pattern LabelEnd, pattern FL, pattern UFL, unFunc_
22 , outputType, boolType, trueExp 22 , outputType, boolType, trueExp
23 , down, Subst (..), free 23 , down, Subst (..), free
24 , initEnv, Env(..), pattern EBind2 24 , initEnv, Env(..), pattern EBind2
@@ -108,8 +108,9 @@ pattern NoLE <- (isNoLabelEnd -> True)
108isNoLabelEnd (LabelEnd_ _) = False 108isNoLabelEnd (LabelEnd_ _) = False
109isNoLabelEnd _ = True 109isNoLabelEnd _ = True
110 110
111pattern Fun f i xs n <- Fun_ _ f _ i xs n where Fun f i xs n = Fun_ (foldMap maxDB_ xs {- <> iterateN i lowerDB (maxDB_ n)-}) f [] i xs n 111pattern Fun' f vs i xs n <- Fun_ _ f vs i xs n where Fun' f vs i xs n = Fun_ (foldMap maxDB_ vs <> foldMap maxDB_ xs {- <> iterateN i lowerDB (maxDB_ n)-}) f vs i xs n
112pattern UTFun a t b <- Neut (Fun (FunName a _ t) _ (reverse -> b) NoLE) 112pattern Fun f i xs n = Fun' f [] i xs n
113pattern UTFun a t b <- (unfixlabel -> Neut (Fun (FunName a _ t) _ (reverse -> b) NoLE))
113pattern UFunN a b <- UTFun a _ b 114pattern UFunN a b <- UTFun a _ b
114pattern DFun_ fn xs <- Fun fn 0 (reverse -> xs) (Delta _) where 115pattern DFun_ fn xs <- Fun fn 0 (reverse -> xs) (Delta _) where
115 DFun_ fn@(FunName n _ _) xs = Fun fn 0 (reverse xs) d where 116 DFun_ fn@(FunName n _ _) xs = Fun fn 0 (reverse xs) d where
@@ -152,7 +153,7 @@ pattern Pi v x y <- Pi_ _ v x y where Pi v x y = Pi_ (maxDB_ x <> lowerDB (maxDB
152pattern TyConN s a <- TyCon (TyConName s _ _ _ _) a 153pattern TyConN s a <- TyCon (TyConName s _ _ _ _) a
153pattern TTyCon s t a <- TyCon (TyConName s _ t _ _) a 154pattern TTyCon s t a <- TyCon (TyConName s _ t _ _) a
154tTyCon s t a cs = TyCon (TyConName s (error "todo: inum") t (map ((,) (error "tTyCon")) cs) $ CaseFunName (error "TTyCon-A") (error "TTyCon-B") $ length a) a 155tTyCon s t a cs = TyCon (TyConName s (error "todo: inum") t (map ((,) (error "tTyCon")) cs) $ CaseFunName (error "TTyCon-A") (error "TTyCon-B") $ length a) a
155pattern TTyCon0 s <- TyCon (TyConName s _ TType _ _) [] 156pattern TTyCon0 s <- (unfixlabel -> TyCon (TyConName s _ TType _ _) [])
156tTyCon0 s cs = Closed $ TyCon (TyConName s 0 TType (map ((,) (error "tTyCon0")) cs) $ CaseFunName (error "TTyCon0-A") (error "TTyCon0-B") 0) [] 157tTyCon0 s cs = Closed $ TyCon (TyConName s 0 TType (map ((,) (error "tTyCon0")) cs) $ CaseFunName (error "TTyCon0-A") (error "TTyCon0-B") 0) []
157pattern a :~> b = Pi Visible a b 158pattern a :~> b = Pi Visible a b
158 159
@@ -238,13 +239,13 @@ trueExp = EBool True
238 239
239pattern LabelEnd x = Neut (LabelEnd_ x) 240pattern LabelEnd x = Neut (LabelEnd_ x)
240 241
241pmLabel' :: FunName -> Int -> [Exp] -> Exp -> Exp 242pmLabel' :: FunName -> [Exp] -> Int -> [Exp] -> Exp -> Exp
242pmLabel' (FunName _ _ _) 0 as (Neut (Delta (SData f))) = f $ reverse as 243pmLabel' (FunName _ _ _) _ 0 as (Neut (Delta (SData f))) = f $ reverse as
243pmLabel' f i xs (unfixlabel -> Neut y) = Neut $ Fun f i xs y 244pmLabel' f vs i xs (unfixlabel -> Neut y) = Neut $ Fun' f vs i xs y
244pmLabel' f i xs y = error $ "pmLabel: " ++ show (f, i, length xs, y) 245pmLabel' f _ i xs y = error $ "pmLabel: " ++ show (f, i, length xs, y)
245 246
246pmLabel :: FunName -> Int -> [Exp] -> Exp -> Exp 247pmLabel :: FunName -> [Exp] -> Int -> [Exp] -> Exp -> Exp
247pmLabel f i xs e = pmLabel' f (i + numLams e) xs (Neut $ dropLams e) 248pmLabel f vs i xs e = pmLabel' f vs (i + numLams e) xs (Neut $ dropLams e)
248 249
249dropLams (unfixlabel -> Lam x) = dropLams x 250dropLams (unfixlabel -> Lam x) = dropLams x
250dropLams (unfixlabel -> Neut x) = x 251dropLams (unfixlabel -> Neut x) = x
@@ -252,7 +253,7 @@ dropLams (unfixlabel -> Neut x) = x
252numLams (unfixlabel -> Lam x) = 1 + numLams x 253numLams (unfixlabel -> Lam x) = 1 + numLams x
253numLams x = 0 254numLams x = 0
254 255
255pattern FL' y <- Fun f 0 xs (LabelEnd_ y) 256pattern FL' y <- Fun' f _ 0 xs (LabelEnd_ y)
256pattern FL y <- Neut (FL' y) 257pattern FL y <- Neut (FL' y)
257 258
258pattern Func n def ty xs <- (mkFunc -> Just (n, def, ty, xs)) 259pattern Func n def ty xs <- (mkFunc -> Just (n, def, ty, xs))
@@ -264,6 +265,14 @@ removeLams 0 (LabelEnd x) = Just x
264removeLams n (Lam x) | n > 0 = Lam <$> removeLams (n-1) x 265removeLams n (Lam x) | n > 0 = Lam <$> removeLams (n-1) x
265removeLams _ _ = Nothing 266removeLams _ _ = Nothing
266 267
268pattern UFL y <- (unFunc -> Just y)
269
270unFunc (Neut (Fun' (FunName _ (Just def) _) _ n xs y)) = Just $ iterateN n Lam $ Neut y
271unFunc _ = Nothing
272
273unFunc_ (Neut (Fun' _ _ n xs y)) = Just $ iterateN n Lam $ Neut y
274unFunc_ _ = Nothing
275
267unfixlabel (FL y) = unfixlabel y 276unfixlabel (FL y) = unfixlabel y
268unfixlabel a = a 277unfixlabel a = a
269 278
@@ -289,7 +298,7 @@ instance Eq Exp where
289 _ == _ = False 298 _ == _ = False
290 299
291instance Eq Neutral where 300instance Eq Neutral where
292 Fun f i a _ == Fun f' i' a' _ = (f, i, a) == (f', i', a') 301 Fun' f vs i a _ == Fun' f' vs' i' a' _ = (f, vs, i, a) == (f', vs', i', a')
293 FL' a == a' = a == Neut a' 302 FL' a == a' = a == Neut a'
294 a == FL' a' = Neut a == a' 303 a == FL' a' = Neut a == a'
295 LabelEnd_ a == LabelEnd_ a' = a == a' 304 LabelEnd_ a == LabelEnd_ a' = a == a'
@@ -356,7 +365,7 @@ instance Subst Exp Exp where
356 CaseFun_ s as n -> evalCaseFun s (f i <$> as) (substNeut n) 365 CaseFun_ s as n -> evalCaseFun s (f i <$> as) (substNeut n)
357 TyCaseFun_ s as n -> evalTyCaseFun s (f i <$> as) (substNeut n) 366 TyCaseFun_ s as n -> evalTyCaseFun s (f i <$> as) (substNeut n)
358 App_ a b -> app_ (substNeut a) (f i b) 367 App_ a b -> app_ (substNeut a) (f i b)
359 Fun fn c xs v -> pmLabel' fn c (f i <$> xs) $ f (i + c) $ Neut v 368 Fun' fn vs c xs v -> pmLabel' fn (f i <$> vs) c (f i <$> xs) $ f (i + c) $ Neut v
360 LabelEnd_ a -> LabelEnd $ f i a 369 LabelEnd_ a -> LabelEnd $ f i a
361 d@Delta{} -> Neut d 370 d@Delta{} -> Neut d
362 f i e | cmpDB i e = e 371 f i e | cmpDB i e = e
@@ -376,7 +385,7 @@ instance Up Neutral where
376 CaseFun__ md s as ne -> CaseFun__ (upDB n md) s (up_ n i <$> as) (up_ n i ne) 385 CaseFun__ md s as ne -> CaseFun__ (upDB n md) s (up_ n i <$> as) (up_ n i ne)
377 TyCaseFun__ md s as ne -> TyCaseFun__ (upDB n md) s (up_ n i <$> as) (up_ n i ne) 386 TyCaseFun__ md s as ne -> TyCaseFun__ (upDB n md) s (up_ n i <$> as) (up_ n i ne)
378 App__ md a b -> App__ (upDB n md) (up_ n i a) (up_ n i b) 387 App__ md a b -> App__ (upDB n md) (up_ n i a) (up_ n i b)
379 Fun fn c x y -> Fun fn c (up_ n i <$> x) $ up_ n (i + c) y 388 Fun' fn vs c x y -> Fun' fn (up_ n i <$> vs) c (up_ n i <$> x) $ up_ n (i + c) y
380 LabelEnd_ x -> LabelEnd_ $ up_ n i x 389 LabelEnd_ x -> LabelEnd_ $ up_ n i x
381 d@Delta{} -> d 390 d@Delta{} -> d
382 391
@@ -389,7 +398,7 @@ instance Up Neutral where
389 CaseFun_ _ as n -> foldMap (fold f i) as <> fold f i n 398 CaseFun_ _ as n -> foldMap (fold f i) as <> fold f i n
390 TyCaseFun_ _ as n -> foldMap (fold f i) as <> fold f i n 399 TyCaseFun_ _ as n -> foldMap (fold f i) as <> fold f i n
391 App_ a b -> fold f i a <> fold f i b 400 App_ a b -> fold f i a <> fold f i b
392 Fun _ j x d -> foldMap (fold f i) x -- <> fold f (i+j) d 401 Fun' _ vs j x d -> foldMap (fold f i) vs <> foldMap (fold f i) x -- <> fold f (i+j) d
393 LabelEnd_ x -> fold f i x 402 LabelEnd_ x -> fold f i x
394 Delta{} -> mempty 403 Delta{} -> mempty
395 404
@@ -511,7 +520,7 @@ getFunDef s f = case s of
511 520
512cstr = f [] 521cstr = f []
513 where 522 where
514 f _ _ a a' | a == a' = Unit 523 f _ _ a a' | unfixlabel a == unfixlabel a' = Unit
515 f ns typ (LabelEnd a) (LabelEnd a') = f ns typ a a' 524 f ns typ (LabelEnd a) (LabelEnd a') = f ns typ a a'
516 f ns typ (FL a) a' = f ns typ a a' 525 f ns typ (FL a) a' = f ns typ a a'
517 f ns typ a (FL a') = f ns typ a a' 526 f ns typ a (FL a') = f ns typ a a'
@@ -597,7 +606,7 @@ app_ (TyCon s xs) a = TyCon s (xs ++ [a])
597app_ (Neut f) a = neutApp f a 606app_ (Neut f) a = neutApp f a
598 where 607 where
599 neutApp (FL' x) a = app_ x a -- ??? 608 neutApp (FL' x) a = app_ x a -- ???
600 neutApp (Fun f i xs e) a | i > 0 = pmLabel f (i-1) (a: xs) (subst (i-1) (up (i-1) a) $ Neut e) 609 neutApp (Fun' f vs i xs e) a | i > 0 = pmLabel f vs (i-1) (a: xs) (subst (i-1) (up (i-1) a) $ Neut e)
601 neutApp f a = Neut $ App_ f a 610 neutApp f a = Neut $ App_ f a
602 611
603-------------------------------------------------------------------------------- constraints env 612-------------------------------------------------------------------------------- constraints env
@@ -650,8 +659,8 @@ data Env
650 | EBind2_ SI Binder Type Env -- zoom into second parameter of SBind 659 | EBind2_ SI Binder Type Env -- zoom into second parameter of SBind
651 | EApp1 SI Visibility Env SExp2 660 | EApp1 SI Visibility Env SExp2
652 | EApp2 SI Visibility ExpType Env 661 | EApp2 SI Visibility ExpType Env
653 | ELet1 LI Env SExp2 662 | ELet1 SIName Env SExp2
654 | ELet2 LI ExpType Env 663 | ELet2 SIName ExpType Env
655 | EGlobal 664 | EGlobal
656 | ELabelEnd Env 665 | ELabelEnd Env
657 666
@@ -679,7 +688,15 @@ parent = \case
679 CheckAppType _ _ _ x _ -> Right x 688 CheckAppType _ _ _ x _ -> Right x
680 ELabelEnd x -> Right x 689 ELabelEnd x -> Right x
681 EGlobal -> Left () 690 EGlobal -> Left ()
682 691{-
692freeVars = \case
693 EGlobal -> []
694 EAssign i _ x -> [Var $ if j > i then j-1 else j | Var j <- freeVars x, j /= i]
695 EBind2 _ _ x -> Var 0: (up 1 <$> freeVars x)
696 ELet2 _ _ x -> Var 0: (up 1 <$> freeVars x)
697 x | Right y <- parent x -> freeVars y
698 x -> error $ "freeVars: " ++ show x
699-}
683-------------------------------------------------------------------------------- simple typing 700-------------------------------------------------------------------------------- simple typing
684 701
685litType = \case 702litType = \case
@@ -702,14 +719,14 @@ neutType te = \case
702 Var_ i -> snd $ varType "C" i te 719 Var_ i -> snd $ varType "C" i te
703 CaseFun_ s ts n -> appTy (foldl appTy (nType s) $ makeCaseFunPars te n ++ ts) (Neut n) 720 CaseFun_ s ts n -> appTy (foldl appTy (nType s) $ makeCaseFunPars te n ++ ts) (Neut n)
704 TyCaseFun_ s [m, t, f] n -> foldl appTy (nType s) [m, t, Neut n, f] 721 TyCaseFun_ s [m, t, f] n -> foldl appTy (nType s) [m, t, Neut n, f]
705 Fun s _ a _ -> foldlrev appTy (nType s) a 722 Fun' s _ _ a _ -> foldlrev appTy (nType s) a
706 723
707neutType' te = \case 724neutType' te = \case
708 App_ f x -> appTy (neutType' te f) x 725 App_ f x -> appTy (neutType' te f) x
709 Var_ i -> varType' i te 726 Var_ i -> varType' i te
710 CaseFun_ s ts n -> appTy (foldl appTy (nType s) $ makeCaseFunPars' te n ++ ts) (Neut n) 727 CaseFun_ s ts n -> appTy (foldl appTy (nType s) $ makeCaseFunPars' te n ++ ts) (Neut n)
711 TyCaseFun_ s [m, t, f] n -> foldl appTy (nType s) [m, t, Neut n, f] 728 TyCaseFun_ s [m, t, f] n -> foldl appTy (nType s) [m, t, Neut n, f]
712 Fun s _ a _ -> foldlrev appTy (nType s) a 729 Fun' s _ _ a _ -> foldlrev appTy (nType s) a
713 730
714mkExpTypes t [] = [] 731mkExpTypes t [] = []
715mkExpTypes t@(Pi _ a _) (x: xs) = (x, t): mkExpTypes (appTy t x) xs 732mkExpTypes t@(Pi _ a _) (x: xs) = (x, t): mkExpTypes (appTy t x) xs
@@ -868,7 +885,7 @@ inferN_ tellTrace = infer where
868 | otherwise -> infer (CheckType_ (sourceInfo b) (Var 2) $ cstr' h (up 2 et) (Pi Visible (Var 1) (Var 1)) (up 2 e) $ EBind2_ (sourceInfo b) BMeta TType $ EBind2_ (sourceInfo b) BMeta TType te) (up 3 b) 885 | otherwise -> infer (CheckType_ (sourceInfo b) (Var 2) $ cstr' h (up 2 et) (Pi Visible (Var 1) (Var 1)) (up 2 e) $ EBind2_ (sourceInfo b) BMeta TType $ EBind2_ (sourceInfo b) BMeta TType te) (up 3 b)
869 where 886 where
870 cstr' h x y e = EApp2 mempty h (evalCoe (up 1 x) (up 1 y) (Var 0) (up 1 e), up 1 y) . EBind2_ (sourceInfo b) BMeta (cstr TType x y) 887 cstr' h x y e = EApp2 mempty h (evalCoe (up 1 x) (up 1 y) (Var 0) (up 1 e), up 1 y) . EBind2_ (sourceInfo b) BMeta (cstr TType x y)
871 ELet2 le (x{-let-}, xt) te -> focus_ te $ subst 0 (mkELet le x xt){-let-} eet{-in-} 888 ELet2 ln (x{-let-}, xt) te -> focus_ te $ subst 0 (mkELet ln x xt){-let-} eet{-in-}
872 CheckIType x te -> checkN te x e 889 CheckIType x te -> checkN te x e
873 CheckType_ si t te 890 CheckType_ si t te
874 | hArgs et > hArgs t 891 | hArgs et > hArgs t
@@ -1007,7 +1024,9 @@ recheck' msg' e (x, xt) = (recheck_ "main" (checkEnv e) (x, xt), xt)
1007 (TyCon s as, zt) -> checkApps (show s) [] zt (TyCon s) te (nType s) as 1024 (TyCon s as, zt) -> checkApps (show s) [] zt (TyCon s) te (nType s) as
1008 (CaseFun s@(CaseFunName _ t pars) as n, zt) -> checkApps (show s) [] zt (\xs -> evalCaseFun s (init $ drop pars xs) (last xs)) te (nType s) (makeCaseFunPars te n ++ as ++ [Neut n]) 1025 (CaseFun s@(CaseFunName _ t pars) as n, zt) -> checkApps (show s) [] zt (\xs -> evalCaseFun s (init $ drop pars xs) (last xs)) te (nType s) (makeCaseFunPars te n ++ as ++ [Neut n])
1009 (TyCaseFun s [m, t, f] n, zt) -> checkApps (show s) [] zt (\[m, t, n, f] -> evalTyCaseFun s [m, t, f] n) te (nType s) [m, t, Neut n, f] 1026 (TyCaseFun s [m, t, f] n, zt) -> checkApps (show s) [] zt (\[m, t, n, f] -> evalTyCaseFun s [m, t, f] n) te (nType s) [m, t, Neut n, f]
1010 (Neut (Fun f i a x), zt) -> checkApps "lab" [] zt (\xs -> Neut $ Fun f i (reverse xs) x) te (nType f) $ reverse a -- TODO: recheck x 1027 (Neut (Fun' f vs@[] i a x), zt) -> checkApps "lab" [] zt (\xs -> Neut $ Fun' f vs i (reverse xs) x) te (nType f) $ reverse a -- TODO: recheck x
1028 -- TODO
1029 (r@(Neut (Fun' f vs i a x)), zt) -> r
1011 (LabelEnd x, zt) -> LabelEnd $ recheck_ msg te (x, zt) 1030 (LabelEnd x, zt) -> LabelEnd $ recheck_ msg te (x, zt)
1012 (Neut d@Delta{}, zt) -> Neut d 1031 (Neut d@Delta{}, zt) -> Neut d
1013 where 1032 where
@@ -1146,7 +1165,7 @@ handleStmt defs = \case
1146 let t__ = maybe id (flip SAnn . af) mt t_ 1165 let t__ = maybe id (flip SAnn . af) mt t_
1147 (x, t) <- inferTerm (snd n) $ trSExp' $ if usedS n t__ then SBuiltin "primFix" `SAppV` SLamV (substSG0 n t__) else t__ 1166 (x, t) <- inferTerm (snd n) $ trSExp' $ if usedS n t__ then SBuiltin "primFix" `SAppV` SLamV (substSG0 n t__) else t__
1148 tellType (fst n) t 1167 tellType (fst n) t
1149 addToEnv n mf (mkELet (True, n) x t, t) 1168 addToEnv n mf (mkELet n x t, t)
1150{- -- hack 1169{- -- hack
1151 when (snd (getParams t) == TType) $ do 1170 when (snd (getParams t) == TType) $ do
1152 let ps' = fst $ getParams t 1171 let ps' = fst $ getParams t
@@ -1218,15 +1237,15 @@ handleStmt defs = \case
1218 1237
1219withEnv e = local $ second (<> e) 1238withEnv e = local $ second (<> e)
1220 1239
1221mkELet (False, n) x xt = x 1240mkELet n x xt = {-(if null vs then id else trace_ $ "mkELet " ++ show (length vs) ++ " " ++ show n)-} term
1222mkELet (True, n) x xt = term
1223 where 1241 where
1242 vs = [Var i | i <- Set.toList $ free x <> free xt]
1224 fn = FunName (snd n) (Just x) xt 1243 fn = FunName (snd n) (Just x) xt
1225 1244
1226 term = pmLabel fn 0 [] $ getFix x 0 1245 term = pmLabel fn vs 0 [] $ getFix x 0
1227 1246
1228 getFix (Lam z) i = Lam $ getFix z (i+1) 1247 getFix (Lam z) i = Lam $ getFix z (i+1)
1229 getFix (TFun "primFix" _ [t, Lam f]) i = subst 0 (foldl app_ term (downTo 0 i)) f 1248 getFix (TFun "primFix" _ [t, Lam f]) i = (if null vs then id else trace_ "!local rec") $ subst 0 (foldl app_ term (downTo 0 i)) f
1230 getFix x _ = x 1249 getFix x _ = x
1231 1250
1232 1251
@@ -1401,7 +1420,7 @@ instance MkDoc Neutral where
1401 g = mkDoc ts 1420 g = mkDoc ts
1402 f = \case 1421 f = \case
1403 CstrT' t a b -> shCstr <$> g (a, t) <*> g (b, t) 1422 CstrT' t a b -> shCstr <$> g (a, t) <*> g (b, t)
1404 Fun s i (mkExpTypes (nType s) . reverse -> xs) _ -> foldl (shApp Visible) (shAtom_ $ show s) <$> mapM g xs 1423 Fun' s vs i (mkExpTypes (nType s) . reverse -> xs) _ -> foldl (shApp Visible) (shAtom_ $ show s) <$> mapM g xs
1405 Var_ k -> shAtom <$> shVar k 1424 Var_ k -> shAtom <$> shVar k
1406 App_ a b -> shApp Visible <$> g a <*> g b 1425 App_ a b -> shApp Visible <$> g a <*> g b
1407 CaseFun_ s xs n -> foldl (shApp Visible) (shAtom_ $ show s) <$> mapM g ({-mkExpTypes (nType s) $ makeCaseFunPars te n ++ -} xs ++ [Neut n]) 1426 CaseFun_ s xs n -> foldl (shApp Visible) (shAtom_ $ show s) <$> mapM g ({-mkExpTypes (nType s) $ makeCaseFunPars te n ++ -} xs ++ [Neut n])
diff --git a/src/LambdaCube/Compiler/Parser.hs b/src/LambdaCube/Compiler/Parser.hs
index 1bdf19f2..283638de 100644
--- a/src/LambdaCube/Compiler/Parser.hs
+++ b/src/LambdaCube/Compiler/Parser.hs
@@ -15,7 +15,7 @@ module LambdaCube.Compiler.Parser
15 , pattern SVar, pattern SType, pattern Wildcard, pattern SAppV, pattern SLamV, pattern SAnn 15 , pattern SVar, pattern SType, pattern Wildcard, pattern SAppV, pattern SLamV, pattern SAnn
16 , pattern SBuiltin, pattern SPi, pattern Primitive, pattern SLabelEnd, pattern SLam 16 , pattern SBuiltin, pattern SPi, pattern Primitive, pattern SLabelEnd, pattern SLam
17 , pattern TyType, pattern Wildcard_ 17 , pattern TyType, pattern Wildcard_
18 , debug, LI, isPi, varDB, lowerDB, justDB, upDB, cmpDB, MaxDB (..), iterateN, traceD 18 , debug, isPi, varDB, lowerDB, justDB, upDB, cmpDB, MaxDB (..), iterateN, traceD
19 , parseLC, runDefParser 19 , parseLC, runDefParser
20 , getParamsS, addParamsS, getApps, apps', downToS, addForalls 20 , getParamsS, addParamsS, getApps, apps', downToS, addForalls
21 , mkDesugarInfo, joinDesugarInfo 21 , mkDesugarInfo, joinDesugarInfo
@@ -94,15 +94,12 @@ data SExp' a
94 = SGlobal SIName 94 = SGlobal SIName
95 | SBind SI Binder (SData SIName{-parameter's name-}) (SExp' a) (SExp' a) 95 | SBind SI Binder (SData SIName{-parameter's name-}) (SExp' a) (SExp' a)
96 | SApp SI Visibility (SExp' a) (SExp' a) 96 | SApp SI Visibility (SExp' a) (SExp' a)
97 | SLet LI (SExp' a) (SExp' a) -- let x = e in f --> SLet e f{-x is Var 0-} 97 | SLet SIName (SExp' a) (SExp' a) -- let x = e in f --> SLet e f{-x is Var 0-}
98 | SVar_ (SData SIName) !Int 98 | SVar_ (SData SIName) !Int
99 | SLit SI Lit 99 | SLit SI Lit
100 | STyped SI a 100 | STyped SI a
101 deriving (Eq, Show) 101 deriving (Eq, Show)
102 102
103-- let info
104type LI = (Bool, SIName)
105
106pattern SVar a b = SVar_ (SData a) b 103pattern SVar a b = SVar_ (SData a) b
107 104
108data Binder 105data Binder
@@ -379,7 +376,7 @@ parseTerm prec = setSI' {-TODO: remove, slow-} $ case prec of
379 ) <|> mkList <$> namespace <*> pure []) 376 ) <|> mkList <$> namespace <*> pure [])
380 <|> mkTuple <$> namespace <*> parens (commaSep $ parseTerm PrecLam) 377 <|> mkTuple <$> namespace <*> parens (commaSep $ parseTerm PrecLam)
381 <|> mkRecord <$> braces (commaSep $ (,) <$> lowerCase <* symbol ":" <*> parseTerm PrecLam) 378 <|> mkRecord <$> braces (commaSep $ (,) <$> lowerCase <* symbol ":" <*> parseTerm PrecLam)
382 <|> mkLets True <$ reserved "let" <*> dsInfo <*> parseDefs xSLabelEnd <* reserved "in" <*> parseTerm PrecLam 379 <|> mkLets <$ reserved "let" <*> dsInfo <*> parseDefs <* reserved "in" <*> parseTerm PrecLam
383 where 380 where
384 level pr f = parseTerm pr >>= \t -> option t $ f t 381 level pr f = parseTerm pr >>= \t -> option t $ f t
385 382
@@ -462,7 +459,7 @@ parseTerm prec = setSI' {-TODO: remove, slow-} $ case prec of
462 ]) 459 ])
463 `SAppV` exp 460 `SAppV` exp
464 461
465 letdecl = mkLets False <$ reserved "let" <*> dsInfo <*> (compileFunAlts' id =<< valueDef) 462 letdecl = mkLets <$ reserved "let" <*> dsInfo <*> (compileFunAlts' SLabelEnd =<< valueDef)
466 463
467 boolExpression = (\pred e -> SBuiltin "primIfThenElse" `SAppV` pred `SAppV` e `SAppV` SBuiltin "Nil") <$> parseTerm PrecLam 464 boolExpression = (\pred e -> SBuiltin "primIfThenElse" `SAppV` pred `SAppV` e `SAppV` SBuiltin "Nil") <$> parseTerm PrecLam
468 465
@@ -813,10 +810,10 @@ parseRHS fe tok = fmap (fmap (fe *** fe) +++ fe) $ do
813 <|> do 810 <|> do
814 reservedOp tok 811 reservedOp tok
815 rhs <- parseTerm PrecLam 812 rhs <- parseTerm PrecLam
816 f <- option id $ mkLets True <$ reserved "where" <*> dsInfo <*> parseDefs xSLabelEnd 813 f <- option id $ mkLets <$ reserved "where" <*> dsInfo <*> parseDefs
817 return $ Right $ f rhs 814 return $ Right $ f rhs
818 815
819parseDefs lend = indentMS True parseDef >>= compileFunAlts' lend . concat 816parseDefs = indentMS True parseDef >>= compileFunAlts' SLabelEnd . concat
820 817
821funAltDef parseName = do -- todo: use ns to determine parseName 818funAltDef parseName = do -- todo: use ns to determine parseName
822 (n, (fee, tss)) <- 819 (n, (fee, tss)) <-
@@ -864,16 +861,14 @@ parseSomeGuards f = do
864 f <$> ((map (dbfGT e') <$> parseSomeGuards (> pos)) <|> (:[]) . GuardLeaf <$ reservedOp "->" <*> (dbf' e' <$> parseETerm PrecLam)) 861 f <$> ((map (dbfGT e') <$> parseSomeGuards (> pos)) <|> (:[]) . GuardLeaf <$ reservedOp "->" <*> (dbf' e' <$> parseETerm PrecLam))
865 <*> option [] (parseSomeGuards (== pos)) 862 <*> option [] (parseSomeGuards (== pos))
866-} 863-}
867mkLets :: Bool -> DesugarInfo -> [Stmt]{-where block-} -> SExp{-main expression-} -> SExp{-big let with lambdas; replaces global names with de bruijn indices-} 864mkLets :: DesugarInfo -> [Stmt]{-where block-} -> SExp{-main expression-} -> SExp{-big let with lambdas; replaces global names with de bruijn indices-}
868mkLets a ds = mkLets' a ds . sortDefs ds where 865mkLets ds = mkLets' . sortDefs ds where
869 mkLets' _ _ [] e = e 866 mkLets' [] e = e
870 mkLets' False ge (Let n _ mt x: ds) e | not $ usedS n x 867 mkLets' (Let n _ mt x: ds) e
871 = SLet (False, n) (maybe id (flip SAnn . addForalls {-todo-}[] []) mt x) (substSG0 n $ mkLets' False ge ds e) 868 = SLet n (maybe id (flip SAnn . addForalls {-todo-}[] []) mt x') (substSG0 n $ mkLets' ds e)
872 mkLets' True ge (Let n _ mt x: ds) e | not $ usedS n x 869 where
873 = SLet (False, n) (maybe id (flip SAnn . addForalls {-todo-}[] []) mt x) (substSG0 n $ mkLets' True ge ds e) 870 x' = if usedS n x then SBuiltin "primFix" `SAppV` SLamV (substSG0 n x) else x
874 mkLets' _ _ (x: ds) e = error $ "mkLets: " ++ show x 871 mkLets' (x: ds) e = error $ "mkLets: " ++ show x
875
876xSLabelEnd = id --SLabelEnd
877 872
878addForalls :: Up a => Extensions -> [SName] -> SExp' a -> SExp' a 873addForalls :: Up a => Extensions -> [SName] -> SExp' a -> SExp' a
879addForalls exs defined x = foldl f x [v | v@(_, vh:_) <- reverse $ freeS x, snd v `notElem'` ("fromInt"{-todo: remove-}: defined), isLower vh || NoConstructorNamespace `elem` exs] 874addForalls exs defined x = foldl f x [v | v@(_, vh:_) <- reverse $ freeS x, snd v `notElem'` ("fromInt"{-todo: remove-}: defined), isLower vh || NoConstructorNamespace `elem` exs]
@@ -1081,7 +1076,7 @@ parseModule f str = do
1081 { extensions = exts 1076 { extensions = exts
1082 , moduleImports = [((mempty, "Prelude"), ImportAllBut []) | NoImplicitPrelude `notElem` exts] ++ idefs 1077 , moduleImports = [((mempty, "Prelude"), ImportAllBut []) | NoImplicitPrelude `notElem` exts] ++ idefs
1083 , moduleExports = join $ snd <$> header 1078 , moduleExports = join $ snd <$> header
1084 , definitions = \ge -> first snd $ runP' (ge, ns) f (parseDefs SLabelEnd <* eof) st 1079 , definitions = \ge -> first snd $ runP' (ge, ns) f (parseDefs <* eof) st
1085 } 1080 }
1086 1081
1087parseLC :: FilePath -> String -> Either ParseError Module 1082parseLC :: FilePath -> String -> Either ParseError Module
diff --git a/test/runTests.hs b/test/runTests.hs
index a175bc7e..dacd0002 100644
--- a/test/runTests.hs
+++ b/test/runTests.hs
@@ -195,7 +195,7 @@ doTest Config{..} (i, fn) = do
195 liftIO $ putStrLn msg 195 liftIO $ putStrLn msg
196 return (runtime, result) 196 return (runtime, result)
197 where 197 where
198 (splitMPath -> (pa, mn', mn), exts) = splitExtensions' $ dropExtension fn 198 (splitMPath -> (pa, mn', mn), reverse -> exts) = splitExtensions' $ dropExtension fn
199 199
200 getMain = do 200 getMain = do
201 r@(fname, x, _) <- local (const $ ioFetch [pa]) $ getDef (mn' ++ concat exts ++ ".lc") "main" Nothing 201 r@(fname, x, _) <- local (const $ ioFetch [pa]) $ getDef (mn' ++ concat exts ++ ".lc") "main" Nothing
diff --git a/testdata/Graphics.out b/testdata/Graphics.out
index fc891b27..cea97671 100644
--- a/testdata/Graphics.out
+++ b/testdata/Graphics.out
@@ -38,6 +38,8 @@ Pipeline
38 vec4 snoc(vec3 z0,float z1) { 38 vec4 snoc(vec3 z0,float z1) {
39 return vec4 ((z0).x,(z0).y,(z0).z,z1); 39 return vec4 ((z0).x,(z0).y,(z0).z,z1);
40 } 40 }
41 mat4 viewProj = viewProj;
42 mat4 worldMat = worldMat;
41 void main() { 43 void main() {
42 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 44 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
43 vo1 = vi2; 45 vo1 = vi2;
@@ -82,6 +84,8 @@ Pipeline
82 vec4 snoc(vec3 z0,float z1) { 84 vec4 snoc(vec3 z0,float z1) {
83 return vec4 ((z0).x,(z0).y,(z0).z,z1); 85 return vec4 ((z0).x,(z0).y,(z0).z,z1);
84 } 86 }
87 mat4 viewProj = viewProj;
88 mat4 worldMat = worldMat;
85 void main() { 89 void main() {
86 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 90 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
87 vo1 = vec4 ((vi2).x,(vi2).y,(vi2).z,0.5); 91 vo1 = vec4 ((vi2).x,(vi2).y,(vi2).z,0.5);
@@ -136,6 +140,8 @@ Pipeline
136 vec4 snoc(vec3 z0,float z1) { 140 vec4 snoc(vec3 z0,float z1) {
137 return vec4 ((z0).x,(z0).y,(z0).z,z1); 141 return vec4 ((z0).x,(z0).y,(z0).z,z1);
138 } 142 }
143 mat4 viewProj = viewProj;
144 mat4 worldMat = worldMat;
139 void main() { 145 void main() {
140 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 146 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
141 vo1 = vi4; 147 vo1 = vi4;
@@ -194,6 +200,8 @@ Pipeline
194 vec4 snoc(vec3 z0,float z1) { 200 vec4 snoc(vec3 z0,float z1) {
195 return vec4 ((z0).x,(z0).y,(z0).z,z1); 201 return vec4 ((z0).x,(z0).y,(z0).z,z1);
196 } 202 }
203 mat4 viewProj = viewProj;
204 mat4 worldMat = worldMat;
197 void main() { 205 void main() {
198 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 206 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
199 vo1 = vi3; 207 vo1 = vi3;
@@ -253,6 +261,9 @@ Pipeline
253 vec4 snoc(vec3 z0,float z1) { 261 vec4 snoc(vec3 z0,float z1) {
254 return vec4 ((z0).x,(z0).y,(z0).z,z1); 262 return vec4 ((z0).x,(z0).y,(z0).z,z1);
255 } 263 }
264 float time = time;
265 mat4 viewProj = viewProj;
266 mat4 worldMat = worldMat;
256 void main() { 267 void main() {
257 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 268 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
258 vo1 = (((vi3) + ((vec2 (0.0,1.0)) * (time))) + ((sin (vec2 269 vo1 = (((vi3) + ((vec2 (0.0,1.0)) * (time))) + ((sin (vec2
@@ -314,6 +325,8 @@ Pipeline
314 vec4 snoc(vec3 z0,float z1) { 325 vec4 snoc(vec3 z0,float z1) {
315 return vec4 ((z0).x,(z0).y,(z0).z,z1); 326 return vec4 ((z0).x,(z0).y,(z0).z,z1);
316 } 327 }
328 mat4 viewProj = viewProj;
329 mat4 worldMat = worldMat;
317 void main() { 330 void main() {
318 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 331 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
319 vo1 = vi3; 332 vo1 = vi3;
@@ -372,6 +385,8 @@ Pipeline
372 vec4 snoc(vec3 z0,float z1) { 385 vec4 snoc(vec3 z0,float z1) {
373 return vec4 ((z0).x,(z0).y,(z0).z,z1); 386 return vec4 ((z0).x,(z0).y,(z0).z,z1);
374 } 387 }
388 mat4 viewProj = viewProj;
389 mat4 worldMat = worldMat;
375 void main() { 390 void main() {
376 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 391 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
377 vo1 = vi3; 392 vo1 = vi3;
@@ -432,6 +447,9 @@ Pipeline
432 vec4 snoc(vec3 z0,float z1) { 447 vec4 snoc(vec3 z0,float z1) {
433 return vec4 ((z0).x,(z0).y,(z0).z,z1); 448 return vec4 ((z0).x,(z0).y,(z0).z,z1);
434 } 449 }
450 float time = time;
451 mat4 viewProj = viewProj;
452 mat4 worldMat = worldMat;
435 void main() { 453 void main() {
436 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 454 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
437 vo1 = (((vi3) + ((vec2 (0.0,1.0)) * (time))) + ((sin (vec2 455 vo1 = (((vi3) + ((vec2 (0.0,1.0)) * (time))) + ((sin (vec2
@@ -494,6 +512,8 @@ Pipeline
494 vec4 snoc(vec3 z0,float z1) { 512 vec4 snoc(vec3 z0,float z1) {
495 return vec4 ((z0).x,(z0).y,(z0).z,z1); 513 return vec4 ((z0).x,(z0).y,(z0).z,z1);
496 } 514 }
515 mat4 viewProj = viewProj;
516 mat4 worldMat = worldMat;
497 void main() { 517 void main() {
498 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 518 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
499 vo1 = vi4; 519 vo1 = vi4;
@@ -554,6 +574,8 @@ Pipeline
554 vec4 snoc(vec3 z0,float z1) { 574 vec4 snoc(vec3 z0,float z1) {
555 return vec4 ((z0).x,(z0).y,(z0).z,z1); 575 return vec4 ((z0).x,(z0).y,(z0).z,z1);
556 } 576 }
577 mat4 viewProj = viewProj;
578 mat4 worldMat = worldMat;
557 void main() { 579 void main() {
558 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 580 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
559 vo1 = vi3; 581 vo1 = vi3;
@@ -614,6 +636,8 @@ Pipeline
614 vec4 snoc(vec3 z0,float z1) { 636 vec4 snoc(vec3 z0,float z1) {
615 return vec4 ((z0).x,(z0).y,(z0).z,z1); 637 return vec4 ((z0).x,(z0).y,(z0).z,z1);
616 } 638 }
639 mat4 viewProj = viewProj;
640 mat4 worldMat = worldMat;
617 void main() { 641 void main() {
618 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 642 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
619 vo1 = vi3; 643 vo1 = vi3;
@@ -674,6 +698,8 @@ Pipeline
674 vec4 snoc(vec3 z0,float z1) { 698 vec4 snoc(vec3 z0,float z1) {
675 return vec4 ((z0).x,(z0).y,(z0).z,z1); 699 return vec4 ((z0).x,(z0).y,(z0).z,z1);
676 } 700 }
701 mat4 viewProj = viewProj;
702 mat4 worldMat = worldMat;
677 void main() { 703 void main() {
678 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 704 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
679 vo1 = vi3; 705 vo1 = vi3;
@@ -733,6 +759,8 @@ Pipeline
733 vec4 snoc(vec3 z0,float z1) { 759 vec4 snoc(vec3 z0,float z1) {
734 return vec4 ((z0).x,(z0).y,(z0).z,z1); 760 return vec4 ((z0).x,(z0).y,(z0).z,z1);
735 } 761 }
762 mat4 viewProj = viewProj;
763 mat4 worldMat = worldMat;
736 void main() { 764 void main() {
737 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 765 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
738 vo1 = vi3; 766 vo1 = vi3;
@@ -793,6 +821,8 @@ Pipeline
793 vec4 snoc(vec3 z0,float z1) { 821 vec4 snoc(vec3 z0,float z1) {
794 return vec4 ((z0).x,(z0).y,(z0).z,z1); 822 return vec4 ((z0).x,(z0).y,(z0).z,z1);
795 } 823 }
824 mat4 viewProj = viewProj;
825 mat4 worldMat = worldMat;
796 void main() { 826 void main() {
797 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 827 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
798 vo1 = vi3; 828 vo1 = vi3;
@@ -853,6 +883,8 @@ Pipeline
853 vec4 snoc(vec3 z0,float z1) { 883 vec4 snoc(vec3 z0,float z1) {
854 return vec4 ((z0).x,(z0).y,(z0).z,z1); 884 return vec4 ((z0).x,(z0).y,(z0).z,z1);
855 } 885 }
886 mat4 viewProj = viewProj;
887 mat4 worldMat = worldMat;
856 void main() { 888 void main() {
857 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 889 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
858 vo1 = vi3; 890 vo1 = vi3;
@@ -913,6 +945,8 @@ Pipeline
913 vec4 snoc(vec3 z0,float z1) { 945 vec4 snoc(vec3 z0,float z1) {
914 return vec4 ((z0).x,(z0).y,(z0).z,z1); 946 return vec4 ((z0).x,(z0).y,(z0).z,z1);
915 } 947 }
948 mat4 viewProj = viewProj;
949 mat4 worldMat = worldMat;
916 void main() { 950 void main() {
917 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 951 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
918 vo1 = vi3; 952 vo1 = vi3;
@@ -973,6 +1007,8 @@ Pipeline
973 vec4 snoc(vec3 z0,float z1) { 1007 vec4 snoc(vec3 z0,float z1) {
974 return vec4 ((z0).x,(z0).y,(z0).z,z1); 1008 return vec4 ((z0).x,(z0).y,(z0).z,z1);
975 } 1009 }
1010 mat4 viewProj = viewProj;
1011 mat4 worldMat = worldMat;
976 void main() { 1012 void main() {
977 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 1013 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
978 vo1 = vi3; 1014 vo1 = vi3;
@@ -1033,6 +1069,8 @@ Pipeline
1033 vec4 snoc(vec3 z0,float z1) { 1069 vec4 snoc(vec3 z0,float z1) {
1034 return vec4 ((z0).x,(z0).y,(z0).z,z1); 1070 return vec4 ((z0).x,(z0).y,(z0).z,z1);
1035 } 1071 }
1072 mat4 viewProj = viewProj;
1073 mat4 worldMat = worldMat;
1036 void main() { 1074 void main() {
1037 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 1075 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
1038 vo1 = vi3; 1076 vo1 = vi3;
@@ -1093,6 +1131,8 @@ Pipeline
1093 vec4 snoc(vec3 z0,float z1) { 1131 vec4 snoc(vec3 z0,float z1) {
1094 return vec4 ((z0).x,(z0).y,(z0).z,z1); 1132 return vec4 ((z0).x,(z0).y,(z0).z,z1);
1095 } 1133 }
1134 mat4 viewProj = viewProj;
1135 mat4 worldMat = worldMat;
1096 void main() { 1136 void main() {
1097 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 1137 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
1098 vo1 = vi3; 1138 vo1 = vi3;
@@ -1153,6 +1193,8 @@ Pipeline
1153 vec4 snoc(vec3 z0,float z1) { 1193 vec4 snoc(vec3 z0,float z1) {
1154 return vec4 ((z0).x,(z0).y,(z0).z,z1); 1194 return vec4 ((z0).x,(z0).y,(z0).z,z1);
1155 } 1195 }
1196 mat4 viewProj = viewProj;
1197 mat4 worldMat = worldMat;
1156 void main() { 1198 void main() {
1157 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 1199 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
1158 vo1 = vi3; 1200 vo1 = vi3;
@@ -1213,6 +1255,8 @@ Pipeline
1213 vec4 snoc(vec3 z0,float z1) { 1255 vec4 snoc(vec3 z0,float z1) {
1214 return vec4 ((z0).x,(z0).y,(z0).z,z1); 1256 return vec4 ((z0).x,(z0).y,(z0).z,z1);
1215 } 1257 }
1258 mat4 viewProj = viewProj;
1259 mat4 worldMat = worldMat;
1216 void main() { 1260 void main() {
1217 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 1261 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
1218 vo1 = vi3; 1262 vo1 = vi3;
@@ -1273,6 +1317,8 @@ Pipeline
1273 vec4 snoc(vec3 z0,float z1) { 1317 vec4 snoc(vec3 z0,float z1) {
1274 return vec4 ((z0).x,(z0).y,(z0).z,z1); 1318 return vec4 ((z0).x,(z0).y,(z0).z,z1);
1275 } 1319 }
1320 mat4 viewProj = viewProj;
1321 mat4 worldMat = worldMat;
1276 void main() { 1322 void main() {
1277 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 1323 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
1278 vo1 = vi3; 1324 vo1 = vi3;
@@ -1333,6 +1379,8 @@ Pipeline
1333 vec4 snoc(vec3 z0,float z1) { 1379 vec4 snoc(vec3 z0,float z1) {
1334 return vec4 ((z0).x,(z0).y,(z0).z,z1); 1380 return vec4 ((z0).x,(z0).y,(z0).z,z1);
1335 } 1381 }
1382 mat4 viewProj = viewProj;
1383 mat4 worldMat = worldMat;
1336 void main() { 1384 void main() {
1337 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 1385 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
1338 vo1 = vi3; 1386 vo1 = vi3;
@@ -1393,6 +1441,8 @@ Pipeline
1393 vec4 snoc(vec3 z0,float z1) { 1441 vec4 snoc(vec3 z0,float z1) {
1394 return vec4 ((z0).x,(z0).y,(z0).z,z1); 1442 return vec4 ((z0).x,(z0).y,(z0).z,z1);
1395 } 1443 }
1444 mat4 viewProj = viewProj;
1445 mat4 worldMat = worldMat;
1396 void main() { 1446 void main() {
1397 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 1447 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
1398 vo1 = vi3; 1448 vo1 = vi3;
@@ -1453,6 +1503,8 @@ Pipeline
1453 vec4 snoc(vec3 z0,float z1) { 1503 vec4 snoc(vec3 z0,float z1) {
1454 return vec4 ((z0).x,(z0).y,(z0).z,z1); 1504 return vec4 ((z0).x,(z0).y,(z0).z,z1);
1455 } 1505 }
1506 mat4 viewProj = viewProj;
1507 mat4 worldMat = worldMat;
1456 void main() { 1508 void main() {
1457 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 1509 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
1458 vo1 = vi3; 1510 vo1 = vi3;
@@ -1513,6 +1565,8 @@ Pipeline
1513 vec4 snoc(vec3 z0,float z1) { 1565 vec4 snoc(vec3 z0,float z1) {
1514 return vec4 ((z0).x,(z0).y,(z0).z,z1); 1566 return vec4 ((z0).x,(z0).y,(z0).z,z1);
1515 } 1567 }
1568 mat4 viewProj = viewProj;
1569 mat4 worldMat = worldMat;
1516 void main() { 1570 void main() {
1517 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 1571 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
1518 vo1 = vi3; 1572 vo1 = vi3;
@@ -1573,6 +1627,8 @@ Pipeline
1573 vec4 snoc(vec3 z0,float z1) { 1627 vec4 snoc(vec3 z0,float z1) {
1574 return vec4 ((z0).x,(z0).y,(z0).z,z1); 1628 return vec4 ((z0).x,(z0).y,(z0).z,z1);
1575 } 1629 }
1630 mat4 viewProj = viewProj;
1631 mat4 worldMat = worldMat;
1576 void main() { 1632 void main() {
1577 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 1633 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
1578 vo1 = vi3; 1634 vo1 = vi3;
@@ -1632,6 +1688,8 @@ Pipeline
1632 vec4 snoc(vec3 z0,float z1) { 1688 vec4 snoc(vec3 z0,float z1) {
1633 return vec4 ((z0).x,(z0).y,(z0).z,z1); 1689 return vec4 ((z0).x,(z0).y,(z0).z,z1);
1634 } 1690 }
1691 mat4 viewProj = viewProj;
1692 mat4 worldMat = worldMat;
1635 void main() { 1693 void main() {
1636 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 1694 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
1637 vo1 = vi3; 1695 vo1 = vi3;
@@ -1692,6 +1750,8 @@ Pipeline
1692 vec4 snoc(vec3 z0,float z1) { 1750 vec4 snoc(vec3 z0,float z1) {
1693 return vec4 ((z0).x,(z0).y,(z0).z,z1); 1751 return vec4 ((z0).x,(z0).y,(z0).z,z1);
1694 } 1752 }
1753 mat4 viewProj = viewProj;
1754 mat4 worldMat = worldMat;
1695 void main() { 1755 void main() {
1696 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 1756 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
1697 vo1 = vi3; 1757 vo1 = vi3;
@@ -1752,6 +1812,8 @@ Pipeline
1752 vec4 snoc(vec3 z0,float z1) { 1812 vec4 snoc(vec3 z0,float z1) {
1753 return vec4 ((z0).x,(z0).y,(z0).z,z1); 1813 return vec4 ((z0).x,(z0).y,(z0).z,z1);
1754 } 1814 }
1815 mat4 viewProj = viewProj;
1816 mat4 worldMat = worldMat;
1755 void main() { 1817 void main() {
1756 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 1818 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
1757 vo1 = vi3; 1819 vo1 = vi3;
@@ -1812,6 +1874,8 @@ Pipeline
1812 vec4 snoc(vec3 z0,float z1) { 1874 vec4 snoc(vec3 z0,float z1) {
1813 return vec4 ((z0).x,(z0).y,(z0).z,z1); 1875 return vec4 ((z0).x,(z0).y,(z0).z,z1);
1814 } 1876 }
1877 mat4 viewProj = viewProj;
1878 mat4 worldMat = worldMat;
1815 void main() { 1879 void main() {
1816 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 1880 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
1817 vo1 = vi3; 1881 vo1 = vi3;
@@ -1872,6 +1936,8 @@ Pipeline
1872 vec4 snoc(vec3 z0,float z1) { 1936 vec4 snoc(vec3 z0,float z1) {
1873 return vec4 ((z0).x,(z0).y,(z0).z,z1); 1937 return vec4 ((z0).x,(z0).y,(z0).z,z1);
1874 } 1938 }
1939 mat4 viewProj = viewProj;
1940 mat4 worldMat = worldMat;
1875 void main() { 1941 void main() {
1876 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 1942 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
1877 vo1 = vi3; 1943 vo1 = vi3;
@@ -1932,6 +1998,8 @@ Pipeline
1932 vec4 snoc(vec3 z0,float z1) { 1998 vec4 snoc(vec3 z0,float z1) {
1933 return vec4 ((z0).x,(z0).y,(z0).z,z1); 1999 return vec4 ((z0).x,(z0).y,(z0).z,z1);
1934 } 2000 }
2001 mat4 viewProj = viewProj;
2002 mat4 worldMat = worldMat;
1935 void main() { 2003 void main() {
1936 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 2004 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
1937 vo1 = vi3; 2005 vo1 = vi3;
@@ -1992,6 +2060,8 @@ Pipeline
1992 vec4 snoc(vec3 z0,float z1) { 2060 vec4 snoc(vec3 z0,float z1) {
1993 return vec4 ((z0).x,(z0).y,(z0).z,z1); 2061 return vec4 ((z0).x,(z0).y,(z0).z,z1);
1994 } 2062 }
2063 mat4 viewProj = viewProj;
2064 mat4 worldMat = worldMat;
1995 void main() { 2065 void main() {
1996 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 2066 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
1997 vo1 = vi3; 2067 vo1 = vi3;
@@ -2052,6 +2122,8 @@ Pipeline
2052 vec4 snoc(vec3 z0,float z1) { 2122 vec4 snoc(vec3 z0,float z1) {
2053 return vec4 ((z0).x,(z0).y,(z0).z,z1); 2123 return vec4 ((z0).x,(z0).y,(z0).z,z1);
2054 } 2124 }
2125 mat4 viewProj = viewProj;
2126 mat4 worldMat = worldMat;
2055 void main() { 2127 void main() {
2056 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 2128 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
2057 vo1 = vi3; 2129 vo1 = vi3;
@@ -2112,6 +2184,8 @@ Pipeline
2112 vec4 snoc(vec3 z0,float z1) { 2184 vec4 snoc(vec3 z0,float z1) {
2113 return vec4 ((z0).x,(z0).y,(z0).z,z1); 2185 return vec4 ((z0).x,(z0).y,(z0).z,z1);
2114 } 2186 }
2187 mat4 viewProj = viewProj;
2188 mat4 worldMat = worldMat;
2115 void main() { 2189 void main() {
2116 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 2190 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
2117 vo1 = vi3; 2191 vo1 = vi3;
@@ -2172,6 +2246,8 @@ Pipeline
2172 vec4 snoc(vec3 z0,float z1) { 2246 vec4 snoc(vec3 z0,float z1) {
2173 return vec4 ((z0).x,(z0).y,(z0).z,z1); 2247 return vec4 ((z0).x,(z0).y,(z0).z,z1);
2174 } 2248 }
2249 mat4 viewProj = viewProj;
2250 mat4 worldMat = worldMat;
2175 void main() { 2251 void main() {
2176 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 2252 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
2177 vo1 = vi3; 2253 vo1 = vi3;
@@ -2232,6 +2308,8 @@ Pipeline
2232 vec4 snoc(vec3 z0,float z1) { 2308 vec4 snoc(vec3 z0,float z1) {
2233 return vec4 ((z0).x,(z0).y,(z0).z,z1); 2309 return vec4 ((z0).x,(z0).y,(z0).z,z1);
2234 } 2310 }
2311 mat4 viewProj = viewProj;
2312 mat4 worldMat = worldMat;
2235 void main() { 2313 void main() {
2236 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 2314 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
2237 vo1 = vi3; 2315 vo1 = vi3;
@@ -2292,6 +2370,8 @@ Pipeline
2292 vec4 snoc(vec3 z0,float z1) { 2370 vec4 snoc(vec3 z0,float z1) {
2293 return vec4 ((z0).x,(z0).y,(z0).z,z1); 2371 return vec4 ((z0).x,(z0).y,(z0).z,z1);
2294 } 2372 }
2373 mat4 viewProj = viewProj;
2374 mat4 worldMat = worldMat;
2295 void main() { 2375 void main() {
2296 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 2376 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
2297 vo1 = vi3; 2377 vo1 = vi3;
@@ -2352,6 +2432,8 @@ Pipeline
2352 vec4 snoc(vec3 z0,float z1) { 2432 vec4 snoc(vec3 z0,float z1) {
2353 return vec4 ((z0).x,(z0).y,(z0).z,z1); 2433 return vec4 ((z0).x,(z0).y,(z0).z,z1);
2354 } 2434 }
2435 mat4 viewProj = viewProj;
2436 mat4 worldMat = worldMat;
2355 void main() { 2437 void main() {
2356 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 2438 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
2357 vo1 = vi3; 2439 vo1 = vi3;
@@ -2412,6 +2494,8 @@ Pipeline
2412 vec4 snoc(vec3 z0,float z1) { 2494 vec4 snoc(vec3 z0,float z1) {
2413 return vec4 ((z0).x,(z0).y,(z0).z,z1); 2495 return vec4 ((z0).x,(z0).y,(z0).z,z1);
2414 } 2496 }
2497 mat4 viewProj = viewProj;
2498 mat4 worldMat = worldMat;
2415 void main() { 2499 void main() {
2416 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 2500 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
2417 vo1 = vi3; 2501 vo1 = vi3;
@@ -2472,6 +2556,8 @@ Pipeline
2472 vec4 snoc(vec3 z0,float z1) { 2556 vec4 snoc(vec3 z0,float z1) {
2473 return vec4 ((z0).x,(z0).y,(z0).z,z1); 2557 return vec4 ((z0).x,(z0).y,(z0).z,z1);
2474 } 2558 }
2559 mat4 viewProj = viewProj;
2560 mat4 worldMat = worldMat;
2475 void main() { 2561 void main() {
2476 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 2562 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
2477 vo1 = vi3; 2563 vo1 = vi3;
@@ -2532,6 +2618,8 @@ Pipeline
2532 vec4 snoc(vec3 z0,float z1) { 2618 vec4 snoc(vec3 z0,float z1) {
2533 return vec4 ((z0).x,(z0).y,(z0).z,z1); 2619 return vec4 ((z0).x,(z0).y,(z0).z,z1);
2534 } 2620 }
2621 mat4 viewProj = viewProj;
2622 mat4 worldMat = worldMat;
2535 void main() { 2623 void main() {
2536 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 2624 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
2537 vo1 = vi3; 2625 vo1 = vi3;
@@ -2591,6 +2679,8 @@ Pipeline
2591 vec4 snoc(vec3 z0,float z1) { 2679 vec4 snoc(vec3 z0,float z1) {
2592 return vec4 ((z0).x,(z0).y,(z0).z,z1); 2680 return vec4 ((z0).x,(z0).y,(z0).z,z1);
2593 } 2681 }
2682 mat4 viewProj = viewProj;
2683 mat4 worldMat = worldMat;
2594 void main() { 2684 void main() {
2595 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 2685 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
2596 vo1 = vi3; 2686 vo1 = vi3;
@@ -2651,6 +2741,8 @@ Pipeline
2651 vec4 snoc(vec3 z0,float z1) { 2741 vec4 snoc(vec3 z0,float z1) {
2652 return vec4 ((z0).x,(z0).y,(z0).z,z1); 2742 return vec4 ((z0).x,(z0).y,(z0).z,z1);
2653 } 2743 }
2744 mat4 viewProj = viewProj;
2745 mat4 worldMat = worldMat;
2654 void main() { 2746 void main() {
2655 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 2747 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
2656 vo1 = vi3; 2748 vo1 = vi3;
@@ -2711,6 +2803,8 @@ Pipeline
2711 vec4 snoc(vec3 z0,float z1) { 2803 vec4 snoc(vec3 z0,float z1) {
2712 return vec4 ((z0).x,(z0).y,(z0).z,z1); 2804 return vec4 ((z0).x,(z0).y,(z0).z,z1);
2713 } 2805 }
2806 mat4 viewProj = viewProj;
2807 mat4 worldMat = worldMat;
2714 void main() { 2808 void main() {
2715 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 2809 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
2716 vo1 = vi3; 2810 vo1 = vi3;
@@ -2771,6 +2865,8 @@ Pipeline
2771 vec4 snoc(vec3 z0,float z1) { 2865 vec4 snoc(vec3 z0,float z1) {
2772 return vec4 ((z0).x,(z0).y,(z0).z,z1); 2866 return vec4 ((z0).x,(z0).y,(z0).z,z1);
2773 } 2867 }
2868 mat4 viewProj = viewProj;
2869 mat4 worldMat = worldMat;
2774 void main() { 2870 void main() {
2775 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 2871 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
2776 vo1 = vi3; 2872 vo1 = vi3;
@@ -2831,6 +2927,8 @@ Pipeline
2831 vec4 snoc(vec3 z0,float z1) { 2927 vec4 snoc(vec3 z0,float z1) {
2832 return vec4 ((z0).x,(z0).y,(z0).z,z1); 2928 return vec4 ((z0).x,(z0).y,(z0).z,z1);
2833 } 2929 }
2930 mat4 viewProj = viewProj;
2931 mat4 worldMat = worldMat;
2834 void main() { 2932 void main() {
2835 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 2933 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
2836 vo1 = vi3; 2934 vo1 = vi3;
@@ -2891,6 +2989,8 @@ Pipeline
2891 vec4 snoc(vec3 z0,float z1) { 2989 vec4 snoc(vec3 z0,float z1) {
2892 return vec4 ((z0).x,(z0).y,(z0).z,z1); 2990 return vec4 ((z0).x,(z0).y,(z0).z,z1);
2893 } 2991 }
2992 mat4 viewProj = viewProj;
2993 mat4 worldMat = worldMat;
2894 void main() { 2994 void main() {
2895 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 2995 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
2896 vo1 = vi3; 2996 vo1 = vi3;
@@ -2951,6 +3051,8 @@ Pipeline
2951 vec4 snoc(vec3 z0,float z1) { 3051 vec4 snoc(vec3 z0,float z1) {
2952 return vec4 ((z0).x,(z0).y,(z0).z,z1); 3052 return vec4 ((z0).x,(z0).y,(z0).z,z1);
2953 } 3053 }
3054 mat4 viewProj = viewProj;
3055 mat4 worldMat = worldMat;
2954 void main() { 3056 void main() {
2955 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 3057 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
2956 vo1 = vi3; 3058 vo1 = vi3;
@@ -3011,6 +3113,8 @@ Pipeline
3011 vec4 snoc(vec3 z0,float z1) { 3113 vec4 snoc(vec3 z0,float z1) {
3012 return vec4 ((z0).x,(z0).y,(z0).z,z1); 3114 return vec4 ((z0).x,(z0).y,(z0).z,z1);
3013 } 3115 }
3116 mat4 viewProj = viewProj;
3117 mat4 worldMat = worldMat;
3014 void main() { 3118 void main() {
3015 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 3119 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
3016 vo1 = vi3; 3120 vo1 = vi3;
@@ -3071,6 +3175,8 @@ Pipeline
3071 vec4 snoc(vec3 z0,float z1) { 3175 vec4 snoc(vec3 z0,float z1) {
3072 return vec4 ((z0).x,(z0).y,(z0).z,z1); 3176 return vec4 ((z0).x,(z0).y,(z0).z,z1);
3073 } 3177 }
3178 mat4 viewProj = viewProj;
3179 mat4 worldMat = worldMat;
3074 void main() { 3180 void main() {
3075 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 3181 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
3076 vo1 = vi3; 3182 vo1 = vi3;
@@ -3131,6 +3237,8 @@ Pipeline
3131 vec4 snoc(vec3 z0,float z1) { 3237 vec4 snoc(vec3 z0,float z1) {
3132 return vec4 ((z0).x,(z0).y,(z0).z,z1); 3238 return vec4 ((z0).x,(z0).y,(z0).z,z1);
3133 } 3239 }
3240 mat4 viewProj = viewProj;
3241 mat4 worldMat = worldMat;
3134 void main() { 3242 void main() {
3135 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 3243 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
3136 vo1 = vi3; 3244 vo1 = vi3;
@@ -3191,6 +3299,8 @@ Pipeline
3191 vec4 snoc(vec3 z0,float z1) { 3299 vec4 snoc(vec3 z0,float z1) {
3192 return vec4 ((z0).x,(z0).y,(z0).z,z1); 3300 return vec4 ((z0).x,(z0).y,(z0).z,z1);
3193 } 3301 }
3302 mat4 viewProj = viewProj;
3303 mat4 worldMat = worldMat;
3194 void main() { 3304 void main() {
3195 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 3305 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
3196 vo1 = vi3; 3306 vo1 = vi3;
@@ -3251,6 +3361,8 @@ Pipeline
3251 vec4 snoc(vec3 z0,float z1) { 3361 vec4 snoc(vec3 z0,float z1) {
3252 return vec4 ((z0).x,(z0).y,(z0).z,z1); 3362 return vec4 ((z0).x,(z0).y,(z0).z,z1);
3253 } 3363 }
3364 mat4 viewProj = viewProj;
3365 mat4 worldMat = worldMat;
3254 void main() { 3366 void main() {
3255 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 3367 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
3256 vo1 = vi3; 3368 vo1 = vi3;
@@ -3311,6 +3423,8 @@ Pipeline
3311 vec4 snoc(vec3 z0,float z1) { 3423 vec4 snoc(vec3 z0,float z1) {
3312 return vec4 ((z0).x,(z0).y,(z0).z,z1); 3424 return vec4 ((z0).x,(z0).y,(z0).z,z1);
3313 } 3425 }
3426 mat4 viewProj = viewProj;
3427 mat4 worldMat = worldMat;
3314 void main() { 3428 void main() {
3315 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0))); 3429 gl_Position = (viewProj) * ((worldMat) * (snoc (vi1,1.0)));
3316 vo1 = vi3; 3430 vo1 = vi3;
diff --git a/testdata/HyperbolicParaboloic.out b/testdata/HyperbolicParaboloic.out
index 28548feb..7b9b420d 100644
--- a/testdata/HyperbolicParaboloic.out
+++ b/testdata/HyperbolicParaboloic.out
@@ -36,17 +36,15 @@ Pipeline
36 vec4 scale(float z0,vec4 z1) { 36 vec4 scale(float z0,vec4 z1) {
37 return (z1) * (vec4 (z0,z0,z0,1.0)); 37 return (z1) * (vec4 (z0,z0,z0,1.0));
38 } 38 }
39 vec4 v3FToV4F(vec3 z0) { 39 float t = (m).y;
40 return vec4 ((z0).x,(z0).y,(z0).z,1.0);
41 }
42 void main() { 40 void main() {
43 gl_Position = scale 41 gl_Position = scale
44 (0.1 42 (0.1
45 ,(MVP) * (vec4 (((m).y) * ((vi1).x) 43 ,(MVP) * (vec4 ((t) * ((vi1).x)
46 ,(((0.5) * ((m).x)) * ((vi1).x)) * ((vi1).y) 44 ,(((0.5) * ((m).x)) * ((vi1).x)) * ((vi1).y)
47 ,((m).y) * ((vi1).y) 45 ,(t) * ((vi1).y)
48 ,1.0))); 46 ,1.0)));
49 vo1 = v3FToV4F (vi1); 47 vo1 = vec4 ((vi1).x,(vi1).y,(vi1).z,1.0);
50 } 48 }
51 """ 49 """
52 , geometryShader = Nothing 50 , geometryShader = Nothing
diff --git a/testdata/Hyperboloid.lc b/testdata/Hyperboloid.lc
index d3f8dc7e..e6ae104a 100644
--- a/testdata/Hyperboloid.lc
+++ b/testdata/Hyperboloid.lc
@@ -14,9 +14,9 @@ mapFragments22 s fs = accumulate colorFragmentCtx (\a -> fs a) s clear
14transform s f = mapPrimitives (\(p) -> let v = v3FToV4F p in (f v, v)) s 14transform s f = mapPrimitives (\(p) -> let v = v3FToV4F p in (f v, v)) s
15 15
16trans :: Vec 4 Float -> Vec 4 Float 16trans :: Vec 4 Float -> Vec 4 Float
17trans (V4 x y _ _) = V4 (k *! sin (s *! x +! r *! y)) y (k *! cos (s *! x +! r *! y)) 1.0 17trans (V4 x y _ _) = V4 (k * sin (s * x + r * y)) y (k * cos (s * x + r * y)) 1.0
18 where 18 where
19 k = 2 *! m%y 19 k = 2 * m%y
20 s = 0.7 20 s = 0.7
21 r = m%x 21 r = m%x
22 22
diff --git a/testdata/Hyperboloid.out b/testdata/Hyperboloid.out
index 3eea868f..bf3367bb 100644
--- a/testdata/Hyperboloid.out
+++ b/testdata/Hyperboloid.out
@@ -33,22 +33,19 @@ Pipeline
33 in vec3 vi1; 33 in vec3 vi1;
34 smooth out vec4 vo1; 34 smooth out vec4 vo1;
35 vec2 m = Mouse; 35 vec2 m = Mouse;
36 float k = (2.0) * ((m).y);
37 float r = (m).x;
36 vec4 scale(float z0,vec4 z1) { 38 vec4 scale(float z0,vec4 z1) {
37 return (z1) * (vec4 (z0,z0,z0,1.0)); 39 return (z1) * (vec4 (z0,z0,z0,1.0));
38 } 40 }
39 vec4 v3FToV4F(vec3 z0) {
40 return vec4 ((z0).x,(z0).y,(z0).z,1.0);
41 }
42 void main() { 41 void main() {
43 gl_Position = scale 42 gl_Position = scale (0.1
44 (0.1 43 ,(MVP) * (vec4
45 ,(MVP) * (vec4 (((2.0) * ((m).y)) * (sin 44 ((k) * (sin (((0.7) * ((vi1).x)) + ((r) * ((vi1).y))))
46 (((0.7) * ((vi1).x)) + (((m).x) * ((vi1).y)))) 45 ,(vi1).y
47 ,(vi1).y 46 ,(k) * (cos (((0.7) * ((vi1).x)) + ((r) * ((vi1).y))))
48 ,((2.0) * ((m).y)) * (cos 47 ,1.0)));
49 (((0.7) * ((vi1).x)) + (((m).x) * ((vi1).y)))) 48 vo1 = vec4 ((vi1).x,(vi1).y,(vi1).z,1.0);
50 ,1.0)));
51 vo1 = v3FToV4F (vi1);
52 } 49 }
53 """ 50 """
54 , geometryShader = Nothing 51 , geometryShader = Nothing
diff --git a/testdata/Spiral.out b/testdata/Spiral.out
index 0364685f..d4922494 100644
--- a/testdata/Spiral.out
+++ b/testdata/Spiral.out
@@ -36,9 +36,6 @@ Pipeline
36 vec4 scale(float z0,vec4 z1) { 36 vec4 scale(float z0,vec4 z1) {
37 return (z1) * (vec4 (z0,z0,z0,1.0)); 37 return (z1) * (vec4 (z0,z0,z0,1.0));
38 } 38 }
39 vec4 v3FToV4F(vec3 z0) {
40 return vec4 ((z0).x,(z0).y,(z0).z,1.0);
41 }
42 void main() { 39 void main() {
43 gl_Position = scale 40 gl_Position = scale
44 (0.5 41 (0.5
@@ -48,7 +45,7 @@ Pipeline
48 ((0.9) * ((vi1).x))) 45 ((0.9) * ((vi1).x)))
49 ,((m).y) * ((0.9) * ((vi1).x)) 46 ,((m).y) * ((0.9) * ((vi1).x))
50 ,1.0))); 47 ,1.0)));
51 vo1 = v3FToV4F (vi1); 48 vo1 = vec4 ((vi1).x,(vi1).y,(vi1).z,1.0);
52 } 49 }
53 """ 50 """
54 , geometryShader = Nothing 51 , geometryShader = Nothing
diff --git a/testdata/editor-examples/Heartbeat.out b/testdata/editor-examples/Heartbeat.out
index 81eec655..435db6b7 100644
--- a/testdata/editor-examples/Heartbeat.out
+++ b/testdata/editor-examples/Heartbeat.out
@@ -108,6 +108,7 @@ Pipeline
108 } 108 }
109 vec4 blue = rgb (0.0,0.0,1.0); 109 vec4 blue = rgb (0.0,0.0,1.0);
110 vec4 navy = rgb (0.0,0.0,0.5); 110 vec4 navy = rgb (0.0,0.0,0.5);
111 float ti = abs ((sin ((time) * (4.0))) - (0.37));
111 float time = Time; 112 float time = Time;
112 vec4 white = rgb (1.0,1.0,1.0); 113 vec4 white = rgb (1.0,1.0,1.0);
113 vec4 yellow = rgb (1.0,1.0,0.0); 114 vec4 yellow = rgb (1.0,1.0,0.0);
@@ -116,18 +117,13 @@ Pipeline
116 ((((((vo1).x) - (0.85)) * (((vo1).x) - (0.85))) + ((((vo1).y) - (0.85)) * (((vo1).y) - (0.85)))) + ((5.0e-4) * (sin 117 ((((((vo1).x) - (0.85)) * (((vo1).x) - (0.85))) + ((((vo1).y) - (0.85)) * (((vo1).y) - (0.85)))) + ((5.0e-4) * (sin
117 (((3.0) * (atan 118 (((3.0) * (atan
118 (((vo1).x) - (0.85) 119 (((vo1).x) - (0.85)
119 ,((vo1).y) - (0.85)))) + ((15.0) * (time)))))) < ((5.0e-3) * (abs 120 ,((vo1).y) - (0.85)))) + ((15.0) * (time)))))) < ((5.0e-3) * (ti)) ? navy : ((((((vo1).x) - (0.85)) * (((vo1).x) - (0.85))) + ((((vo1).y) - (0.85)) * (((vo1).y) - (0.85)))) + ((2.0e-3) * (sin
120 ((sin
121 ((time) * (4.0))) - (0.37)))) ? navy : ((((((vo1).x) - (0.85)) * (((vo1).x) - (0.85))) + ((((vo1).y) - (0.85)) * (((vo1).y) - (0.85)))) + ((2.0e-3) * (sin
122 (((5.0) * (atan 121 (((5.0) * (atan
123 (((vo1).x) - (0.85) 122 (((vo1).x) - (0.85)
124 ,((vo1).y) - (0.85)))) - ((5.0) * (time)))))) < ((2.0e-2) * (abs 123 ,((vo1).y) - (0.85)))) - ((5.0) * (time)))))) < ((2.0e-2) * (ti)) ? blue : ((((((vo1).x) - (0.85)) * (((vo1).x) - (0.85))) + ((((vo1).y) - (0.85)) * (((vo1).y) - (0.85)))) + ((2.0e-3) * (sin
125 ((sin
126 ((time) * (4.0))) - (0.37)))) ? blue : ((((((vo1).x) - (0.85)) * (((vo1).x) - (0.85))) + ((((vo1).y) - (0.85)) * (((vo1).y) - (0.85)))) + ((2.0e-3) * (sin
127 (((7.0) * (atan 124 (((7.0) * (atan
128 (((vo1).x) - (0.85) 125 (((vo1).x) - (0.85)
129 ,((vo1).y) - (0.85)))) + ((3.0) * (time)))))) < ((5.0e-2) * (abs 126 ,((vo1).y) - (0.85)))) + ((3.0) * (time)))))) < ((5.0e-2) * (ti)) ? white : yellow;
130 ((sin ((time) * (4.0))) - (0.37)))) ? white : yellow;
131 } 127 }
132 """ 128 """
133 } 129 }
diff --git a/testdata/fetcharrays01.out b/testdata/fetcharrays01.out
index aa49e5fd..06db8806 100644
--- a/testdata/fetcharrays01.out
+++ b/testdata/fetcharrays01.out
@@ -36,12 +36,10 @@ Pipeline
36 vec4 scale(float z0,vec4 z1) { 36 vec4 scale(float z0,vec4 z1) {
37 return (z1) * (vec4 (z0,z0,z0,1.0)); 37 return (z1) * (vec4 (z0,z0,z0,1.0));
38 } 38 }
39 vec4 v3FToV4F(vec3 z0) {
40 return vec4 ((z0).x,(z0).y,(z0).z,1.0);
41 }
42 void main() { 39 void main() {
43 gl_Position = scale (0.5,(MVP) * (v3FToV4F (vi1))); 40 gl_Position = scale
44 vo1 = v3FToV4F (vi1); 41 (0.5,(MVP) * (vec4 ((vi1).x,(vi1).y,(vi1).z,1.0)));
42 vo1 = vec4 ((vi1).x,(vi1).y,(vi1).z,1.0);
45 } 43 }
46 """ 44 """
47 , geometryShader = Nothing 45 , geometryShader = Nothing
diff --git a/testdata/gfx03.out b/testdata/gfx03.out
index b3c238b4..1462c801 100644
--- a/testdata/gfx03.out
+++ b/testdata/gfx03.out
@@ -28,11 +28,10 @@ Pipeline
28 } 28 }
29 uniform mat4 MVP2; 29 uniform mat4 MVP2;
30 in vec3 vi1; 30 in vec3 vi1;
31 vec4 v3FToV4F(vec3 z0) { 31 mat4 modelViewProj = MVP2;
32 return vec4 ((z0).x,(z0).y,(z0).z,1.0);
33 }
34 void main() { 32 void main() {
35 gl_Position = (MVP2) * (v3FToV4F (vi1)); 33 gl_Position = (modelViewProj) * (vec4
34 ((vi1).x,(vi1).y,(vi1).z,1.0));
36 } 35 }
37 """ 36 """
38 , geometryShader = Nothing 37 , geometryShader = Nothing
@@ -63,12 +62,11 @@ Pipeline
63 uniform mat4 MVP2; 62 uniform mat4 MVP2;
64 in vec3 vi1; 63 in vec3 vi1;
65 smooth out vec4 vo1; 64 smooth out vec4 vo1;
66 vec4 v3FToV4F(vec3 z0) { 65 mat4 modelViewProj = MVP2;
67 return vec4 ((z0).x,(z0).y,(z0).z,1.0);
68 }
69 void main() { 66 void main() {
70 gl_Position = (MVP2) * (v3FToV4F (vi1)); 67 gl_Position = (modelViewProj) * (vec4
71 vo1 = v3FToV4F (vi1); 68 ((vi1).x,(vi1).y,(vi1).z,1.0));
69 vo1 = vec4 ((vi1).x,(vi1).y,(vi1).z,1.0);
72 } 70 }
73 """ 71 """
74 , geometryShader = Nothing 72 , geometryShader = Nothing
@@ -101,8 +99,9 @@ Pipeline
101 uniform mat4 MVP; 99 uniform mat4 MVP;
102 in vec4 vi1; 100 in vec4 vi1;
103 flat out vec4 vo1; 101 flat out vec4 vo1;
102 mat4 modelViewProj = MVP;
104 void main() { 103 void main() {
105 gl_Position = (MVP) * (vi1); 104 gl_Position = (modelViewProj) * (vi1);
106 vo1 = vi1; 105 vo1 = vi1;
107 } 106 }
108 """ 107 """
diff --git a/testdata/gfx04.out b/testdata/gfx04.out
index b39f1a1c..e17394f1 100644
--- a/testdata/gfx04.out
+++ b/testdata/gfx04.out
@@ -33,11 +33,12 @@ Pipeline
33 in vec3 vi1; 33 in vec3 vi1;
34 in vec3 vi2; 34 in vec3 vi2;
35 smooth out vec4 vo1; 35 smooth out vec4 vo1;
36 mat4 modelViewProj = MVP;
36 vec4 v3FToV4F(vec3 z0) { 37 vec4 v3FToV4F(vec3 z0) {
37 return vec4 ((z0).x,(z0).y,(z0).z,1.0); 38 return vec4 ((z0).x,(z0).y,(z0).z,1.0);
38 } 39 }
39 void main() { 40 void main() {
40 gl_Position = (MVP) * (v3FToV4F (vi1)); 41 gl_Position = (modelViewProj) * (v3FToV4F (vi1));
41 vo1 = v3FToV4F (vi2); 42 vo1 = v3FToV4F (vi2);
42 } 43 }
43 """ 44 """
diff --git a/testdata/gfx05.out b/testdata/gfx05.out
index aaa1ce3d..a06d0612 100644
--- a/testdata/gfx05.out
+++ b/testdata/gfx05.out
@@ -81,11 +81,10 @@ Pipeline
81 } 81 }
82 uniform mat4 MVP2; 82 uniform mat4 MVP2;
83 in vec3 vi1; 83 in vec3 vi1;
84 vec4 v3FToV4F(vec3 z0) { 84 mat4 modelViewProj = MVP2;
85 return vec4 ((z0).x,(z0).y,(z0).z,1.0);
86 }
87 void main() { 85 void main() {
88 gl_Position = (MVP2) * (v3FToV4F (vi1)); 86 gl_Position = (modelViewProj) * (vec4
87 ((vi1).x,(vi1).y,(vi1).z,1.0));
89 } 88 }
90 """ 89 """
91 , geometryShader = Nothing 90 , geometryShader = Nothing
@@ -116,12 +115,11 @@ Pipeline
116 uniform mat4 MVP2; 115 uniform mat4 MVP2;
117 in vec3 vi1; 116 in vec3 vi1;
118 smooth out vec4 vo1; 117 smooth out vec4 vo1;
119 vec4 v3FToV4F(vec3 z0) { 118 mat4 modelViewProj = MVP2;
120 return vec4 ((z0).x,(z0).y,(z0).z,1.0);
121 }
122 void main() { 119 void main() {
123 gl_Position = (MVP2) * (v3FToV4F (vi1)); 120 gl_Position = (modelViewProj) * (vec4
124 vo1 = v3FToV4F (vi1); 121 ((vi1).x,(vi1).y,(vi1).z,1.0));
122 vo1 = vec4 ((vi1).x,(vi1).y,(vi1).z,1.0);
125 } 123 }
126 """ 124 """
127 , geometryShader = Nothing 125 , geometryShader = Nothing
@@ -157,8 +155,9 @@ Pipeline
157 in vec4 vi1; 155 in vec4 vi1;
158 in vec2 vi2; 156 in vec2 vi2;
159 smooth out vec2 vo1; 157 smooth out vec2 vo1;
158 mat4 modelViewProj = MVP;
160 void main() { 159 void main() {
161 gl_Position = (MVP) * (vi1); 160 gl_Position = (modelViewProj) * (vi1);
162 vo1 = vi2; 161 vo1 = vi2;
163 } 162 }
164 """ 163 """
diff --git a/testdata/heartbeat01.out b/testdata/heartbeat01.out
index 70857c9b..35528cae 100644
--- a/testdata/heartbeat01.out
+++ b/testdata/heartbeat01.out
@@ -108,6 +108,7 @@ Pipeline
108 } 108 }
109 vec4 blue = rgb (0.0,0.0,1.0); 109 vec4 blue = rgb (0.0,0.0,1.0);
110 vec4 navy = rgb (0.0,0.0,0.5); 110 vec4 navy = rgb (0.0,0.0,0.5);
111 float ti = abs ((sin ((time) * (4.0))) - (0.37));
111 float time = Time; 112 float time = Time;
112 vec4 white = rgb (1.0,1.0,1.0); 113 vec4 white = rgb (1.0,1.0,1.0);
113 vec4 yellow = rgb (1.0,1.0,0.0); 114 vec4 yellow = rgb (1.0,1.0,0.0);
@@ -116,18 +117,13 @@ Pipeline
116 ((((((vo1).x) - (0.85)) * (((vo1).x) - (0.85))) + ((((vo1).y) - (0.85)) * (((vo1).y) - (0.85)))) + ((5.0e-4) * (sin 117 ((((((vo1).x) - (0.85)) * (((vo1).x) - (0.85))) + ((((vo1).y) - (0.85)) * (((vo1).y) - (0.85)))) + ((5.0e-4) * (sin
117 (((3.0) * (atan 118 (((3.0) * (atan
118 (((vo1).x) - (0.85) 119 (((vo1).x) - (0.85)
119 ,((vo1).y) - (0.85)))) + ((15.0) * (time)))))) < ((5.0e-3) * (abs 120 ,((vo1).y) - (0.85)))) + ((15.0) * (time)))))) < ((5.0e-3) * (ti)) ? navy : ((((((vo1).x) - (0.85)) * (((vo1).x) - (0.85))) + ((((vo1).y) - (0.85)) * (((vo1).y) - (0.85)))) + ((2.0e-3) * (sin
120 ((sin
121 ((time) * (4.0))) - (0.37)))) ? navy : ((((((vo1).x) - (0.85)) * (((vo1).x) - (0.85))) + ((((vo1).y) - (0.85)) * (((vo1).y) - (0.85)))) + ((2.0e-3) * (sin
122 (((5.0) * (atan 121 (((5.0) * (atan
123 (((vo1).x) - (0.85) 122 (((vo1).x) - (0.85)
124 ,((vo1).y) - (0.85)))) - ((5.0) * (time)))))) < ((2.0e-2) * (abs 123 ,((vo1).y) - (0.85)))) - ((5.0) * (time)))))) < ((2.0e-2) * (ti)) ? blue : ((((((vo1).x) - (0.85)) * (((vo1).x) - (0.85))) + ((((vo1).y) - (0.85)) * (((vo1).y) - (0.85)))) + ((2.0e-3) * (sin
125 ((sin
126 ((time) * (4.0))) - (0.37)))) ? blue : ((((((vo1).x) - (0.85)) * (((vo1).x) - (0.85))) + ((((vo1).y) - (0.85)) * (((vo1).y) - (0.85)))) + ((2.0e-3) * (sin
127 (((7.0) * (atan 124 (((7.0) * (atan
128 (((vo1).x) - (0.85) 125 (((vo1).x) - (0.85)
129 ,((vo1).y) - (0.85)))) + ((3.0) * (time)))))) < ((5.0e-2) * (abs 126 ,((vo1).y) - (0.85)))) + ((3.0) * (time)))))) < ((5.0e-2) * (ti)) ? white : yellow;
130 ((sin ((time) * (4.0))) - (0.37)))) ? white : yellow;
131 } 127 }
132 """ 128 """
133 } 129 }
diff --git a/testdata/language-features/recursion/simplerec02.wip.lc b/testdata/language-features/recursion/simplerec02.lc
index 71f046fd..71f046fd 100644
--- a/testdata/language-features/recursion/simplerec02.wip.lc
+++ b/testdata/language-features/recursion/simplerec02.lc
diff --git a/testdata/language-features/recursion/simplerec02.out b/testdata/language-features/recursion/simplerec02.out
new file mode 100644
index 00000000..5f8d48b2
--- /dev/null
+++ b/testdata/language-features/recursion/simplerec02.out
@@ -0,0 +1,9 @@
1main is not found
2------------ trace
3value :: 'Tuple0
4------------ tooltips
5testdata/language-features/recursion/simplerec02.lc 1:1-1:6 Tuple0
6testdata/language-features/recursion/simplerec02.lc 1:21-1:24 Char
7testdata/language-features/recursion/simplerec02.lc 1:21-2:26 Bool->Char | V0->V1
8testdata/language-features/recursion/simplerec02.lc 2:21-2:24 V4
9testdata/language-features/recursion/simplerec02.lc 3:12-3:14 Tuple0
diff --git a/testdata/language-features/recursion/simplerec03.wip.lc b/testdata/language-features/recursion/simplerec03.lc
index 5f602a04..5f602a04 100644
--- a/testdata/language-features/recursion/simplerec03.wip.lc
+++ b/testdata/language-features/recursion/simplerec03.lc
diff --git a/testdata/language-features/recursion/simplerec03.out b/testdata/language-features/recursion/simplerec03.out
new file mode 100644
index 00000000..16802cb7
--- /dev/null
+++ b/testdata/language-features/recursion/simplerec03.out
@@ -0,0 +1,9 @@
1main is not found
2------------ trace
3value :: 'Tuple0
4------------ tooltips
5testdata/language-features/recursion/simplerec03.lc 1:1-1:6 Tuple0
6testdata/language-features/recursion/simplerec03.lc 1:9-1:11 Tuple0
7testdata/language-features/recursion/simplerec03.lc 3:13-3:16 Char
8testdata/language-features/recursion/simplerec03.lc 3:13-4:18 Bool->Char | V0->V1
9testdata/language-features/recursion/simplerec03.lc 4:13-4:16 V4
diff --git a/testdata/line01.out b/testdata/line01.out
index 67124a52..a19722c6 100644
--- a/testdata/line01.out
+++ b/testdata/line01.out
@@ -33,12 +33,10 @@ Pipeline
33 vec4 scale(float z0,vec4 z1) { 33 vec4 scale(float z0,vec4 z1) {
34 return (z1) * (vec4 (z0,z0,z0,1.0)); 34 return (z1) * (vec4 (z0,z0,z0,1.0));
35 } 35 }
36 vec4 v3FToV4F(vec3 z0) {
37 return vec4 ((z0).x,(z0).y,(z0).z,1.0);
38 }
39 void main() { 36 void main() {
40 gl_Position = scale (0.5,(MVP) * (v3FToV4F (vi1))); 37 gl_Position = scale
41 vo1 = v3FToV4F (vi1); 38 (0.5,(MVP) * (vec4 ((vi1).x,(vi1).y,(vi1).z,1.0)));
39 vo1 = vec4 ((vi1).x,(vi1).y,(vi1).z,1.0);
42 } 40 }
43 """ 41 """
44 , geometryShader = Nothing 42 , geometryShader = Nothing
diff --git a/testdata/simple02.out b/testdata/simple02.out
index faf41dea..63f86974 100644
--- a/testdata/simple02.out
+++ b/testdata/simple02.out
@@ -30,8 +30,9 @@ Pipeline
30 uniform mat4 MVP; 30 uniform mat4 MVP;
31 in vec4 vi1; 31 in vec4 vi1;
32 smooth out vec4 vo1; 32 smooth out vec4 vo1;
33 mat4 modelViewProj = MVP;
33 void main() { 34 void main() {
34 gl_Position = (MVP) * (vi1); 35 gl_Position = (modelViewProj) * (vi1);
35 vo1 = vi1; 36 vo1 = vi1;
36 } 37 }
37 """ 38 """
diff --git a/testdata/simple03.out b/testdata/simple03.out
index dc2dcca3..79bc503a 100644
--- a/testdata/simple03.out
+++ b/testdata/simple03.out
@@ -33,11 +33,12 @@ Pipeline
33 in vec3 vi1; 33 in vec3 vi1;
34 in vec3 vi2; 34 in vec3 vi2;
35 smooth out vec4 vo1; 35 smooth out vec4 vo1;
36 mat4 modelViewProj = viewProj;
36 vec4 v3FToV4F(vec3 z0) { 37 vec4 v3FToV4F(vec3 z0) {
37 return vec4 ((z0).x,(z0).y,(z0).z,1.0); 38 return vec4 ((z0).x,(z0).y,(z0).z,1.0);
38 } 39 }
39 void main() { 40 void main() {
40 gl_Position = (viewProj) * (v3FToV4F (vi1)); 41 gl_Position = (modelViewProj) * (v3FToV4F (vi1));
41 vo1 = v3FToV4F (vi2); 42 vo1 = v3FToV4F (vi2);
42 } 43 }
43 """ 44 """
@@ -74,11 +75,12 @@ Pipeline
74 in vec3 vi1; 75 in vec3 vi1;
75 in vec3 vi2; 76 in vec3 vi2;
76 smooth out vec4 vo1; 77 smooth out vec4 vo1;
78 mat4 modelViewProj = viewProj;
77 vec4 v3FToV4F(vec3 z0) { 79 vec4 v3FToV4F(vec3 z0) {
78 return vec4 ((z0).x,(z0).y,(z0).z,1.0); 80 return vec4 ((z0).x,(z0).y,(z0).z,1.0);
79 } 81 }
80 void main() { 82 void main() {
81 gl_Position = (viewProj) * (v3FToV4F (vi1)); 83 gl_Position = (modelViewProj) * (v3FToV4F (vi1));
82 vo1 = v3FToV4F (vi2); 84 vo1 = v3FToV4F (vi2);
83 } 85 }
84 """ 86 """