summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--lc/Builtins.lc2
-rw-r--r--lc/Internals.lc4
-rw-r--r--src/LambdaCube/Compiler/CoreToIR.hs2
-rw-r--r--src/LambdaCube/Compiler/DesugaredSource.hs5
-rw-r--r--src/LambdaCube/Compiler/Infer.hs2
-rw-r--r--src/LambdaCube/Compiler/Lexer.hs5
-rw-r--r--src/LambdaCube/Compiler/Parser.hs2
-rw-r--r--src/LambdaCube/Compiler/Patterns.hs4
-rw-r--r--src/LambdaCube/Compiler/Pretty.hs1
-rw-r--r--testdata/Builtins.out74
-rw-r--r--testdata/Internals.out52
-rw-r--r--testdata/Material.out2
-rw-r--r--testdata/Prelude.out42
-rw-r--r--testdata/SampleMaterial.out870
-rw-r--r--testdata/framebuffer02.reject.out6
-rw-r--r--testdata/language-features/basic-list/list01.out6
-rw-r--r--testdata/language-features/basic-list/list02.out6
-rw-r--r--testdata/language-features/basic-list/list08.out2
-rw-r--r--testdata/language-features/basic-list/list09.out2
-rw-r--r--testdata/language-features/basic-list/listcomp01.out6
-rw-r--r--testdata/language-features/basic-list/listcomp02.out4
-rw-r--r--testdata/language-features/basic-list/listcomp03.out4
-rw-r--r--testdata/language-features/basic-list/listcomp04.out4
-rw-r--r--testdata/language-features/basic-list/listcomp05.out4
-rw-r--r--testdata/language-features/basic-list/listcomp06.out8
-rw-r--r--testdata/language-features/basic-list/listcomp07.out12
-rw-r--r--testdata/language-features/basic-list/listcomp09.out2
-rw-r--r--testdata/language-features/basic-values/data03.reject.out2
-rw-r--r--testdata/performance/Material.out2
-rw-r--r--testdata/performance/SampleMaterial.out870
-rw-r--r--testdata/record01.reject.out82
-rw-r--r--testdata/traceTest.out2
-rw-r--r--testdata/zip01.out3
33 files changed, 882 insertions, 1212 deletions
diff --git a/lc/Builtins.lc b/lc/Builtins.lc
index fb7c288f..0ff2f3b1 100644
--- a/lc/Builtins.lc
+++ b/lc/Builtins.lc
@@ -479,7 +479,7 @@ data Interpolated t where
479 479
480rasterizePrimitive 480rasterizePrimitive
481 :: ( map Interpolated b ~ interpolation 481 :: ( map Interpolated b ~ interpolation
482 , a ~ 'Cons (Vec 4 Float) b ) 482 , a ~ Vec 4 Float: b )
483 => HList interpolation -- tuple of Smooth & Flat 483 => HList interpolation -- tuple of Smooth & Flat
484 -> RasterContext (HList a) x 484 -> RasterContext (HList a) x
485 -> Primitive (HList a) x 485 -> Primitive (HList a) x
diff --git a/lc/Internals.lc b/lc/Internals.lc
index 6e61b4eb..170f2c39 100644
--- a/lc/Internals.lc
+++ b/lc/Internals.lc
@@ -119,7 +119,7 @@ instance Eq Nat where
119 Succ a == Succ b = a == b 119 Succ a == Succ b = a == b
120 _ == _ = False 120 _ == _ = False
121 121
122data List a = Nil | Cons a (List a) 122data List a = Nil | (:) a (List a)
123 123
124infixr 5 : 124infixr 5 :
125 125
@@ -132,7 +132,7 @@ hlistConsCase
132 :: forall (e :: Type) (f :: List Type) 132 :: forall (e :: Type) (f :: List Type)
133 . forall c 133 . forall c
134 -> (e -> HList f -> c) 134 -> (e -> HList f -> c)
135 -> HList (Cons e f) 135 -> HList (e: f)
136 -> c 136 -> c
137 137
138{- 138{-
diff --git a/src/LambdaCube/Compiler/CoreToIR.hs b/src/LambdaCube/Compiler/CoreToIR.hs
index 7e4a938e..c8c0dcaa 100644
--- a/src/LambdaCube/Compiler/CoreToIR.hs
+++ b/src/LambdaCube/Compiler/CoreToIR.hs
@@ -226,7 +226,7 @@ compFrameBuffer = \case
226 226
227compSemantics = map compSemantic . compList 227compSemantics = map compSemantic . compList
228 228
229compList (A2 "Cons" a x) = a : compList x 229compList (A2 ":" a x) = a : compList x
230compList (A0 "Nil") = [] 230compList (A0 "Nil") = []
231compList x = error $ "compList: " ++ ppShow x 231compList x = error $ "compList: " ++ ppShow x
232 232
diff --git a/src/LambdaCube/Compiler/DesugaredSource.hs b/src/LambdaCube/Compiler/DesugaredSource.hs
index c17717f3..5d3a70f3 100644
--- a/src/LambdaCube/Compiler/DesugaredSource.hs
+++ b/src/LambdaCube/Compiler/DesugaredSource.hs
@@ -242,6 +242,9 @@ infixl 2 `SAppV`, `SAppH`
242pattern SBuiltin s <- SGlobal (SIName _ s) 242pattern SBuiltin s <- SGlobal (SIName _ s)
243 where SBuiltin s = SGlobal (SIName (debugSI $ "builtin " ++ s) s) 243 where SBuiltin s = SGlobal (SIName (debugSI $ "builtin " ++ s) s)
244 244
245pattern ConsName <- SIName _ ":"
246 where ConsName = SIName_ mempty (Just $ InfixR 5) ":"
247
245pattern SRHS a = SBuiltin "_rhs" `SAppV` a 248pattern SRHS a = SBuiltin "_rhs" `SAppV` a
246pattern Section e = SBuiltin "^section" `SAppV` e 249pattern Section e = SBuiltin "^section" `SAppV` e
247pattern SType = SBuiltin "'Type" 250pattern SType = SBuiltin "'Type"
@@ -256,7 +259,7 @@ pattern HNil = SBuiltin "HNil"
256 259
257-- builtin list 260-- builtin list
258pattern BList a = SBuiltin "'List" `SAppV` a 261pattern BList a = SBuiltin "'List" `SAppV` a
259pattern BCons a b = SBuiltin "Cons" `SAppV` a `SAppV` b 262pattern BCons a b = SGlobal ConsName `SAppV` a `SAppV` b
260pattern BNil = SBuiltin "Nil" 263pattern BNil = SBuiltin "Nil"
261 264
262getTTuple (HList (getList -> Just xs)) = xs 265getTTuple (HList (getList -> Just xs)) = xs
diff --git a/src/LambdaCube/Compiler/Infer.hs b/src/LambdaCube/Compiler/Infer.hs
index 1b747e69..986a564d 100644
--- a/src/LambdaCube/Compiler/Infer.hs
+++ b/src/LambdaCube/Compiler/Infer.hs
@@ -192,7 +192,7 @@ fntable =
192 , (,) "EQ" FEQ 192 , (,) "EQ" FEQ
193 , (,) "TT" FTT 193 , (,) "TT" FTT
194 , (,) "Nil" FNil 194 , (,) "Nil" FNil
195 , (,) "Cons" FCons 195 , (,) ":" FCons
196 , (,) "'Split" FSplit 196 , (,) "'Split" FSplit
197 ] 197 ]
198 198
diff --git a/src/LambdaCube/Compiler/Lexer.hs b/src/LambdaCube/Compiler/Lexer.hs
index e10ac817..9f5e1c7d 100644
--- a/src/LambdaCube/Compiler/Lexer.hs
+++ b/src/LambdaCube/Compiler/Lexer.hs
@@ -233,10 +233,7 @@ expect msg p i = i >>= \n -> if p n then unexpected (msg ++ " " ++ show n) else
233 233
234identifier name = lexemeName $ try $ expect "reserved word" (`Set.member` theReservedNames) name 234identifier name = lexemeName $ try $ expect "reserved word" (`Set.member` theReservedNames) name
235 235
236operator name = lexemeName $ try $ trCons <$> expect "reserved operator" (`Set.member` theReservedOpNames) name 236operator name = lexemeName $ try $ expect "reserved operator" (`Set.member` theReservedOpNames) name
237 where
238 trCons ":" = "Cons"
239 trCons x = x
240 237
241theReservedOpNames = Set.fromList ["::","..","=","\\","|","<-","->","@","~","=>"] 238theReservedOpNames = Set.fromList ["::","..","=","\\","|","<-","->","@","~","=>"]
242 239
diff --git a/src/LambdaCube/Compiler/Parser.hs b/src/LambdaCube/Compiler/Parser.hs
index 70525cba..8f457e49 100644
--- a/src/LambdaCube/Compiler/Parser.hs
+++ b/src/LambdaCube/Compiler/Parser.hs
@@ -404,7 +404,7 @@ parseDef =
404 (af, cs) <- option (True, []) $ 404 (af, cs) <- option (True, []) $
405 (,) True . map (second $ (,) Nothing) . concat <$ reserved "where" <*> identation True (typedIds id npsd Nothing) 405 (,) True . map (second $ (,) Nothing) . concat <$ reserved "where" <*> identation True (typedIds id npsd Nothing)
406 <|> (,) False <$ reservedOp "=" <*> 406 <|> (,) False <$ reservedOp "=" <*>
407 sepBy1 ((,) <$> addFixity' upperCase 407 sepBy1 ((,) <$> (addFixity' upperCase <|> parens (addFixity colonSymbols))
408 <*> (mkConTy True <$> braces telescopeDataFields <|> mkConTy False <$> telescope Nothing) 408 <*> (mkConTy True <$> braces telescopeDataFields <|> mkConTy False <$> telescope Nothing)
409 ) 409 )
410 (reservedOp "|") 410 (reservedOp "|")
diff --git a/src/LambdaCube/Compiler/Patterns.hs b/src/LambdaCube/Compiler/Patterns.hs
index a6b96d58..856de00d 100644
--- a/src/LambdaCube/Compiler/Patterns.hs
+++ b/src/LambdaCube/Compiler/Patterns.hs
@@ -92,12 +92,12 @@ pBuiltin n = pBuiltin_ (SIName (debugSI $ "Constructor_" ++ n) n)
92 92
93cTrue = pBuiltin "True" (Left ((CaseName "'Bool", 0), [("False", 0), ("True", 0)])) [] 93cTrue = pBuiltin "True" (Left ((CaseName "'Bool", 0), [("False", 0), ("True", 0)])) []
94cZero = pBuiltin "Zero" (Left ((CaseName "'Nat", 0), [("Zero", 0), ("Succ", 1)])) [] 94cZero = pBuiltin "Zero" (Left ((CaseName "'Nat", 0), [("Zero", 0), ("Succ", 1)])) []
95cNil = pBuiltin "Nil" (Left ((CaseName "'List", 0), [("Nil", 0), ("Cons", 2)])) [] 95cNil = pBuiltin "Nil" (Left ((CaseName "'List", 0), [("Nil", 0), (":", 2)])) []
96cHNil = pBuiltin "HNil" (Left (("hlistNilCase", -1), [("HNil", 0)])) [] 96cHNil = pBuiltin "HNil" (Left (("hlistNilCase", -1), [("HNil", 0)])) []
97cList a = pBuiltin "'List" (Right 1) [a] 97cList a = pBuiltin "'List" (Right 1) [a]
98cHList a = pBuiltin "'HList" (Right 1) [a] 98cHList a = pBuiltin "'HList" (Right 1) [a]
99cSucc a = pBuiltin "Succ" (Left ((CaseName "'Nat", 0), [("Zero", 0), ("Succ", 1)])) [a] 99cSucc a = pBuiltin "Succ" (Left ((CaseName "'Nat", 0), [("Zero", 0), ("Succ", 1)])) [a]
100cCons a b = pBuiltin_ (SIName_ mempty (Just $ InfixR 5) "Cons") (Left ((CaseName "'List", 0), [("Nil", 0), ("Cons", 2)])) [a, b] 100cCons a b = pBuiltin_ ConsName (Left ((CaseName "'List", 0), [("Nil", 0), (":", 2)])) [a, b]
101cHCons a b = pBuiltin "HCons" (Left (("hlistConsCase", -1), [("HCons", 2)])) [a, b] 101cHCons a b = pBuiltin "HCons" (Left (("hlistConsCase", -1), [("HCons", 2)])) [a, b]
102 102
103pattern PParens p = ViewPatSimp (SBuiltin "parens") p 103pattern PParens p = ViewPatSimp (SBuiltin "parens") p
diff --git a/src/LambdaCube/Compiler/Pretty.hs b/src/LambdaCube/Compiler/Pretty.hs
index 204a9547..e7047a7e 100644
--- a/src/LambdaCube/Compiler/Pretty.hs
+++ b/src/LambdaCube/Compiler/Pretty.hs
@@ -175,7 +175,6 @@ renderDoc
175 addParA (ComplexAtom s i d a) = ComplexAtom s i (addPar tn (Infix i) d) $ addParA a 175 addParA (ComplexAtom s i d a) = ComplexAtom s i (addPar tn (Infix i) d) $ addParA a
176 176
177 addBackquotes "'EqCTt" = "~" 177 addBackquotes "'EqCTt" = "~"
178 addBackquotes "Cons" = ":"
179 addBackquotes s@(c:_) | isAlpha c || c == '_' || c == '\'' = '`': s ++ "`" 178 addBackquotes s@(c:_) | isAlpha c || c == '_' || c == '\'' = '`': s ++ "`"
180 addBackquotes s = s 179 addBackquotes s = s
181 180
diff --git a/testdata/Builtins.out b/testdata/Builtins.out
index bdf4fecf..a9ac34e1 100644
--- a/testdata/Builtins.out
+++ b/testdata/Builtins.out
@@ -566,7 +566,7 @@ PrimSign
566 :: forall (a :: _) (b :: _) (c :: _) . (Signed a, b ~ VecScalar c a) => b -> b 566 :: forall (a :: _) (b :: _) (c :: _) . (Signed a, b ~ VecScalar c a) => b -> b
567PrimModF 567PrimModF
568 :: forall (a :: _) (b :: _) 568 :: forall (a :: _) (b :: _)
569 . (a ~ VecScalar b Float) => a -> HList ('Cons a ('Cons a 'Nil)) 569 . (a ~ VecScalar b Float) => a -> HList (a : a : 'Nil)
570PrimClamp 570PrimClamp
571 :: forall (a :: _) (b :: _) (c :: _) 571 :: forall (a :: _) (b :: _) (c :: _)
572 . (Num a, b ~ VecScalar c a) => b -> b -> b -> b 572 . (Num a, b ~ VecScalar c a) => b -> b -> b -> b
@@ -898,11 +898,10 @@ data Blending :: Type -> Type where
898 NoBlending :: forall (a :: _) . Blending a 898 NoBlending :: forall (a :: _) . Blending a
899 BlendLogicOp :: forall (b :: _) . Integral b => LogicOperation -> Blending b 899 BlendLogicOp :: forall (b :: _) . Integral b => LogicOperation -> Blending b
900 Blend 900 Blend
901 :: HList ('Cons BlendEquation ('Cons BlendEquation 'Nil)) 901 :: HList (BlendEquation : BlendEquation : 'Nil)
902 -> HList 902 -> HList
903 ('Cons 903 (HList (BlendingFactor : BlendingFactor : 'Nil)
904 (HList ('Cons BlendingFactor ('Cons BlendingFactor 'Nil))) 904 : HList (BlendingFactor : BlendingFactor : 'Nil) : 'Nil)
905 ('Cons (HList ('Cons BlendingFactor ('Cons BlendingFactor 'Nil))) 'Nil))
906 -> Vec (fromInt 4) Float -> Blending Float 905 -> Vec (fromInt 4) Float -> Blending Float
907data StencilTests :: Type where 906data StencilTests :: Type where
908 907
@@ -922,7 +921,7 @@ data Interpolated (_ :: Type) :: Type where
922 Flat :: Interpolated _a 921 Flat :: Interpolated _a
923rasterizePrimitive 922rasterizePrimitive
924 :: forall (a :: _) (b :: _) (c :: _) (d :: _) 923 :: forall (a :: _) (b :: _) (c :: _) (d :: _)
925 . (map Interpolated a ~ b, c ~ 'Cons (Vec (fromInt 4) Float) a) 924 . (map Interpolated a ~ b, c ~ Vec (fromInt 4) Float : a)
926 => HList b 925 => HList b
927 -> RasterContext (HList c) d 926 -> RasterContext (HList c) d
928 -> Primitive (HList c) d -> FragmentStream (fromInt 1) (HList a) 927 -> Primitive (HList c) d -> FragmentStream (fromInt 1) (HList a)
@@ -987,12 +986,9 @@ accumulate
987 = \(a :: _) (b :: _) (c :: _) (d :: _) -> _rhs 986 = \(a :: _) (b :: _) (c :: _) (d :: _) -> _rhs
988 (Accumulate a (mapFragments b c) d) 987 (Accumulate a (mapFragments b c) d)
989PrjImage 988PrjImage
990 :: forall (a :: _) 989 :: forall (a :: _) . FrameBuffer (fromInt 1) (a : 'Nil) -> Image (fromInt 1) a
991 . FrameBuffer (fromInt 1) ('Cons a 'Nil) -> Image (fromInt 1) a
992PrjImageColor 990PrjImageColor
993 :: FrameBuffer 991 :: FrameBuffer (fromInt 1) ('Depth : 'Color (Vec (fromInt 4) Float) : 'Nil)
994 (fromInt 1)
995 ('Cons 'Depth ('Cons ('Color (Vec (fromInt 4) Float)) 'Nil))
996 -> Image (fromInt 1) (Color (Vec (fromInt 4) Float)) 992 -> Image (fromInt 1) (Color (Vec (fromInt 4) Float))
997data Output :: Type where 993data Output :: Type where
998 ScreenOut :: forall (a :: _) (b :: _) . FrameBuffer a b -> Output 994 ScreenOut :: forall (a :: _) (b :: _) . FrameBuffer a b -> Output
@@ -1652,15 +1648,15 @@ match'Interpolated
1652rasterizePrimitive 1648rasterizePrimitive
1653 :: forall (a :: List Type) 1649 :: forall (a :: List Type)
1654 (b :: List Type) (c :: List Type) (d :: PrimitiveType) 1650 (b :: List Type) (c :: List Type) (d :: PrimitiveType)
1655 . (map Type Type Interpolated a ~ b, c ~ 'Cons (Vec 4 Float) a) 1651 . (map Type Type Interpolated a ~ b, c ~ : (Vec 4 Float) a)
1656 => HList b 1652 => HList b
1657 -> RasterContext (HList c) d 1653 -> RasterContext (HList c) d
1658 -> Primitive (HList c) d -> FragmentStream 1 (HList a) 1654 -> Primitive (HList c) d -> FragmentStream 1 (HList a)
1659rasterizePrimitives 1655rasterizePrimitives
1660 :: forall (a :: List Type) (b :: PrimitiveType) 1656 :: forall (a :: List Type) (b :: PrimitiveType)
1661 . RasterContext (HList ('Cons (Vec 4 Float) a)) b 1657 . RasterContext (HList (: (Vec 4 Float) a)) b
1662 -> HList (map Type Type Interpolated a) 1658 -> HList (map Type Type Interpolated a)
1663 -> List (Primitive (HList ('Cons (Vec 4 Float) a)) b) 1659 -> List (Primitive (HList (: (Vec 4 Float) a)) b)
1664 -> List (Vector 1 (Maybe (SimpleFragment (HList a)))) 1660 -> List (Vector 1 (Maybe (SimpleFragment (HList a))))
1665'ImageLC :: Type -> Nat 1661'ImageLC :: Type -> Nat
1666allSame :: forall a . List a -> Type 1662allSame :: forall a . List a -> Type
@@ -1705,9 +1701,9 @@ accumulate
1705 -> List (Vector a (Maybe (SimpleFragment c))) 1701 -> List (Vector a (Maybe (SimpleFragment c)))
1706 -> FrameBuffer a (map Type ImageKind FragmentOperationKind b) 1702 -> FrameBuffer a (map Type ImageKind FragmentOperationKind b)
1707 -> FrameBuffer a (map Type ImageKind FragmentOperationKind b) 1703 -> FrameBuffer a (map Type ImageKind FragmentOperationKind b)
1708PrjImage :: forall (a :: ImageKind) . FrameBuffer 1 ('Cons a 'Nil) -> Image 1 a 1704PrjImage :: forall (a :: ImageKind) . FrameBuffer 1 (: a 'Nil) -> Image 1 a
1709PrjImageColor 1705PrjImageColor
1710 :: FrameBuffer 1 ('Cons 'Depth ('Cons ('Color (Vec 4 Float)) 'Nil)) 1706 :: FrameBuffer 1 (: 'Depth (: ('Color (Vec 4 Float)) 'Nil))
1711 -> Image 1 ('Color (Vec 4 Float)) 1707 -> Image 1 ('Color (Vec 4 Float))
1712'Output :: Type 1708'Output :: Type
1713ScreenOut :: forall (a :: Nat) (b :: List ImageKind) . FrameBuffer a b -> Output 1709ScreenOut :: forall (a :: Nat) (b :: List ImageKind) . FrameBuffer a b -> Output
@@ -6393,7 +6389,7 @@ testdata/Builtins.lc 478:55-478:56
6393 Type 6389 Type
6394testdata/Builtins.lc 480:1-480:19 6390testdata/Builtins.lc 480:1-480:19
6395 forall (a :: List Type) (b :: List Type) (c :: List Type) (d :: PrimitiveType) 6391 forall (a :: List Type) (b :: List Type) (c :: List Type) (d :: PrimitiveType)
6396 . (map Type Type Interpolated a ~ b, c ~ 'Cons (Vec 4 Float) a) 6392 . (map Type Type Interpolated a ~ b, c ~ : (Vec 4 Float) a)
6397 => HList b 6393 => HList b
6398 -> RasterContext (HList c) d 6394 -> RasterContext (HList c) d
6399 -> Primitive (HList c) d -> FragmentStream 1 (HList a) 6395 -> Primitive (HList c) d -> FragmentStream 1 (HList a)
@@ -6421,29 +6417,29 @@ testdata/Builtins.lc 482:10-482:11
6421 _f 6417 _f
6422testdata/Builtins.lc 482:10-482:13 6418testdata/Builtins.lc 482:10-482:13
6423 _e -> Type 6419 _e -> Type
6424testdata/Builtins.lc 482:10-482:35 6420testdata/Builtins.lc 482:10-482:28
6425 Type 6421 Type
6426testdata/Builtins.lc 482:10-486:34 6422testdata/Builtins.lc 482:10-486:34
6427 Type 6423 Type
6428testdata/Builtins.lc 482:12-482:13 6424testdata/Builtins.lc 482:12-482:13
6429 forall a . a -> a -> Type 6425 forall a . a -> a -> Type
6430testdata/Builtins.lc 482:14-482:19 6426testdata/Builtins.lc 482:14-482:17
6431 forall a . a -> List a -> List a
6432testdata/Builtins.lc 482:14-482:33
6433 List Type -> List Type
6434testdata/Builtins.lc 482:14-482:35
6435 List Type
6436testdata/Builtins.lc 482:21-482:24
6437 Nat -> Type -> Type 6427 Nat -> Type -> Type
6438testdata/Builtins.lc 482:21-482:26 6428testdata/Builtins.lc 482:14-482:19
6439 Type -> Type 6429 Type -> Type
6440testdata/Builtins.lc 482:21-482:32 6430testdata/Builtins.lc 482:14-482:25
6441 Type 6431 Type
6442testdata/Builtins.lc 482:25-482:26 6432testdata/Builtins.lc 482:14-482:26
6433 List Type -> List Type
6434testdata/Builtins.lc 482:14-482:28
6435 List Type
6436testdata/Builtins.lc 482:18-482:19
6443 _b 6437 _b
6444testdata/Builtins.lc 482:27-482:32 6438testdata/Builtins.lc 482:20-482:25
6445 Type 6439 Type
6446testdata/Builtins.lc 482:34-482:35 6440testdata/Builtins.lc 482:25-482:26
6441 forall a . a -> List a -> List a
6442testdata/Builtins.lc 482:27-482:28
6447 List Type 6443 List Type
6448testdata/Builtins.lc 483:8-483:13 6444testdata/Builtins.lc 483:8-483:13
6449 List Type -> Type 6445 List Type -> Type
@@ -6501,9 +6497,9 @@ testdata/Builtins.lc 486:32-486:33
6501 List Type 6497 List Type
6502testdata/Builtins.lc 488:1-488:20 6498testdata/Builtins.lc 488:1-488:20
6503 forall (a :: List Type) (b :: PrimitiveType) 6499 forall (a :: List Type) (b :: PrimitiveType)
6504 . RasterContext (HList ('Cons (Vec 4 Float) a)) b 6500 . RasterContext (HList (: (Vec 4 Float) a)) b
6505 -> HList (map Type Type Interpolated a) 6501 -> HList (map Type Type Interpolated a)
6506 -> List (Primitive (HList ('Cons (Vec 4 Float) a)) b) 6502 -> List (Primitive (HList (: (Vec 4 Float) a)) b)
6507 -> List (Vector 1 (Maybe (SimpleFragment (HList a)))) 6503 -> List (Vector 1 (Maybe (SimpleFragment (HList a))))
6508testdata/Builtins.lc 488:32-488:38 6504testdata/Builtins.lc 488:32-488:38
6509 forall a . List (List a) -> List a 6505 forall a . List (List a) -> List a
@@ -6512,21 +6508,21 @@ testdata/Builtins.lc 488:32-488:74
6512testdata/Builtins.lc 488:40-488:43 6508testdata/Builtins.lc 488:40-488:43
6513 forall a b . (a -> b) -> List a -> List b 6509 forall a b . (a -> b) -> List a -> List b
6514testdata/Builtins.lc 488:40-488:71 6510testdata/Builtins.lc 488:40-488:71
6515 List (Primitive (HList ('Cons (Vec 4 Float) _b)) _a) 6511 List (Primitive (HList (: (Vec 4 Float) _b)) _a)
6516 -> List (List (Fragment 1 (HList _b))) 6512 -> List (List (Fragment 1 (HList _b)))
6517testdata/Builtins.lc 488:40-488:73 6513testdata/Builtins.lc 488:40-488:73
6518 List (List (Fragment 1 (HList _b))) 6514 List (List (Fragment 1 (HList _b)))
6519testdata/Builtins.lc 488:45-488:63 6515testdata/Builtins.lc 488:45-488:63
6520 forall (a :: List Type) (b :: List Type) (c :: List Type) (d :: PrimitiveType) 6516 forall (a :: List Type) (b :: List Type) (c :: List Type) (d :: PrimitiveType)
6521 . (map Type Type Interpolated a ~ b, c ~ 'Cons (Vec 4 Float) a) 6517 . (map Type Type Interpolated a ~ b, c ~ : (Vec 4 Float) a)
6522 => HList b 6518 => HList b
6523 -> RasterContext (HList c) d 6519 -> RasterContext (HList c) d
6524 -> Primitive (HList c) d -> FragmentStream 1 (HList a) 6520 -> Primitive (HList c) d -> FragmentStream 1 (HList a)
6525testdata/Builtins.lc 488:45-488:66 6521testdata/Builtins.lc 488:45-488:66
6526 RasterContext (HList ('Cons (Vec 4 Float) _b)) _a 6522 RasterContext (HList (: (Vec 4 Float) _b)) _a
6527 -> Primitive (HList ('Cons (Vec 4 Float) _b)) _a -> FragmentStream 1 (HList _b) 6523 -> Primitive (HList (: (Vec 4 Float) _b)) _a -> FragmentStream 1 (HList _b)
6528testdata/Builtins.lc 488:45-488:70 6524testdata/Builtins.lc 488:45-488:70
6529 Primitive (HList ('Cons (Vec 4 Float) _b)) _a -> FragmentStream 1 (HList _b) 6525 Primitive (HList (: (Vec 4 Float) _b)) _a -> FragmentStream 1 (HList _b)
6530testdata/Builtins.lc 488:64-488:66 6526testdata/Builtins.lc 488:64-488:66
6531 _i 6527 _i
6532testdata/Builtins.lc 488:67-488:70 6528testdata/Builtins.lc 488:67-488:70
@@ -6895,7 +6891,7 @@ testdata/Builtins.lc 534:71-534:75
6895testdata/Builtins.lc 534:77-534:79 6891testdata/Builtins.lc 534:77-534:79
6896 _e 6892 _e
6897testdata/Builtins.lc 537:1-537:9 6893testdata/Builtins.lc 537:1-537:9
6898 forall (a :: ImageKind) . FrameBuffer 1 ('Cons a 'Nil) -> Image 1 a 6894 forall (a :: ImageKind) . FrameBuffer 1 (: a 'Nil) -> Image 1 a
6899testdata/Builtins.lc 537:24-537:35 6895testdata/Builtins.lc 537:24-537:35
6900 Nat -> List ImageKind -> Type 6896 Nat -> List ImageKind -> Type
6901testdata/Builtins.lc 537:24-537:37 6897testdata/Builtins.lc 537:24-537:37
@@ -6921,7 +6917,7 @@ testdata/Builtins.lc 537:52-537:53
6921testdata/Builtins.lc 537:54-537:55 6917testdata/Builtins.lc 537:54-537:55
6922 ImageKind 6918 ImageKind
6923testdata/Builtins.lc 538:1-538:14 6919testdata/Builtins.lc 538:1-538:14
6924 FrameBuffer 1 ('Cons 'Depth ('Cons ('Color (Vec 4 Float)) 'Nil)) 6920 FrameBuffer 1 (: 'Depth (: ('Color (Vec 4 Float)) 'Nil))
6925 -> Image 1 ('Color (Vec 4 Float)) 6921 -> Image 1 ('Color (Vec 4 Float))
6926testdata/Builtins.lc 538:24-538:35 6922testdata/Builtins.lc 538:24-538:35
6927 Nat -> List ImageKind -> Type 6923 Nat -> List ImageKind -> Type
diff --git a/testdata/Internals.out b/testdata/Internals.out
index cec9ea8d..b2e7246e 100644
--- a/testdata/Internals.out
+++ b/testdata/Internals.out
@@ -193,15 +193,15 @@ negate
193infix 4 == 193infix 4 ==
194data List (_ :: Type) :: Type where 194data List (_ :: Type) :: Type where
195 Nil :: List _a 195 Nil :: List _a
196 Cons :: _a -> List _a -> List _a 196 (:) :: _a -> List _a -> List _a
197infixr 5 Cons 197infixr 5 :
198data HList :: List Type -> Type where 198data HList :: List Type -> Type where
199 HNil :: HList 'Nil 199 HNil :: HList 'Nil
200 HCons :: forall (a :: _) (b :: _) . a -> HList b -> HList (a : b) 200 HCons :: forall (a :: _) (b :: _) . a -> HList b -> HList (a : b)
201hlistNilCase :: forall (a :: _) -> a -> HList Nil -> a 201hlistNilCase :: forall (a :: _) -> a -> HList Nil -> a
202hlistConsCase 202hlistConsCase
203 :: forall a (b :: List Type) 203 :: forall a (b :: List Type)
204 . forall (c :: _) -> (a -> HList b -> c) -> HList (Cons a b) -> c 204 . forall (c :: _) -> (a -> HList b -> c) -> HList (a : b) -> c
205main is not found 205main is not found
206------------ trace 206------------ trace
207typeAnn :: forall a . a -> a 207typeAnn :: forall a . a -> a
@@ -289,24 +289,23 @@ negate :: forall a . Num a => a -> a
289== :: forall a . Eq a => a -> a -> Bool 289== :: forall a . Eq a => a -> a -> Bool
290'List :: Type -> Type 290'List :: Type -> Type
291Nil :: forall a . List a 291Nil :: forall a . List a
292Cons :: forall a . a -> List a -> List a 292(:) :: forall a . a -> List a -> List a
293'ListCase 293'ListCase
294 :: forall a 294 :: forall a
295 . forall (b :: List a -> Type) 295 . forall (b :: List a -> Type)
296 -> b 'Nil 296 -> b 'Nil
297 -> (forall (c :: a) (d :: List a) -> b ('Cons c d)) 297 -> (forall (c :: a) (d :: List a) -> b (: c d)) -> forall (e :: List a) -> b e
298 -> forall (e :: List a) -> b e
299match'List 298match'List
300 :: forall (a :: Type -> Type) 299 :: forall (a :: Type -> Type)
301 -> (forall b -> a (List b)) -> forall c -> a c -> a c 300 -> (forall b -> a (List b)) -> forall c -> a c -> a c
302'HList :: List Type -> Type 301'HList :: List Type -> Type
303HNil :: () 302HNil :: ()
304HCons :: forall a (b :: List Type) . a -> HList b -> HList ('Cons a b) 303HCons :: forall a (b :: List Type) . a -> HList b -> HList (: a b)
305'HListCase 304'HListCase
306 :: forall (a :: forall (b :: List Type) -> HList b -> Type) 305 :: forall (a :: forall (b :: List Type) -> HList b -> Type)
307 -> a 'Nil () 306 -> a 'Nil ()
308 -> (forall c (d :: List Type) 307 -> (forall c (d :: List Type)
309 . forall (e :: c) (f :: HList d) -> a ('Cons c d) ('HCons c d e f)) 308 . forall (e :: c) (f :: HList d) -> a (: c d) ('HCons c d e f))
310 -> forall (g :: List Type) . forall (h :: HList g) -> a g h 309 -> forall (g :: List Type) . forall (h :: HList g) -> a g h
311match'HList 310match'HList
312 :: forall (a :: Type -> Type) 311 :: forall (a :: Type -> Type)
@@ -314,7 +313,7 @@ match'HList
314hlistNilCase :: forall a -> a -> () -> a 313hlistNilCase :: forall a -> a -> () -> a
315hlistConsCase 314hlistConsCase
316 :: forall a (b :: List Type) 315 :: forall a (b :: List Type)
317 . forall c -> (a -> HList b -> c) -> HList ('Cons a b) -> c 316 . forall c -> (a -> HList b -> c) -> HList (: a b) -> c
318------------ tooltips 317------------ tooltips
319testdata/Internals.lc 6:1-6:8 318testdata/Internals.lc 6:1-6:8
320 forall a . a -> a 319 forall a . a -> a
@@ -822,23 +821,23 @@ testdata/Internals.lc 122:6-122:10
822 Type -> Type | Type -> Type | Type -> Type | Type -> Type | Type -> Type | Type 821 Type -> Type | Type -> Type | Type -> Type | Type -> Type | Type -> Type | Type
823testdata/Internals.lc 122:6-122:12 822testdata/Internals.lc 122:6-122:12
824 Type | Type | Type | Type 823 Type | Type | Type | Type
825testdata/Internals.lc 122:6-122:25 824testdata/Internals.lc 122:6-122:23
826 Type | Type | Type 825 Type | Type | Type
827testdata/Internals.lc 122:6-122:36 826testdata/Internals.lc 122:6-122:35
828 Type | Type 827 Type | Type
829testdata/Internals.lc 122:11-122:12 828testdata/Internals.lc 122:11-122:12
830 Type | Type 829 Type | Type
831testdata/Internals.lc 122:15-122:18 830testdata/Internals.lc 122:15-122:18
832 forall a . List a | List _b 831 forall a . List a | List _b
833testdata/Internals.lc 122:21-122:25 832testdata/Internals.lc 122:22-122:23
834 forall a . a -> List a -> List a | List _e | Type | Type | Type 833 forall a . a -> List a -> List a | List _e | Type | Type | Type
835testdata/Internals.lc 122:26-122:27 834testdata/Internals.lc 122:25-122:26
836 Type 835 Type
837testdata/Internals.lc 122:29-122:33 836testdata/Internals.lc 122:28-122:32
838 Type -> Type 837 Type -> Type
839testdata/Internals.lc 122:29-122:35 838testdata/Internals.lc 122:28-122:34
840 Type 839 Type
841testdata/Internals.lc 122:34-122:35 840testdata/Internals.lc 122:33-122:34
842 Type 841 Type
843testdata/Internals.lc 126:6-126:11 842testdata/Internals.lc 126:6-126:11
844 List Type -> Type | List Type -> Type | Type | List Type -> Type | Type | Type 843 List Type -> Type | List Type -> Type | Type | List Type -> Type | Type | Type
@@ -861,8 +860,7 @@ testdata/Internals.lc 127:13-127:22
861testdata/Internals.lc 127:19-127:22 860testdata/Internals.lc 127:19-127:22
862 forall a . List a | forall a . List a 861 forall a . List a | forall a . List a
863testdata/Internals.lc 128:5-128:10 862testdata/Internals.lc 128:5-128:10
864 forall a (b :: List Type) . a -> HList b -> HList ('Cons a b) | HList 863 forall a (b :: List Type) . a -> HList b -> HList (: a b) | HList (: _d _c)
865 ('Cons _d _c)
866testdata/Internals.lc 128:5-128:45 864testdata/Internals.lc 128:5-128:45
867 Type | Type | Type | Type | Type 865 Type | Type | Type | Type | Type
868testdata/Internals.lc 128:14-128:15 866testdata/Internals.lc 128:14-128:15
@@ -909,7 +907,7 @@ testdata/Internals.lc 130:47-130:48
909 Type | Type 907 Type | Type
910testdata/Internals.lc 131:1-131:14 908testdata/Internals.lc 131:1-131:14
911 forall a (b :: List Type) 909 forall a (b :: List Type)
912 . forall c -> (a -> HList b -> c) -> HList ('Cons a b) -> c 910 . forall c -> (a -> HList b -> c) -> HList (: a b) -> c
913testdata/Internals.lc 132:21-132:25 911testdata/Internals.lc 132:21-132:25
914 Type 912 Type
915testdata/Internals.lc 132:33-132:37 913testdata/Internals.lc 132:33-132:37
@@ -938,19 +936,19 @@ testdata/Internals.lc 134:25-134:26
938 _d | Type 936 _d | Type
939testdata/Internals.lc 135:8-135:13 937testdata/Internals.lc 135:8-135:13
940 List Type -> Type 938 List Type -> Type
941testdata/Internals.lc 135:8-135:24 939testdata/Internals.lc 135:8-135:20
942 Type 940 Type
943testdata/Internals.lc 135:8-136:9 941testdata/Internals.lc 135:8-136:9
944 Type 942 Type
945testdata/Internals.lc 135:15-135:19 943testdata/Internals.lc 135:15-135:16
946 forall a . a -> List a -> List a 944 Type
947testdata/Internals.lc 135:15-135:21 945testdata/Internals.lc 135:15-135:17
948 List Type -> List Type 946 List Type -> List Type
949testdata/Internals.lc 135:15-135:23 947testdata/Internals.lc 135:15-135:19
950 List Type 948 List Type
951testdata/Internals.lc 135:20-135:21 949testdata/Internals.lc 135:16-135:17
952 Type 950 forall a . a -> List a -> List a
953testdata/Internals.lc 135:22-135:23 951testdata/Internals.lc 135:18-135:19
954 List Type 952 List Type
955testdata/Internals.lc 136:8-136:9 953testdata/Internals.lc 136:8-136:9
956 Type | Type \ No newline at end of file 954 Type | Type \ No newline at end of file
diff --git a/testdata/Material.out b/testdata/Material.out
index c4d3447c..998117ca 100644
--- a/testdata/Material.out
+++ b/testdata/Material.out
@@ -105,7 +105,7 @@ data DepthFunction :: Type where
105 D_Lequal :: DepthFunction 105 D_Lequal :: DepthFunction
106data StageAttrs :: Type where 106data StageAttrs :: Type where
107 StageAttrs 107 StageAttrs
108 :: Maybe (HList ('Cons Blending' ('Cons Blending' 'Nil))) 108 :: Maybe (HList (Blending' : Blending' : 'Nil))
109 -> RGBGen 109 -> RGBGen
110 -> AlphaGen 110 -> AlphaGen
111 -> TCGen 111 -> TCGen
diff --git a/testdata/Prelude.out b/testdata/Prelude.out
index 2fd400f9..3f3db079 100644
--- a/testdata/Prelude.out
+++ b/testdata/Prelude.out
@@ -40,8 +40,7 @@ zip
40 \(e :: _) (f :: _) -> _rhs (HCons c (HCons e HNil) : zip d f) 40 \(e :: _) (f :: _) -> _rhs (HCons c (HCons e HNil) : zip d f)
41 b 41 b
42 a) 42 a)
43 :: forall (g :: _) (h :: _) 43 :: forall (g :: _) (h :: _) . List g -> List h -> List (HList (g : h : 'Nil))
44 . List g -> List h -> List (HList ('Cons g ('Cons h 'Nil)))
45unzip 44unzip
46 = (\(a :: _) -> 'ListCase 45 = (\(a :: _) -> 'ListCase
47 \_ -> _ :: _ 46 \_ -> _ :: _
@@ -79,8 +78,7 @@ unzip
79 b 78 b
80 a) 79 a)
81 :: forall (s :: _) (t :: _) 80 :: forall (s :: _) (t :: _)
82 . List (HList ('Cons s ('Cons t 'Nil))) 81 . List (HList (s : t : 'Nil)) -> HList (List s : List t : 'Nil)
83 -> HList ('Cons (List s) ('Cons (List t) 'Nil))
84filter 82filter
85 = \(a :: _) (b :: _) -> 'ListCase 83 = \(a :: _) (b :: _) -> 'ListCase
86 \_ -> _ :: _ 84 \_ -> _ :: _
@@ -93,7 +91,7 @@ tail
93 :: forall (c :: _) . List c -> List c 91 :: forall (c :: _) . List c -> List c
94pairs 92pairs
95 = (\(a :: _) -> _rhs (zip a (tail a))) 93 = (\(a :: _) -> _rhs (zip a (tail a)))
96 :: forall (b :: _) . List b -> List (HList ('Cons b ('Cons b 'Nil))) 94 :: forall (b :: _) . List b -> List (HList (b : b : 'Nil))
97foldl' 95foldl'
98 = \(a :: _) (b :: _) (c :: _) -> 'ListCase 96 = \(a :: _) (b :: _) (c :: _) -> 'ListCase
99 \_ -> _ :: _ 97 \_ -> _ :: _
@@ -156,7 +154,7 @@ sortBy
156 (_rhs Nil) 154 (_rhs Nil)
157 \(c :: _) (d :: _) -> 'ListCase 155 \(c :: _) (d :: _) -> 'ListCase
158 \_ -> _ :: _ 156 \_ -> _ :: _
159 (_rhs (Cons c Nil)) 157 (_rhs (c : Nil))
160 \_ -> \_ -> _rhs (uncurry (mergeBy a) ((sortBy a *** sortBy a) (split b))) 158 \_ -> \_ -> _rhs (uncurry (mergeBy a) ((sortBy a *** sortBy a) (split b)))
161 d 159 d
162 b 160 b
@@ -514,8 +512,8 @@ match'RecordC
514 :: forall (a :: Type -> Type) 512 :: forall (a :: Type -> Type)
515 -> (forall (b :: List RecItem) -> a (RecordC b)) -> forall c -> a c -> a c 513 -> (forall (b :: List RecItem) -> a (RecordC b)) -> forall c -> a c -> a c
516isKeyC :: String -> Type -> List RecItem -> Type 514isKeyC :: String -> Type -> List RecItem -> Type
517fstTup :: forall a (b :: List Type) . HList ('Cons a b) -> a 515fstTup :: forall a (b :: List Type) . HList (: a b) -> a
518sndTup :: forall a (b :: List Type) . HList ('Cons a b) -> HList b 516sndTup :: forall a (b :: List Type) . HList (: a b) -> HList b
519project 517project
520 :: forall a (b :: List RecItem) 518 :: forall a (b :: List RecItem)
521 . forall (c :: String) -> isKeyC c a b => RecordC b -> a 519 . forall (c :: String) -> isKeyC c a b => RecordC b -> a
@@ -1296,25 +1294,25 @@ testdata/Prelude.lc 130:71-130:72
1296testdata/Prelude.lc 130:73-130:75 1294testdata/Prelude.lc 130:73-130:75
1297 List _i 1295 List _i
1298testdata/Prelude.lc 132:1-132:7 1296testdata/Prelude.lc 132:1-132:7
1299 forall a (b :: List Type) . HList ('Cons a b) -> a 1297 forall a (b :: List Type) . HList (: a b) -> a
1300testdata/Prelude.lc 132:10-132:23 1298testdata/Prelude.lc 132:10-132:23
1301 forall a (b :: List Type) 1299 forall a (b :: List Type)
1302 . forall c -> (a -> HList b -> c) -> HList ('Cons a b) -> c 1300 . forall c -> (a -> HList b -> c) -> HList (: a b) -> c
1303testdata/Prelude.lc 132:10-132:25 1301testdata/Prelude.lc 132:10-132:25
1304 (_c -> HList _b -> _a) -> HList ('Cons _c _b) -> _a 1302 (_c -> HList _b -> _a) -> HList (: _c _b) -> _a
1305testdata/Prelude.lc 132:10-132:37 1303testdata/Prelude.lc 132:10-132:37
1306 HList ('Cons _b _a) -> _b 1304 HList (: _b _a) -> _b
1307testdata/Prelude.lc 132:35-132:36 1305testdata/Prelude.lc 132:35-132:36
1308 _e 1306 _e
1309testdata/Prelude.lc 133:1-133:7 1307testdata/Prelude.lc 133:1-133:7
1310 forall a (b :: List Type) . HList ('Cons a b) -> HList b 1308 forall a (b :: List Type) . HList (: a b) -> HList b
1311testdata/Prelude.lc 133:10-133:23 1309testdata/Prelude.lc 133:10-133:23
1312 forall a (b :: List Type) 1310 forall a (b :: List Type)
1313 . forall c -> (a -> HList b -> c) -> HList ('Cons a b) -> c 1311 . forall c -> (a -> HList b -> c) -> HList (: a b) -> c
1314testdata/Prelude.lc 133:10-133:25 1312testdata/Prelude.lc 133:10-133:25
1315 (_c -> HList _b -> _a) -> HList ('Cons _c _b) -> _a 1313 (_c -> HList _b -> _a) -> HList (: _c _b) -> _a
1316testdata/Prelude.lc 133:10-133:37 1314testdata/Prelude.lc 133:10-133:37
1317 HList ('Cons _b _a) -> HList _a 1315 HList (: _b _a) -> HList _a
1318testdata/Prelude.lc 133:35-133:36 1316testdata/Prelude.lc 133:35-133:36
1319 HList _d 1317 HList _d
1320testdata/Prelude.lc 136:12-138:181 1318testdata/Prelude.lc 136:12-138:181
@@ -1372,7 +1370,7 @@ testdata/Prelude.lc 137:59-137:61
1372testdata/Prelude.lc 137:62-137:64 1370testdata/Prelude.lc 137:62-137:64
1373 String 1371 String
1374testdata/Prelude.lc 137:67-137:73 1372testdata/Prelude.lc 137:67-137:73
1375 forall a (b :: List Type) . HList ('Cons a b) -> a 1373 forall a (b :: List Type) . HList (: a b) -> a
1376testdata/Prelude.lc 137:67-137:129 1374testdata/Prelude.lc 137:67-137:129
1377 _n 1375 _n
1378testdata/Prelude.lc 137:67-138:181 1376testdata/Prelude.lc 137:67-138:181
@@ -1382,9 +1380,9 @@ testdata/Prelude.lc 137:75-137:87
1382testdata/Prelude.lc 137:75-137:90 1380testdata/Prelude.lc 137:75-137:90
1383 forall a . _a -> a 1381 forall a . _a -> a
1384testdata/Prelude.lc 137:75-137:125 1382testdata/Prelude.lc 137:75-137:125
1385 _a -> HList ('Cons _q (map RecItem Type recItemType _j)) 1383 _a -> HList (: _q (map RecItem Type recItemType _j))
1386testdata/Prelude.lc 137:75-137:128 1384testdata/Prelude.lc 137:75-137:128
1387 HList ('Cons _n (map RecItem Type recItemType _g)) 1385 HList (: _n (map RecItem Type recItemType _g))
1388testdata/Prelude.lc 137:93-137:98 1386testdata/Prelude.lc 137:93-137:98
1389 List Type -> Type 1387 List Type -> Type
1390testdata/Prelude.lc 137:93-137:124 1388testdata/Prelude.lc 137:93-137:124
@@ -1452,7 +1450,7 @@ testdata/Prelude.lc 138:105-138:115
1452testdata/Prelude.lc 138:105-138:180 1450testdata/Prelude.lc 138:105-138:180
1453 RecordC _b 1451 RecordC _b
1454testdata/Prelude.lc 138:117-138:123 1452testdata/Prelude.lc 138:117-138:123
1455 forall a (b :: List Type) . HList ('Cons a b) -> HList b 1453 forall a (b :: List Type) . HList (: a b) -> HList b
1456testdata/Prelude.lc 138:117-138:179 1454testdata/Prelude.lc 138:117-138:179
1457 HList (map RecItem Type recItemType _h) 1455 HList (map RecItem Type recItemType _h)
1458testdata/Prelude.lc 138:125-138:137 1456testdata/Prelude.lc 138:125-138:137
@@ -1460,9 +1458,9 @@ testdata/Prelude.lc 138:125-138:137
1460testdata/Prelude.lc 138:125-138:140 1458testdata/Prelude.lc 138:125-138:140
1461 forall a . _a -> a 1459 forall a . _a -> a
1462testdata/Prelude.lc 138:125-138:175 1460testdata/Prelude.lc 138:125-138:175
1463 _a -> HList ('Cons _r (map RecItem Type recItemType _k)) 1461 _a -> HList (: _r (map RecItem Type recItemType _k))
1464testdata/Prelude.lc 138:125-138:178 1462testdata/Prelude.lc 138:125-138:178
1465 HList ('Cons _o (map RecItem Type recItemType _h)) 1463 HList (: _o (map RecItem Type recItemType _h))
1466testdata/Prelude.lc 138:143-138:148 1464testdata/Prelude.lc 138:143-138:148
1467 List Type -> Type 1465 List Type -> Type
1468testdata/Prelude.lc 138:143-138:174 1466testdata/Prelude.lc 138:143-138:174
diff --git a/testdata/SampleMaterial.out b/testdata/SampleMaterial.out
index a1225581..9f1d4319 100644
--- a/testdata/SampleMaterial.out
+++ b/testdata/SampleMaterial.out
@@ -1,8 +1,7 @@
1------------ desugared source code 1------------ desugared source code
2sampleMaterial 2sampleMaterial
3 = _rhs 3 = _rhs
4 (Cons 4 (HCons
5 (HCons
6 "textures/gothic_block/blocks11b" 5 "textures/gothic_block/blocks11b"
7 (HCons 6 (HCons
8 (CommonAttrs 7 (CommonAttrs
@@ -16,8 +15,7 @@ sampleMaterial
16 Nil 15 Nil
17 False 16 False
18 False 17 False
19 (Cons 18 (StageAttrs
20 (StageAttrs
21 Nothing 19 Nothing
22 RGB_IdentityLighting 20 RGB_IdentityLighting
23 A_Identity 21 A_Identity
@@ -28,9 +26,8 @@ sampleMaterial
28 D_Lequal 26 D_Lequal
29 Nothing 27 Nothing
30 False 28 False
31 "Tex_4288602201") 29 "Tex_4288602201"
32 (Cons 30 : StageAttrs
33 (StageAttrs
34 (Just (HCons B_DstColor (HCons B_Zero HNil))) 31 (Just (HCons B_DstColor (HCons B_Zero HNil)))
35 RGB_IdentityLighting 32 RGB_IdentityLighting
36 A_Identity 33 A_Identity
@@ -41,12 +38,11 @@ sampleMaterial
41 D_Lequal 38 D_Lequal
42 Nothing 39 Nothing
43 False 40 False
44 "Tex_3226210144") 41 "Tex_3226210144"
45 Nil)) 42 : Nil)
46 False) 43 False)
47 HNil)) 44 HNil)
48 (Cons 45 : HCons
49 (HCons
50 "textures/gothic_block/blocks15" 46 "textures/gothic_block/blocks15"
51 (HCons 47 (HCons
52 (CommonAttrs 48 (CommonAttrs
@@ -60,8 +56,7 @@ sampleMaterial
60 Nil 56 Nil
61 False 57 False
62 False 58 False
63 (Cons 59 (StageAttrs
64 (StageAttrs
65 Nothing 60 Nothing
66 RGB_IdentityLighting 61 RGB_IdentityLighting
67 A_Identity 62 A_Identity
@@ -72,9 +67,8 @@ sampleMaterial
72 D_Lequal 67 D_Lequal
73 Nothing 68 Nothing
74 False 69 False
75 "Tex_2523116863") 70 "Tex_2523116863"
76 (Cons 71 : StageAttrs
77 (StageAttrs
78 (Just (HCons B_DstColor (HCons B_Zero HNil))) 72 (Just (HCons B_DstColor (HCons B_Zero HNil)))
79 RGB_IdentityLighting 73 RGB_IdentityLighting
80 A_Identity 74 A_Identity
@@ -85,12 +79,11 @@ sampleMaterial
85 D_Lequal 79 D_Lequal
86 Nothing 80 Nothing
87 False 81 False
88 "Tex_3226210144") 82 "Tex_3226210144"
89 Nil)) 83 : Nil)
90 False) 84 False)
91 HNil)) 85 HNil)
92 (Cons 86 : HCons
93 (HCons
94 "textures/gothic_block/blocks18b" 87 "textures/gothic_block/blocks18b"
95 (HCons 88 (HCons
96 (CommonAttrs 89 (CommonAttrs
@@ -104,8 +97,7 @@ sampleMaterial
104 Nil 97 Nil
105 False 98 False
106 False 99 False
107 (Cons 100 (StageAttrs
108 (StageAttrs
109 Nothing 101 Nothing
110 RGB_IdentityLighting 102 RGB_IdentityLighting
111 A_Identity 103 A_Identity
@@ -116,9 +108,8 @@ sampleMaterial
116 D_Lequal 108 D_Lequal
117 Nothing 109 Nothing
118 False 110 False
119 "Tex_2639119078") 111 "Tex_2639119078"
120 (Cons 112 : StageAttrs
121 (StageAttrs
122 (Just (HCons B_DstColor (HCons B_Zero HNil))) 113 (Just (HCons B_DstColor (HCons B_Zero HNil)))
123 RGB_IdentityLighting 114 RGB_IdentityLighting
124 A_Identity 115 A_Identity
@@ -129,12 +120,11 @@ sampleMaterial
129 D_Lequal 120 D_Lequal
130 Nothing 121 Nothing
131 False 122 False
132 "Tex_3226210144") 123 "Tex_3226210144"
133 Nil)) 124 : Nil)
134 False) 125 False)
135 HNil)) 126 HNil)
136 (Cons 127 : HCons
137 (HCons
138 "textures/gothic_block/blocks18c_3" 128 "textures/gothic_block/blocks18c_3"
139 (HCons 129 (HCons
140 (CommonAttrs 130 (CommonAttrs
@@ -148,8 +138,7 @@ sampleMaterial
148 Nil 138 Nil
149 False 139 False
150 False 140 False
151 (Cons 141 (StageAttrs
152 (StageAttrs
153 Nothing 142 Nothing
154 RGB_IdentityLighting 143 RGB_IdentityLighting
155 A_Identity 144 A_Identity
@@ -160,9 +149,8 @@ sampleMaterial
160 D_Lequal 149 D_Lequal
161 Nothing 150 Nothing
162 False 151 False
163 "Tex_3939430064") 152 "Tex_3939430064"
164 (Cons 153 : StageAttrs
165 (StageAttrs
166 (Just (HCons B_DstColor (HCons B_Zero HNil))) 154 (Just (HCons B_DstColor (HCons B_Zero HNil)))
167 RGB_IdentityLighting 155 RGB_IdentityLighting
168 A_Identity 156 A_Identity
@@ -173,12 +161,11 @@ sampleMaterial
173 D_Lequal 161 D_Lequal
174 Nothing 162 Nothing
175 False 163 False
176 "Tex_3226210144") 164 "Tex_3226210144"
177 Nil)) 165 : Nil)
178 False) 166 False)
179 HNil)) 167 HNil)
180 (Cons 168 : HCons
181 (HCons
182 "textures/gothic_block/demon_block15fx" 169 "textures/gothic_block/demon_block15fx"
183 (HCons 170 (HCons
184 (CommonAttrs 171 (CommonAttrs
@@ -192,23 +179,19 @@ sampleMaterial
192 Nil 179 Nil
193 False 180 False
194 False 181 False
195 (Cons 182 (StageAttrs
196 (StageAttrs
197 Nothing 183 Nothing
198 RGB_Identity 184 RGB_Identity
199 A_Identity 185 A_Identity
200 TG_Base 186 TG_Base
201 (Cons 187 (TM_Scroll 0.0 1.0 : TM_Turb 0.0 0.25 0.0 1.6 : TM_Scale 4.0 4.0 : Nil)
202 (TM_Scroll 0.0 1.0)
203 (Cons (TM_Turb 0.0 0.25 0.0 1.6) (Cons (TM_Scale 4.0 4.0) Nil)))
204 (ST_Map "textures/sfx/firegorre.tga") 188 (ST_Map "textures/sfx/firegorre.tga")
205 True 189 True
206 D_Lequal 190 D_Lequal
207 Nothing 191 Nothing
208 False 192 False
209 "Tex_47037129") 193 "Tex_47037129"
210 (Cons 194 : StageAttrs
211 (StageAttrs
212 (Just (HCons B_SrcAlpha (HCons B_OneMinusSrcAlpha HNil))) 195 (Just (HCons B_SrcAlpha (HCons B_OneMinusSrcAlpha HNil)))
213 RGB_Identity 196 RGB_Identity
214 A_Identity 197 A_Identity
@@ -219,9 +202,8 @@ sampleMaterial
219 D_Lequal 202 D_Lequal
220 Nothing 203 Nothing
221 False 204 False
222 "Tex_3562558025") 205 "Tex_3562558025"
223 (Cons 206 : StageAttrs
224 (StageAttrs
225 (Just (HCons B_DstColor (HCons B_OneMinusDstAlpha HNil))) 207 (Just (HCons B_DstColor (HCons B_OneMinusDstAlpha HNil)))
226 RGB_Identity 208 RGB_Identity
227 A_Identity 209 A_Identity
@@ -232,12 +214,11 @@ sampleMaterial
232 D_Lequal 214 D_Lequal
233 Nothing 215 Nothing
234 False 216 False
235 "Tex_2065974340") 217 "Tex_2065974340"
236 Nil))) 218 : Nil)
237 False) 219 False)
238 HNil)) 220 HNil)
239 (Cons 221 : HCons
240 (HCons
241 "textures/gothic_block/killblock" 222 "textures/gothic_block/killblock"
242 (HCons 223 (HCons
243 (CommonAttrs 224 (CommonAttrs
@@ -251,8 +232,7 @@ sampleMaterial
251 Nil 232 Nil
252 False 233 False
253 False 234 False
254 (Cons 235 (StageAttrs
255 (StageAttrs
256 Nothing 236 Nothing
257 RGB_IdentityLighting 237 RGB_IdentityLighting
258 A_Identity 238 A_Identity
@@ -263,9 +243,8 @@ sampleMaterial
263 D_Lequal 243 D_Lequal
264 Nothing 244 Nothing
265 False 245 False
266 "Tex_3647563961") 246 "Tex_3647563961"
267 (Cons 247 : StageAttrs
268 (StageAttrs
269 (Just (HCons B_DstColor (HCons B_Zero HNil))) 248 (Just (HCons B_DstColor (HCons B_Zero HNil)))
270 RGB_IdentityLighting 249 RGB_IdentityLighting
271 A_Identity 250 A_Identity
@@ -276,12 +255,11 @@ sampleMaterial
276 D_Lequal 255 D_Lequal
277 Nothing 256 Nothing
278 False 257 False
279 "Tex_3226210144") 258 "Tex_3226210144"
280 Nil)) 259 : Nil)
281 False) 260 False)
282 HNil)) 261 HNil)
283 (Cons 262 : HCons
284 (HCons
285 "textures/gothic_block/killblock_i" 263 "textures/gothic_block/killblock_i"
286 (HCons 264 (HCons
287 (CommonAttrs 265 (CommonAttrs
@@ -295,8 +273,7 @@ sampleMaterial
295 Nil 273 Nil
296 False 274 False
297 False 275 False
298 (Cons 276 (StageAttrs
299 (StageAttrs
300 Nothing 277 Nothing
301 RGB_IdentityLighting 278 RGB_IdentityLighting
302 A_Identity 279 A_Identity
@@ -307,9 +284,8 @@ sampleMaterial
307 D_Lequal 284 D_Lequal
308 Nothing 285 Nothing
309 False 286 False
310 "Tex_209322640") 287 "Tex_209322640"
311 (Cons 288 : StageAttrs
312 (StageAttrs
313 (Just (HCons B_DstColor (HCons B_Zero HNil))) 289 (Just (HCons B_DstColor (HCons B_Zero HNil)))
314 RGB_IdentityLighting 290 RGB_IdentityLighting
315 A_Identity 291 A_Identity
@@ -320,12 +296,11 @@ sampleMaterial
320 D_Lequal 296 D_Lequal
321 Nothing 297 Nothing
322 False 298 False
323 "Tex_3226210144") 299 "Tex_3226210144"
324 Nil)) 300 : Nil)
325 False) 301 False)
326 HNil)) 302 HNil)
327 (Cons 303 : HCons
328 (HCons
329 "textures/gothic_block/killblock_i4" 304 "textures/gothic_block/killblock_i4"
330 (HCons 305 (HCons
331 (CommonAttrs 306 (CommonAttrs
@@ -339,8 +314,7 @@ sampleMaterial
339 Nil 314 Nil
340 False 315 False
341 False 316 False
342 (Cons 317 (StageAttrs
343 (StageAttrs
344 Nothing 318 Nothing
345 RGB_IdentityLighting 319 RGB_IdentityLighting
346 A_Identity 320 A_Identity
@@ -351,9 +325,8 @@ sampleMaterial
351 D_Lequal 325 D_Lequal
352 Nothing 326 Nothing
353 False 327 False
354 "Tex_3617993418") 328 "Tex_3617993418"
355 (Cons 329 : StageAttrs
356 (StageAttrs
357 (Just (HCons B_DstColor (HCons B_Zero HNil))) 330 (Just (HCons B_DstColor (HCons B_Zero HNil)))
358 RGB_IdentityLighting 331 RGB_IdentityLighting
359 A_Identity 332 A_Identity
@@ -364,12 +337,11 @@ sampleMaterial
364 D_Lequal 337 D_Lequal
365 Nothing 338 Nothing
366 False 339 False
367 "Tex_3226210144") 340 "Tex_3226210144"
368 Nil)) 341 : Nil)
369 False) 342 False)
370 HNil)) 343 HNil)
371 (Cons 344 : HCons
372 (HCons
373 "textures/gothic_door/km_arena1archfinalc_mid" 345 "textures/gothic_door/km_arena1archfinalc_mid"
374 (HCons 346 (HCons
375 (CommonAttrs 347 (CommonAttrs
@@ -383,8 +355,7 @@ sampleMaterial
383 Nil 355 Nil
384 False 356 False
385 False 357 False
386 (Cons 358 (StageAttrs
387 (StageAttrs
388 Nothing 359 Nothing
389 RGB_IdentityLighting 360 RGB_IdentityLighting
390 A_Identity 361 A_Identity
@@ -395,9 +366,8 @@ sampleMaterial
395 D_Lequal 366 D_Lequal
396 Nothing 367 Nothing
397 False 368 False
398 "Tex_2073154888") 369 "Tex_2073154888"
399 (Cons 370 : StageAttrs
400 (StageAttrs
401 (Just (HCons B_DstColor (HCons B_Zero HNil))) 371 (Just (HCons B_DstColor (HCons B_Zero HNil)))
402 RGB_IdentityLighting 372 RGB_IdentityLighting
403 A_Identity 373 A_Identity
@@ -408,12 +378,11 @@ sampleMaterial
408 D_Lequal 378 D_Lequal
409 Nothing 379 Nothing
410 False 380 False
411 "Tex_3226210144") 381 "Tex_3226210144"
412 Nil)) 382 : Nil)
413 False) 383 False)
414 HNil)) 384 HNil)
415 (Cons 385 : HCons
416 (HCons
417 "textures/gothic_door/km_arena1archfinalc_top" 386 "textures/gothic_door/km_arena1archfinalc_top"
418 (HCons 387 (HCons
419 (CommonAttrs 388 (CommonAttrs
@@ -427,8 +396,7 @@ sampleMaterial
427 Nil 396 Nil
428 False 397 False
429 False 398 False
430 (Cons 399 (StageAttrs
431 (StageAttrs
432 Nothing 400 Nothing
433 RGB_IdentityLighting 401 RGB_IdentityLighting
434 A_Identity 402 A_Identity
@@ -439,9 +407,8 @@ sampleMaterial
439 D_Lequal 407 D_Lequal
440 Nothing 408 Nothing
441 False 409 False
442 "Tex_3071107621") 410 "Tex_3071107621"
443 (Cons 411 : StageAttrs
444 (StageAttrs
445 (Just (HCons B_DstColor (HCons B_Zero HNil))) 412 (Just (HCons B_DstColor (HCons B_Zero HNil)))
446 RGB_IdentityLighting 413 RGB_IdentityLighting
447 A_Identity 414 A_Identity
@@ -452,12 +419,11 @@ sampleMaterial
452 D_Lequal 419 D_Lequal
453 Nothing 420 Nothing
454 False 421 False
455 "Tex_3226210144") 422 "Tex_3226210144"
456 Nil)) 423 : Nil)
457 False) 424 False)
458 HNil)) 425 HNil)
459 (Cons 426 : HCons
460 (HCons
461 "textures/gothic_door/km_arena1archfinald_bot" 427 "textures/gothic_door/km_arena1archfinald_bot"
462 (HCons 428 (HCons
463 (CommonAttrs 429 (CommonAttrs
@@ -471,8 +437,7 @@ sampleMaterial
471 Nil 437 Nil
472 False 438 False
473 False 439 False
474 (Cons 440 (StageAttrs
475 (StageAttrs
476 Nothing 441 Nothing
477 RGB_IdentityLighting 442 RGB_IdentityLighting
478 A_Identity 443 A_Identity
@@ -483,9 +448,8 @@ sampleMaterial
483 D_Lequal 448 D_Lequal
484 Nothing 449 Nothing
485 False 450 False
486 "Tex_1201212243") 451 "Tex_1201212243"
487 (Cons 452 : StageAttrs
488 (StageAttrs
489 (Just (HCons B_DstColor (HCons B_Zero HNil))) 453 (Just (HCons B_DstColor (HCons B_Zero HNil)))
490 RGB_IdentityLighting 454 RGB_IdentityLighting
491 A_Identity 455 A_Identity
@@ -496,12 +460,11 @@ sampleMaterial
496 D_Lequal 460 D_Lequal
497 Nothing 461 Nothing
498 False 462 False
499 "Tex_3226210144") 463 "Tex_3226210144"
500 Nil)) 464 : Nil)
501 False) 465 False)
502 HNil)) 466 HNil)
503 (Cons 467 : HCons
504 (HCons
505 "textures/gothic_door/km_arena1archfinald_mid" 468 "textures/gothic_door/km_arena1archfinald_mid"
506 (HCons 469 (HCons
507 (CommonAttrs 470 (CommonAttrs
@@ -515,8 +478,7 @@ sampleMaterial
515 Nil 478 Nil
516 False 479 False
517 False 480 False
518 (Cons 481 (StageAttrs
519 (StageAttrs
520 Nothing 482 Nothing
521 RGB_IdentityLighting 483 RGB_IdentityLighting
522 A_Identity 484 A_Identity
@@ -527,9 +489,8 @@ sampleMaterial
527 D_Lequal 489 D_Lequal
528 Nothing 490 Nothing
529 False 491 False
530 "Tex_3768122504") 492 "Tex_3768122504"
531 (Cons 493 : StageAttrs
532 (StageAttrs
533 (Just (HCons B_DstColor (HCons B_Zero HNil))) 494 (Just (HCons B_DstColor (HCons B_Zero HNil)))
534 RGB_IdentityLighting 495 RGB_IdentityLighting
535 A_Identity 496 A_Identity
@@ -540,12 +501,11 @@ sampleMaterial
540 D_Lequal 501 D_Lequal
541 Nothing 502 Nothing
542 False 503 False
543 "Tex_3226210144") 504 "Tex_3226210144"
544 Nil)) 505 : Nil)
545 False) 506 False)
546 HNil)) 507 HNil)
547 (Cons 508 : HCons
548 (HCons
549 "textures/gothic_door/skull_door_a" 509 "textures/gothic_door/skull_door_a"
550 (HCons 510 (HCons
551 (CommonAttrs 511 (CommonAttrs
@@ -559,8 +519,7 @@ sampleMaterial
559 Nil 519 Nil
560 False 520 False
561 False 521 False
562 (Cons 522 (StageAttrs
563 (StageAttrs
564 Nothing 523 Nothing
565 RGB_IdentityLighting 524 RGB_IdentityLighting
566 A_Identity 525 A_Identity
@@ -571,9 +530,8 @@ sampleMaterial
571 D_Lequal 530 D_Lequal
572 Nothing 531 Nothing
573 False 532 False
574 "Tex_1284708166") 533 "Tex_1284708166"
575 (Cons 534 : StageAttrs
576 (StageAttrs
577 (Just (HCons B_DstColor (HCons B_Zero HNil))) 535 (Just (HCons B_DstColor (HCons B_Zero HNil)))
578 RGB_IdentityLighting 536 RGB_IdentityLighting
579 A_Identity 537 A_Identity
@@ -584,12 +542,11 @@ sampleMaterial
584 D_Lequal 542 D_Lequal
585 Nothing 543 Nothing
586 False 544 False
587 "Tex_3226210144") 545 "Tex_3226210144"
588 Nil)) 546 : Nil)
589 False) 547 False)
590 HNil)) 548 HNil)
591 (Cons 549 : HCons
592 (HCons
593 "textures/gothic_door/skull_door_b" 550 "textures/gothic_door/skull_door_b"
594 (HCons 551 (HCons
595 (CommonAttrs 552 (CommonAttrs
@@ -603,8 +560,7 @@ sampleMaterial
603 Nil 560 Nil
604 False 561 False
605 False 562 False
606 (Cons 563 (StageAttrs
607 (StageAttrs
608 Nothing 564 Nothing
609 RGB_IdentityLighting 565 RGB_IdentityLighting
610 A_Identity 566 A_Identity
@@ -615,9 +571,8 @@ sampleMaterial
615 D_Lequal 571 D_Lequal
616 Nothing 572 Nothing
617 False 573 False
618 "Tex_1318715778") 574 "Tex_1318715778"
619 (Cons 575 : StageAttrs
620 (StageAttrs
621 (Just (HCons B_DstColor (HCons B_Zero HNil))) 576 (Just (HCons B_DstColor (HCons B_Zero HNil)))
622 RGB_IdentityLighting 577 RGB_IdentityLighting
623 A_Identity 578 A_Identity
@@ -628,12 +583,11 @@ sampleMaterial
628 D_Lequal 583 D_Lequal
629 Nothing 584 Nothing
630 False 585 False
631 "Tex_3226210144") 586 "Tex_3226210144"
632 Nil)) 587 : Nil)
633 False) 588 False)
634 HNil)) 589 HNil)
635 (Cons 590 : HCons
636 (HCons
637 "textures/gothic_door/skull_door_c" 591 "textures/gothic_door/skull_door_c"
638 (HCons 592 (HCons
639 (CommonAttrs 593 (CommonAttrs
@@ -647,8 +601,7 @@ sampleMaterial
647 Nil 601 Nil
648 False 602 False
649 False 603 False
650 (Cons 604 (StageAttrs
651 (StageAttrs
652 Nothing 605 Nothing
653 RGB_IdentityLighting 606 RGB_IdentityLighting
654 A_Identity 607 A_Identity
@@ -659,9 +612,8 @@ sampleMaterial
659 D_Lequal 612 D_Lequal
660 Nothing 613 Nothing
661 False 614 False
662 "Tex_4189195777") 615 "Tex_4189195777"
663 (Cons 616 : StageAttrs
664 (StageAttrs
665 (Just (HCons B_DstColor (HCons B_Zero HNil))) 617 (Just (HCons B_DstColor (HCons B_Zero HNil)))
666 RGB_IdentityLighting 618 RGB_IdentityLighting
667 A_Identity 619 A_Identity
@@ -672,12 +624,11 @@ sampleMaterial
672 D_Lequal 624 D_Lequal
673 Nothing 625 Nothing
674 False 626 False
675 "Tex_3226210144") 627 "Tex_3226210144"
676 Nil)) 628 : Nil)
677 False) 629 False)
678 HNil)) 630 HNil)
679 (Cons 631 : HCons
680 (HCons
681 "textures/gothic_door/skull_door_d" 632 "textures/gothic_door/skull_door_d"
682 (HCons 633 (HCons
683 (CommonAttrs 634 (CommonAttrs
@@ -691,8 +642,7 @@ sampleMaterial
691 Nil 642 Nil
692 False 643 False
693 False 644 False
694 (Cons 645 (StageAttrs
695 (StageAttrs
696 Nothing 646 Nothing
697 RGB_IdentityLighting 647 RGB_IdentityLighting
698 A_Identity 648 A_Identity
@@ -703,9 +653,8 @@ sampleMaterial
703 D_Lequal 653 D_Lequal
704 Nothing 654 Nothing
705 False 655 False
706 "Tex_1250438154") 656 "Tex_1250438154"
707 (Cons 657 : StageAttrs
708 (StageAttrs
709 (Just (HCons B_DstColor (HCons B_Zero HNil))) 658 (Just (HCons B_DstColor (HCons B_Zero HNil)))
710 RGB_IdentityLighting 659 RGB_IdentityLighting
711 A_Identity 660 A_Identity
@@ -716,12 +665,11 @@ sampleMaterial
716 D_Lequal 665 D_Lequal
717 Nothing 666 Nothing
718 False 667 False
719 "Tex_3226210144") 668 "Tex_3226210144"
720 Nil)) 669 : Nil)
721 False) 670 False)
722 HNil)) 671 HNil)
723 (Cons 672 : HCons
724 (HCons
725 "textures/gothic_door/skull_door_e" 673 "textures/gothic_door/skull_door_e"
726 (HCons 674 (HCons
727 (CommonAttrs 675 (CommonAttrs
@@ -735,8 +683,7 @@ sampleMaterial
735 Nil 683 Nil
736 False 684 False
737 False 685 False
738 (Cons 686 (StageAttrs
739 (StageAttrs
740 Nothing 687 Nothing
741 RGB_IdentityLighting 688 RGB_IdentityLighting
742 A_Identity 689 A_Identity
@@ -747,9 +694,8 @@ sampleMaterial
747 D_Lequal 694 D_Lequal
748 Nothing 695 Nothing
749 False 696 False
750 "Tex_4255130505") 697 "Tex_4255130505"
751 (Cons 698 : StageAttrs
752 (StageAttrs
753 (Just (HCons B_DstColor (HCons B_Zero HNil))) 699 (Just (HCons B_DstColor (HCons B_Zero HNil)))
754 RGB_IdentityLighting 700 RGB_IdentityLighting
755 A_Identity 701 A_Identity
@@ -760,12 +706,11 @@ sampleMaterial
760 D_Lequal 706 D_Lequal
761 Nothing 707 Nothing
762 False 708 False
763 "Tex_3226210144") 709 "Tex_3226210144"
764 Nil)) 710 : Nil)
765 False) 711 False)
766 HNil)) 712 HNil)
767 (Cons 713 : HCons
768 (HCons
769 "textures/gothic_door/skull_door_f" 714 "textures/gothic_door/skull_door_f"
770 (HCons 715 (HCons
771 (CommonAttrs 716 (CommonAttrs
@@ -779,8 +724,7 @@ sampleMaterial
779 Nil 724 Nil
780 False 725 False
781 False 726 False
782 (Cons 727 (StageAttrs
783 (StageAttrs
784 Nothing 728 Nothing
785 RGB_IdentityLighting 729 RGB_IdentityLighting
786 A_Identity 730 A_Identity
@@ -791,9 +735,8 @@ sampleMaterial
791 D_Lequal 735 D_Lequal
792 Nothing 736 Nothing
793 False 737 False
794 "Tex_4289279309") 738 "Tex_4289279309"
795 (Cons 739 : StageAttrs
796 (StageAttrs
797 (Just (HCons B_DstColor (HCons B_Zero HNil))) 740 (Just (HCons B_DstColor (HCons B_Zero HNil)))
798 RGB_IdentityLighting 741 RGB_IdentityLighting
799 A_Identity 742 A_Identity
@@ -804,12 +747,11 @@ sampleMaterial
804 D_Lequal 747 D_Lequal
805 Nothing 748 Nothing
806 False 749 False
807 "Tex_3226210144") 750 "Tex_3226210144"
808 Nil)) 751 : Nil)
809 False) 752 False)
810 HNil)) 753 HNil)
811 (Cons 754 : HCons
812 (HCons
813 "textures/gothic_door/skullarch_a" 755 "textures/gothic_door/skullarch_a"
814 (HCons 756 (HCons
815 (CommonAttrs 757 (CommonAttrs
@@ -823,8 +765,7 @@ sampleMaterial
823 Nil 765 Nil
824 False 766 False
825 False 767 False
826 (Cons 768 (StageAttrs
827 (StageAttrs
828 Nothing 769 Nothing
829 RGB_IdentityLighting 770 RGB_IdentityLighting
830 A_Identity 771 A_Identity
@@ -835,9 +776,8 @@ sampleMaterial
835 D_Lequal 776 D_Lequal
836 Nothing 777 Nothing
837 False 778 False
838 "Tex_3448884269") 779 "Tex_3448884269"
839 (Cons 780 : StageAttrs
840 (StageAttrs
841 (Just (HCons B_DstColor (HCons B_Zero HNil))) 781 (Just (HCons B_DstColor (HCons B_Zero HNil)))
842 RGB_IdentityLighting 782 RGB_IdentityLighting
843 A_Identity 783 A_Identity
@@ -848,12 +788,11 @@ sampleMaterial
848 D_Lequal 788 D_Lequal
849 Nothing 789 Nothing
850 False 790 False
851 "Tex_3226210144") 791 "Tex_3226210144"
852 Nil)) 792 : Nil)
853 False) 793 False)
854 HNil)) 794 HNil)
855 (Cons 795 : HCons
856 (HCons
857 "textures/gothic_door/skullarch_b" 796 "textures/gothic_door/skullarch_b"
858 (HCons 797 (HCons
859 (CommonAttrs 798 (CommonAttrs
@@ -867,23 +806,19 @@ sampleMaterial
867 Nil 806 Nil
868 False 807 False
869 False 808 False
870 (Cons 809 (StageAttrs
871 (StageAttrs
872 Nothing 810 Nothing
873 RGB_Identity 811 RGB_Identity
874 A_Identity 812 A_Identity
875 TG_Base 813 TG_Base
876 (Cons 814 (TM_Scroll 0.0 1.0 : TM_Turb 0.0 0.25 0.0 5.6 : TM_Scale 1.5 1.5 : Nil)
877 (TM_Scroll 0.0 1.0)
878 (Cons (TM_Turb 0.0 0.25 0.0 5.6) (Cons (TM_Scale 1.5 1.5) Nil)))
879 (ST_Map "textures/sfx/firegorre.tga") 815 (ST_Map "textures/sfx/firegorre.tga")
880 True 816 True
881 D_Lequal 817 D_Lequal
882 Nothing 818 Nothing
883 False 819 False
884 "Tex_3416962274") 820 "Tex_3416962274"
885 (Cons 821 : StageAttrs
886 (StageAttrs
887 (Just (HCons B_SrcAlpha (HCons B_OneMinusSrcAlpha HNil))) 822 (Just (HCons B_SrcAlpha (HCons B_OneMinusSrcAlpha HNil)))
888 RGB_Identity 823 RGB_Identity
889 A_Identity 824 A_Identity
@@ -894,9 +829,8 @@ sampleMaterial
894 D_Lequal 829 D_Lequal
895 Nothing 830 Nothing
896 False 831 False
897 "Tex_4077187607") 832 "Tex_4077187607"
898 (Cons 833 : StageAttrs
899 (StageAttrs
900 (Just (HCons B_DstColor (HCons B_Zero HNil))) 834 (Just (HCons B_DstColor (HCons B_Zero HNil)))
901 RGB_Identity 835 RGB_Identity
902 A_Identity 836 A_Identity
@@ -907,12 +841,11 @@ sampleMaterial
907 D_Lequal 841 D_Lequal
908 Nothing 842 Nothing
909 False 843 False
910 "Tex_1196599720") 844 "Tex_1196599720"
911 Nil))) 845 : Nil)
912 False) 846 False)
913 HNil)) 847 HNil)
914 (Cons 848 : HCons
915 (HCons
916 "textures/gothic_door/skullarch_c" 849 "textures/gothic_door/skullarch_c"
917 (HCons 850 (HCons
918 (CommonAttrs 851 (CommonAttrs
@@ -926,8 +859,7 @@ sampleMaterial
926 Nil 859 Nil
927 False 860 False
928 False 861 False
929 (Cons 862 (StageAttrs
930 (StageAttrs
931 Nothing 863 Nothing
932 RGB_IdentityLighting 864 RGB_IdentityLighting
933 A_Identity 865 A_Identity
@@ -938,9 +870,8 @@ sampleMaterial
938 D_Lequal 870 D_Lequal
939 Nothing 871 Nothing
940 False 872 False
941 "Tex_2024854890") 873 "Tex_2024854890"
942 (Cons 874 : StageAttrs
943 (StageAttrs
944 (Just (HCons B_DstColor (HCons B_Zero HNil))) 875 (Just (HCons B_DstColor (HCons B_Zero HNil)))
945 RGB_IdentityLighting 876 RGB_IdentityLighting
946 A_Identity 877 A_Identity
@@ -951,12 +882,11 @@ sampleMaterial
951 D_Lequal 882 D_Lequal
952 Nothing 883 Nothing
953 False 884 False
954 "Tex_3226210144") 885 "Tex_3226210144"
955 Nil)) 886 : Nil)
956 False) 887 False)
957 HNil)) 888 HNil)
958 (Cons 889 : HCons
959 (HCons
960 "textures/gothic_door/xian_tourneyarch_inside2" 890 "textures/gothic_door/xian_tourneyarch_inside2"
961 (HCons 891 (HCons
962 (CommonAttrs 892 (CommonAttrs
@@ -970,8 +900,7 @@ sampleMaterial
970 Nil 900 Nil
971 False 901 False
972 False 902 False
973 (Cons 903 (StageAttrs
974 (StageAttrs
975 Nothing 904 Nothing
976 RGB_IdentityLighting 905 RGB_IdentityLighting
977 A_Identity 906 A_Identity
@@ -982,9 +911,8 @@ sampleMaterial
982 D_Lequal 911 D_Lequal
983 Nothing 912 Nothing
984 False 913 False
985 "Tex_1435187472") 914 "Tex_1435187472"
986 (Cons 915 : StageAttrs
987 (StageAttrs
988 (Just (HCons B_DstColor (HCons B_Zero HNil))) 916 (Just (HCons B_DstColor (HCons B_Zero HNil)))
989 RGB_IdentityLighting 917 RGB_IdentityLighting
990 A_Identity 918 A_Identity
@@ -995,12 +923,11 @@ sampleMaterial
995 D_Lequal 923 D_Lequal
996 Nothing 924 Nothing
997 False 925 False
998 "Tex_3226210144") 926 "Tex_3226210144"
999 Nil)) 927 : Nil)
1000 False) 928 False)
1001 HNil)) 929 HNil)
1002 (Cons 930 : HCons
1003 (HCons
1004 "textures/gothic_floor/blocks17floor2" 931 "textures/gothic_floor/blocks17floor2"
1005 (HCons 932 (HCons
1006 (CommonAttrs 933 (CommonAttrs
@@ -1014,8 +941,7 @@ sampleMaterial
1014 Nil 941 Nil
1015 False 942 False
1016 False 943 False
1017 (Cons 944 (StageAttrs
1018 (StageAttrs
1019 Nothing 945 Nothing
1020 RGB_IdentityLighting 946 RGB_IdentityLighting
1021 A_Identity 947 A_Identity
@@ -1026,9 +952,8 @@ sampleMaterial
1026 D_Lequal 952 D_Lequal
1027 Nothing 953 Nothing
1028 False 954 False
1029 "Tex_3814342582") 955 "Tex_3814342582"
1030 (Cons 956 : StageAttrs
1031 (StageAttrs
1032 (Just (HCons B_DstColor (HCons B_Zero HNil))) 957 (Just (HCons B_DstColor (HCons B_Zero HNil)))
1033 RGB_IdentityLighting 958 RGB_IdentityLighting
1034 A_Identity 959 A_Identity
@@ -1039,12 +964,11 @@ sampleMaterial
1039 D_Lequal 964 D_Lequal
1040 Nothing 965 Nothing
1041 False 966 False
1042 "Tex_3226210144") 967 "Tex_3226210144"
1043 Nil)) 968 : Nil)
1044 False) 969 False)
1045 HNil)) 970 HNil)
1046 (Cons 971 : HCons
1047 (HCons
1048 "textures/gothic_floor/largerblock3b" 972 "textures/gothic_floor/largerblock3b"
1049 (HCons 973 (HCons
1050 (CommonAttrs 974 (CommonAttrs
@@ -1058,8 +982,7 @@ sampleMaterial
1058 Nil 982 Nil
1059 False 983 False
1060 False 984 False
1061 (Cons 985 (StageAttrs
1062 (StageAttrs
1063 Nothing 986 Nothing
1064 RGB_IdentityLighting 987 RGB_IdentityLighting
1065 A_Identity 988 A_Identity
@@ -1070,9 +993,8 @@ sampleMaterial
1070 D_Lequal 993 D_Lequal
1071 Nothing 994 Nothing
1072 False 995 False
1073 "Tex_2966885788") 996 "Tex_2966885788"
1074 (Cons 997 : StageAttrs
1075 (StageAttrs
1076 (Just (HCons B_DstColor (HCons B_Zero HNil))) 998 (Just (HCons B_DstColor (HCons B_Zero HNil)))
1077 RGB_IdentityLighting 999 RGB_IdentityLighting
1078 A_Identity 1000 A_Identity
@@ -1083,12 +1005,11 @@ sampleMaterial
1083 D_Lequal 1005 D_Lequal
1084 Nothing 1006 Nothing
1085 False 1007 False
1086 "Tex_3226210144") 1008 "Tex_3226210144"
1087 Nil)) 1009 : Nil)
1088 False) 1010 False)
1089 HNil)) 1011 HNil)
1090 (Cons 1012 : HCons
1091 (HCons
1092 "textures/gothic_floor/metalbridge06" 1013 "textures/gothic_floor/metalbridge06"
1093 (HCons 1014 (HCons
1094 (CommonAttrs 1015 (CommonAttrs
@@ -1102,8 +1023,7 @@ sampleMaterial
1102 Nil 1023 Nil
1103 False 1024 False
1104 False 1025 False
1105 (Cons 1026 (StageAttrs
1106 (StageAttrs
1107 Nothing 1027 Nothing
1108 RGB_IdentityLighting 1028 RGB_IdentityLighting
1109 A_Identity 1029 A_Identity
@@ -1114,9 +1034,8 @@ sampleMaterial
1114 D_Lequal 1034 D_Lequal
1115 Nothing 1035 Nothing
1116 False 1036 False
1117 "Tex_1581337759") 1037 "Tex_1581337759"
1118 (Cons 1038 : StageAttrs
1119 (StageAttrs
1120 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1039 (Just (HCons B_DstColor (HCons B_Zero HNil)))
1121 RGB_IdentityLighting 1040 RGB_IdentityLighting
1122 A_Identity 1041 A_Identity
@@ -1127,12 +1046,11 @@ sampleMaterial
1127 D_Lequal 1046 D_Lequal
1128 Nothing 1047 Nothing
1129 False 1048 False
1130 "Tex_3226210144") 1049 "Tex_3226210144"
1131 Nil)) 1050 : Nil)
1132 False) 1051 False)
1133 HNil)) 1052 HNil)
1134 (Cons 1053 : HCons
1135 (HCons
1136 "textures/gothic_floor/metalbridge06broke" 1054 "textures/gothic_floor/metalbridge06broke"
1137 (HCons 1055 (HCons
1138 (CommonAttrs 1056 (CommonAttrs
@@ -1146,8 +1064,7 @@ sampleMaterial
1146 Nil 1064 Nil
1147 False 1065 False
1148 False 1066 False
1149 (Cons 1067 (StageAttrs
1150 (StageAttrs
1151 Nothing 1068 Nothing
1152 RGB_IdentityLighting 1069 RGB_IdentityLighting
1153 A_Identity 1070 A_Identity
@@ -1158,9 +1075,8 @@ sampleMaterial
1158 D_Lequal 1075 D_Lequal
1159 Nothing 1076 Nothing
1160 False 1077 False
1161 "Tex_3921745736") 1078 "Tex_3921745736"
1162 (Cons 1079 : StageAttrs
1163 (StageAttrs
1164 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1080 (Just (HCons B_DstColor (HCons B_Zero HNil)))
1165 RGB_IdentityLighting 1081 RGB_IdentityLighting
1166 A_Identity 1082 A_Identity
@@ -1171,12 +1087,11 @@ sampleMaterial
1171 D_Lequal 1087 D_Lequal
1172 Nothing 1088 Nothing
1173 False 1089 False
1174 "Tex_3226210144") 1090 "Tex_3226210144"
1175 Nil)) 1091 : Nil)
1176 False) 1092 False)
1177 HNil)) 1093 HNil)
1178 (Cons 1094 : HCons
1179 (HCons
1180 "textures/gothic_floor/xstairtop4" 1095 "textures/gothic_floor/xstairtop4"
1181 (HCons 1096 (HCons
1182 (CommonAttrs 1097 (CommonAttrs
@@ -1190,8 +1105,7 @@ sampleMaterial
1190 Nil 1105 Nil
1191 False 1106 False
1192 False 1107 False
1193 (Cons 1108 (StageAttrs
1194 (StageAttrs
1195 Nothing 1109 Nothing
1196 RGB_IdentityLighting 1110 RGB_IdentityLighting
1197 A_Identity 1111 A_Identity
@@ -1202,9 +1116,8 @@ sampleMaterial
1202 D_Lequal 1116 D_Lequal
1203 Nothing 1117 Nothing
1204 False 1118 False
1205 "Tex_3836020895") 1119 "Tex_3836020895"
1206 (Cons 1120 : StageAttrs
1207 (StageAttrs
1208 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1121 (Just (HCons B_DstColor (HCons B_Zero HNil)))
1209 RGB_IdentityLighting 1122 RGB_IdentityLighting
1210 A_Identity 1123 A_Identity
@@ -1215,12 +1128,11 @@ sampleMaterial
1215 D_Lequal 1128 D_Lequal
1216 Nothing 1129 Nothing
1217 False 1130 False
1218 "Tex_3226210144") 1131 "Tex_3226210144"
1219 Nil)) 1132 : Nil)
1220 False) 1133 False)
1221 HNil)) 1134 HNil)
1222 (Cons 1135 : HCons
1223 (HCons
1224 "textures/gothic_floor/xstepborder3" 1136 "textures/gothic_floor/xstepborder3"
1225 (HCons 1137 (HCons
1226 (CommonAttrs 1138 (CommonAttrs
@@ -1234,8 +1146,7 @@ sampleMaterial
1234 Nil 1146 Nil
1235 False 1147 False
1236 False 1148 False
1237 (Cons 1149 (StageAttrs
1238 (StageAttrs
1239 Nothing 1150 Nothing
1240 RGB_IdentityLighting 1151 RGB_IdentityLighting
1241 A_Identity 1152 A_Identity
@@ -1246,9 +1157,8 @@ sampleMaterial
1246 D_Lequal 1157 D_Lequal
1247 Nothing 1158 Nothing
1248 False 1159 False
1249 "Tex_3269743316") 1160 "Tex_3269743316"
1250 (Cons 1161 : StageAttrs
1251 (StageAttrs
1252 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1162 (Just (HCons B_DstColor (HCons B_Zero HNil)))
1253 RGB_IdentityLighting 1163 RGB_IdentityLighting
1254 A_Identity 1164 A_Identity
@@ -1259,12 +1169,11 @@ sampleMaterial
1259 D_Lequal 1169 D_Lequal
1260 Nothing 1170 Nothing
1261 False 1171 False
1262 "Tex_3226210144") 1172 "Tex_3226210144"
1263 Nil)) 1173 : Nil)
1264 False) 1174 False)
1265 HNil)) 1175 HNil)
1266 (Cons 1176 : HCons
1267 (HCons
1268 "textures/gothic_trim/baseboard04" 1177 "textures/gothic_trim/baseboard04"
1269 (HCons 1178 (HCons
1270 (CommonAttrs 1179 (CommonAttrs
@@ -1278,8 +1187,7 @@ sampleMaterial
1278 Nil 1187 Nil
1279 False 1188 False
1280 False 1189 False
1281 (Cons 1190 (StageAttrs
1282 (StageAttrs
1283 Nothing 1191 Nothing
1284 RGB_IdentityLighting 1192 RGB_IdentityLighting
1285 A_Identity 1193 A_Identity
@@ -1290,9 +1198,8 @@ sampleMaterial
1290 D_Lequal 1198 D_Lequal
1291 Nothing 1199 Nothing
1292 False 1200 False
1293 "Tex_1002517541") 1201 "Tex_1002517541"
1294 (Cons 1202 : StageAttrs
1295 (StageAttrs
1296 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1203 (Just (HCons B_DstColor (HCons B_Zero HNil)))
1297 RGB_IdentityLighting 1204 RGB_IdentityLighting
1298 A_Identity 1205 A_Identity
@@ -1303,12 +1210,11 @@ sampleMaterial
1303 D_Lequal 1210 D_Lequal
1304 Nothing 1211 Nothing
1305 False 1212 False
1306 "Tex_3226210144") 1213 "Tex_3226210144"
1307 Nil)) 1214 : Nil)
1308 False) 1215 False)
1309 HNil)) 1216 HNil)
1310 (Cons 1217 : HCons
1311 (HCons
1312 "textures/gothic_trim/baseboard09_c3" 1218 "textures/gothic_trim/baseboard09_c3"
1313 (HCons 1219 (HCons
1314 (CommonAttrs 1220 (CommonAttrs
@@ -1322,8 +1228,7 @@ sampleMaterial
1322 Nil 1228 Nil
1323 False 1229 False
1324 False 1230 False
1325 (Cons 1231 (StageAttrs
1326 (StageAttrs
1327 Nothing 1232 Nothing
1328 RGB_IdentityLighting 1233 RGB_IdentityLighting
1329 A_Identity 1234 A_Identity
@@ -1334,9 +1239,8 @@ sampleMaterial
1334 D_Lequal 1239 D_Lequal
1335 Nothing 1240 Nothing
1336 False 1241 False
1337 "Tex_2289735512") 1242 "Tex_2289735512"
1338 (Cons 1243 : StageAttrs
1339 (StageAttrs
1340 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1244 (Just (HCons B_DstColor (HCons B_Zero HNil)))
1341 RGB_IdentityLighting 1245 RGB_IdentityLighting
1342 A_Identity 1246 A_Identity
@@ -1347,12 +1251,11 @@ sampleMaterial
1347 D_Lequal 1251 D_Lequal
1348 Nothing 1252 Nothing
1349 False 1253 False
1350 "Tex_3226210144") 1254 "Tex_3226210144"
1351 Nil)) 1255 : Nil)
1352 False) 1256 False)
1353 HNil)) 1257 HNil)
1354 (Cons 1258 : HCons
1355 (HCons
1356 "textures/gothic_trim/baseboard09_e" 1259 "textures/gothic_trim/baseboard09_e"
1357 (HCons 1260 (HCons
1358 (CommonAttrs 1261 (CommonAttrs
@@ -1366,8 +1269,7 @@ sampleMaterial
1366 Nil 1269 Nil
1367 False 1270 False
1368 False 1271 False
1369 (Cons 1272 (StageAttrs
1370 (StageAttrs
1371 Nothing 1273 Nothing
1372 RGB_IdentityLighting 1274 RGB_IdentityLighting
1373 A_Identity 1275 A_Identity
@@ -1378,9 +1280,8 @@ sampleMaterial
1378 D_Lequal 1280 D_Lequal
1379 Nothing 1281 Nothing
1380 False 1282 False
1381 "Tex_2367525081") 1283 "Tex_2367525081"
1382 (Cons 1284 : StageAttrs
1383 (StageAttrs
1384 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1285 (Just (HCons B_DstColor (HCons B_Zero HNil)))
1385 RGB_IdentityLighting 1286 RGB_IdentityLighting
1386 A_Identity 1287 A_Identity
@@ -1391,12 +1292,11 @@ sampleMaterial
1391 D_Lequal 1292 D_Lequal
1392 Nothing 1293 Nothing
1393 False 1294 False
1394 "Tex_3226210144") 1295 "Tex_3226210144"
1395 Nil)) 1296 : Nil)
1396 False) 1297 False)
1397 HNil)) 1298 HNil)
1398 (Cons 1299 : HCons
1399 (HCons
1400 "textures/gothic_trim/baseboard09_e2" 1300 "textures/gothic_trim/baseboard09_e2"
1401 (HCons 1301 (HCons
1402 (CommonAttrs 1302 (CommonAttrs
@@ -1410,8 +1310,7 @@ sampleMaterial
1410 Nil 1310 Nil
1411 False 1311 False
1412 False 1312 False
1413 (Cons 1313 (StageAttrs
1414 (StageAttrs
1415 Nothing 1314 Nothing
1416 RGB_IdentityLighting 1315 RGB_IdentityLighting
1417 A_Identity 1316 A_Identity
@@ -1422,9 +1321,8 @@ sampleMaterial
1422 D_Lequal 1321 D_Lequal
1423 Nothing 1322 Nothing
1424 False 1323 False
1425 "Tex_3694494180") 1324 "Tex_3694494180"
1426 (Cons 1325 : StageAttrs
1427 (StageAttrs
1428 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1326 (Just (HCons B_DstColor (HCons B_Zero HNil)))
1429 RGB_IdentityLighting 1327 RGB_IdentityLighting
1430 A_Identity 1328 A_Identity
@@ -1435,12 +1333,11 @@ sampleMaterial
1435 D_Lequal 1333 D_Lequal
1436 Nothing 1334 Nothing
1437 False 1335 False
1438 "Tex_3226210144") 1336 "Tex_3226210144"
1439 Nil)) 1337 : Nil)
1440 False) 1338 False)
1441 HNil)) 1339 HNil)
1442 (Cons 1340 : HCons
1443 (HCons
1444 "textures/gothic_trim/baseboard09_l2" 1341 "textures/gothic_trim/baseboard09_l2"
1445 (HCons 1342 (HCons
1446 (CommonAttrs 1343 (CommonAttrs
@@ -1454,8 +1351,7 @@ sampleMaterial
1454 Nil 1351 Nil
1455 False 1352 False
1456 False 1353 False
1457 (Cons 1354 (StageAttrs
1458 (StageAttrs
1459 Nothing 1355 Nothing
1460 RGB_IdentityLighting 1356 RGB_IdentityLighting
1461 A_Identity 1357 A_Identity
@@ -1466,9 +1362,8 @@ sampleMaterial
1466 D_Lequal 1362 D_Lequal
1467 Nothing 1363 Nothing
1468 False 1364 False
1469 "Tex_3202786139") 1365 "Tex_3202786139"
1470 (Cons 1366 : StageAttrs
1471 (StageAttrs
1472 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1367 (Just (HCons B_DstColor (HCons B_Zero HNil)))
1473 RGB_IdentityLighting 1368 RGB_IdentityLighting
1474 A_Identity 1369 A_Identity
@@ -1479,12 +1374,11 @@ sampleMaterial
1479 D_Lequal 1374 D_Lequal
1480 Nothing 1375 Nothing
1481 False 1376 False
1482 "Tex_3226210144") 1377 "Tex_3226210144"
1483 Nil)) 1378 : Nil)
1484 False) 1379 False)
1485 HNil)) 1380 HNil)
1486 (Cons 1381 : HCons
1487 (HCons
1488 "textures/gothic_trim/baseboard09_o3" 1382 "textures/gothic_trim/baseboard09_o3"
1489 (HCons 1383 (HCons
1490 (CommonAttrs 1384 (CommonAttrs
@@ -1498,8 +1392,7 @@ sampleMaterial
1498 Nil 1392 Nil
1499 False 1393 False
1500 False 1394 False
1501 (Cons 1395 (StageAttrs
1502 (StageAttrs
1503 Nothing 1396 Nothing
1504 RGB_IdentityLighting 1397 RGB_IdentityLighting
1505 A_Identity 1398 A_Identity
@@ -1510,9 +1403,8 @@ sampleMaterial
1510 D_Lequal 1403 D_Lequal
1511 Nothing 1404 Nothing
1512 False 1405 False
1513 "Tex_2512757607") 1406 "Tex_2512757607"
1514 (Cons 1407 : StageAttrs
1515 (StageAttrs
1516 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1408 (Just (HCons B_DstColor (HCons B_Zero HNil)))
1517 RGB_IdentityLighting 1409 RGB_IdentityLighting
1518 A_Identity 1410 A_Identity
@@ -1523,12 +1415,11 @@ sampleMaterial
1523 D_Lequal 1415 D_Lequal
1524 Nothing 1416 Nothing
1525 False 1417 False
1526 "Tex_3226210144") 1418 "Tex_3226210144"
1527 Nil)) 1419 : Nil)
1528 False) 1420 False)
1529 HNil)) 1421 HNil)
1530 (Cons 1422 : HCons
1531 (HCons
1532 "textures/gothic_trim/km_arena1tower4" 1423 "textures/gothic_trim/km_arena1tower4"
1533 (HCons 1424 (HCons
1534 (CommonAttrs 1425 (CommonAttrs
@@ -1542,8 +1433,7 @@ sampleMaterial
1542 Nil 1433 Nil
1543 False 1434 False
1544 False 1435 False
1545 (Cons 1436 (StageAttrs
1546 (StageAttrs
1547 Nothing 1437 Nothing
1548 RGB_IdentityLighting 1438 RGB_IdentityLighting
1549 A_Identity 1439 A_Identity
@@ -1554,9 +1444,8 @@ sampleMaterial
1554 D_Lequal 1444 D_Lequal
1555 Nothing 1445 Nothing
1556 False 1446 False
1557 "Tex_3479185666") 1447 "Tex_3479185666"
1558 (Cons 1448 : StageAttrs
1559 (StageAttrs
1560 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1449 (Just (HCons B_DstColor (HCons B_Zero HNil)))
1561 RGB_IdentityLighting 1450 RGB_IdentityLighting
1562 A_Identity 1451 A_Identity
@@ -1567,12 +1456,11 @@ sampleMaterial
1567 D_Lequal 1456 D_Lequal
1568 Nothing 1457 Nothing
1569 False 1458 False
1570 "Tex_3226210144") 1459 "Tex_3226210144"
1571 Nil)) 1460 : Nil)
1572 False) 1461 False)
1573 HNil)) 1462 HNil)
1574 (Cons 1463 : HCons
1575 (HCons
1576 "textures/gothic_trim/km_arena1tower4_a" 1464 "textures/gothic_trim/km_arena1tower4_a"
1577 (HCons 1465 (HCons
1578 (CommonAttrs 1466 (CommonAttrs
@@ -1586,8 +1474,7 @@ sampleMaterial
1586 Nil 1474 Nil
1587 False 1475 False
1588 False 1476 False
1589 (Cons 1477 (StageAttrs
1590 (StageAttrs
1591 Nothing 1478 Nothing
1592 RGB_IdentityLighting 1479 RGB_IdentityLighting
1593 A_Identity 1480 A_Identity
@@ -1598,9 +1485,8 @@ sampleMaterial
1598 D_Lequal 1485 D_Lequal
1599 Nothing 1486 Nothing
1600 False 1487 False
1601 "Tex_3012001075") 1488 "Tex_3012001075"
1602 (Cons 1489 : StageAttrs
1603 (StageAttrs
1604 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1490 (Just (HCons B_DstColor (HCons B_Zero HNil)))
1605 RGB_IdentityLighting 1491 RGB_IdentityLighting
1606 A_Identity 1492 A_Identity
@@ -1611,12 +1497,11 @@ sampleMaterial
1611 D_Lequal 1497 D_Lequal
1612 Nothing 1498 Nothing
1613 False 1499 False
1614 "Tex_3226210144") 1500 "Tex_3226210144"
1615 Nil)) 1501 : Nil)
1616 False) 1502 False)
1617 HNil)) 1503 HNil)
1618 (Cons 1504 : HCons
1619 (HCons
1620 "textures/gothic_trim/metaldemonkillblock" 1505 "textures/gothic_trim/metaldemonkillblock"
1621 (HCons 1506 (HCons
1622 (CommonAttrs 1507 (CommonAttrs
@@ -1630,8 +1515,7 @@ sampleMaterial
1630 Nil 1515 Nil
1631 False 1516 False
1632 False 1517 False
1633 (Cons 1518 (StageAttrs
1634 (StageAttrs
1635 Nothing 1519 Nothing
1636 RGB_IdentityLighting 1520 RGB_IdentityLighting
1637 A_Identity 1521 A_Identity
@@ -1642,9 +1526,8 @@ sampleMaterial
1642 D_Lequal 1526 D_Lequal
1643 Nothing 1527 Nothing
1644 False 1528 False
1645 "Tex_1062467595") 1529 "Tex_1062467595"
1646 (Cons 1530 : StageAttrs
1647 (StageAttrs
1648 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1531 (Just (HCons B_DstColor (HCons B_Zero HNil)))
1649 RGB_IdentityLighting 1532 RGB_IdentityLighting
1650 A_Identity 1533 A_Identity
@@ -1655,12 +1538,11 @@ sampleMaterial
1655 D_Lequal 1538 D_Lequal
1656 Nothing 1539 Nothing
1657 False 1540 False
1658 "Tex_3226210144") 1541 "Tex_3226210144"
1659 Nil)) 1542 : Nil)
1660 False) 1543 False)
1661 HNil)) 1544 HNil)
1662 (Cons 1545 : HCons
1663 (HCons
1664 "textures/gothic_trim/metalsupport4b" 1546 "textures/gothic_trim/metalsupport4b"
1665 (HCons 1547 (HCons
1666 (CommonAttrs 1548 (CommonAttrs
@@ -1674,8 +1556,7 @@ sampleMaterial
1674 Nil 1556 Nil
1675 False 1557 False
1676 False 1558 False
1677 (Cons 1559 (StageAttrs
1678 (StageAttrs
1679 Nothing 1560 Nothing
1680 RGB_IdentityLighting 1561 RGB_IdentityLighting
1681 A_Identity 1562 A_Identity
@@ -1686,9 +1567,8 @@ sampleMaterial
1686 D_Lequal 1567 D_Lequal
1687 Nothing 1568 Nothing
1688 False 1569 False
1689 "Tex_3593923076") 1570 "Tex_3593923076"
1690 (Cons 1571 : StageAttrs
1691 (StageAttrs
1692 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1572 (Just (HCons B_DstColor (HCons B_Zero HNil)))
1693 RGB_IdentityLighting 1573 RGB_IdentityLighting
1694 A_Identity 1574 A_Identity
@@ -1699,12 +1579,11 @@ sampleMaterial
1699 D_Lequal 1579 D_Lequal
1700 Nothing 1580 Nothing
1701 False 1581 False
1702 "Tex_3226210144") 1582 "Tex_3226210144"
1703 Nil)) 1583 : Nil)
1704 False) 1584 False)
1705 HNil)) 1585 HNil)
1706 (Cons 1586 : HCons
1707 (HCons
1708 "textures/gothic_trim/metalsupsolid" 1587 "textures/gothic_trim/metalsupsolid"
1709 (HCons 1588 (HCons
1710 (CommonAttrs 1589 (CommonAttrs
@@ -1718,8 +1597,7 @@ sampleMaterial
1718 Nil 1597 Nil
1719 False 1598 False
1720 False 1599 False
1721 (Cons 1600 (StageAttrs
1722 (StageAttrs
1723 Nothing 1601 Nothing
1724 RGB_IdentityLighting 1602 RGB_IdentityLighting
1725 A_Identity 1603 A_Identity
@@ -1730,9 +1608,8 @@ sampleMaterial
1730 D_Lequal 1608 D_Lequal
1731 Nothing 1609 Nothing
1732 False 1610 False
1733 "Tex_2893650486") 1611 "Tex_2893650486"
1734 (Cons 1612 : StageAttrs
1735 (StageAttrs
1736 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1613 (Just (HCons B_DstColor (HCons B_Zero HNil)))
1737 RGB_IdentityLighting 1614 RGB_IdentityLighting
1738 A_Identity 1615 A_Identity
@@ -1743,12 +1620,11 @@ sampleMaterial
1743 D_Lequal 1620 D_Lequal
1744 Nothing 1621 Nothing
1745 False 1622 False
1746 "Tex_3226210144") 1623 "Tex_3226210144"
1747 Nil)) 1624 : Nil)
1748 False) 1625 False)
1749 HNil)) 1626 HNil)
1750 (Cons 1627 : HCons
1751 (HCons
1752 "textures/gothic_trim/pitted_rust" 1628 "textures/gothic_trim/pitted_rust"
1753 (HCons 1629 (HCons
1754 (CommonAttrs 1630 (CommonAttrs
@@ -1762,8 +1638,7 @@ sampleMaterial
1762 Nil 1638 Nil
1763 False 1639 False
1764 False 1640 False
1765 (Cons 1641 (StageAttrs
1766 (StageAttrs
1767 Nothing 1642 Nothing
1768 RGB_IdentityLighting 1643 RGB_IdentityLighting
1769 A_Identity 1644 A_Identity
@@ -1774,9 +1649,8 @@ sampleMaterial
1774 D_Lequal 1649 D_Lequal
1775 Nothing 1650 Nothing
1776 False 1651 False
1777 "Tex_1243894392") 1652 "Tex_1243894392"
1778 (Cons 1653 : StageAttrs
1779 (StageAttrs
1780 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1654 (Just (HCons B_DstColor (HCons B_Zero HNil)))
1781 RGB_IdentityLighting 1655 RGB_IdentityLighting
1782 A_Identity 1656 A_Identity
@@ -1787,12 +1661,11 @@ sampleMaterial
1787 D_Lequal 1661 D_Lequal
1788 Nothing 1662 Nothing
1789 False 1663 False
1790 "Tex_3226210144") 1664 "Tex_3226210144"
1791 Nil)) 1665 : Nil)
1792 False) 1666 False)
1793 HNil)) 1667 HNil)
1794 (Cons 1668 : HCons
1795 (HCons
1796 "textures/gothic_trim/pitted_rust2" 1669 "textures/gothic_trim/pitted_rust2"
1797 (HCons 1670 (HCons
1798 (CommonAttrs 1671 (CommonAttrs
@@ -1806,8 +1679,7 @@ sampleMaterial
1806 Nil 1679 Nil
1807 False 1680 False
1808 False 1681 False
1809 (Cons 1682 (StageAttrs
1810 (StageAttrs
1811 Nothing 1683 Nothing
1812 RGB_IdentityLighting 1684 RGB_IdentityLighting
1813 A_Identity 1685 A_Identity
@@ -1818,9 +1690,8 @@ sampleMaterial
1818 D_Lequal 1690 D_Lequal
1819 Nothing 1691 Nothing
1820 False 1692 False
1821 "Tex_2099456856") 1693 "Tex_2099456856"
1822 (Cons 1694 : StageAttrs
1823 (StageAttrs
1824 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1695 (Just (HCons B_DstColor (HCons B_Zero HNil)))
1825 RGB_IdentityLighting 1696 RGB_IdentityLighting
1826 A_Identity 1697 A_Identity
@@ -1831,12 +1702,11 @@ sampleMaterial
1831 D_Lequal 1702 D_Lequal
1832 Nothing 1703 Nothing
1833 False 1704 False
1834 "Tex_3226210144") 1705 "Tex_3226210144"
1835 Nil)) 1706 : Nil)
1836 False) 1707 False)
1837 HNil)) 1708 HNil)
1838 (Cons 1709 : HCons
1839 (HCons
1840 "textures/gothic_trim/pitted_rust2_trans" 1710 "textures/gothic_trim/pitted_rust2_trans"
1841 (HCons 1711 (HCons
1842 (CommonAttrs 1712 (CommonAttrs
@@ -1850,8 +1720,7 @@ sampleMaterial
1850 Nil 1720 Nil
1851 False 1721 False
1852 False 1722 False
1853 (Cons 1723 (StageAttrs
1854 (StageAttrs
1855 Nothing 1724 Nothing
1856 RGB_Identity 1725 RGB_Identity
1857 A_Identity 1726 A_Identity
@@ -1862,9 +1731,8 @@ sampleMaterial
1862 D_Lequal 1731 D_Lequal
1863 Nothing 1732 Nothing
1864 False 1733 False
1865 "Tex_511571587") 1734 "Tex_511571587"
1866 (Cons 1735 : StageAttrs
1867 (StageAttrs
1868 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1736 (Just (HCons B_DstColor (HCons B_Zero HNil)))
1869 RGB_Identity 1737 RGB_Identity
1870 A_Identity 1738 A_Identity
@@ -1875,12 +1743,11 @@ sampleMaterial
1875 D_Lequal 1743 D_Lequal
1876 Nothing 1744 Nothing
1877 False 1745 False
1878 "Tex_1910997598") 1746 "Tex_1910997598"
1879 Nil)) 1747 : Nil)
1880 False) 1748 False)
1881 HNil)) 1749 HNil)
1882 (Cons 1750 : HCons
1883 (HCons
1884 "textures/gothic_trim/pitted_rust3" 1751 "textures/gothic_trim/pitted_rust3"
1885 (HCons 1752 (HCons
1886 (CommonAttrs 1753 (CommonAttrs
@@ -1894,8 +1761,7 @@ sampleMaterial
1894 Nil 1761 Nil
1895 False 1762 False
1896 False 1763 False
1897 (Cons 1764 (StageAttrs
1898 (StageAttrs
1899 Nothing 1765 Nothing
1900 RGB_IdentityLighting 1766 RGB_IdentityLighting
1901 A_Identity 1767 A_Identity
@@ -1906,9 +1772,8 @@ sampleMaterial
1906 D_Lequal 1772 D_Lequal
1907 Nothing 1773 Nothing
1908 False 1774 False
1909 "Tex_3389727963") 1775 "Tex_3389727963"
1910 (Cons 1776 : StageAttrs
1911 (StageAttrs
1912 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1777 (Just (HCons B_DstColor (HCons B_Zero HNil)))
1913 RGB_IdentityLighting 1778 RGB_IdentityLighting
1914 A_Identity 1779 A_Identity
@@ -1919,12 +1784,11 @@ sampleMaterial
1919 D_Lequal 1784 D_Lequal
1920 Nothing 1785 Nothing
1921 False 1786 False
1922 "Tex_3226210144") 1787 "Tex_3226210144"
1923 Nil)) 1788 : Nil)
1924 False) 1789 False)
1925 HNil)) 1790 HNil)
1926 (Cons 1791 : HCons
1927 (HCons
1928 "textures/gothic_trim/skullsvertgray02b" 1792 "textures/gothic_trim/skullsvertgray02b"
1929 (HCons 1793 (HCons
1930 (CommonAttrs 1794 (CommonAttrs
@@ -1938,8 +1802,7 @@ sampleMaterial
1938 Nil 1802 Nil
1939 False 1803 False
1940 False 1804 False
1941 (Cons 1805 (StageAttrs
1942 (StageAttrs
1943 Nothing 1806 Nothing
1944 RGB_IdentityLighting 1807 RGB_IdentityLighting
1945 A_Identity 1808 A_Identity
@@ -1950,9 +1813,8 @@ sampleMaterial
1950 D_Lequal 1813 D_Lequal
1951 Nothing 1814 Nothing
1952 False 1815 False
1953 "Tex_2634868983") 1816 "Tex_2634868983"
1954 (Cons 1817 : StageAttrs
1955 (StageAttrs
1956 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1818 (Just (HCons B_DstColor (HCons B_Zero HNil)))
1957 RGB_IdentityLighting 1819 RGB_IdentityLighting
1958 A_Identity 1820 A_Identity
@@ -1963,12 +1825,11 @@ sampleMaterial
1963 D_Lequal 1825 D_Lequal
1964 Nothing 1826 Nothing
1965 False 1827 False
1966 "Tex_3226210144") 1828 "Tex_3226210144"
1967 Nil)) 1829 : Nil)
1968 False) 1830 False)
1969 HNil)) 1831 HNil)
1970 (Cons 1832 : HCons
1971 (HCons
1972 "textures/gothic_wall/iron01_e" 1833 "textures/gothic_wall/iron01_e"
1973 (HCons 1834 (HCons
1974 (CommonAttrs 1835 (CommonAttrs
@@ -1982,8 +1843,7 @@ sampleMaterial
1982 Nil 1843 Nil
1983 False 1844 False
1984 False 1845 False
1985 (Cons 1846 (StageAttrs
1986 (StageAttrs
1987 Nothing 1847 Nothing
1988 RGB_IdentityLighting 1848 RGB_IdentityLighting
1989 A_Identity 1849 A_Identity
@@ -1994,9 +1854,8 @@ sampleMaterial
1994 D_Lequal 1854 D_Lequal
1995 Nothing 1855 Nothing
1996 False 1856 False
1997 "Tex_2432583247") 1857 "Tex_2432583247"
1998 (Cons 1858 : StageAttrs
1999 (StageAttrs
2000 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1859 (Just (HCons B_DstColor (HCons B_Zero HNil)))
2001 RGB_IdentityLighting 1860 RGB_IdentityLighting
2002 A_Identity 1861 A_Identity
@@ -2007,12 +1866,11 @@ sampleMaterial
2007 D_Lequal 1866 D_Lequal
2008 Nothing 1867 Nothing
2009 False 1868 False
2010 "Tex_3226210144") 1869 "Tex_3226210144"
2011 Nil)) 1870 : Nil)
2012 False) 1871 False)
2013 HNil)) 1872 HNil)
2014 (Cons 1873 : HCons
2015 (HCons
2016 "textures/gothic_wall/iron01_ntech3" 1874 "textures/gothic_wall/iron01_ntech3"
2017 (HCons 1875 (HCons
2018 (CommonAttrs 1876 (CommonAttrs
@@ -2026,8 +1884,7 @@ sampleMaterial
2026 Nil 1884 Nil
2027 False 1885 False
2028 False 1886 False
2029 (Cons 1887 (StageAttrs
2030 (StageAttrs
2031 Nothing 1888 Nothing
2032 RGB_IdentityLighting 1889 RGB_IdentityLighting
2033 A_Identity 1890 A_Identity
@@ -2038,9 +1895,8 @@ sampleMaterial
2038 D_Lequal 1895 D_Lequal
2039 Nothing 1896 Nothing
2040 False 1897 False
2041 "Tex_442868841") 1898 "Tex_442868841"
2042 (Cons 1899 : StageAttrs
2043 (StageAttrs
2044 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1900 (Just (HCons B_DstColor (HCons B_Zero HNil)))
2045 RGB_IdentityLighting 1901 RGB_IdentityLighting
2046 A_Identity 1902 A_Identity
@@ -2051,12 +1907,11 @@ sampleMaterial
2051 D_Lequal 1907 D_Lequal
2052 Nothing 1908 Nothing
2053 False 1909 False
2054 "Tex_3226210144") 1910 "Tex_3226210144"
2055 Nil)) 1911 : Nil)
2056 False) 1912 False)
2057 HNil)) 1913 HNil)
2058 (Cons 1914 : HCons
2059 (HCons
2060 "textures/gothic_wall/skull4" 1915 "textures/gothic_wall/skull4"
2061 (HCons 1916 (HCons
2062 (CommonAttrs 1917 (CommonAttrs
@@ -2070,8 +1925,7 @@ sampleMaterial
2070 Nil 1925 Nil
2071 False 1926 False
2072 False 1927 False
2073 (Cons 1928 (StageAttrs
2074 (StageAttrs
2075 Nothing 1929 Nothing
2076 RGB_IdentityLighting 1930 RGB_IdentityLighting
2077 A_Identity 1931 A_Identity
@@ -2082,9 +1936,8 @@ sampleMaterial
2082 D_Lequal 1936 D_Lequal
2083 Nothing 1937 Nothing
2084 False 1938 False
2085 "Tex_2239853403") 1939 "Tex_2239853403"
2086 (Cons 1940 : StageAttrs
2087 (StageAttrs
2088 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1941 (Just (HCons B_DstColor (HCons B_Zero HNil)))
2089 RGB_IdentityLighting 1942 RGB_IdentityLighting
2090 A_Identity 1943 A_Identity
@@ -2095,12 +1948,11 @@ sampleMaterial
2095 D_Lequal 1948 D_Lequal
2096 Nothing 1949 Nothing
2097 False 1950 False
2098 "Tex_3226210144") 1951 "Tex_3226210144"
2099 Nil)) 1952 : Nil)
2100 False) 1953 False)
2101 HNil)) 1954 HNil)
2102 (Cons 1955 : HCons
2103 (HCons
2104 "textures/gothic_wall/slateroofc" 1956 "textures/gothic_wall/slateroofc"
2105 (HCons 1957 (HCons
2106 (CommonAttrs 1958 (CommonAttrs
@@ -2114,8 +1966,7 @@ sampleMaterial
2114 Nil 1966 Nil
2115 False 1967 False
2116 False 1968 False
2117 (Cons 1969 (StageAttrs
2118 (StageAttrs
2119 Nothing 1970 Nothing
2120 RGB_IdentityLighting 1971 RGB_IdentityLighting
2121 A_Identity 1972 A_Identity
@@ -2126,9 +1977,8 @@ sampleMaterial
2126 D_Lequal 1977 D_Lequal
2127 Nothing 1978 Nothing
2128 False 1979 False
2129 "Tex_2490648334") 1980 "Tex_2490648334"
2130 (Cons 1981 : StageAttrs
2131 (StageAttrs
2132 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1982 (Just (HCons B_DstColor (HCons B_Zero HNil)))
2133 RGB_IdentityLighting 1983 RGB_IdentityLighting
2134 A_Identity 1984 A_Identity
@@ -2139,12 +1989,11 @@ sampleMaterial
2139 D_Lequal 1989 D_Lequal
2140 Nothing 1990 Nothing
2141 False 1991 False
2142 "Tex_3226210144") 1992 "Tex_3226210144"
2143 Nil)) 1993 : Nil)
2144 False) 1994 False)
2145 HNil)) 1995 HNil)
2146 (Cons 1996 : HCons
2147 (HCons
2148 "textures/gothic_wall/supportborder_blue_b" 1997 "textures/gothic_wall/supportborder_blue_b"
2149 (HCons 1998 (HCons
2150 (CommonAttrs 1999 (CommonAttrs
@@ -2158,8 +2007,7 @@ sampleMaterial
2158 Nil 2007 Nil
2159 False 2008 False
2160 False 2009 False
2161 (Cons 2010 (StageAttrs
2162 (StageAttrs
2163 Nothing 2011 Nothing
2164 RGB_IdentityLighting 2012 RGB_IdentityLighting
2165 A_Identity 2013 A_Identity
@@ -2170,9 +2018,8 @@ sampleMaterial
2170 D_Lequal 2018 D_Lequal
2171 Nothing 2019 Nothing
2172 False 2020 False
2173 "Tex_564811775") 2021 "Tex_564811775"
2174 (Cons 2022 : StageAttrs
2175 (StageAttrs
2176 (Just (HCons B_DstColor (HCons B_Zero HNil))) 2023 (Just (HCons B_DstColor (HCons B_Zero HNil)))
2177 RGB_IdentityLighting 2024 RGB_IdentityLighting
2178 A_Identity 2025 A_Identity
@@ -2183,12 +2030,11 @@ sampleMaterial
2183 D_Lequal 2030 D_Lequal
2184 Nothing 2031 Nothing
2185 False 2032 False
2186 "Tex_3226210144") 2033 "Tex_3226210144"
2187 Nil)) 2034 : Nil)
2188 False) 2035 False)
2189 HNil)) 2036 HNil)
2190 (Cons 2037 : HCons
2191 (HCons
2192 "textures/gothic_wall/supportborder_blue_c" 2038 "textures/gothic_wall/supportborder_blue_c"
2193 (HCons 2039 (HCons
2194 (CommonAttrs 2040 (CommonAttrs
@@ -2202,8 +2048,7 @@ sampleMaterial
2202 Nil 2048 Nil
2203 False 2049 False
2204 False 2050 False
2205 (Cons 2051 (StageAttrs
2206 (StageAttrs
2207 Nothing 2052 Nothing
2208 RGB_IdentityLighting 2053 RGB_IdentityLighting
2209 A_Identity 2054 A_Identity
@@ -2214,9 +2059,8 @@ sampleMaterial
2214 D_Lequal 2059 D_Lequal
2215 Nothing 2060 Nothing
2216 False 2061 False
2217 "Tex_2525124732") 2062 "Tex_2525124732"
2218 (Cons 2063 : StageAttrs
2219 (StageAttrs
2220 (Just (HCons B_DstColor (HCons B_Zero HNil))) 2064 (Just (HCons B_DstColor (HCons B_Zero HNil)))
2221 RGB_IdentityLighting 2065 RGB_IdentityLighting
2222 A_Identity 2066 A_Identity
@@ -2227,11 +2071,11 @@ sampleMaterial
2227 D_Lequal 2071 D_Lequal
2228 Nothing 2072 Nothing
2229 False 2073 False
2230 "Tex_3226210144") 2074 "Tex_3226210144"
2231 Nil)) 2075 : Nil)
2232 False) 2076 False)
2233 HNil)) 2077 HNil)
2234 Nil)))))))))))))))))))))))))))))))))))))))))))))))))) 2078 : Nil)
2235main is not found 2079main is not found
2236------------ trace 2080------------ trace
2237sampleMaterial :: List (String, CommonAttrs) 2081sampleMaterial :: List (String, CommonAttrs)
diff --git a/testdata/framebuffer02.reject.out b/testdata/framebuffer02.reject.out
index 458214b0..b733b615 100644
--- a/testdata/framebuffer02.reject.out
+++ b/testdata/framebuffer02.reject.out
@@ -32,11 +32,11 @@ testdata/framebuffer02.reject.lc 2:17-5:30
32 Type 32 Type
33 ImageKind 33 ImageKind
34 GetImageKind 34 GetImageKind
35 ('Cons 35 (:
36 (Image 1 ('Color (VecScalar 4 Float))) 36 (Image 1 ('Color (VecScalar 4 Float)))
37 ('Cons 37 (:
38 (Image 2 ('Color (VecScalar 4 Float))) 38 (Image 2 ('Color (VecScalar 4 Float)))
39 ('Cons (Image 1 ('Color (VecScalar 1 Float))) 'Nil)))) 39 (: (Image 1 ('Color (VecScalar 1 Float))) 'Nil))))
40testdata/framebuffer02.reject.lc 2:29-5:30 40testdata/framebuffer02.reject.lc 2:29-5:30
41 (Image 1 ('Color (VecScalar 4 Float)), Image 41 (Image 1 ('Color (VecScalar 4 Float)), Image
42 2 42 2
diff --git a/testdata/language-features/basic-list/list01.out b/testdata/language-features/basic-list/list01.out
index 621aa15a..0172a5e3 100644
--- a/testdata/language-features/basic-list/list01.out
+++ b/testdata/language-features/basic-list/list01.out
@@ -1,9 +1,7 @@
1------------ desugared source code 1------------ desugared source code
2value1 = _rhs Nil 2value1 = _rhs Nil
3value2 3value2 = _rhs (fromInt 1 : fromInt 2 : fromInt 3 : fromInt 4 : Nil)
4 = _rhs 4value3 = _rhs ('h' : 'e' : 'l' : 'l' : 'o' : Nil)
5 (Cons (fromInt 1) (Cons (fromInt 2) (Cons (fromInt 3) (Cons (fromInt 4) Nil))))
6value3 = _rhs (Cons 'h' (Cons 'e' (Cons 'l' (Cons 'l' (Cons 'o' Nil)))))
7main is not found 5main is not found
8------------ trace 6------------ trace
9value1 :: forall a . List a 7value1 :: forall a . List a
diff --git a/testdata/language-features/basic-list/list02.out b/testdata/language-features/basic-list/list02.out
index 665e8b7d..74e7428a 100644
--- a/testdata/language-features/basic-list/list02.out
+++ b/testdata/language-features/basic-list/list02.out
@@ -1,9 +1,7 @@
1------------ desugared source code 1------------ desugared source code
2value1 = _rhs Nil 2value1 = _rhs Nil
3value2 3value2 = _rhs (fromInt 1 : fromInt 2 : fromInt 3 : fromInt 4 : Nil)
4 = _rhs 4value3 = _rhs ('h' : 'e' : 'l' : 'l' : 'o' : Nil)
5 (Cons (fromInt 1) (Cons (fromInt 2) (Cons (fromInt 3) (Cons (fromInt 4) Nil))))
6value3 = _rhs (Cons 'h' (Cons 'e' (Cons 'l' (Cons 'l' (Cons 'o' Nil)))))
7main is not found 5main is not found
8------------ trace 6------------ trace
9value1 :: forall a . List a 7value1 :: forall a . List a
diff --git a/testdata/language-features/basic-list/list08.out b/testdata/language-features/basic-list/list08.out
index 66a0526e..9f5d3514 100644
--- a/testdata/language-features/basic-list/list08.out
+++ b/testdata/language-features/basic-list/list08.out
@@ -1,5 +1,5 @@
1------------ desugared source code 1------------ desugared source code
2value = _rhs (Cons (fromInt 1) (Cons 1.2 Nil)) 2value = _rhs (fromInt 1 : 1.2 : Nil)
3main is not found 3main is not found
4------------ trace 4------------ trace
5value :: List Float 5value :: List Float
diff --git a/testdata/language-features/basic-list/list09.out b/testdata/language-features/basic-list/list09.out
index 7b7e8d99..24260675 100644
--- a/testdata/language-features/basic-list/list09.out
+++ b/testdata/language-features/basic-list/list09.out
@@ -1,5 +1,5 @@
1------------ desugared source code 1------------ desugared source code
2value = _rhs (Cons (fromInt 1) (Cons 1.2 Nil) :: List Float) 2value = _rhs (fromInt 1 : 1.2 : Nil :: List Float)
3main is not found 3main is not found
4------------ trace 4------------ trace
5value :: List Float 5value :: List Float
diff --git a/testdata/language-features/basic-list/listcomp01.out b/testdata/language-features/basic-list/listcomp01.out
index 56aeb025..99b023cd 100644
--- a/testdata/language-features/basic-list/listcomp01.out
+++ b/testdata/language-features/basic-list/listcomp01.out
@@ -1,9 +1,5 @@
1------------ desugared source code 1------------ desugared source code
2value 2value = _rhs (concatMap \_ -> HNil : Nil (HNil : HNil : HNil : HNil : Nil))
3 = _rhs
4 (concatMap
5 \_ -> Cons HNil Nil
6 (Cons HNil (Cons HNil (Cons HNil (Cons HNil Nil)))))
7main is not found 3main is not found
8------------ trace 4------------ trace
9value :: List () 5value :: List ()
diff --git a/testdata/language-features/basic-list/listcomp02.out b/testdata/language-features/basic-list/listcomp02.out
index dfd424a4..80550f51 100644
--- a/testdata/language-features/basic-list/listcomp02.out
+++ b/testdata/language-features/basic-list/listcomp02.out
@@ -1,6 +1,6 @@
1------------ desugared source code 1------------ desugared source code
2l = _rhs (Cons HNil (Cons HNil (Cons HNil (Cons HNil Nil)))) 2l = _rhs (HNil : HNil : HNil : HNil : Nil)
3value = _rhs (concatMap \(a :: _) -> Cons a Nil l) 3value = _rhs (concatMap \(a :: _) -> a : Nil l)
4main is not found 4main is not found
5------------ trace 5------------ trace
6l :: List () 6l :: List ()
diff --git a/testdata/language-features/basic-list/listcomp03.out b/testdata/language-features/basic-list/listcomp03.out
index 4fce997f..c77ff572 100644
--- a/testdata/language-features/basic-list/listcomp03.out
+++ b/testdata/language-features/basic-list/listcomp03.out
@@ -2,8 +2,8 @@
2value 2value
3 = _rhs 3 = _rhs
4 (concatMap 4 (concatMap
5 \_ -> primIfThenElse False (Cons HNil Nil) Nil 5 \_ -> primIfThenElse False (HNil : Nil) Nil
6 (Cons HNil (Cons HNil (Cons HNil (Cons HNil Nil))))) 6 (HNil : HNil : HNil : HNil : Nil))
7main is not found 7main is not found
8------------ trace 8------------ trace
9value :: List () 9value :: List ()
diff --git a/testdata/language-features/basic-list/listcomp04.out b/testdata/language-features/basic-list/listcomp04.out
index 05e9c859..6894cd99 100644
--- a/testdata/language-features/basic-list/listcomp04.out
+++ b/testdata/language-features/basic-list/listcomp04.out
@@ -1,6 +1,6 @@
1------------ desugared source code 1------------ desugared source code
2l = _rhs (Cons HNil (Cons HNil (Cons HNil (Cons HNil Nil)))) 2l = _rhs (HNil : HNil : HNil : HNil : Nil)
3value = _rhs (concatMap \_ -> concatMap \_ -> Cons HNil Nil l l) 3value = _rhs (concatMap \_ -> concatMap \_ -> HNil : Nil l l)
4main is not found 4main is not found
5------------ trace 5------------ trace
6l :: List () 6l :: List ()
diff --git a/testdata/language-features/basic-list/listcomp05.out b/testdata/language-features/basic-list/listcomp05.out
index c345731c..a1b49e8d 100644
--- a/testdata/language-features/basic-list/listcomp05.out
+++ b/testdata/language-features/basic-list/listcomp05.out
@@ -2,8 +2,8 @@
2value 2value
3 = _rhs 3 = _rhs
4 (concatMap 4 (concatMap
5 \_ (a := _rhs HNil) (b := _rhs ((\(c :: _) -> c) a)) -> Cons b Nil 5 \_ (a := _rhs HNil) (b := _rhs ((\(c :: _) -> c) a)) -> b : Nil
6 (Cons HNil (Cons HNil Nil))) 6 (HNil : HNil : Nil))
7main is not found 7main is not found
8------------ trace 8------------ trace
9value :: List () 9value :: List ()
diff --git a/testdata/language-features/basic-list/listcomp06.out b/testdata/language-features/basic-list/listcomp06.out
index c06f6155..a79e0ce0 100644
--- a/testdata/language-features/basic-list/listcomp06.out
+++ b/testdata/language-features/basic-list/listcomp06.out
@@ -4,17 +4,17 @@ value1
4 (concatMap 4 (concatMap
5 \_ (a := _rhs HNil) (b := _rhs ((\(c :: _) -> c) a)) -> primIfThenElse 5 \_ (a := _rhs HNil) (b := _rhs ((\(c :: _) -> c) a)) -> primIfThenElse
6 True 6 True
7 (Cons b Nil) 7 (b : Nil)
8 Nil 8 Nil
9 (Cons HNil (Cons HNil Nil))) 9 (HNil : HNil : Nil))
10value2 10value2
11 = _rhs 11 = _rhs
12 (concatMap 12 (concatMap
13 \_ -> primIfThenElse 13 \_ -> primIfThenElse
14 True 14 True
15 \(a := _rhs HNil) (b := _rhs ((\(c :: _) -> c) a)) -> Cons b Nil 15 \(a := _rhs HNil) (b := _rhs ((\(c :: _) -> c) a)) -> b : Nil
16 Nil 16 Nil
17 (Cons HNil (Cons HNil Nil))) 17 (HNil : HNil : Nil))
18main is not found 18main is not found
19------------ trace 19------------ trace
20value1 :: List () 20value1 :: List ()
diff --git a/testdata/language-features/basic-list/listcomp07.out b/testdata/language-features/basic-list/listcomp07.out
index 617c9b61..8cd1a663 100644
--- a/testdata/language-features/basic-list/listcomp07.out
+++ b/testdata/language-features/basic-list/listcomp07.out
@@ -4,25 +4,25 @@ value1
4 (concatMap 4 (concatMap
5 \_ (a := _rhs HNil) (b := _rhs ((\(c :: _) -> c) a)) -> primIfThenElse 5 \_ (a := _rhs HNil) (b := _rhs ((\(c :: _) -> c) a)) -> primIfThenElse
6 True 6 True
7 \(d := _rhs b) (e := _rhs ((\(f :: _) -> f) d)) -> Cons b Nil 7 \(d := _rhs b) (e := _rhs ((\(f :: _) -> f) d)) -> b : Nil
8 Nil 8 Nil
9 (Cons HNil (Cons HNil Nil))) 9 (HNil : HNil : Nil))
10value2 10value2
11 = _rhs 11 = _rhs
12 (concatMap 12 (concatMap
13 \_ (a := _rhs HNil) (b := _rhs ((\(c :: _) -> c) a)) -> primIfThenElse 13 \_ (a := _rhs HNil) (b := _rhs ((\(c :: _) -> c) a)) -> primIfThenElse
14 True 14 True
15 \(d := _rhs b) (e := _rhs ((\(f :: _) -> f) d)) -> Cons b Nil 15 \(d := _rhs b) (e := _rhs ((\(f :: _) -> f) d)) -> b : Nil
16 Nil 16 Nil
17 (Cons HNil (Cons HNil Nil))) 17 (HNil : HNil : Nil))
18value3 18value3
19 = _rhs 19 = _rhs
20 (concatMap 20 (concatMap
21 \_ (a := _rhs HNil) (b := _rhs ((\(c :: _) -> c) a)) -> primIfThenElse 21 \_ (a := _rhs HNil) (b := _rhs ((\(c :: _) -> c) a)) -> primIfThenElse
22 True 22 True
23 \(d := _rhs b) (e := _rhs ((\(f :: _) -> f) d)) -> Cons b Nil 23 \(d := _rhs b) (e := _rhs ((\(f :: _) -> f) d)) -> b : Nil
24 Nil 24 Nil
25 (Cons HNil (Cons HNil Nil))) 25 (HNil : HNil : Nil))
26main is not found 26main is not found
27------------ trace 27------------ trace
28value1 :: List () 28value1 :: List ()
diff --git a/testdata/language-features/basic-list/listcomp09.out b/testdata/language-features/basic-list/listcomp09.out
index 60e73fcc..ce95bbad 100644
--- a/testdata/language-features/basic-list/listcomp09.out
+++ b/testdata/language-features/basic-list/listcomp09.out
@@ -1,7 +1,7 @@
1------------ desugared source code 1------------ desugared source code
2value1 2value1
3 = _rhs 3 = _rhs
4 (concatMap \_ -> Cons \(a :: _) -> hlistNilCase (_ :: _) "Hello" a Nil Nil) 4 (concatMap \_ -> (\(a :: _) -> hlistNilCase (_ :: _) "Hello" a) : Nil Nil)
5main is not found 5main is not found
6------------ trace 6------------ trace
7value1 :: Type => List (() -> String) 7value1 :: Type => List (() -> String)
diff --git a/testdata/language-features/basic-values/data03.reject.out b/testdata/language-features/basic-values/data03.reject.out
index 38c02960..2769951d 100644
--- a/testdata/language-features/basic-values/data03.reject.out
+++ b/testdata/language-features/basic-values/data03.reject.out
@@ -1,3 +1,3 @@
1testdata/language-features/basic-values/data03.reject.lc:1:10: 1testdata/language-features/basic-values/data03.reject.lc:1:10:
2unexpected 'd' 2unexpected 'd'
3expecting uppercase ident 3expecting '(' or uppercase ident \ No newline at end of file
diff --git a/testdata/performance/Material.out b/testdata/performance/Material.out
index f9a7e3c1..69d8a209 100644
--- a/testdata/performance/Material.out
+++ b/testdata/performance/Material.out
@@ -105,7 +105,7 @@ data DepthFunction :: Type where
105 D_Lequal :: DepthFunction 105 D_Lequal :: DepthFunction
106data StageAttrs :: Type where 106data StageAttrs :: Type where
107 StageAttrs 107 StageAttrs
108 :: Maybe (HList ('Cons Blending' ('Cons Blending' 'Nil))) 108 :: Maybe (HList (Blending' : Blending' : 'Nil))
109 -> RGBGen 109 -> RGBGen
110 -> AlphaGen 110 -> AlphaGen
111 -> TCGen 111 -> TCGen
diff --git a/testdata/performance/SampleMaterial.out b/testdata/performance/SampleMaterial.out
index 17ed027d..84692f2b 100644
--- a/testdata/performance/SampleMaterial.out
+++ b/testdata/performance/SampleMaterial.out
@@ -1,8 +1,7 @@
1------------ desugared source code 1------------ desugared source code
2sampleMaterial 2sampleMaterial
3 = _rhs 3 = _rhs
4 (Cons 4 (HCons
5 (HCons
6 "textures/gothic_block/blocks11b" 5 "textures/gothic_block/blocks11b"
7 (HCons 6 (HCons
8 (CommonAttrs 7 (CommonAttrs
@@ -16,8 +15,7 @@ sampleMaterial
16 Nil 15 Nil
17 False 16 False
18 False 17 False
19 (Cons 18 (StageAttrs
20 (StageAttrs
21 Nothing 19 Nothing
22 RGB_IdentityLighting 20 RGB_IdentityLighting
23 A_Identity 21 A_Identity
@@ -28,9 +26,8 @@ sampleMaterial
28 D_Lequal 26 D_Lequal
29 Nothing 27 Nothing
30 False 28 False
31 "Tex_4288602201") 29 "Tex_4288602201"
32 (Cons 30 : StageAttrs
33 (StageAttrs
34 (Just (HCons B_DstColor (HCons B_Zero HNil))) 31 (Just (HCons B_DstColor (HCons B_Zero HNil)))
35 RGB_IdentityLighting 32 RGB_IdentityLighting
36 A_Identity 33 A_Identity
@@ -41,12 +38,11 @@ sampleMaterial
41 D_Lequal 38 D_Lequal
42 Nothing 39 Nothing
43 False 40 False
44 "Tex_3226210144") 41 "Tex_3226210144"
45 Nil)) 42 : Nil)
46 False) 43 False)
47 HNil)) 44 HNil)
48 (Cons 45 : HCons
49 (HCons
50 "textures/gothic_block/blocks15" 46 "textures/gothic_block/blocks15"
51 (HCons 47 (HCons
52 (CommonAttrs 48 (CommonAttrs
@@ -60,8 +56,7 @@ sampleMaterial
60 Nil 56 Nil
61 False 57 False
62 False 58 False
63 (Cons 59 (StageAttrs
64 (StageAttrs
65 Nothing 60 Nothing
66 RGB_IdentityLighting 61 RGB_IdentityLighting
67 A_Identity 62 A_Identity
@@ -72,9 +67,8 @@ sampleMaterial
72 D_Lequal 67 D_Lequal
73 Nothing 68 Nothing
74 False 69 False
75 "Tex_2523116863") 70 "Tex_2523116863"
76 (Cons 71 : StageAttrs
77 (StageAttrs
78 (Just (HCons B_DstColor (HCons B_Zero HNil))) 72 (Just (HCons B_DstColor (HCons B_Zero HNil)))
79 RGB_IdentityLighting 73 RGB_IdentityLighting
80 A_Identity 74 A_Identity
@@ -85,12 +79,11 @@ sampleMaterial
85 D_Lequal 79 D_Lequal
86 Nothing 80 Nothing
87 False 81 False
88 "Tex_3226210144") 82 "Tex_3226210144"
89 Nil)) 83 : Nil)
90 False) 84 False)
91 HNil)) 85 HNil)
92 (Cons 86 : HCons
93 (HCons
94 "textures/gothic_block/blocks18b" 87 "textures/gothic_block/blocks18b"
95 (HCons 88 (HCons
96 (CommonAttrs 89 (CommonAttrs
@@ -104,8 +97,7 @@ sampleMaterial
104 Nil 97 Nil
105 False 98 False
106 False 99 False
107 (Cons 100 (StageAttrs
108 (StageAttrs
109 Nothing 101 Nothing
110 RGB_IdentityLighting 102 RGB_IdentityLighting
111 A_Identity 103 A_Identity
@@ -116,9 +108,8 @@ sampleMaterial
116 D_Lequal 108 D_Lequal
117 Nothing 109 Nothing
118 False 110 False
119 "Tex_2639119078") 111 "Tex_2639119078"
120 (Cons 112 : StageAttrs
121 (StageAttrs
122 (Just (HCons B_DstColor (HCons B_Zero HNil))) 113 (Just (HCons B_DstColor (HCons B_Zero HNil)))
123 RGB_IdentityLighting 114 RGB_IdentityLighting
124 A_Identity 115 A_Identity
@@ -129,12 +120,11 @@ sampleMaterial
129 D_Lequal 120 D_Lequal
130 Nothing 121 Nothing
131 False 122 False
132 "Tex_3226210144") 123 "Tex_3226210144"
133 Nil)) 124 : Nil)
134 False) 125 False)
135 HNil)) 126 HNil)
136 (Cons 127 : HCons
137 (HCons
138 "textures/gothic_block/blocks18c_3" 128 "textures/gothic_block/blocks18c_3"
139 (HCons 129 (HCons
140 (CommonAttrs 130 (CommonAttrs
@@ -148,8 +138,7 @@ sampleMaterial
148 Nil 138 Nil
149 False 139 False
150 False 140 False
151 (Cons 141 (StageAttrs
152 (StageAttrs
153 Nothing 142 Nothing
154 RGB_IdentityLighting 143 RGB_IdentityLighting
155 A_Identity 144 A_Identity
@@ -160,9 +149,8 @@ sampleMaterial
160 D_Lequal 149 D_Lequal
161 Nothing 150 Nothing
162 False 151 False
163 "Tex_3939430064") 152 "Tex_3939430064"
164 (Cons 153 : StageAttrs
165 (StageAttrs
166 (Just (HCons B_DstColor (HCons B_Zero HNil))) 154 (Just (HCons B_DstColor (HCons B_Zero HNil)))
167 RGB_IdentityLighting 155 RGB_IdentityLighting
168 A_Identity 156 A_Identity
@@ -173,12 +161,11 @@ sampleMaterial
173 D_Lequal 161 D_Lequal
174 Nothing 162 Nothing
175 False 163 False
176 "Tex_3226210144") 164 "Tex_3226210144"
177 Nil)) 165 : Nil)
178 False) 166 False)
179 HNil)) 167 HNil)
180 (Cons 168 : HCons
181 (HCons
182 "textures/gothic_block/demon_block15fx" 169 "textures/gothic_block/demon_block15fx"
183 (HCons 170 (HCons
184 (CommonAttrs 171 (CommonAttrs
@@ -192,23 +179,19 @@ sampleMaterial
192 Nil 179 Nil
193 False 180 False
194 False 181 False
195 (Cons 182 (StageAttrs
196 (StageAttrs
197 Nothing 183 Nothing
198 RGB_Identity 184 RGB_Identity
199 A_Identity 185 A_Identity
200 TG_Base 186 TG_Base
201 (Cons 187 (TM_Scroll 0.0 1.0 : TM_Turb 0.0 0.25 0.0 1.6 : TM_Scale 4.0 4.0 : Nil)
202 (TM_Scroll 0.0 1.0)
203 (Cons (TM_Turb 0.0 0.25 0.0 1.6) (Cons (TM_Scale 4.0 4.0) Nil)))
204 (ST_Map "textures/sfx/firegorre.tga") 188 (ST_Map "textures/sfx/firegorre.tga")
205 True 189 True
206 D_Lequal 190 D_Lequal
207 Nothing 191 Nothing
208 False 192 False
209 "Tex_47037129") 193 "Tex_47037129"
210 (Cons 194 : StageAttrs
211 (StageAttrs
212 (Just (HCons B_SrcAlpha (HCons B_OneMinusSrcAlpha HNil))) 195 (Just (HCons B_SrcAlpha (HCons B_OneMinusSrcAlpha HNil)))
213 RGB_Identity 196 RGB_Identity
214 A_Identity 197 A_Identity
@@ -219,9 +202,8 @@ sampleMaterial
219 D_Lequal 202 D_Lequal
220 Nothing 203 Nothing
221 False 204 False
222 "Tex_3562558025") 205 "Tex_3562558025"
223 (Cons 206 : StageAttrs
224 (StageAttrs
225 (Just (HCons B_DstColor (HCons B_OneMinusDstAlpha HNil))) 207 (Just (HCons B_DstColor (HCons B_OneMinusDstAlpha HNil)))
226 RGB_Identity 208 RGB_Identity
227 A_Identity 209 A_Identity
@@ -232,12 +214,11 @@ sampleMaterial
232 D_Lequal 214 D_Lequal
233 Nothing 215 Nothing
234 False 216 False
235 "Tex_2065974340") 217 "Tex_2065974340"
236 Nil))) 218 : Nil)
237 False) 219 False)
238 HNil)) 220 HNil)
239 (Cons 221 : HCons
240 (HCons
241 "textures/gothic_block/killblock" 222 "textures/gothic_block/killblock"
242 (HCons 223 (HCons
243 (CommonAttrs 224 (CommonAttrs
@@ -251,8 +232,7 @@ sampleMaterial
251 Nil 232 Nil
252 False 233 False
253 False 234 False
254 (Cons 235 (StageAttrs
255 (StageAttrs
256 Nothing 236 Nothing
257 RGB_IdentityLighting 237 RGB_IdentityLighting
258 A_Identity 238 A_Identity
@@ -263,9 +243,8 @@ sampleMaterial
263 D_Lequal 243 D_Lequal
264 Nothing 244 Nothing
265 False 245 False
266 "Tex_3647563961") 246 "Tex_3647563961"
267 (Cons 247 : StageAttrs
268 (StageAttrs
269 (Just (HCons B_DstColor (HCons B_Zero HNil))) 248 (Just (HCons B_DstColor (HCons B_Zero HNil)))
270 RGB_IdentityLighting 249 RGB_IdentityLighting
271 A_Identity 250 A_Identity
@@ -276,12 +255,11 @@ sampleMaterial
276 D_Lequal 255 D_Lequal
277 Nothing 256 Nothing
278 False 257 False
279 "Tex_3226210144") 258 "Tex_3226210144"
280 Nil)) 259 : Nil)
281 False) 260 False)
282 HNil)) 261 HNil)
283 (Cons 262 : HCons
284 (HCons
285 "textures/gothic_block/killblock_i" 263 "textures/gothic_block/killblock_i"
286 (HCons 264 (HCons
287 (CommonAttrs 265 (CommonAttrs
@@ -295,8 +273,7 @@ sampleMaterial
295 Nil 273 Nil
296 False 274 False
297 False 275 False
298 (Cons 276 (StageAttrs
299 (StageAttrs
300 Nothing 277 Nothing
301 RGB_IdentityLighting 278 RGB_IdentityLighting
302 A_Identity 279 A_Identity
@@ -307,9 +284,8 @@ sampleMaterial
307 D_Lequal 284 D_Lequal
308 Nothing 285 Nothing
309 False 286 False
310 "Tex_209322640") 287 "Tex_209322640"
311 (Cons 288 : StageAttrs
312 (StageAttrs
313 (Just (HCons B_DstColor (HCons B_Zero HNil))) 289 (Just (HCons B_DstColor (HCons B_Zero HNil)))
314 RGB_IdentityLighting 290 RGB_IdentityLighting
315 A_Identity 291 A_Identity
@@ -320,12 +296,11 @@ sampleMaterial
320 D_Lequal 296 D_Lequal
321 Nothing 297 Nothing
322 False 298 False
323 "Tex_3226210144") 299 "Tex_3226210144"
324 Nil)) 300 : Nil)
325 False) 301 False)
326 HNil)) 302 HNil)
327 (Cons 303 : HCons
328 (HCons
329 "textures/gothic_block/killblock_i4" 304 "textures/gothic_block/killblock_i4"
330 (HCons 305 (HCons
331 (CommonAttrs 306 (CommonAttrs
@@ -339,8 +314,7 @@ sampleMaterial
339 Nil 314 Nil
340 False 315 False
341 False 316 False
342 (Cons 317 (StageAttrs
343 (StageAttrs
344 Nothing 318 Nothing
345 RGB_IdentityLighting 319 RGB_IdentityLighting
346 A_Identity 320 A_Identity
@@ -351,9 +325,8 @@ sampleMaterial
351 D_Lequal 325 D_Lequal
352 Nothing 326 Nothing
353 False 327 False
354 "Tex_3617993418") 328 "Tex_3617993418"
355 (Cons 329 : StageAttrs
356 (StageAttrs
357 (Just (HCons B_DstColor (HCons B_Zero HNil))) 330 (Just (HCons B_DstColor (HCons B_Zero HNil)))
358 RGB_IdentityLighting 331 RGB_IdentityLighting
359 A_Identity 332 A_Identity
@@ -364,12 +337,11 @@ sampleMaterial
364 D_Lequal 337 D_Lequal
365 Nothing 338 Nothing
366 False 339 False
367 "Tex_3226210144") 340 "Tex_3226210144"
368 Nil)) 341 : Nil)
369 False) 342 False)
370 HNil)) 343 HNil)
371 (Cons 344 : HCons
372 (HCons
373 "textures/gothic_door/km_arena1archfinalc_mid" 345 "textures/gothic_door/km_arena1archfinalc_mid"
374 (HCons 346 (HCons
375 (CommonAttrs 347 (CommonAttrs
@@ -383,8 +355,7 @@ sampleMaterial
383 Nil 355 Nil
384 False 356 False
385 False 357 False
386 (Cons 358 (StageAttrs
387 (StageAttrs
388 Nothing 359 Nothing
389 RGB_IdentityLighting 360 RGB_IdentityLighting
390 A_Identity 361 A_Identity
@@ -395,9 +366,8 @@ sampleMaterial
395 D_Lequal 366 D_Lequal
396 Nothing 367 Nothing
397 False 368 False
398 "Tex_2073154888") 369 "Tex_2073154888"
399 (Cons 370 : StageAttrs
400 (StageAttrs
401 (Just (HCons B_DstColor (HCons B_Zero HNil))) 371 (Just (HCons B_DstColor (HCons B_Zero HNil)))
402 RGB_IdentityLighting 372 RGB_IdentityLighting
403 A_Identity 373 A_Identity
@@ -408,12 +378,11 @@ sampleMaterial
408 D_Lequal 378 D_Lequal
409 Nothing 379 Nothing
410 False 380 False
411 "Tex_3226210144") 381 "Tex_3226210144"
412 Nil)) 382 : Nil)
413 False) 383 False)
414 HNil)) 384 HNil)
415 (Cons 385 : HCons
416 (HCons
417 "textures/gothic_door/km_arena1archfinalc_top" 386 "textures/gothic_door/km_arena1archfinalc_top"
418 (HCons 387 (HCons
419 (CommonAttrs 388 (CommonAttrs
@@ -427,8 +396,7 @@ sampleMaterial
427 Nil 396 Nil
428 False 397 False
429 False 398 False
430 (Cons 399 (StageAttrs
431 (StageAttrs
432 Nothing 400 Nothing
433 RGB_IdentityLighting 401 RGB_IdentityLighting
434 A_Identity 402 A_Identity
@@ -439,9 +407,8 @@ sampleMaterial
439 D_Lequal 407 D_Lequal
440 Nothing 408 Nothing
441 False 409 False
442 "Tex_3071107621") 410 "Tex_3071107621"
443 (Cons 411 : StageAttrs
444 (StageAttrs
445 (Just (HCons B_DstColor (HCons B_Zero HNil))) 412 (Just (HCons B_DstColor (HCons B_Zero HNil)))
446 RGB_IdentityLighting 413 RGB_IdentityLighting
447 A_Identity 414 A_Identity
@@ -452,12 +419,11 @@ sampleMaterial
452 D_Lequal 419 D_Lequal
453 Nothing 420 Nothing
454 False 421 False
455 "Tex_3226210144") 422 "Tex_3226210144"
456 Nil)) 423 : Nil)
457 False) 424 False)
458 HNil)) 425 HNil)
459 (Cons 426 : HCons
460 (HCons
461 "textures/gothic_door/km_arena1archfinald_bot" 427 "textures/gothic_door/km_arena1archfinald_bot"
462 (HCons 428 (HCons
463 (CommonAttrs 429 (CommonAttrs
@@ -471,8 +437,7 @@ sampleMaterial
471 Nil 437 Nil
472 False 438 False
473 False 439 False
474 (Cons 440 (StageAttrs
475 (StageAttrs
476 Nothing 441 Nothing
477 RGB_IdentityLighting 442 RGB_IdentityLighting
478 A_Identity 443 A_Identity
@@ -483,9 +448,8 @@ sampleMaterial
483 D_Lequal 448 D_Lequal
484 Nothing 449 Nothing
485 False 450 False
486 "Tex_1201212243") 451 "Tex_1201212243"
487 (Cons 452 : StageAttrs
488 (StageAttrs
489 (Just (HCons B_DstColor (HCons B_Zero HNil))) 453 (Just (HCons B_DstColor (HCons B_Zero HNil)))
490 RGB_IdentityLighting 454 RGB_IdentityLighting
491 A_Identity 455 A_Identity
@@ -496,12 +460,11 @@ sampleMaterial
496 D_Lequal 460 D_Lequal
497 Nothing 461 Nothing
498 False 462 False
499 "Tex_3226210144") 463 "Tex_3226210144"
500 Nil)) 464 : Nil)
501 False) 465 False)
502 HNil)) 466 HNil)
503 (Cons 467 : HCons
504 (HCons
505 "textures/gothic_door/km_arena1archfinald_mid" 468 "textures/gothic_door/km_arena1archfinald_mid"
506 (HCons 469 (HCons
507 (CommonAttrs 470 (CommonAttrs
@@ -515,8 +478,7 @@ sampleMaterial
515 Nil 478 Nil
516 False 479 False
517 False 480 False
518 (Cons 481 (StageAttrs
519 (StageAttrs
520 Nothing 482 Nothing
521 RGB_IdentityLighting 483 RGB_IdentityLighting
522 A_Identity 484 A_Identity
@@ -527,9 +489,8 @@ sampleMaterial
527 D_Lequal 489 D_Lequal
528 Nothing 490 Nothing
529 False 491 False
530 "Tex_3768122504") 492 "Tex_3768122504"
531 (Cons 493 : StageAttrs
532 (StageAttrs
533 (Just (HCons B_DstColor (HCons B_Zero HNil))) 494 (Just (HCons B_DstColor (HCons B_Zero HNil)))
534 RGB_IdentityLighting 495 RGB_IdentityLighting
535 A_Identity 496 A_Identity
@@ -540,12 +501,11 @@ sampleMaterial
540 D_Lequal 501 D_Lequal
541 Nothing 502 Nothing
542 False 503 False
543 "Tex_3226210144") 504 "Tex_3226210144"
544 Nil)) 505 : Nil)
545 False) 506 False)
546 HNil)) 507 HNil)
547 (Cons 508 : HCons
548 (HCons
549 "textures/gothic_door/skull_door_a" 509 "textures/gothic_door/skull_door_a"
550 (HCons 510 (HCons
551 (CommonAttrs 511 (CommonAttrs
@@ -559,8 +519,7 @@ sampleMaterial
559 Nil 519 Nil
560 False 520 False
561 False 521 False
562 (Cons 522 (StageAttrs
563 (StageAttrs
564 Nothing 523 Nothing
565 RGB_IdentityLighting 524 RGB_IdentityLighting
566 A_Identity 525 A_Identity
@@ -571,9 +530,8 @@ sampleMaterial
571 D_Lequal 530 D_Lequal
572 Nothing 531 Nothing
573 False 532 False
574 "Tex_1284708166") 533 "Tex_1284708166"
575 (Cons 534 : StageAttrs
576 (StageAttrs
577 (Just (HCons B_DstColor (HCons B_Zero HNil))) 535 (Just (HCons B_DstColor (HCons B_Zero HNil)))
578 RGB_IdentityLighting 536 RGB_IdentityLighting
579 A_Identity 537 A_Identity
@@ -584,12 +542,11 @@ sampleMaterial
584 D_Lequal 542 D_Lequal
585 Nothing 543 Nothing
586 False 544 False
587 "Tex_3226210144") 545 "Tex_3226210144"
588 Nil)) 546 : Nil)
589 False) 547 False)
590 HNil)) 548 HNil)
591 (Cons 549 : HCons
592 (HCons
593 "textures/gothic_door/skull_door_b" 550 "textures/gothic_door/skull_door_b"
594 (HCons 551 (HCons
595 (CommonAttrs 552 (CommonAttrs
@@ -603,8 +560,7 @@ sampleMaterial
603 Nil 560 Nil
604 False 561 False
605 False 562 False
606 (Cons 563 (StageAttrs
607 (StageAttrs
608 Nothing 564 Nothing
609 RGB_IdentityLighting 565 RGB_IdentityLighting
610 A_Identity 566 A_Identity
@@ -615,9 +571,8 @@ sampleMaterial
615 D_Lequal 571 D_Lequal
616 Nothing 572 Nothing
617 False 573 False
618 "Tex_1318715778") 574 "Tex_1318715778"
619 (Cons 575 : StageAttrs
620 (StageAttrs
621 (Just (HCons B_DstColor (HCons B_Zero HNil))) 576 (Just (HCons B_DstColor (HCons B_Zero HNil)))
622 RGB_IdentityLighting 577 RGB_IdentityLighting
623 A_Identity 578 A_Identity
@@ -628,12 +583,11 @@ sampleMaterial
628 D_Lequal 583 D_Lequal
629 Nothing 584 Nothing
630 False 585 False
631 "Tex_3226210144") 586 "Tex_3226210144"
632 Nil)) 587 : Nil)
633 False) 588 False)
634 HNil)) 589 HNil)
635 (Cons 590 : HCons
636 (HCons
637 "textures/gothic_door/skull_door_c" 591 "textures/gothic_door/skull_door_c"
638 (HCons 592 (HCons
639 (CommonAttrs 593 (CommonAttrs
@@ -647,8 +601,7 @@ sampleMaterial
647 Nil 601 Nil
648 False 602 False
649 False 603 False
650 (Cons 604 (StageAttrs
651 (StageAttrs
652 Nothing 605 Nothing
653 RGB_IdentityLighting 606 RGB_IdentityLighting
654 A_Identity 607 A_Identity
@@ -659,9 +612,8 @@ sampleMaterial
659 D_Lequal 612 D_Lequal
660 Nothing 613 Nothing
661 False 614 False
662 "Tex_4189195777") 615 "Tex_4189195777"
663 (Cons 616 : StageAttrs
664 (StageAttrs
665 (Just (HCons B_DstColor (HCons B_Zero HNil))) 617 (Just (HCons B_DstColor (HCons B_Zero HNil)))
666 RGB_IdentityLighting 618 RGB_IdentityLighting
667 A_Identity 619 A_Identity
@@ -672,12 +624,11 @@ sampleMaterial
672 D_Lequal 624 D_Lequal
673 Nothing 625 Nothing
674 False 626 False
675 "Tex_3226210144") 627 "Tex_3226210144"
676 Nil)) 628 : Nil)
677 False) 629 False)
678 HNil)) 630 HNil)
679 (Cons 631 : HCons
680 (HCons
681 "textures/gothic_door/skull_door_d" 632 "textures/gothic_door/skull_door_d"
682 (HCons 633 (HCons
683 (CommonAttrs 634 (CommonAttrs
@@ -691,8 +642,7 @@ sampleMaterial
691 Nil 642 Nil
692 False 643 False
693 False 644 False
694 (Cons 645 (StageAttrs
695 (StageAttrs
696 Nothing 646 Nothing
697 RGB_IdentityLighting 647 RGB_IdentityLighting
698 A_Identity 648 A_Identity
@@ -703,9 +653,8 @@ sampleMaterial
703 D_Lequal 653 D_Lequal
704 Nothing 654 Nothing
705 False 655 False
706 "Tex_1250438154") 656 "Tex_1250438154"
707 (Cons 657 : StageAttrs
708 (StageAttrs
709 (Just (HCons B_DstColor (HCons B_Zero HNil))) 658 (Just (HCons B_DstColor (HCons B_Zero HNil)))
710 RGB_IdentityLighting 659 RGB_IdentityLighting
711 A_Identity 660 A_Identity
@@ -716,12 +665,11 @@ sampleMaterial
716 D_Lequal 665 D_Lequal
717 Nothing 666 Nothing
718 False 667 False
719 "Tex_3226210144") 668 "Tex_3226210144"
720 Nil)) 669 : Nil)
721 False) 670 False)
722 HNil)) 671 HNil)
723 (Cons 672 : HCons
724 (HCons
725 "textures/gothic_door/skull_door_e" 673 "textures/gothic_door/skull_door_e"
726 (HCons 674 (HCons
727 (CommonAttrs 675 (CommonAttrs
@@ -735,8 +683,7 @@ sampleMaterial
735 Nil 683 Nil
736 False 684 False
737 False 685 False
738 (Cons 686 (StageAttrs
739 (StageAttrs
740 Nothing 687 Nothing
741 RGB_IdentityLighting 688 RGB_IdentityLighting
742 A_Identity 689 A_Identity
@@ -747,9 +694,8 @@ sampleMaterial
747 D_Lequal 694 D_Lequal
748 Nothing 695 Nothing
749 False 696 False
750 "Tex_4255130505") 697 "Tex_4255130505"
751 (Cons 698 : StageAttrs
752 (StageAttrs
753 (Just (HCons B_DstColor (HCons B_Zero HNil))) 699 (Just (HCons B_DstColor (HCons B_Zero HNil)))
754 RGB_IdentityLighting 700 RGB_IdentityLighting
755 A_Identity 701 A_Identity
@@ -760,12 +706,11 @@ sampleMaterial
760 D_Lequal 706 D_Lequal
761 Nothing 707 Nothing
762 False 708 False
763 "Tex_3226210144") 709 "Tex_3226210144"
764 Nil)) 710 : Nil)
765 False) 711 False)
766 HNil)) 712 HNil)
767 (Cons 713 : HCons
768 (HCons
769 "textures/gothic_door/skull_door_f" 714 "textures/gothic_door/skull_door_f"
770 (HCons 715 (HCons
771 (CommonAttrs 716 (CommonAttrs
@@ -779,8 +724,7 @@ sampleMaterial
779 Nil 724 Nil
780 False 725 False
781 False 726 False
782 (Cons 727 (StageAttrs
783 (StageAttrs
784 Nothing 728 Nothing
785 RGB_IdentityLighting 729 RGB_IdentityLighting
786 A_Identity 730 A_Identity
@@ -791,9 +735,8 @@ sampleMaterial
791 D_Lequal 735 D_Lequal
792 Nothing 736 Nothing
793 False 737 False
794 "Tex_4289279309") 738 "Tex_4289279309"
795 (Cons 739 : StageAttrs
796 (StageAttrs
797 (Just (HCons B_DstColor (HCons B_Zero HNil))) 740 (Just (HCons B_DstColor (HCons B_Zero HNil)))
798 RGB_IdentityLighting 741 RGB_IdentityLighting
799 A_Identity 742 A_Identity
@@ -804,12 +747,11 @@ sampleMaterial
804 D_Lequal 747 D_Lequal
805 Nothing 748 Nothing
806 False 749 False
807 "Tex_3226210144") 750 "Tex_3226210144"
808 Nil)) 751 : Nil)
809 False) 752 False)
810 HNil)) 753 HNil)
811 (Cons 754 : HCons
812 (HCons
813 "textures/gothic_door/skullarch_a" 755 "textures/gothic_door/skullarch_a"
814 (HCons 756 (HCons
815 (CommonAttrs 757 (CommonAttrs
@@ -823,8 +765,7 @@ sampleMaterial
823 Nil 765 Nil
824 False 766 False
825 False 767 False
826 (Cons 768 (StageAttrs
827 (StageAttrs
828 Nothing 769 Nothing
829 RGB_IdentityLighting 770 RGB_IdentityLighting
830 A_Identity 771 A_Identity
@@ -835,9 +776,8 @@ sampleMaterial
835 D_Lequal 776 D_Lequal
836 Nothing 777 Nothing
837 False 778 False
838 "Tex_3448884269") 779 "Tex_3448884269"
839 (Cons 780 : StageAttrs
840 (StageAttrs
841 (Just (HCons B_DstColor (HCons B_Zero HNil))) 781 (Just (HCons B_DstColor (HCons B_Zero HNil)))
842 RGB_IdentityLighting 782 RGB_IdentityLighting
843 A_Identity 783 A_Identity
@@ -848,12 +788,11 @@ sampleMaterial
848 D_Lequal 788 D_Lequal
849 Nothing 789 Nothing
850 False 790 False
851 "Tex_3226210144") 791 "Tex_3226210144"
852 Nil)) 792 : Nil)
853 False) 793 False)
854 HNil)) 794 HNil)
855 (Cons 795 : HCons
856 (HCons
857 "textures/gothic_door/skullarch_b" 796 "textures/gothic_door/skullarch_b"
858 (HCons 797 (HCons
859 (CommonAttrs 798 (CommonAttrs
@@ -867,23 +806,19 @@ sampleMaterial
867 Nil 806 Nil
868 False 807 False
869 False 808 False
870 (Cons 809 (StageAttrs
871 (StageAttrs
872 Nothing 810 Nothing
873 RGB_Identity 811 RGB_Identity
874 A_Identity 812 A_Identity
875 TG_Base 813 TG_Base
876 (Cons 814 (TM_Scroll 0.0 1.0 : TM_Turb 0.0 0.25 0.0 5.6 : TM_Scale 1.5 1.5 : Nil)
877 (TM_Scroll 0.0 1.0)
878 (Cons (TM_Turb 0.0 0.25 0.0 5.6) (Cons (TM_Scale 1.5 1.5) Nil)))
879 (ST_Map "textures/sfx/firegorre.tga") 815 (ST_Map "textures/sfx/firegorre.tga")
880 True 816 True
881 D_Lequal 817 D_Lequal
882 Nothing 818 Nothing
883 False 819 False
884 "Tex_3416962274") 820 "Tex_3416962274"
885 (Cons 821 : StageAttrs
886 (StageAttrs
887 (Just (HCons B_SrcAlpha (HCons B_OneMinusSrcAlpha HNil))) 822 (Just (HCons B_SrcAlpha (HCons B_OneMinusSrcAlpha HNil)))
888 RGB_Identity 823 RGB_Identity
889 A_Identity 824 A_Identity
@@ -894,9 +829,8 @@ sampleMaterial
894 D_Lequal 829 D_Lequal
895 Nothing 830 Nothing
896 False 831 False
897 "Tex_4077187607") 832 "Tex_4077187607"
898 (Cons 833 : StageAttrs
899 (StageAttrs
900 (Just (HCons B_DstColor (HCons B_Zero HNil))) 834 (Just (HCons B_DstColor (HCons B_Zero HNil)))
901 RGB_Identity 835 RGB_Identity
902 A_Identity 836 A_Identity
@@ -907,12 +841,11 @@ sampleMaterial
907 D_Lequal 841 D_Lequal
908 Nothing 842 Nothing
909 False 843 False
910 "Tex_1196599720") 844 "Tex_1196599720"
911 Nil))) 845 : Nil)
912 False) 846 False)
913 HNil)) 847 HNil)
914 (Cons 848 : HCons
915 (HCons
916 "textures/gothic_door/skullarch_c" 849 "textures/gothic_door/skullarch_c"
917 (HCons 850 (HCons
918 (CommonAttrs 851 (CommonAttrs
@@ -926,8 +859,7 @@ sampleMaterial
926 Nil 859 Nil
927 False 860 False
928 False 861 False
929 (Cons 862 (StageAttrs
930 (StageAttrs
931 Nothing 863 Nothing
932 RGB_IdentityLighting 864 RGB_IdentityLighting
933 A_Identity 865 A_Identity
@@ -938,9 +870,8 @@ sampleMaterial
938 D_Lequal 870 D_Lequal
939 Nothing 871 Nothing
940 False 872 False
941 "Tex_2024854890") 873 "Tex_2024854890"
942 (Cons 874 : StageAttrs
943 (StageAttrs
944 (Just (HCons B_DstColor (HCons B_Zero HNil))) 875 (Just (HCons B_DstColor (HCons B_Zero HNil)))
945 RGB_IdentityLighting 876 RGB_IdentityLighting
946 A_Identity 877 A_Identity
@@ -951,12 +882,11 @@ sampleMaterial
951 D_Lequal 882 D_Lequal
952 Nothing 883 Nothing
953 False 884 False
954 "Tex_3226210144") 885 "Tex_3226210144"
955 Nil)) 886 : Nil)
956 False) 887 False)
957 HNil)) 888 HNil)
958 (Cons 889 : HCons
959 (HCons
960 "textures/gothic_door/xian_tourneyarch_inside2" 890 "textures/gothic_door/xian_tourneyarch_inside2"
961 (HCons 891 (HCons
962 (CommonAttrs 892 (CommonAttrs
@@ -970,8 +900,7 @@ sampleMaterial
970 Nil 900 Nil
971 False 901 False
972 False 902 False
973 (Cons 903 (StageAttrs
974 (StageAttrs
975 Nothing 904 Nothing
976 RGB_IdentityLighting 905 RGB_IdentityLighting
977 A_Identity 906 A_Identity
@@ -982,9 +911,8 @@ sampleMaterial
982 D_Lequal 911 D_Lequal
983 Nothing 912 Nothing
984 False 913 False
985 "Tex_1435187472") 914 "Tex_1435187472"
986 (Cons 915 : StageAttrs
987 (StageAttrs
988 (Just (HCons B_DstColor (HCons B_Zero HNil))) 916 (Just (HCons B_DstColor (HCons B_Zero HNil)))
989 RGB_IdentityLighting 917 RGB_IdentityLighting
990 A_Identity 918 A_Identity
@@ -995,12 +923,11 @@ sampleMaterial
995 D_Lequal 923 D_Lequal
996 Nothing 924 Nothing
997 False 925 False
998 "Tex_3226210144") 926 "Tex_3226210144"
999 Nil)) 927 : Nil)
1000 False) 928 False)
1001 HNil)) 929 HNil)
1002 (Cons 930 : HCons
1003 (HCons
1004 "textures/gothic_floor/blocks17floor2" 931 "textures/gothic_floor/blocks17floor2"
1005 (HCons 932 (HCons
1006 (CommonAttrs 933 (CommonAttrs
@@ -1014,8 +941,7 @@ sampleMaterial
1014 Nil 941 Nil
1015 False 942 False
1016 False 943 False
1017 (Cons 944 (StageAttrs
1018 (StageAttrs
1019 Nothing 945 Nothing
1020 RGB_IdentityLighting 946 RGB_IdentityLighting
1021 A_Identity 947 A_Identity
@@ -1026,9 +952,8 @@ sampleMaterial
1026 D_Lequal 952 D_Lequal
1027 Nothing 953 Nothing
1028 False 954 False
1029 "Tex_3814342582") 955 "Tex_3814342582"
1030 (Cons 956 : StageAttrs
1031 (StageAttrs
1032 (Just (HCons B_DstColor (HCons B_Zero HNil))) 957 (Just (HCons B_DstColor (HCons B_Zero HNil)))
1033 RGB_IdentityLighting 958 RGB_IdentityLighting
1034 A_Identity 959 A_Identity
@@ -1039,12 +964,11 @@ sampleMaterial
1039 D_Lequal 964 D_Lequal
1040 Nothing 965 Nothing
1041 False 966 False
1042 "Tex_3226210144") 967 "Tex_3226210144"
1043 Nil)) 968 : Nil)
1044 False) 969 False)
1045 HNil)) 970 HNil)
1046 (Cons 971 : HCons
1047 (HCons
1048 "textures/gothic_floor/largerblock3b" 972 "textures/gothic_floor/largerblock3b"
1049 (HCons 973 (HCons
1050 (CommonAttrs 974 (CommonAttrs
@@ -1058,8 +982,7 @@ sampleMaterial
1058 Nil 982 Nil
1059 False 983 False
1060 False 984 False
1061 (Cons 985 (StageAttrs
1062 (StageAttrs
1063 Nothing 986 Nothing
1064 RGB_IdentityLighting 987 RGB_IdentityLighting
1065 A_Identity 988 A_Identity
@@ -1070,9 +993,8 @@ sampleMaterial
1070 D_Lequal 993 D_Lequal
1071 Nothing 994 Nothing
1072 False 995 False
1073 "Tex_2966885788") 996 "Tex_2966885788"
1074 (Cons 997 : StageAttrs
1075 (StageAttrs
1076 (Just (HCons B_DstColor (HCons B_Zero HNil))) 998 (Just (HCons B_DstColor (HCons B_Zero HNil)))
1077 RGB_IdentityLighting 999 RGB_IdentityLighting
1078 A_Identity 1000 A_Identity
@@ -1083,12 +1005,11 @@ sampleMaterial
1083 D_Lequal 1005 D_Lequal
1084 Nothing 1006 Nothing
1085 False 1007 False
1086 "Tex_3226210144") 1008 "Tex_3226210144"
1087 Nil)) 1009 : Nil)
1088 False) 1010 False)
1089 HNil)) 1011 HNil)
1090 (Cons 1012 : HCons
1091 (HCons
1092 "textures/gothic_floor/metalbridge06" 1013 "textures/gothic_floor/metalbridge06"
1093 (HCons 1014 (HCons
1094 (CommonAttrs 1015 (CommonAttrs
@@ -1102,8 +1023,7 @@ sampleMaterial
1102 Nil 1023 Nil
1103 False 1024 False
1104 False 1025 False
1105 (Cons 1026 (StageAttrs
1106 (StageAttrs
1107 Nothing 1027 Nothing
1108 RGB_IdentityLighting 1028 RGB_IdentityLighting
1109 A_Identity 1029 A_Identity
@@ -1114,9 +1034,8 @@ sampleMaterial
1114 D_Lequal 1034 D_Lequal
1115 Nothing 1035 Nothing
1116 False 1036 False
1117 "Tex_1581337759") 1037 "Tex_1581337759"
1118 (Cons 1038 : StageAttrs
1119 (StageAttrs
1120 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1039 (Just (HCons B_DstColor (HCons B_Zero HNil)))
1121 RGB_IdentityLighting 1040 RGB_IdentityLighting
1122 A_Identity 1041 A_Identity
@@ -1127,12 +1046,11 @@ sampleMaterial
1127 D_Lequal 1046 D_Lequal
1128 Nothing 1047 Nothing
1129 False 1048 False
1130 "Tex_3226210144") 1049 "Tex_3226210144"
1131 Nil)) 1050 : Nil)
1132 False) 1051 False)
1133 HNil)) 1052 HNil)
1134 (Cons 1053 : HCons
1135 (HCons
1136 "textures/gothic_floor/metalbridge06broke" 1054 "textures/gothic_floor/metalbridge06broke"
1137 (HCons 1055 (HCons
1138 (CommonAttrs 1056 (CommonAttrs
@@ -1146,8 +1064,7 @@ sampleMaterial
1146 Nil 1064 Nil
1147 False 1065 False
1148 False 1066 False
1149 (Cons 1067 (StageAttrs
1150 (StageAttrs
1151 Nothing 1068 Nothing
1152 RGB_IdentityLighting 1069 RGB_IdentityLighting
1153 A_Identity 1070 A_Identity
@@ -1158,9 +1075,8 @@ sampleMaterial
1158 D_Lequal 1075 D_Lequal
1159 Nothing 1076 Nothing
1160 False 1077 False
1161 "Tex_3921745736") 1078 "Tex_3921745736"
1162 (Cons 1079 : StageAttrs
1163 (StageAttrs
1164 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1080 (Just (HCons B_DstColor (HCons B_Zero HNil)))
1165 RGB_IdentityLighting 1081 RGB_IdentityLighting
1166 A_Identity 1082 A_Identity
@@ -1171,12 +1087,11 @@ sampleMaterial
1171 D_Lequal 1087 D_Lequal
1172 Nothing 1088 Nothing
1173 False 1089 False
1174 "Tex_3226210144") 1090 "Tex_3226210144"
1175 Nil)) 1091 : Nil)
1176 False) 1092 False)
1177 HNil)) 1093 HNil)
1178 (Cons 1094 : HCons
1179 (HCons
1180 "textures/gothic_floor/xstairtop4" 1095 "textures/gothic_floor/xstairtop4"
1181 (HCons 1096 (HCons
1182 (CommonAttrs 1097 (CommonAttrs
@@ -1190,8 +1105,7 @@ sampleMaterial
1190 Nil 1105 Nil
1191 False 1106 False
1192 False 1107 False
1193 (Cons 1108 (StageAttrs
1194 (StageAttrs
1195 Nothing 1109 Nothing
1196 RGB_IdentityLighting 1110 RGB_IdentityLighting
1197 A_Identity 1111 A_Identity
@@ -1202,9 +1116,8 @@ sampleMaterial
1202 D_Lequal 1116 D_Lequal
1203 Nothing 1117 Nothing
1204 False 1118 False
1205 "Tex_3836020895") 1119 "Tex_3836020895"
1206 (Cons 1120 : StageAttrs
1207 (StageAttrs
1208 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1121 (Just (HCons B_DstColor (HCons B_Zero HNil)))
1209 RGB_IdentityLighting 1122 RGB_IdentityLighting
1210 A_Identity 1123 A_Identity
@@ -1215,12 +1128,11 @@ sampleMaterial
1215 D_Lequal 1128 D_Lequal
1216 Nothing 1129 Nothing
1217 False 1130 False
1218 "Tex_3226210144") 1131 "Tex_3226210144"
1219 Nil)) 1132 : Nil)
1220 False) 1133 False)
1221 HNil)) 1134 HNil)
1222 (Cons 1135 : HCons
1223 (HCons
1224 "textures/gothic_floor/xstepborder3" 1136 "textures/gothic_floor/xstepborder3"
1225 (HCons 1137 (HCons
1226 (CommonAttrs 1138 (CommonAttrs
@@ -1234,8 +1146,7 @@ sampleMaterial
1234 Nil 1146 Nil
1235 False 1147 False
1236 False 1148 False
1237 (Cons 1149 (StageAttrs
1238 (StageAttrs
1239 Nothing 1150 Nothing
1240 RGB_IdentityLighting 1151 RGB_IdentityLighting
1241 A_Identity 1152 A_Identity
@@ -1246,9 +1157,8 @@ sampleMaterial
1246 D_Lequal 1157 D_Lequal
1247 Nothing 1158 Nothing
1248 False 1159 False
1249 "Tex_3269743316") 1160 "Tex_3269743316"
1250 (Cons 1161 : StageAttrs
1251 (StageAttrs
1252 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1162 (Just (HCons B_DstColor (HCons B_Zero HNil)))
1253 RGB_IdentityLighting 1163 RGB_IdentityLighting
1254 A_Identity 1164 A_Identity
@@ -1259,12 +1169,11 @@ sampleMaterial
1259 D_Lequal 1169 D_Lequal
1260 Nothing 1170 Nothing
1261 False 1171 False
1262 "Tex_3226210144") 1172 "Tex_3226210144"
1263 Nil)) 1173 : Nil)
1264 False) 1174 False)
1265 HNil)) 1175 HNil)
1266 (Cons 1176 : HCons
1267 (HCons
1268 "textures/gothic_trim/baseboard04" 1177 "textures/gothic_trim/baseboard04"
1269 (HCons 1178 (HCons
1270 (CommonAttrs 1179 (CommonAttrs
@@ -1278,8 +1187,7 @@ sampleMaterial
1278 Nil 1187 Nil
1279 False 1188 False
1280 False 1189 False
1281 (Cons 1190 (StageAttrs
1282 (StageAttrs
1283 Nothing 1191 Nothing
1284 RGB_IdentityLighting 1192 RGB_IdentityLighting
1285 A_Identity 1193 A_Identity
@@ -1290,9 +1198,8 @@ sampleMaterial
1290 D_Lequal 1198 D_Lequal
1291 Nothing 1199 Nothing
1292 False 1200 False
1293 "Tex_1002517541") 1201 "Tex_1002517541"
1294 (Cons 1202 : StageAttrs
1295 (StageAttrs
1296 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1203 (Just (HCons B_DstColor (HCons B_Zero HNil)))
1297 RGB_IdentityLighting 1204 RGB_IdentityLighting
1298 A_Identity 1205 A_Identity
@@ -1303,12 +1210,11 @@ sampleMaterial
1303 D_Lequal 1210 D_Lequal
1304 Nothing 1211 Nothing
1305 False 1212 False
1306 "Tex_3226210144") 1213 "Tex_3226210144"
1307 Nil)) 1214 : Nil)
1308 False) 1215 False)
1309 HNil)) 1216 HNil)
1310 (Cons 1217 : HCons
1311 (HCons
1312 "textures/gothic_trim/baseboard09_c3" 1218 "textures/gothic_trim/baseboard09_c3"
1313 (HCons 1219 (HCons
1314 (CommonAttrs 1220 (CommonAttrs
@@ -1322,8 +1228,7 @@ sampleMaterial
1322 Nil 1228 Nil
1323 False 1229 False
1324 False 1230 False
1325 (Cons 1231 (StageAttrs
1326 (StageAttrs
1327 Nothing 1232 Nothing
1328 RGB_IdentityLighting 1233 RGB_IdentityLighting
1329 A_Identity 1234 A_Identity
@@ -1334,9 +1239,8 @@ sampleMaterial
1334 D_Lequal 1239 D_Lequal
1335 Nothing 1240 Nothing
1336 False 1241 False
1337 "Tex_2289735512") 1242 "Tex_2289735512"
1338 (Cons 1243 : StageAttrs
1339 (StageAttrs
1340 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1244 (Just (HCons B_DstColor (HCons B_Zero HNil)))
1341 RGB_IdentityLighting 1245 RGB_IdentityLighting
1342 A_Identity 1246 A_Identity
@@ -1347,12 +1251,11 @@ sampleMaterial
1347 D_Lequal 1251 D_Lequal
1348 Nothing 1252 Nothing
1349 False 1253 False
1350 "Tex_3226210144") 1254 "Tex_3226210144"
1351 Nil)) 1255 : Nil)
1352 False) 1256 False)
1353 HNil)) 1257 HNil)
1354 (Cons 1258 : HCons
1355 (HCons
1356 "textures/gothic_trim/baseboard09_e" 1259 "textures/gothic_trim/baseboard09_e"
1357 (HCons 1260 (HCons
1358 (CommonAttrs 1261 (CommonAttrs
@@ -1366,8 +1269,7 @@ sampleMaterial
1366 Nil 1269 Nil
1367 False 1270 False
1368 False 1271 False
1369 (Cons 1272 (StageAttrs
1370 (StageAttrs
1371 Nothing 1273 Nothing
1372 RGB_IdentityLighting 1274 RGB_IdentityLighting
1373 A_Identity 1275 A_Identity
@@ -1378,9 +1280,8 @@ sampleMaterial
1378 D_Lequal 1280 D_Lequal
1379 Nothing 1281 Nothing
1380 False 1282 False
1381 "Tex_2367525081") 1283 "Tex_2367525081"
1382 (Cons 1284 : StageAttrs
1383 (StageAttrs
1384 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1285 (Just (HCons B_DstColor (HCons B_Zero HNil)))
1385 RGB_IdentityLighting 1286 RGB_IdentityLighting
1386 A_Identity 1287 A_Identity
@@ -1391,12 +1292,11 @@ sampleMaterial
1391 D_Lequal 1292 D_Lequal
1392 Nothing 1293 Nothing
1393 False 1294 False
1394 "Tex_3226210144") 1295 "Tex_3226210144"
1395 Nil)) 1296 : Nil)
1396 False) 1297 False)
1397 HNil)) 1298 HNil)
1398 (Cons 1299 : HCons
1399 (HCons
1400 "textures/gothic_trim/baseboard09_e2" 1300 "textures/gothic_trim/baseboard09_e2"
1401 (HCons 1301 (HCons
1402 (CommonAttrs 1302 (CommonAttrs
@@ -1410,8 +1310,7 @@ sampleMaterial
1410 Nil 1310 Nil
1411 False 1311 False
1412 False 1312 False
1413 (Cons 1313 (StageAttrs
1414 (StageAttrs
1415 Nothing 1314 Nothing
1416 RGB_IdentityLighting 1315 RGB_IdentityLighting
1417 A_Identity 1316 A_Identity
@@ -1422,9 +1321,8 @@ sampleMaterial
1422 D_Lequal 1321 D_Lequal
1423 Nothing 1322 Nothing
1424 False 1323 False
1425 "Tex_3694494180") 1324 "Tex_3694494180"
1426 (Cons 1325 : StageAttrs
1427 (StageAttrs
1428 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1326 (Just (HCons B_DstColor (HCons B_Zero HNil)))
1429 RGB_IdentityLighting 1327 RGB_IdentityLighting
1430 A_Identity 1328 A_Identity
@@ -1435,12 +1333,11 @@ sampleMaterial
1435 D_Lequal 1333 D_Lequal
1436 Nothing 1334 Nothing
1437 False 1335 False
1438 "Tex_3226210144") 1336 "Tex_3226210144"
1439 Nil)) 1337 : Nil)
1440 False) 1338 False)
1441 HNil)) 1339 HNil)
1442 (Cons 1340 : HCons
1443 (HCons
1444 "textures/gothic_trim/baseboard09_l2" 1341 "textures/gothic_trim/baseboard09_l2"
1445 (HCons 1342 (HCons
1446 (CommonAttrs 1343 (CommonAttrs
@@ -1454,8 +1351,7 @@ sampleMaterial
1454 Nil 1351 Nil
1455 False 1352 False
1456 False 1353 False
1457 (Cons 1354 (StageAttrs
1458 (StageAttrs
1459 Nothing 1355 Nothing
1460 RGB_IdentityLighting 1356 RGB_IdentityLighting
1461 A_Identity 1357 A_Identity
@@ -1466,9 +1362,8 @@ sampleMaterial
1466 D_Lequal 1362 D_Lequal
1467 Nothing 1363 Nothing
1468 False 1364 False
1469 "Tex_3202786139") 1365 "Tex_3202786139"
1470 (Cons 1366 : StageAttrs
1471 (StageAttrs
1472 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1367 (Just (HCons B_DstColor (HCons B_Zero HNil)))
1473 RGB_IdentityLighting 1368 RGB_IdentityLighting
1474 A_Identity 1369 A_Identity
@@ -1479,12 +1374,11 @@ sampleMaterial
1479 D_Lequal 1374 D_Lequal
1480 Nothing 1375 Nothing
1481 False 1376 False
1482 "Tex_3226210144") 1377 "Tex_3226210144"
1483 Nil)) 1378 : Nil)
1484 False) 1379 False)
1485 HNil)) 1380 HNil)
1486 (Cons 1381 : HCons
1487 (HCons
1488 "textures/gothic_trim/baseboard09_o3" 1382 "textures/gothic_trim/baseboard09_o3"
1489 (HCons 1383 (HCons
1490 (CommonAttrs 1384 (CommonAttrs
@@ -1498,8 +1392,7 @@ sampleMaterial
1498 Nil 1392 Nil
1499 False 1393 False
1500 False 1394 False
1501 (Cons 1395 (StageAttrs
1502 (StageAttrs
1503 Nothing 1396 Nothing
1504 RGB_IdentityLighting 1397 RGB_IdentityLighting
1505 A_Identity 1398 A_Identity
@@ -1510,9 +1403,8 @@ sampleMaterial
1510 D_Lequal 1403 D_Lequal
1511 Nothing 1404 Nothing
1512 False 1405 False
1513 "Tex_2512757607") 1406 "Tex_2512757607"
1514 (Cons 1407 : StageAttrs
1515 (StageAttrs
1516 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1408 (Just (HCons B_DstColor (HCons B_Zero HNil)))
1517 RGB_IdentityLighting 1409 RGB_IdentityLighting
1518 A_Identity 1410 A_Identity
@@ -1523,12 +1415,11 @@ sampleMaterial
1523 D_Lequal 1415 D_Lequal
1524 Nothing 1416 Nothing
1525 False 1417 False
1526 "Tex_3226210144") 1418 "Tex_3226210144"
1527 Nil)) 1419 : Nil)
1528 False) 1420 False)
1529 HNil)) 1421 HNil)
1530 (Cons 1422 : HCons
1531 (HCons
1532 "textures/gothic_trim/km_arena1tower4" 1423 "textures/gothic_trim/km_arena1tower4"
1533 (HCons 1424 (HCons
1534 (CommonAttrs 1425 (CommonAttrs
@@ -1542,8 +1433,7 @@ sampleMaterial
1542 Nil 1433 Nil
1543 False 1434 False
1544 False 1435 False
1545 (Cons 1436 (StageAttrs
1546 (StageAttrs
1547 Nothing 1437 Nothing
1548 RGB_IdentityLighting 1438 RGB_IdentityLighting
1549 A_Identity 1439 A_Identity
@@ -1554,9 +1444,8 @@ sampleMaterial
1554 D_Lequal 1444 D_Lequal
1555 Nothing 1445 Nothing
1556 False 1446 False
1557 "Tex_3479185666") 1447 "Tex_3479185666"
1558 (Cons 1448 : StageAttrs
1559 (StageAttrs
1560 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1449 (Just (HCons B_DstColor (HCons B_Zero HNil)))
1561 RGB_IdentityLighting 1450 RGB_IdentityLighting
1562 A_Identity 1451 A_Identity
@@ -1567,12 +1456,11 @@ sampleMaterial
1567 D_Lequal 1456 D_Lequal
1568 Nothing 1457 Nothing
1569 False 1458 False
1570 "Tex_3226210144") 1459 "Tex_3226210144"
1571 Nil)) 1460 : Nil)
1572 False) 1461 False)
1573 HNil)) 1462 HNil)
1574 (Cons 1463 : HCons
1575 (HCons
1576 "textures/gothic_trim/km_arena1tower4_a" 1464 "textures/gothic_trim/km_arena1tower4_a"
1577 (HCons 1465 (HCons
1578 (CommonAttrs 1466 (CommonAttrs
@@ -1586,8 +1474,7 @@ sampleMaterial
1586 Nil 1474 Nil
1587 False 1475 False
1588 False 1476 False
1589 (Cons 1477 (StageAttrs
1590 (StageAttrs
1591 Nothing 1478 Nothing
1592 RGB_IdentityLighting 1479 RGB_IdentityLighting
1593 A_Identity 1480 A_Identity
@@ -1598,9 +1485,8 @@ sampleMaterial
1598 D_Lequal 1485 D_Lequal
1599 Nothing 1486 Nothing
1600 False 1487 False
1601 "Tex_3012001075") 1488 "Tex_3012001075"
1602 (Cons 1489 : StageAttrs
1603 (StageAttrs
1604 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1490 (Just (HCons B_DstColor (HCons B_Zero HNil)))
1605 RGB_IdentityLighting 1491 RGB_IdentityLighting
1606 A_Identity 1492 A_Identity
@@ -1611,12 +1497,11 @@ sampleMaterial
1611 D_Lequal 1497 D_Lequal
1612 Nothing 1498 Nothing
1613 False 1499 False
1614 "Tex_3226210144") 1500 "Tex_3226210144"
1615 Nil)) 1501 : Nil)
1616 False) 1502 False)
1617 HNil)) 1503 HNil)
1618 (Cons 1504 : HCons
1619 (HCons
1620 "textures/gothic_trim/metaldemonkillblock" 1505 "textures/gothic_trim/metaldemonkillblock"
1621 (HCons 1506 (HCons
1622 (CommonAttrs 1507 (CommonAttrs
@@ -1630,8 +1515,7 @@ sampleMaterial
1630 Nil 1515 Nil
1631 False 1516 False
1632 False 1517 False
1633 (Cons 1518 (StageAttrs
1634 (StageAttrs
1635 Nothing 1519 Nothing
1636 RGB_IdentityLighting 1520 RGB_IdentityLighting
1637 A_Identity 1521 A_Identity
@@ -1642,9 +1526,8 @@ sampleMaterial
1642 D_Lequal 1526 D_Lequal
1643 Nothing 1527 Nothing
1644 False 1528 False
1645 "Tex_1062467595") 1529 "Tex_1062467595"
1646 (Cons 1530 : StageAttrs
1647 (StageAttrs
1648 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1531 (Just (HCons B_DstColor (HCons B_Zero HNil)))
1649 RGB_IdentityLighting 1532 RGB_IdentityLighting
1650 A_Identity 1533 A_Identity
@@ -1655,12 +1538,11 @@ sampleMaterial
1655 D_Lequal 1538 D_Lequal
1656 Nothing 1539 Nothing
1657 False 1540 False
1658 "Tex_3226210144") 1541 "Tex_3226210144"
1659 Nil)) 1542 : Nil)
1660 False) 1543 False)
1661 HNil)) 1544 HNil)
1662 (Cons 1545 : HCons
1663 (HCons
1664 "textures/gothic_trim/metalsupport4b" 1546 "textures/gothic_trim/metalsupport4b"
1665 (HCons 1547 (HCons
1666 (CommonAttrs 1548 (CommonAttrs
@@ -1674,8 +1556,7 @@ sampleMaterial
1674 Nil 1556 Nil
1675 False 1557 False
1676 False 1558 False
1677 (Cons 1559 (StageAttrs
1678 (StageAttrs
1679 Nothing 1560 Nothing
1680 RGB_IdentityLighting 1561 RGB_IdentityLighting
1681 A_Identity 1562 A_Identity
@@ -1686,9 +1567,8 @@ sampleMaterial
1686 D_Lequal 1567 D_Lequal
1687 Nothing 1568 Nothing
1688 False 1569 False
1689 "Tex_3593923076") 1570 "Tex_3593923076"
1690 (Cons 1571 : StageAttrs
1691 (StageAttrs
1692 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1572 (Just (HCons B_DstColor (HCons B_Zero HNil)))
1693 RGB_IdentityLighting 1573 RGB_IdentityLighting
1694 A_Identity 1574 A_Identity
@@ -1699,12 +1579,11 @@ sampleMaterial
1699 D_Lequal 1579 D_Lequal
1700 Nothing 1580 Nothing
1701 False 1581 False
1702 "Tex_3226210144") 1582 "Tex_3226210144"
1703 Nil)) 1583 : Nil)
1704 False) 1584 False)
1705 HNil)) 1585 HNil)
1706 (Cons 1586 : HCons
1707 (HCons
1708 "textures/gothic_trim/metalsupsolid" 1587 "textures/gothic_trim/metalsupsolid"
1709 (HCons 1588 (HCons
1710 (CommonAttrs 1589 (CommonAttrs
@@ -1718,8 +1597,7 @@ sampleMaterial
1718 Nil 1597 Nil
1719 False 1598 False
1720 False 1599 False
1721 (Cons 1600 (StageAttrs
1722 (StageAttrs
1723 Nothing 1601 Nothing
1724 RGB_IdentityLighting 1602 RGB_IdentityLighting
1725 A_Identity 1603 A_Identity
@@ -1730,9 +1608,8 @@ sampleMaterial
1730 D_Lequal 1608 D_Lequal
1731 Nothing 1609 Nothing
1732 False 1610 False
1733 "Tex_2893650486") 1611 "Tex_2893650486"
1734 (Cons 1612 : StageAttrs
1735 (StageAttrs
1736 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1613 (Just (HCons B_DstColor (HCons B_Zero HNil)))
1737 RGB_IdentityLighting 1614 RGB_IdentityLighting
1738 A_Identity 1615 A_Identity
@@ -1743,12 +1620,11 @@ sampleMaterial
1743 D_Lequal 1620 D_Lequal
1744 Nothing 1621 Nothing
1745 False 1622 False
1746 "Tex_3226210144") 1623 "Tex_3226210144"
1747 Nil)) 1624 : Nil)
1748 False) 1625 False)
1749 HNil)) 1626 HNil)
1750 (Cons 1627 : HCons
1751 (HCons
1752 "textures/gothic_trim/pitted_rust" 1628 "textures/gothic_trim/pitted_rust"
1753 (HCons 1629 (HCons
1754 (CommonAttrs 1630 (CommonAttrs
@@ -1762,8 +1638,7 @@ sampleMaterial
1762 Nil 1638 Nil
1763 False 1639 False
1764 False 1640 False
1765 (Cons 1641 (StageAttrs
1766 (StageAttrs
1767 Nothing 1642 Nothing
1768 RGB_IdentityLighting 1643 RGB_IdentityLighting
1769 A_Identity 1644 A_Identity
@@ -1774,9 +1649,8 @@ sampleMaterial
1774 D_Lequal 1649 D_Lequal
1775 Nothing 1650 Nothing
1776 False 1651 False
1777 "Tex_1243894392") 1652 "Tex_1243894392"
1778 (Cons 1653 : StageAttrs
1779 (StageAttrs
1780 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1654 (Just (HCons B_DstColor (HCons B_Zero HNil)))
1781 RGB_IdentityLighting 1655 RGB_IdentityLighting
1782 A_Identity 1656 A_Identity
@@ -1787,12 +1661,11 @@ sampleMaterial
1787 D_Lequal 1661 D_Lequal
1788 Nothing 1662 Nothing
1789 False 1663 False
1790 "Tex_3226210144") 1664 "Tex_3226210144"
1791 Nil)) 1665 : Nil)
1792 False) 1666 False)
1793 HNil)) 1667 HNil)
1794 (Cons 1668 : HCons
1795 (HCons
1796 "textures/gothic_trim/pitted_rust2" 1669 "textures/gothic_trim/pitted_rust2"
1797 (HCons 1670 (HCons
1798 (CommonAttrs 1671 (CommonAttrs
@@ -1806,8 +1679,7 @@ sampleMaterial
1806 Nil 1679 Nil
1807 False 1680 False
1808 False 1681 False
1809 (Cons 1682 (StageAttrs
1810 (StageAttrs
1811 Nothing 1683 Nothing
1812 RGB_IdentityLighting 1684 RGB_IdentityLighting
1813 A_Identity 1685 A_Identity
@@ -1818,9 +1690,8 @@ sampleMaterial
1818 D_Lequal 1690 D_Lequal
1819 Nothing 1691 Nothing
1820 False 1692 False
1821 "Tex_2099456856") 1693 "Tex_2099456856"
1822 (Cons 1694 : StageAttrs
1823 (StageAttrs
1824 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1695 (Just (HCons B_DstColor (HCons B_Zero HNil)))
1825 RGB_IdentityLighting 1696 RGB_IdentityLighting
1826 A_Identity 1697 A_Identity
@@ -1831,12 +1702,11 @@ sampleMaterial
1831 D_Lequal 1702 D_Lequal
1832 Nothing 1703 Nothing
1833 False 1704 False
1834 "Tex_3226210144") 1705 "Tex_3226210144"
1835 Nil)) 1706 : Nil)
1836 False) 1707 False)
1837 HNil)) 1708 HNil)
1838 (Cons 1709 : HCons
1839 (HCons
1840 "textures/gothic_trim/pitted_rust2_trans" 1710 "textures/gothic_trim/pitted_rust2_trans"
1841 (HCons 1711 (HCons
1842 (CommonAttrs 1712 (CommonAttrs
@@ -1850,8 +1720,7 @@ sampleMaterial
1850 Nil 1720 Nil
1851 False 1721 False
1852 False 1722 False
1853 (Cons 1723 (StageAttrs
1854 (StageAttrs
1855 Nothing 1724 Nothing
1856 RGB_Identity 1725 RGB_Identity
1857 A_Identity 1726 A_Identity
@@ -1862,9 +1731,8 @@ sampleMaterial
1862 D_Lequal 1731 D_Lequal
1863 Nothing 1732 Nothing
1864 False 1733 False
1865 "Tex_511571587") 1734 "Tex_511571587"
1866 (Cons 1735 : StageAttrs
1867 (StageAttrs
1868 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1736 (Just (HCons B_DstColor (HCons B_Zero HNil)))
1869 RGB_Identity 1737 RGB_Identity
1870 A_Identity 1738 A_Identity
@@ -1875,12 +1743,11 @@ sampleMaterial
1875 D_Lequal 1743 D_Lequal
1876 Nothing 1744 Nothing
1877 False 1745 False
1878 "Tex_1910997598") 1746 "Tex_1910997598"
1879 Nil)) 1747 : Nil)
1880 False) 1748 False)
1881 HNil)) 1749 HNil)
1882 (Cons 1750 : HCons
1883 (HCons
1884 "textures/gothic_trim/pitted_rust3" 1751 "textures/gothic_trim/pitted_rust3"
1885 (HCons 1752 (HCons
1886 (CommonAttrs 1753 (CommonAttrs
@@ -1894,8 +1761,7 @@ sampleMaterial
1894 Nil 1761 Nil
1895 False 1762 False
1896 False 1763 False
1897 (Cons 1764 (StageAttrs
1898 (StageAttrs
1899 Nothing 1765 Nothing
1900 RGB_IdentityLighting 1766 RGB_IdentityLighting
1901 A_Identity 1767 A_Identity
@@ -1906,9 +1772,8 @@ sampleMaterial
1906 D_Lequal 1772 D_Lequal
1907 Nothing 1773 Nothing
1908 False 1774 False
1909 "Tex_3389727963") 1775 "Tex_3389727963"
1910 (Cons 1776 : StageAttrs
1911 (StageAttrs
1912 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1777 (Just (HCons B_DstColor (HCons B_Zero HNil)))
1913 RGB_IdentityLighting 1778 RGB_IdentityLighting
1914 A_Identity 1779 A_Identity
@@ -1919,12 +1784,11 @@ sampleMaterial
1919 D_Lequal 1784 D_Lequal
1920 Nothing 1785 Nothing
1921 False 1786 False
1922 "Tex_3226210144") 1787 "Tex_3226210144"
1923 Nil)) 1788 : Nil)
1924 False) 1789 False)
1925 HNil)) 1790 HNil)
1926 (Cons 1791 : HCons
1927 (HCons
1928 "textures/gothic_trim/skullsvertgray02b" 1792 "textures/gothic_trim/skullsvertgray02b"
1929 (HCons 1793 (HCons
1930 (CommonAttrs 1794 (CommonAttrs
@@ -1938,8 +1802,7 @@ sampleMaterial
1938 Nil 1802 Nil
1939 False 1803 False
1940 False 1804 False
1941 (Cons 1805 (StageAttrs
1942 (StageAttrs
1943 Nothing 1806 Nothing
1944 RGB_IdentityLighting 1807 RGB_IdentityLighting
1945 A_Identity 1808 A_Identity
@@ -1950,9 +1813,8 @@ sampleMaterial
1950 D_Lequal 1813 D_Lequal
1951 Nothing 1814 Nothing
1952 False 1815 False
1953 "Tex_2634868983") 1816 "Tex_2634868983"
1954 (Cons 1817 : StageAttrs
1955 (StageAttrs
1956 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1818 (Just (HCons B_DstColor (HCons B_Zero HNil)))
1957 RGB_IdentityLighting 1819 RGB_IdentityLighting
1958 A_Identity 1820 A_Identity
@@ -1963,12 +1825,11 @@ sampleMaterial
1963 D_Lequal 1825 D_Lequal
1964 Nothing 1826 Nothing
1965 False 1827 False
1966 "Tex_3226210144") 1828 "Tex_3226210144"
1967 Nil)) 1829 : Nil)
1968 False) 1830 False)
1969 HNil)) 1831 HNil)
1970 (Cons 1832 : HCons
1971 (HCons
1972 "textures/gothic_wall/iron01_e" 1833 "textures/gothic_wall/iron01_e"
1973 (HCons 1834 (HCons
1974 (CommonAttrs 1835 (CommonAttrs
@@ -1982,8 +1843,7 @@ sampleMaterial
1982 Nil 1843 Nil
1983 False 1844 False
1984 False 1845 False
1985 (Cons 1846 (StageAttrs
1986 (StageAttrs
1987 Nothing 1847 Nothing
1988 RGB_IdentityLighting 1848 RGB_IdentityLighting
1989 A_Identity 1849 A_Identity
@@ -1994,9 +1854,8 @@ sampleMaterial
1994 D_Lequal 1854 D_Lequal
1995 Nothing 1855 Nothing
1996 False 1856 False
1997 "Tex_2432583247") 1857 "Tex_2432583247"
1998 (Cons 1858 : StageAttrs
1999 (StageAttrs
2000 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1859 (Just (HCons B_DstColor (HCons B_Zero HNil)))
2001 RGB_IdentityLighting 1860 RGB_IdentityLighting
2002 A_Identity 1861 A_Identity
@@ -2007,12 +1866,11 @@ sampleMaterial
2007 D_Lequal 1866 D_Lequal
2008 Nothing 1867 Nothing
2009 False 1868 False
2010 "Tex_3226210144") 1869 "Tex_3226210144"
2011 Nil)) 1870 : Nil)
2012 False) 1871 False)
2013 HNil)) 1872 HNil)
2014 (Cons 1873 : HCons
2015 (HCons
2016 "textures/gothic_wall/iron01_ntech3" 1874 "textures/gothic_wall/iron01_ntech3"
2017 (HCons 1875 (HCons
2018 (CommonAttrs 1876 (CommonAttrs
@@ -2026,8 +1884,7 @@ sampleMaterial
2026 Nil 1884 Nil
2027 False 1885 False
2028 False 1886 False
2029 (Cons 1887 (StageAttrs
2030 (StageAttrs
2031 Nothing 1888 Nothing
2032 RGB_IdentityLighting 1889 RGB_IdentityLighting
2033 A_Identity 1890 A_Identity
@@ -2038,9 +1895,8 @@ sampleMaterial
2038 D_Lequal 1895 D_Lequal
2039 Nothing 1896 Nothing
2040 False 1897 False
2041 "Tex_442868841") 1898 "Tex_442868841"
2042 (Cons 1899 : StageAttrs
2043 (StageAttrs
2044 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1900 (Just (HCons B_DstColor (HCons B_Zero HNil)))
2045 RGB_IdentityLighting 1901 RGB_IdentityLighting
2046 A_Identity 1902 A_Identity
@@ -2051,12 +1907,11 @@ sampleMaterial
2051 D_Lequal 1907 D_Lequal
2052 Nothing 1908 Nothing
2053 False 1909 False
2054 "Tex_3226210144") 1910 "Tex_3226210144"
2055 Nil)) 1911 : Nil)
2056 False) 1912 False)
2057 HNil)) 1913 HNil)
2058 (Cons 1914 : HCons
2059 (HCons
2060 "textures/gothic_wall/skull4" 1915 "textures/gothic_wall/skull4"
2061 (HCons 1916 (HCons
2062 (CommonAttrs 1917 (CommonAttrs
@@ -2070,8 +1925,7 @@ sampleMaterial
2070 Nil 1925 Nil
2071 False 1926 False
2072 False 1927 False
2073 (Cons 1928 (StageAttrs
2074 (StageAttrs
2075 Nothing 1929 Nothing
2076 RGB_IdentityLighting 1930 RGB_IdentityLighting
2077 A_Identity 1931 A_Identity
@@ -2082,9 +1936,8 @@ sampleMaterial
2082 D_Lequal 1936 D_Lequal
2083 Nothing 1937 Nothing
2084 False 1938 False
2085 "Tex_2239853403") 1939 "Tex_2239853403"
2086 (Cons 1940 : StageAttrs
2087 (StageAttrs
2088 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1941 (Just (HCons B_DstColor (HCons B_Zero HNil)))
2089 RGB_IdentityLighting 1942 RGB_IdentityLighting
2090 A_Identity 1943 A_Identity
@@ -2095,12 +1948,11 @@ sampleMaterial
2095 D_Lequal 1948 D_Lequal
2096 Nothing 1949 Nothing
2097 False 1950 False
2098 "Tex_3226210144") 1951 "Tex_3226210144"
2099 Nil)) 1952 : Nil)
2100 False) 1953 False)
2101 HNil)) 1954 HNil)
2102 (Cons 1955 : HCons
2103 (HCons
2104 "textures/gothic_wall/slateroofc" 1956 "textures/gothic_wall/slateroofc"
2105 (HCons 1957 (HCons
2106 (CommonAttrs 1958 (CommonAttrs
@@ -2114,8 +1966,7 @@ sampleMaterial
2114 Nil 1966 Nil
2115 False 1967 False
2116 False 1968 False
2117 (Cons 1969 (StageAttrs
2118 (StageAttrs
2119 Nothing 1970 Nothing
2120 RGB_IdentityLighting 1971 RGB_IdentityLighting
2121 A_Identity 1972 A_Identity
@@ -2126,9 +1977,8 @@ sampleMaterial
2126 D_Lequal 1977 D_Lequal
2127 Nothing 1978 Nothing
2128 False 1979 False
2129 "Tex_2490648334") 1980 "Tex_2490648334"
2130 (Cons 1981 : StageAttrs
2131 (StageAttrs
2132 (Just (HCons B_DstColor (HCons B_Zero HNil))) 1982 (Just (HCons B_DstColor (HCons B_Zero HNil)))
2133 RGB_IdentityLighting 1983 RGB_IdentityLighting
2134 A_Identity 1984 A_Identity
@@ -2139,12 +1989,11 @@ sampleMaterial
2139 D_Lequal 1989 D_Lequal
2140 Nothing 1990 Nothing
2141 False 1991 False
2142 "Tex_3226210144") 1992 "Tex_3226210144"
2143 Nil)) 1993 : Nil)
2144 False) 1994 False)
2145 HNil)) 1995 HNil)
2146 (Cons 1996 : HCons
2147 (HCons
2148 "textures/gothic_wall/supportborder_blue_b" 1997 "textures/gothic_wall/supportborder_blue_b"
2149 (HCons 1998 (HCons
2150 (CommonAttrs 1999 (CommonAttrs
@@ -2158,8 +2007,7 @@ sampleMaterial
2158 Nil 2007 Nil
2159 False 2008 False
2160 False 2009 False
2161 (Cons 2010 (StageAttrs
2162 (StageAttrs
2163 Nothing 2011 Nothing
2164 RGB_IdentityLighting 2012 RGB_IdentityLighting
2165 A_Identity 2013 A_Identity
@@ -2170,9 +2018,8 @@ sampleMaterial
2170 D_Lequal 2018 D_Lequal
2171 Nothing 2019 Nothing
2172 False 2020 False
2173 "Tex_564811775") 2021 "Tex_564811775"
2174 (Cons 2022 : StageAttrs
2175 (StageAttrs
2176 (Just (HCons B_DstColor (HCons B_Zero HNil))) 2023 (Just (HCons B_DstColor (HCons B_Zero HNil)))
2177 RGB_IdentityLighting 2024 RGB_IdentityLighting
2178 A_Identity 2025 A_Identity
@@ -2183,12 +2030,11 @@ sampleMaterial
2183 D_Lequal 2030 D_Lequal
2184 Nothing 2031 Nothing
2185 False 2032 False
2186 "Tex_3226210144") 2033 "Tex_3226210144"
2187 Nil)) 2034 : Nil)
2188 False) 2035 False)
2189 HNil)) 2036 HNil)
2190 (Cons 2037 : HCons
2191 (HCons
2192 "textures/gothic_wall/supportborder_blue_c" 2038 "textures/gothic_wall/supportborder_blue_c"
2193 (HCons 2039 (HCons
2194 (CommonAttrs 2040 (CommonAttrs
@@ -2202,8 +2048,7 @@ sampleMaterial
2202 Nil 2048 Nil
2203 False 2049 False
2204 False 2050 False
2205 (Cons 2051 (StageAttrs
2206 (StageAttrs
2207 Nothing 2052 Nothing
2208 RGB_IdentityLighting 2053 RGB_IdentityLighting
2209 A_Identity 2054 A_Identity
@@ -2214,9 +2059,8 @@ sampleMaterial
2214 D_Lequal 2059 D_Lequal
2215 Nothing 2060 Nothing
2216 False 2061 False
2217 "Tex_2525124732") 2062 "Tex_2525124732"
2218 (Cons 2063 : StageAttrs
2219 (StageAttrs
2220 (Just (HCons B_DstColor (HCons B_Zero HNil))) 2064 (Just (HCons B_DstColor (HCons B_Zero HNil)))
2221 RGB_IdentityLighting 2065 RGB_IdentityLighting
2222 A_Identity 2066 A_Identity
@@ -2227,11 +2071,11 @@ sampleMaterial
2227 D_Lequal 2071 D_Lequal
2228 Nothing 2072 Nothing
2229 False 2073 False
2230 "Tex_3226210144") 2074 "Tex_3226210144"
2231 Nil)) 2075 : Nil)
2232 False) 2076 False)
2233 HNil)) 2077 HNil)
2234 Nil)))))))))))))))))))))))))))))))))))))))))))))))))) 2078 : Nil)
2235main is not found 2079main is not found
2236------------ trace 2080------------ trace
2237sampleMaterial :: List (String, CommonAttrs) 2081sampleMaterial :: List (String, CommonAttrs)
diff --git a/testdata/record01.reject.out b/testdata/record01.reject.out
index cc4fe342..3af31081 100644
--- a/testdata/record01.reject.out
+++ b/testdata/record01.reject.out
@@ -170,7 +170,7 @@ testdata/record01.reject.lc 8:23-8:75
170 Type 170 Type
171 ImageKind 171 ImageKind
172 GetImageKind 172 GetImageKind
173 ('Cons (Image 1 'Depth) ('Cons (Image 1 ('Color (VecScalar 4 Float))) 'Nil))) 173 (: (Image 1 'Depth) (: (Image 1 ('Color (VecScalar 4 Float))) 'Nil)))
174testdata/record01.reject.lc 8:35-8:75 174testdata/record01.reject.lc 8:35-8:75
175 (Image 1 'Depth, Image 1 ('Color (VecScalar 4 Float))) 175 (Image 1 'Depth, Image 1 ('Color (VecScalar 4 Float)))
176testdata/record01.reject.lc 8:36-8:47 176testdata/record01.reject.lc 8:36-8:47
@@ -350,16 +350,16 @@ testdata/record01.reject.lc 19:50-19:62
350 forall (a :: PrimitiveType) . PrimitiveStream a ((Vec 4 Float)) 350 forall (a :: PrimitiveType) . PrimitiveStream a ((Vec 4 Float))
351testdata/record01.reject.lc 20:23-20:42 351testdata/record01.reject.lc 20:23-20:42
352 forall (a :: List Type) (b :: PrimitiveType) 352 forall (a :: List Type) (b :: PrimitiveType)
353 . RasterContext (HList ('Cons (Vec 4 Float) a)) b 353 . RasterContext (HList (: (Vec 4 Float) a)) b
354 -> HList (map Type Type Interpolated a) 354 -> HList (map Type Type Interpolated a)
355 -> List (Primitive (HList ('Cons (Vec 4 Float) a)) b) 355 -> List (Primitive (HList (: (Vec 4 Float) a)) b)
356 -> List (Vector 1 (Maybe (SimpleFragment (HList a)))) 356 -> List (Vector 1 (Maybe (SimpleFragment (HList a))))
357testdata/record01.reject.lc 20:23-20:52 357testdata/record01.reject.lc 20:23-20:52
358 HList (map Type Type Interpolated _a) 358 HList (map Type Type Interpolated _a)
359 -> List (Primitive (HList ('Cons (Vec 4 Float) _a)) 'Triangle) 359 -> List (Primitive (HList (: (Vec 4 Float) _a)) 'Triangle)
360 -> List (Vector 1 (Maybe (SimpleFragment (HList _a)))) 360 -> List (Vector 1 (Maybe (SimpleFragment (HList _a))))
361testdata/record01.reject.lc 20:23-20:63 361testdata/record01.reject.lc 20:23-20:63
362 List (Primitive (HList ('Cons (Vec 4 Float) _d)) 'Triangle) 362 List (Primitive (HList (: (Vec 4 Float) _d)) 'Triangle)
363 -> List (Vector 1 (Maybe (SimpleFragment (HList _d)))) 363 -> List (Vector 1 (Maybe (SimpleFragment (HList _d))))
364testdata/record01.reject.lc 20:23-20:79 364testdata/record01.reject.lc 20:23-20:79
365 List (Vector 1 (Maybe (SimpleFragment ((VecS Float 4))))) 365 List (Vector 1 (Maybe (SimpleFragment ((VecS Float 4)))))
@@ -437,18 +437,18 @@ testdata/record01.reject.lc 23:23-23:45
437 Type 437 Type
438 ImageKind 438 ImageKind
439 FragmentOperationKind 439 FragmentOperationKind
440 ('Cons 440 (:
441 (FragmentOperation 'Depth) 441 (FragmentOperation 'Depth)
442 ('Cons (FragmentOperation ('Color (VecScalar 4 Float))) 'Nil))) 442 (: (FragmentOperation ('Color (VecScalar 4 Float))) 'Nil)))
443 -> FrameBuffer 443 -> FrameBuffer
444 _b 444 _b
445 (map 445 (map
446 Type 446 Type
447 ImageKind 447 ImageKind
448 FragmentOperationKind 448 FragmentOperationKind
449 ('Cons 449 (:
450 (FragmentOperation 'Depth) 450 (FragmentOperation 'Depth)
451 ('Cons (FragmentOperation ('Color (VecScalar 4 Float))) 'Nil))) 451 (: (FragmentOperation ('Color (VecScalar 4 Float))) 'Nil)))
452testdata/record01.reject.lc 23:23-23:60 452testdata/record01.reject.lc 23:23-23:60
453 List (Vector _a (Maybe (SimpleFragment ((VecS Float 4))))) 453 List (Vector _a (Maybe (SimpleFragment ((VecS Float 4)))))
454 -> FrameBuffer 454 -> FrameBuffer
@@ -457,18 +457,18 @@ testdata/record01.reject.lc 23:23-23:60
457 Type 457 Type
458 ImageKind 458 ImageKind
459 FragmentOperationKind 459 FragmentOperationKind
460 ('Cons 460 (:
461 (FragmentOperation 'Depth) 461 (FragmentOperation 'Depth)
462 ('Cons (FragmentOperation ('Color (VecScalar 4 Float))) 'Nil))) 462 (: (FragmentOperation ('Color (VecScalar 4 Float))) 'Nil)))
463 -> FrameBuffer 463 -> FrameBuffer
464 _a 464 _a
465 (map 465 (map
466 Type 466 Type
467 ImageKind 467 ImageKind
468 FragmentOperationKind 468 FragmentOperationKind
469 ('Cons 469 (:
470 (FragmentOperation 'Depth) 470 (FragmentOperation 'Depth)
471 ('Cons (FragmentOperation ('Color (VecScalar 4 Float))) 'Nil))) 471 (: (FragmentOperation ('Color (VecScalar 4 Float))) 'Nil)))
472testdata/record01.reject.lc 23:23-23:75 472testdata/record01.reject.lc 23:23-23:75
473 FrameBuffer 473 FrameBuffer
474 1 474 1
@@ -476,18 +476,18 @@ testdata/record01.reject.lc 23:23-23:75
476 Type 476 Type
477 ImageKind 477 ImageKind
478 FragmentOperationKind 478 FragmentOperationKind
479 ('Cons 479 (:
480 (FragmentOperation 'Depth) 480 (FragmentOperation 'Depth)
481 ('Cons (FragmentOperation ('Color (VecScalar 4 Float))) 'Nil))) 481 (: (FragmentOperation ('Color (VecScalar 4 Float))) 'Nil)))
482 -> FrameBuffer 482 -> FrameBuffer
483 1 483 1
484 (map 484 (map
485 Type 485 Type
486 ImageKind 486 ImageKind
487 FragmentOperationKind 487 FragmentOperationKind
488 ('Cons 488 (:
489 (FragmentOperation 'Depth) 489 (FragmentOperation 'Depth)
490 ('Cons (FragmentOperation ('Color (VecScalar 4 Float))) 'Nil))) 490 (: (FragmentOperation ('Color (VecScalar 4 Float))) 'Nil)))
491testdata/record01.reject.lc 23:23-23:83 491testdata/record01.reject.lc 23:23-23:83
492 FrameBuffer 492 FrameBuffer
493 1 493 1
@@ -495,9 +495,9 @@ testdata/record01.reject.lc 23:23-23:83
495 Type 495 Type
496 ImageKind 496 ImageKind
497 FragmentOperationKind 497 FragmentOperationKind
498 ('Cons 498 (:
499 (FragmentOperation 'Depth) 499 (FragmentOperation 'Depth)
500 ('Cons (FragmentOperation ('Color (VecScalar 4 Float))) 'Nil))) 500 (: (FragmentOperation ('Color (VecScalar 4 Float))) 'Nil)))
501testdata/record01.reject.lc 23:34-23:45 501testdata/record01.reject.lc 23:34-23:45
502 (FragmentOperation 'Depth, FragmentOperation ('Color (VecScalar 4 Float))) 502 (FragmentOperation 'Depth, FragmentOperation ('Color (VecScalar 4 Float)))
503testdata/record01.reject.lc 23:46-23:60 503testdata/record01.reject.lc 23:46-23:60
@@ -511,12 +511,12 @@ testdata/record01.reject.lc 23:76-23:83
511 Type 511 Type
512 ImageKind 512 ImageKind
513 GetImageKind 513 GetImageKind
514 ('Cons (Image 1 'Depth) ('Cons (Image 1 ('Color (VecScalar 4 Float))) 'Nil))) 514 (: (Image 1 'Depth) (: (Image 1 ('Color (VecScalar 4 Float))) 'Nil)))
515testdata/record01.reject.lc 24:12-24:58 515testdata/record01.reject.lc 24:12-24:58
516 RecordC 516 RecordC
517 ('Cons 517 (:
518 ('RecItem "fieldA" Float) 518 ('RecItem "fieldA" Float)
519 ('Cons 519 (:
520 ('RecItem 520 ('RecItem
521 "fieldB" 521 "fieldB"
522 (FrameBuffer 522 (FrameBuffer
@@ -525,10 +525,10 @@ testdata/record01.reject.lc 24:12-24:58
525 Type 525 Type
526 ImageKind 526 ImageKind
527 FragmentOperationKind 527 FragmentOperationKind
528 ('Cons 528 (:
529 (FragmentOperation 'Depth) 529 (FragmentOperation 'Depth)
530 ('Cons (FragmentOperation ('Color (VecScalar 4 Float))) 'Nil))))) 530 (: (FragmentOperation ('Color (VecScalar 4 Float))) 'Nil)))))
531 ('Cons 531 (:
532 ('RecItem "fieldC" ((BlendEquation, BlendEquation) -> Blending Float)) 532 ('RecItem "fieldC" ((BlendEquation, BlendEquation) -> Blending Float))
533 'Nil))) 533 'Nil)))
534testdata/record01.reject.lc 24:13-24:19 534testdata/record01.reject.lc 24:13-24:19
@@ -547,9 +547,9 @@ testdata/record01.reject.lc 24:21-24:57
547 Type 547 Type
548 ImageKind 548 ImageKind
549 FragmentOperationKind 549 FragmentOperationKind
550 ('Cons 550 (:
551 (FragmentOperation 'Depth) 551 (FragmentOperation 'Depth)
552 ('Cons (FragmentOperation ('Color (VecScalar 4 Float))) 'Nil))))), recItemType 552 (: (FragmentOperation ('Color (VecScalar 4 Float))) 'Nil))))), recItemType
553 ('RecItem "fieldC" ((BlendEquation, BlendEquation) -> Blending Float))) 553 ('RecItem "fieldC" ((BlendEquation, BlendEquation) -> Blending Float)))
554testdata/record01.reject.lc 24:26-24:32 554testdata/record01.reject.lc 24:26-24:32
555 String | RecItem 555 String | RecItem
@@ -562,9 +562,9 @@ testdata/record01.reject.lc 24:34-24:39
562 Type 562 Type
563 ImageKind 563 ImageKind
564 FragmentOperationKind 564 FragmentOperationKind
565 ('Cons 565 (:
566 (FragmentOperation 'Depth) 566 (FragmentOperation 'Depth)
567 ('Cons (FragmentOperation ('Color (VecScalar 4 Float))) 'Nil))) 567 (: (FragmentOperation ('Color (VecScalar 4 Float))) 'Nil)))
568testdata/record01.reject.lc 24:34-24:57 568testdata/record01.reject.lc 24:34-24:57
569 (FrameBuffer 569 (FrameBuffer
570 1 570 1
@@ -572,9 +572,9 @@ testdata/record01.reject.lc 24:34-24:57
572 Type 572 Type
573 ImageKind 573 ImageKind
574 FragmentOperationKind 574 FragmentOperationKind
575 ('Cons 575 (:
576 (FragmentOperation 'Depth) 576 (FragmentOperation 'Depth)
577 ('Cons (FragmentOperation ('Color (VecScalar 4 Float))) 'Nil))), recItemType 577 (: (FragmentOperation ('Color (VecScalar 4 Float))) 'Nil))), recItemType
578 ('RecItem "fieldC" ((BlendEquation, BlendEquation) -> Blending Float))) 578 ('RecItem "fieldC" ((BlendEquation, BlendEquation) -> Blending Float)))
579testdata/record01.reject.lc 24:41-24:47 579testdata/record01.reject.lc 24:41-24:47
580 String | RecItem | List RecItem 580 String | RecItem | List RecItem
@@ -583,9 +583,9 @@ testdata/record01.reject.lc 24:49-24:57
583 -> Blending Float | (((BlendEquation, BlendEquation) -> Blending Float)) 583 -> Blending Float | (((BlendEquation, BlendEquation) -> Blending Float))
584testdata/record01.reject.lc 25:11-25:17 584testdata/record01.reject.lc 25:11-25:17
585 RecordC 585 RecordC
586 ('Cons 586 (:
587 ('RecItem "fieldA" Float) 587 ('RecItem "fieldA" Float)
588 ('Cons 588 (:
589 ('RecItem 589 ('RecItem
590 "fieldB" 590 "fieldB"
591 (FrameBuffer 591 (FrameBuffer
@@ -594,10 +594,10 @@ testdata/record01.reject.lc 25:11-25:17
594 Type 594 Type
595 ImageKind 595 ImageKind
596 FragmentOperationKind 596 FragmentOperationKind
597 ('Cons 597 (:
598 (FragmentOperation 'Depth) 598 (FragmentOperation 'Depth)
599 ('Cons (FragmentOperation ('Color (VecScalar 4 Float))) 'Nil))))) 599 (: (FragmentOperation ('Color (VecScalar 4 Float))) 'Nil)))))
600 ('Cons 600 (:
601 ('RecItem "fieldC" ((BlendEquation, BlendEquation) -> Blending Float)) 601 ('RecItem "fieldC" ((BlendEquation, BlendEquation) -> Blending Float))
602 'Nil))) 602 'Nil)))
603testdata/record01.reject.lc 25:11-25:24 603testdata/record01.reject.lc 25:11-25:24
@@ -608,9 +608,9 @@ testdata/record01.reject.lc 26:5-26:14
608 forall (a :: Nat) (b :: List ImageKind) . FrameBuffer a b -> Output 608 forall (a :: Nat) (b :: List ImageKind) . FrameBuffer a b -> Output
609testdata/record01.reject.lc 26:15-26:21 609testdata/record01.reject.lc 26:15-26:21
610 RecordC 610 RecordC
611 ('Cons 611 (:
612 ('RecItem "fieldA" Float) 612 ('RecItem "fieldA" Float)
613 ('Cons 613 (:
614 ('RecItem 614 ('RecItem
615 "fieldB" 615 "fieldB"
616 (FrameBuffer 616 (FrameBuffer
@@ -619,10 +619,10 @@ testdata/record01.reject.lc 26:15-26:21
619 Type 619 Type
620 ImageKind 620 ImageKind
621 FragmentOperationKind 621 FragmentOperationKind
622 ('Cons 622 (:
623 (FragmentOperation 'Depth) 623 (FragmentOperation 'Depth)
624 ('Cons (FragmentOperation ('Color (VecScalar 4 Float))) 'Nil))))) 624 (: (FragmentOperation ('Color (VecScalar 4 Float))) 'Nil)))))
625 ('Cons 625 (:
626 ('RecItem "fieldC" ((BlendEquation, BlendEquation) -> Blending Float)) 626 ('RecItem "fieldC" ((BlendEquation, BlendEquation) -> Blending Float))
627 'Nil))) 627 'Nil)))
628testdata/record01.reject.lc 26:15-26:28 628testdata/record01.reject.lc 26:15-26:28
diff --git a/testdata/traceTest.out b/testdata/traceTest.out
index 4ab055c6..ef065db6 100644
--- a/testdata/traceTest.out
+++ b/testdata/traceTest.out
@@ -2,7 +2,7 @@
2id = \(a :: _) -> _rhs a 2id = \(a :: _) -> _rhs a
3data X (_ :: Type) (_ :: _a) :: Type where 3data X (_ :: Type) (_ :: _a) :: Type where
4 4
5x = _rhs undefined :: X \(a :: _) (b :: _) -> HList ('Cons a ('Cons b 'Nil)) 5x = _rhs undefined :: X \(a :: _) (b :: _) -> HList (a : b : 'Nil)
6main is not found 6main is not found
7------------ trace 7------------ trace
8id :: forall a . a -> a 8id :: forall a . a -> a
diff --git a/testdata/zip01.out b/testdata/zip01.out
index 21511345..b14eadeb 100644
--- a/testdata/zip01.out
+++ b/testdata/zip01.out
@@ -9,8 +9,7 @@ zip2
9 \(e :: _) (f :: _) -> _rhs (HCons c (HCons e HNil) : zip2 d f) 9 \(e :: _) (f :: _) -> _rhs (HCons c (HCons e HNil) : zip2 d f)
10 b 10 b
11 a) 11 a)
12 :: forall (g :: _) (h :: _) 12 :: forall (g :: _) (h :: _) . List g -> List h -> List (HList (g : h : 'Nil))
13 . List g -> List h -> List (HList ('Cons g ('Cons h 'Nil)))
14main is not found 13main is not found
15------------ trace 14------------ trace
16zip2 :: forall a b . List a -> List b -> List (a, b) 15zip2 :: forall a b . List a -> List b -> List (a, b)