From 438e4a1b062a73b667adf0fd94167dcc311929d3 Mon Sep 17 00:00:00 2001 From: Péter Diviánszky Date: Mon, 2 May 2016 17:52:01 +0200 Subject: more list syntax in pretty print --- src/LambdaCube/Compiler/DesugaredSource.hs | 2 +- src/LambdaCube/Compiler/Pretty.hs | 4 + testdata/Builtins.out | 565 ++-- testdata/Internals.out | 84 +- testdata/Material.out | 95 +- testdata/Prelude.out | 449 ++- testdata/SampleMaterial.out | 3090 +++++++++----------- testdata/data.out | 8 +- testdata/framebuffer02.reject.out | 4 +- testdata/language-features/basic-list/list01.out | 32 +- testdata/language-features/basic-list/list02.out | 32 +- testdata/language-features/basic-list/list08.out | 8 +- testdata/language-features/basic-list/list09.out | 10 +- testdata/language-features/basic-list/list11.out | 12 +- testdata/language-features/basic-list/list12.out | 36 +- testdata/language-features/basic-list/list13.out | 36 +- .../language-features/basic-list/list14.reject.out | 12 +- .../language-features/basic-list/list15.reject.out | 12 +- .../language-features/basic-list/list16.reject.out | 8 +- .../language-features/basic-list/listcomp01.out | 16 +- .../language-features/basic-list/listcomp02.out | 22 +- .../language-features/basic-list/listcomp03.out | 18 +- .../language-features/basic-list/listcomp04.out | 26 +- .../language-features/basic-list/listcomp05.out | 10 +- .../language-features/basic-list/listcomp06.out | 26 +- .../language-features/basic-list/listcomp07.out | 30 +- .../language-features/basic-list/listcomp09.out | 10 +- testdata/language-features/basic-values/data01.out | 4 +- .../language-features/basic-values/fixity02.out | 4 +- .../language-features/basic-values/infix03.out | 4 +- .../language-features/basic-values/typesig03.out | 4 +- .../language-features/basic-values/typesig04.out | 4 +- .../language-features/basic-values/typesig07.out | 6 +- testdata/language-features/pattern/uncovered.out | 8 +- testdata/performance/Material.out | 95 +- testdata/performance/SampleMaterial.out | 3090 +++++++++----------- testdata/record01.reject.out | 92 +- testdata/traceTest.out | 6 +- testdata/zip01.out | 36 +- 39 files changed, 3639 insertions(+), 4371 deletions(-) diff --git a/src/LambdaCube/Compiler/DesugaredSource.hs b/src/LambdaCube/Compiler/DesugaredSource.hs index 5d3a70f3..f0af5437 100644 --- a/src/LambdaCube/Compiler/DesugaredSource.hs +++ b/src/LambdaCube/Compiler/DesugaredSource.hs @@ -453,7 +453,7 @@ instance PShow Stmt where pShow stmt = DResetFreshNames $ case stmt of Primitive n t -> shAnn (pShow n) (pShow t) Let n ty e -> DLet "=" (pShow n) $ maybe (pShow e) (\ty -> shAnn (pShow e) (pShow ty)) ty - Data n ps ty cs -> nest 2 $ "data" <+> nest 2 (shAnn (foldl dApp (DTypeNamespace True $ pShow n) [shAnn (text "_") (pShow t) | (v, t) <- ps]) (pShow ty)) "where" <> nest 2 (hardline <> vcat [shAnn (pShow n) $ pShow t | (n, t) <- cs]) + Data n ps ty cs -> nest 2 $ "data" <+> nest 2 (shAnn (foldl dApp (DTypeNamespace True $ pShow n) [shAnn (text "_") (pShow t) | (v, t) <- ps]) (pShow ty)) "where" <> nest 2 (hardline <> vcat [shAnn (pShow n) $ pShow $ UncurryS (first (const Hidden) <$> ps) t | (n, t) <- cs]) PrecDef n i -> pShow i <+> shortForm (pShow n) --DOp0 (sName n) i instance DeBruijnify SIName Stmt where diff --git a/src/LambdaCube/Compiler/Pretty.hs b/src/LambdaCube/Compiler/Pretty.hs index 6a80da1f..6f8fdb20 100644 --- a/src/LambdaCube/Compiler/Pretty.hs +++ b/src/LambdaCube/Compiler/Pretty.hs @@ -159,6 +159,7 @@ renderDoc addPar :: Bool -> Fixity -> Doc -> Doc addPar tn pr x = case x of DAtom x -> DAtom $ addParA x + DText "'List" `DApp` x -> addPar tn pr $ DBracket x DOp0 s f -> DParen $ DOp0 s f DOp0 s f `DApp` x `DApp` y -> addPar tn pr $ DOp (addBackquotes s) f x y -- DOpL s f x -> DParen $ DOpL s f $ addPar tn (InfixL $ leftPrecedence f) x @@ -199,12 +200,14 @@ renderDoc where render' = \case DText "Nil" -> rtext "[]" + DText "'Nil" -> rtext "'[]" DAtom x -> renderA x DFormat c x -> second c $ render' x DDocOp f d -> (('\0', '\0'), f $ render <$> d) DPreOp _ op y -> renderA op <++> render' y DSep (InfixR 11) a b -> gr $ render' a <+++> render' b x@DApp{} -> case getApps x of +-- (DText "List", [x]) -> gr $ rtext "[" <+++> render' x <++> rtext "]" (n, reverse -> xs) -> ((\xs -> (fst $ head xs, snd $ last xs)) *** P.nest 2 . P.sep) (unzip $ render' n: (render' <$> xs)) DInfix _ x op y -> gr $ render' x <+++> renderA op <++> render' y @@ -293,6 +296,7 @@ pattern DPar l d r = DAtom (ComplexAtom l (-20) d (SimpleAtom r)) pattern DParen x = DPar "(" x ")" pattern DBrace x = DPar "{" x "}" +pattern DBracket x = DPar "[" x "]" pattern DOp s f l r = DInfix f l (SimpleAtom s) r pattern DOp0 s f = DOp s f (DText "") (DText "") pattern DSep p a b = DOp " " p a b diff --git a/testdata/Builtins.out b/testdata/Builtins.out index 85fa9d7f..4010c01b 100644 --- a/testdata/Builtins.out +++ b/testdata/Builtins.out @@ -1,9 +1,9 @@ ------------ desugared source code id = \(a :: _) -> _rhs a data VecS (_ :: Type) :: Nat -> Type where - V2 :: _a -> _a -> VecS _a (fromInt 2) - V3 :: _a -> _a -> _a -> VecS _a (fromInt 3) - V4 :: _a -> _a -> _a -> _a -> VecS _a (fromInt 4) + V2 :: forall a . a -> a -> VecS a (fromInt 2) + V3 :: forall b . b -> b -> b -> VecS b (fromInt 3) + V4 :: forall c . c -> c -> c -> c -> VecS c (fromInt 4) mapVec = (\(a :: _) (b :: _) -> 'VecSCase \_ -> \_ -> _ :: _ @@ -566,7 +566,7 @@ PrimSign :: forall (a :: _) (b :: _) (c :: _) . (Signed a, b ~ VecScalar c a) => b -> b PrimModF :: forall (a :: _) (b :: _) - . (a ~ VecScalar b Float) => a -> HList (a : a : 'Nil) + . (a ~ VecScalar b Float) => a -> HList (a : a : '[]) PrimClamp :: forall (a :: _) (b :: _) (c :: _) . (Num a, b ~ VecScalar c a) => b -> b -> b -> b @@ -671,7 +671,7 @@ map b concatMap = (\(a :: _) (b :: _) -> _rhs (concat (map a b))) - :: forall (c :: _) (d :: _) . (c -> List d) -> List c -> List d + :: forall (c :: _) (d :: _) . (c -> [d]) -> [c] -> [d] len = \(a :: _) -> 'ListCase \_ -> _ :: _ @@ -679,8 +679,8 @@ len \_ (b :: _) -> _rhs (fromInt 1 `primAddInt` len b) a data Maybe (_ :: Type) :: Type where - Nothing :: Maybe _a - Just :: _a -> Maybe _a + Nothing :: forall a . Maybe a + Just :: forall b . b -> Maybe b data Vector (_ :: Nat) (_ :: Type) :: Type where data PrimitiveType :: Type where @@ -690,13 +690,13 @@ data PrimitiveType :: Type where TriangleAdjacency :: PrimitiveType LineAdjacency :: PrimitiveType data Primitive (_ :: Type) :: PrimitiveType -> Type where - PrimPoint :: _a -> Primitive _a Point - PrimLine :: _a -> _a -> Primitive _a Line - PrimTriangle :: _a -> _a -> _a -> Primitive _a Triangle + PrimPoint :: forall a . a -> Primitive a Point + PrimLine :: forall b . b -> b -> Primitive b Line + PrimTriangle :: forall c . c -> c -> c -> Primitive c Triangle mapPrimitive :: forall (a :: _) (b :: _) (c :: _) . (a -> b) -> Primitive a c -> Primitive b c -'PrimitiveStream = \(a :: _) (b :: _) -> _rhs ('List ('Primitive b a)) +'PrimitiveStream = \(a :: _) (b :: _) -> _rhs ['Primitive b a] mapPrimitives = (\(a :: _) -> _rhs (map (mapPrimitive a))) :: forall (b :: _) (c :: _) (d :: _) @@ -711,17 +711,17 @@ fetch :: forall (a :: _) (b :: _) . String -> HList b -> PrimitiveStream a (HList b) Attribute :: forall (a :: _) . String -> a fetchStream - :: forall (a :: _) (b :: List Type) + :: forall (a :: _) (b :: [Type]) . String - -> forall (c :: List String) -> (len c ~ len b) => PrimitiveStream a (HList b) + -> forall (c :: [String]) -> (len c ~ len b) => PrimitiveStream a (HList b) data SimpleFragment (_ :: Type) :: Type where - SimpleFragment :: Vec (fromInt 3) Float -> _a -> SimpleFragment _a + SimpleFragment :: forall a . Vec (fromInt 3) Float -> a -> SimpleFragment a 'Fragment = \(a :: _) (b :: _) -> _rhs ('Vector a ('Maybe ('SimpleFragment b))) sFragmentCoords = \(a :: _) -> 'SimpleFragmentCase \_ -> _ :: _ \(b :: _) -> \_ -> _rhs b a sFragmentValue = \(a :: _) -> 'SimpleFragmentCase \_ -> _ :: _ \_ (b :: _) -> _rhs b a -'FragmentStream = \(a :: _) (b :: _) -> _rhs ('List ('Fragment a b)) +'FragmentStream = \(a :: _) (b :: _) -> _rhs ['Fragment a b] customizeDepth :: forall (a :: _) (b :: _) . (a -> Float) -> Fragment b a -> Fragment b a customizeDepths @@ -872,36 +872,37 @@ data CullMode :: Type where CullBack :: CullMode CullNone :: CullMode data PointSize (_ :: Type) :: Type where - PointSize :: Float -> PointSize _a - ProgramPointSize :: (_a -> Float) -> PointSize _a + PointSize :: forall a . Float -> PointSize a + ProgramPointSize :: forall b . (b -> Float) -> PointSize b data PolygonMode (_ :: Type) :: Type where - PolygonFill :: PolygonMode _a - PolygonPoint :: PointSize _a -> PolygonMode _a - PolygonLine :: Float -> PolygonMode _a + PolygonFill :: forall a . PolygonMode a + PolygonPoint :: forall b . PointSize b -> PolygonMode b + PolygonLine :: forall c . Float -> PolygonMode c data PolygonOffset :: Type where NoOffset :: PolygonOffset Offset :: Float -> Float -> PolygonOffset data PointSpriteCoordOrigin :: Type where LowerLeft :: PointSpriteCoordOrigin UpperLeft :: PointSpriteCoordOrigin -primTexture :: HList 'Nil -> Vec (fromInt 2) Float -> Vec (fromInt 4) Float +primTexture :: HList '[] -> Vec (fromInt 2) Float -> Vec (fromInt 4) Float Uniform :: forall (a :: _) . String -> a data RasterContext (_ :: Type) :: PrimitiveType -> Type where TriangleCtx - :: CullMode - -> PolygonMode _a - -> PolygonOffset -> ProvokingVertex -> RasterContext _a Triangle + :: forall a + . CullMode + -> PolygonMode a -> PolygonOffset -> ProvokingVertex -> RasterContext a Triangle PointCtx - :: PointSize _a -> Float -> PointSpriteCoordOrigin -> RasterContext _a Point - LineCtx :: Float -> ProvokingVertex -> RasterContext _a Line + :: forall b + . PointSize b -> Float -> PointSpriteCoordOrigin -> RasterContext b Point + LineCtx :: forall c . Float -> ProvokingVertex -> RasterContext c Line data Blending :: Type -> Type where NoBlending :: forall (a :: _) . Blending a BlendLogicOp :: forall (b :: _) . Integral b => LogicOperation -> Blending b Blend - :: HList (BlendEquation : BlendEquation : 'Nil) + :: HList (BlendEquation : BlendEquation : '[]) -> HList - (HList (BlendingFactor : BlendingFactor : 'Nil) - : HList (BlendingFactor : BlendingFactor : 'Nil) : 'Nil) + (HList (BlendingFactor : BlendingFactor : '[]) + : HList (BlendingFactor : BlendingFactor : '[]) : '[]) -> Vec (fromInt 4) Float -> Blending Float data StencilTests :: Type where @@ -916,9 +917,9 @@ data FragmentOperation :: ImageKind -> Type where StencilOp :: StencilTests -> StencilOps -> StencilOps -> FragmentOperation Stencil data Interpolated (_ :: Type) :: Type where - Smooth :: Floating _a => Interpolated _a - NoPerspective :: Floating _a => Interpolated _a - Flat :: Interpolated _a + Smooth :: forall a . Floating a => Interpolated a + NoPerspective :: forall b . Floating b => Interpolated b + Flat :: forall c . Interpolated c rasterizePrimitive :: forall (a :: _) (b :: _) (c :: _) (d :: _) . (map Interpolated a ~ b, c ~ Vec (fromInt 4) Float : a) @@ -940,9 +941,9 @@ allSame \(d :: _) (e :: _) -> _rhs ('T2 (b ~ d) (allSame (d : e))) c a) - :: forall (f :: _) . List f -> Type + :: forall (f :: _) . [f] -> Type sameLayerCounts = \(a :: _) -> _rhs (allSame (map 'ImageLC a)) -data FrameBuffer (_ :: Nat) (_ :: List ImageKind) :: Type where +data FrameBuffer (_ :: Nat) (_ :: [ImageKind]) :: Type where imageType' = (\(a :: _) -> 'ListCase @@ -955,12 +956,12 @@ imageType' (_rhs (map imageType a)) b a) - :: List ImageKind -> List Type + :: [ImageKind] -> [Type] 'FragmentOperationKind = (\(a :: _) -> match'FragmentOperation \_ -> _ \(b :: _) -> _rhs b a undefined) :: Type -> ImageKind Accumulate - :: forall (a :: _) (b :: Nat) (c :: List Type) + :: forall (a :: _) (b :: Nat) (c :: [Type]) . (a ~ map FragmentOperationKind c) => HList c -> FragmentStream b (HList (imageType' a)) -> FrameBuffer b a -> FrameBuffer b a @@ -978,7 +979,7 @@ infixl 0 overlay = (\(a :: _) -> match'Image \_ -> _ \_ (b :: _) -> _rhs b a undefined) :: Type -> ImageKind FrameBuffer - :: forall (a :: List Type) + :: forall (a :: [Type]) . sameLayerCounts a => HList a -> FrameBuffer (ImageLC (head a)) (map GetImageKind a) imageFrame = _rhs FrameBuffer @@ -986,9 +987,9 @@ accumulate = \(a :: _) (b :: _) (c :: _) (d :: _) -> _rhs (Accumulate a (mapFragments b c) d) PrjImage - :: forall (a :: _) . FrameBuffer (fromInt 1) (a : 'Nil) -> Image (fromInt 1) a + :: forall (a :: _) . FrameBuffer (fromInt 1) (a : '[]) -> Image (fromInt 1) a PrjImageColor - :: FrameBuffer (fromInt 1) ('Depth : 'Color (Vec (fromInt 4) Float) : 'Nil) + :: FrameBuffer (fromInt 1) ('Depth : 'Color (Vec (fromInt 4) Float) : '[]) -> Image (fromInt 1) (Color (Vec (fromInt 4) Float)) data Output :: Type where ScreenOut :: forall (a :: _) (b :: _) . FrameBuffer a b -> Output @@ -1222,13 +1223,13 @@ PrimNoise1 :: forall (a :: Nat) . VecScalar a Float -> Float PrimNoise2 :: forall (a :: Nat) . VecScalar a Float -> Vec 2 Float PrimNoise3 :: forall (a :: Nat) . VecScalar a Float -> Vec 3 Float PrimNoise4 :: forall (a :: Nat) . VecScalar a Float -> Vec 4 Float -head :: forall a . List a -> a -++ :: forall a . List a -> List a -> List a -foldr :: forall a b . (b -> a -> a) -> a -> List b -> a -concat :: forall a . List (List a) -> List a -map :: forall a b . (a -> b) -> List a -> List b -concatMap :: forall a b . (a -> List b) -> List a -> List b -len :: forall a . List a -> Int +head :: forall a . [a] -> a +++ :: forall a . [a] -> [a] -> [a] +foldr :: forall a b . (b -> a -> a) -> a -> [b] -> a +concat :: forall a . [[a]] -> [a] +map :: forall a b . (a -> b) -> [a] -> [b] +concatMap :: forall a b . (a -> [b]) -> [a] -> [b] +len :: forall a . [a] -> Int 'Maybe :: Type -> Type Nothing :: forall a . Maybe a Just :: forall a . a -> Maybe a @@ -1282,19 +1283,19 @@ mapPrimitive 'PrimitiveStream :: PrimitiveType -> Type -> Type mapPrimitives :: forall a b (c :: PrimitiveType) - . (a -> b) -> List (Primitive a c) -> List (Primitive b c) + . (a -> b) -> [Primitive a c] -> [Primitive b c] 'ListElem :: Type -> Type fetchArrays - :: forall (a :: PrimitiveType) (b :: List Type) (c :: List Type) + :: forall (a :: PrimitiveType) (b :: [Type]) (c :: [Type]) . (b ~ map Type Type ListElem c) => HList c -> PrimitiveStream a (HList b) fetch - :: forall (a :: PrimitiveType) (b :: List Type) + :: forall (a :: PrimitiveType) (b :: [Type]) . String -> HList b -> PrimitiveStream a (HList b) Attribute :: forall a . String -> a fetchStream - :: forall (a :: PrimitiveType) (b :: List Type) + :: forall (a :: PrimitiveType) (b :: [Type]) . String - -> forall (c :: List String) + -> forall (c :: [String]) -> (len String c ~ len Type b) => PrimitiveStream a (HList b) 'SimpleFragment :: Type -> Type SimpleFragment :: forall a . Vec 3 Float -> a -> SimpleFragment a @@ -1315,21 +1316,21 @@ customizeDepth customizeDepths :: forall a (b :: Nat) . (a -> Float) - -> List (Vector b (Maybe (SimpleFragment a))) - -> List (Vector b (Maybe (SimpleFragment a))) + -> [Vector b (Maybe (SimpleFragment a))] + -> [Vector b (Maybe (SimpleFragment a))] filterFragment :: forall a (b :: Nat) . (a -> Bool) -> Fragment b a -> Fragment b a filterFragments :: forall a (b :: Nat) . (a -> Bool) - -> List (Vector b (Maybe (SimpleFragment a))) - -> List (Vector b (Maybe (SimpleFragment a))) + -> [Vector b (Maybe (SimpleFragment a))] + -> [Vector b (Maybe (SimpleFragment a))] mapFragment :: forall a b (c :: Nat) . (a -> b) -> Fragment c a -> Fragment c b mapFragments :: forall a b (c :: Nat) . (a -> b) - -> List (Vector c (Maybe (SimpleFragment a))) - -> List (Vector c (Maybe (SimpleFragment b))) + -> [Vector c (Maybe (SimpleFragment a))] + -> [Vector c (Maybe (SimpleFragment b))] 'ImageKind :: Type Color :: Type -> ImageKind Depth :: ImageKind @@ -1646,75 +1647,74 @@ match'Interpolated :: forall (a :: Type -> Type) -> (forall b -> a (Interpolated b)) -> forall c -> a c -> a c rasterizePrimitive - :: forall (a :: List Type) - (b :: List Type) (c :: List Type) (d :: PrimitiveType) + :: forall (a :: [Type]) (b :: [Type]) (c :: [Type]) (d :: PrimitiveType) . (map Type Type Interpolated a ~ b, c ~ : (Vec 4 Float) a) => HList b -> RasterContext (HList c) d -> Primitive (HList c) d -> FragmentStream 1 (HList a) rasterizePrimitives - :: forall (a :: List Type) (b :: PrimitiveType) + :: forall (a :: [Type]) (b :: PrimitiveType) . RasterContext (HList (: (Vec 4 Float) a)) b -> HList (map Type Type Interpolated a) - -> List (Primitive (HList (: (Vec 4 Float) a)) b) - -> List (Vector 1 (Maybe (SimpleFragment (HList a)))) + -> [Primitive (HList (: (Vec 4 Float) a)) b] + -> [Vector 1 (Maybe (SimpleFragment (HList a)))] 'ImageLC :: Type -> Nat -allSame :: forall a . List a -> Type -sameLayerCounts :: List Type -> Type -'FrameBuffer :: Nat -> List ImageKind -> Type +allSame :: forall a . [a] -> Type +sameLayerCounts :: [Type] -> Type +'FrameBuffer :: Nat -> [ImageKind] -> Type 'FrameBufferCase - :: forall (a :: Nat) (b :: List ImageKind) + :: forall (a :: Nat) (b :: [ImageKind]) . forall (c :: FrameBuffer a b -> Type) (d :: FrameBuffer a b) -> c d match'FrameBuffer :: forall (a :: Type -> Type) - -> (forall (b :: Nat) (c :: List ImageKind) -> a (FrameBuffer b c)) + -> (forall (b :: Nat) (c :: [ImageKind]) -> a (FrameBuffer b c)) -> forall d -> a d -> a d -imageType' :: List ImageKind -> List Type +imageType' :: [ImageKind] -> [Type] 'FragmentOperationKind :: Type -> ImageKind Accumulate - :: forall (a :: List ImageKind) (b :: Nat) (c :: List Type) + :: forall (a :: [ImageKind]) (b :: Nat) (c :: [Type]) . (a ~ map Type ImageKind FragmentOperationKind c) => HList c -> FragmentStream b (HList (imageType' a)) -> FrameBuffer b a -> FrameBuffer b a accumulateWith :: forall a b . a -> b -> (a, b) overlay - :: forall (a :: Nat) (b :: List Type) + :: forall (a :: Nat) (b :: [Type]) . FrameBuffer a (map Type ImageKind FragmentOperationKind b) - -> (HList b, List - (Fragment a (HList (imageType' (map Type ImageKind FragmentOperationKind b))))) + -> (HList b, [Fragment + a + (HList (imageType' (map Type ImageKind FragmentOperationKind b)))]) -> FrameBuffer a (map Type ImageKind FragmentOperationKind b) 'GetImageKind :: Type -> ImageKind FrameBuffer - :: forall (a :: List Type) + :: forall (a :: [Type]) . sameLayerCounts a => HList a -> FrameBuffer (ImageLC (head Type a)) (map Type ImageKind GetImageKind a) imageFrame - :: forall (a :: List Type) + :: forall (a :: [Type]) . sameLayerCounts a => HList a -> FrameBuffer (ImageLC (head Type a)) (map Type ImageKind GetImageKind a) accumulate - :: forall (a :: Nat) (b :: List Type) c + :: forall (a :: Nat) (b :: [Type]) c . HList b -> (c -> HList (imageType' (map Type ImageKind FragmentOperationKind b))) - -> List (Vector a (Maybe (SimpleFragment c))) + -> [Vector a (Maybe (SimpleFragment c))] -> FrameBuffer a (map Type ImageKind FragmentOperationKind b) -> FrameBuffer a (map Type ImageKind FragmentOperationKind b) -PrjImage :: forall (a :: ImageKind) . FrameBuffer 1 (: a 'Nil) -> Image 1 a +PrjImage :: forall (a :: ImageKind) . FrameBuffer 1 (: a '[]) -> Image 1 a PrjImageColor - :: FrameBuffer 1 (: 'Depth (: ('Color (Vec 4 Float)) 'Nil)) + :: FrameBuffer 1 (: 'Depth (: ('Color (Vec 4 Float)) '[])) -> Image 1 ('Color (Vec 4 Float)) 'Output :: Type -ScreenOut :: forall (a :: Nat) (b :: List ImageKind) . FrameBuffer a b -> Output +ScreenOut :: forall (a :: Nat) (b :: [ImageKind]) . FrameBuffer a b -> Output 'OutputCase :: forall (a :: Output -> Type) - -> (forall (b :: Nat) (c :: List ImageKind) + -> (forall (b :: Nat) (c :: [ImageKind]) . forall (d :: FrameBuffer b c) -> a ('ScreenOut b c d)) -> forall (e :: Output) -> a e match'Output :: forall (a :: Type -> Type) -> a Output -> forall b -> a b -> a b -renderFrame - :: forall (a :: Nat) (b :: List ImageKind) . FrameBuffer a b -> Output +renderFrame :: forall (a :: Nat) (b :: [ImageKind]) . FrameBuffer a b -> Output 'Texture :: Type Texture2DSlot :: String -> Texture Texture2D :: Vec 2 Int -> Image 1 ('Color (Vec 4 Float)) -> Texture @@ -3628,9 +3628,9 @@ testdata/Builtins.lc 145:66-145:72 testdata/Builtins.lc 145:67-145:68 Type testdata/Builtins.lc 145:67-145:71 - List Type + [Type] testdata/Builtins.lc 145:70-145:71 - Type | List Type + Type | [Type] testdata/Builtins.lc 146:1-146:10 forall a b (c :: Nat) . (Num a, b ~ VecScalar c a) => b -> b -> b -> b testdata/Builtins.lc 146:34-146:80 @@ -4761,35 +4761,35 @@ testdata/Builtins.lc 187:59-187:60 testdata/Builtins.lc 187:61-187:66 Type testdata/Builtins.lc 201:1-201:5 - forall a . List a -> a + forall a . [a] -> a testdata/Builtins.lc 201:15-201:16 _d testdata/Builtins.lc 203:6-203:8 - forall a . List a -> List a -> List a + forall a . [a] -> [a] -> [a] testdata/Builtins.lc 203:14-203:16 _d testdata/Builtins.lc 203:14-204:26 - List _a -> List _a + [_a] -> [_a] testdata/Builtins.lc 204:14-204:15 _d testdata/Builtins.lc 204:14-204:17 - List _c -> List _c + [_c] -> [_c] testdata/Builtins.lc 204:14-204:26 - List _c + [_c] testdata/Builtins.lc 204:16-204:17 - forall a . a -> List a -> List a + forall a . a -> [a] -> [a] testdata/Builtins.lc 204:18-204:20 - List _f + [_f] testdata/Builtins.lc 204:21-204:23 _h testdata/Builtins.lc 204:24-204:26 - List _g + [_g] testdata/Builtins.lc 206:1-206:6 - forall a b . (b -> a -> a) -> a -> List b -> a + forall a b . (b -> a -> a) -> a -> [b] -> a testdata/Builtins.lc 206:16-206:17 _f testdata/Builtins.lc 206:16-207:39 - List _b -> _f + [_b] -> _f testdata/Builtins.lc 207:21-207:22 _i testdata/Builtins.lc 207:23-207:24 @@ -4801,41 +4801,41 @@ testdata/Builtins.lc 207:32-207:33 testdata/Builtins.lc 207:34-207:35 _o testdata/Builtins.lc 207:36-207:38 - List _k + [_k] testdata/Builtins.lc 209:1-209:7 - forall a . List (List a) -> List a + forall a . [[a]] -> [a] testdata/Builtins.lc 209:10-209:15 - forall a b . (b -> a -> a) -> a -> List b -> a + forall a b . (b -> a -> a) -> a -> [b] -> a testdata/Builtins.lc 209:10-209:20 - List _a -> List (List _a) -> List _a + [_a] -> [[_a]] -> [_a] testdata/Builtins.lc 209:10-209:23 - List (List _a) -> List _a + [[_a]] -> [_a] testdata/Builtins.lc 209:16-209:20 - forall a . List a -> List a -> List a + forall a . [a] -> [a] -> [a] testdata/Builtins.lc 209:21-209:23 - forall a . List a + forall a . [a] testdata/Builtins.lc 211:1-211:4 - forall a b . (a -> b) -> List a -> List b + forall a b . (a -> b) -> [a] -> [b] testdata/Builtins.lc 211:16-211:18 - forall a . List a + forall a . [a] testdata/Builtins.lc 211:16-212:30 - List _b -> List _a + [_b] -> [_a] testdata/Builtins.lc 212:16-212:17 _i testdata/Builtins.lc 212:16-212:21 - List _a -> List _a + [_a] -> [_a] testdata/Builtins.lc 212:16-212:30 - List _c + [_c] testdata/Builtins.lc 212:18-212:19 _h testdata/Builtins.lc 212:20-212:21 - forall a . a -> List a -> List a + forall a . a -> [a] -> [a] testdata/Builtins.lc 212:22-212:25 _i testdata/Builtins.lc 212:26-212:27 _g -> _f testdata/Builtins.lc 212:28-212:30 - List _h + [_h] testdata/Builtins.lc 214:14-214:38 Type | Type testdata/Builtins.lc 214:15-214:16 @@ -4855,27 +4855,27 @@ testdata/Builtins.lc 214:35-214:38 testdata/Builtins.lc 214:36-214:37 Type testdata/Builtins.lc 215:1-215:10 - forall a b . (a -> List b) -> List a -> List b + forall a b . (a -> [b]) -> [a] -> [b] testdata/Builtins.lc 215:17-215:23 - forall a . List (List a) -> List a + forall a . [[a]] -> [a] testdata/Builtins.lc 215:17-215:33 - List _c + [_c] testdata/Builtins.lc 215:25-215:28 - forall a b . (a -> b) -> List a -> List b + forall a b . (a -> b) -> [a] -> [b] testdata/Builtins.lc 215:25-215:30 - List _e -> List (List _d) + [_e] -> [[_d]] testdata/Builtins.lc 215:25-215:32 - List (List _c) + [[_c]] testdata/Builtins.lc 215:29-215:30 - _g -> List _f + _g -> [_f] testdata/Builtins.lc 215:31-215:32 - List _d + [_d] testdata/Builtins.lc 217:1-217:4 - forall a . List a -> Int + forall a . [a] -> Int testdata/Builtins.lc 217:10-217:11 _b testdata/Builtins.lc 217:10-218:35 - List _b -> Int + [_b] -> Int testdata/Builtins.lc 218:14-218:15 _b testdata/Builtins.lc 218:14-218:28 @@ -4887,7 +4887,7 @@ testdata/Builtins.lc 218:16-218:28 testdata/Builtins.lc 218:29-218:32 _h testdata/Builtins.lc 218:33-218:35 - List _g + [_g] testdata/Builtins.lc 222:6-222:11 Type -> Type | Type -> Type | Type -> Type | Type -> Type | Type -> Type | Type testdata/Builtins.lc 222:6-222:13 @@ -5073,12 +5073,11 @@ testdata/Builtins.lc 252:69-252:70 testdata/Builtins.lc 252:71-252:72 Type testdata/Builtins.lc 253:1-253:14 - forall a b (c :: PrimitiveType) - . (a -> b) -> List (Primitive a c) -> List (Primitive b c) + forall a b (c :: PrimitiveType) . (a -> b) -> [Primitive a c] -> [Primitive b c] testdata/Builtins.lc 253:19-253:22 - forall a b . (a -> b) -> List a -> List b + forall a b . (a -> b) -> [a] -> [b] testdata/Builtins.lc 253:19-253:39 - List (Primitive _e _a) -> List (Primitive _d _a) + [Primitive _e _a] -> [Primitive _d _a] testdata/Builtins.lc 253:24-253:36 forall a b (c :: PrimitiveType) . (a -> b) -> Primitive a c -> Primitive b c testdata/Builtins.lc 253:24-253:38 @@ -5090,7 +5089,7 @@ testdata/Builtins.lc 255:30-255:38 testdata/Builtins.lc 255:45-255:46 Type testdata/Builtins.lc 260:1-260:12 - forall (a :: PrimitiveType) (b :: List Type) (c :: List Type) + forall (a :: PrimitiveType) (b :: [Type]) (c :: [Type]) . (b ~ map Type Type ListElem c) => HList c -> PrimitiveStream a (HList b) testdata/Builtins.lc 260:32-260:119 Type | Type | Type @@ -5103,23 +5102,23 @@ testdata/Builtins.lc 260:56-260:75 testdata/Builtins.lc 260:58-260:59 forall a . a -> a -> Type testdata/Builtins.lc 260:60-260:63 - forall a b . (a -> b) -> List a -> List b + forall a b . (a -> b) -> [a] -> [b] testdata/Builtins.lc 260:60-260:72 - List Type -> List Type + [Type] -> [Type] testdata/Builtins.lc 260:60-260:75 - List Type + [Type] testdata/Builtins.lc 260:64-260:72 Type -> Type testdata/Builtins.lc 260:73-260:75 _b testdata/Builtins.lc 260:80-260:85 - List Type -> Type + [Type] -> Type testdata/Builtins.lc 260:80-260:88 Type testdata/Builtins.lc 260:80-260:119 Type testdata/Builtins.lc 260:86-260:88 - List Type + [Type] testdata/Builtins.lc 260:92-260:107 PrimitiveType -> Type -> Type testdata/Builtins.lc 260:92-260:109 @@ -5129,20 +5128,20 @@ testdata/Builtins.lc 260:92-260:119 testdata/Builtins.lc 260:108-260:109 _f testdata/Builtins.lc 260:111-260:116 - List Type -> Type + [Type] -> Type testdata/Builtins.lc 260:111-260:118 Type testdata/Builtins.lc 260:117-260:118 - List Type + [Type] testdata/Builtins.lc 262:1-262:6 - forall (a :: PrimitiveType) (b :: List Type) + forall (a :: PrimitiveType) (b :: [Type]) . String -> HList b -> PrimitiveStream a (HList b) testdata/Builtins.lc 262:56-262:62 Type testdata/Builtins.lc 262:56-262:104 Type | Type testdata/Builtins.lc 262:66-262:71 - List Type -> Type + [Type] -> Type testdata/Builtins.lc 262:66-262:73 Type testdata/Builtins.lc 262:66-262:104 @@ -5158,11 +5157,11 @@ testdata/Builtins.lc 262:77-262:104 testdata/Builtins.lc 262:93-262:94 _e testdata/Builtins.lc 262:96-262:101 - List Type -> Type + [Type] -> Type testdata/Builtins.lc 262:96-262:103 Type testdata/Builtins.lc 262:102-262:103 - List Type + [Type] testdata/Builtins.lc 264:1-264:10 forall a . String -> a testdata/Builtins.lc 264:14-264:20 @@ -5172,9 +5171,9 @@ testdata/Builtins.lc 264:14-264:25 testdata/Builtins.lc 264:24-264:25 _c | Type testdata/Builtins.lc 266:1-266:12 - forall (a :: PrimitiveType) (b :: List Type) + forall (a :: PrimitiveType) (b :: [Type]) . String - -> forall (c :: List String) + -> forall (c :: [String]) -> (len String c ~ len Type b) => PrimitiveStream a (HList b) testdata/Builtins.lc 266:31-266:37 Type @@ -5193,7 +5192,7 @@ testdata/Builtins.lc 266:65-266:73 testdata/Builtins.lc 266:66-266:72 Type testdata/Builtins.lc 266:78-266:81 - forall a . List a -> Int + forall a . [a] -> Int testdata/Builtins.lc 266:78-266:84 Int testdata/Builtins.lc 266:78-266:86 @@ -5203,15 +5202,15 @@ testdata/Builtins.lc 266:78-266:92 testdata/Builtins.lc 266:78-266:123 Type testdata/Builtins.lc 266:82-266:84 - List String + [String] testdata/Builtins.lc 266:85-266:86 forall a . a -> a -> Type testdata/Builtins.lc 266:87-266:90 - forall a . List a -> Int + forall a . [a] -> Int testdata/Builtins.lc 266:87-266:92 Int testdata/Builtins.lc 266:91-266:92 - List Type + [Type] testdata/Builtins.lc 266:96-266:111 PrimitiveType -> Type -> Type testdata/Builtins.lc 266:96-266:113 @@ -5221,11 +5220,11 @@ testdata/Builtins.lc 266:96-266:123 testdata/Builtins.lc 266:112-266:113 _f testdata/Builtins.lc 266:115-266:120 - List Type -> Type + [Type] -> Type testdata/Builtins.lc 266:115-266:122 Type testdata/Builtins.lc 266:121-266:122 - List Type + [Type] testdata/Builtins.lc 270:6-270:14 Nat -> Type -> Type testdata/Builtins.lc 270:21-270:27 @@ -5350,13 +5349,13 @@ testdata/Builtins.lc 281:75-281:76 testdata/Builtins.lc 282:1-282:16 forall a (b :: Nat) . (a -> Float) - -> List (Vector b (Maybe (SimpleFragment a))) - -> List (Vector b (Maybe (SimpleFragment a))) + -> [Vector b (Maybe (SimpleFragment a))] + -> [Vector b (Maybe (SimpleFragment a))] testdata/Builtins.lc 282:21-282:24 - forall a b . (a -> b) -> List a -> List b + forall a b . (a -> b) -> [a] -> [b] testdata/Builtins.lc 282:21-282:43 - List (Vector _a (Maybe (SimpleFragment _d))) - -> List (Vector _a (Maybe (SimpleFragment _d))) + [Vector _a (Maybe (SimpleFragment _d))] + -> [Vector _a (Maybe (SimpleFragment _d))] testdata/Builtins.lc 282:26-282:40 forall a (b :: Nat) . (a -> Float) -> Fragment b a -> Fragment b a testdata/Builtins.lc 282:26-282:42 @@ -5424,13 +5423,13 @@ testdata/Builtins.lc 286:74-286:75 testdata/Builtins.lc 287:1-287:16 forall a (b :: Nat) . (a -> Bool) - -> List (Vector b (Maybe (SimpleFragment a))) - -> List (Vector b (Maybe (SimpleFragment a))) + -> [Vector b (Maybe (SimpleFragment a))] + -> [Vector b (Maybe (SimpleFragment a))] testdata/Builtins.lc 287:21-287:24 - forall a b . (a -> b) -> List a -> List b + forall a b . (a -> b) -> [a] -> [b] testdata/Builtins.lc 287:21-287:43 - List (Vector _a (Maybe (SimpleFragment _d))) - -> List (Vector _a (Maybe (SimpleFragment _d))) + [Vector _a (Maybe (SimpleFragment _d))] + -> [Vector _a (Maybe (SimpleFragment _d))] testdata/Builtins.lc 287:26-287:40 forall a (b :: Nat) . (a -> Bool) -> Fragment b a -> Fragment b a testdata/Builtins.lc 287:26-287:42 @@ -5498,13 +5497,13 @@ testdata/Builtins.lc 291:68-291:69 testdata/Builtins.lc 292:1-292:13 forall a b (c :: Nat) . (a -> b) - -> List (Vector c (Maybe (SimpleFragment a))) - -> List (Vector c (Maybe (SimpleFragment b))) + -> [Vector c (Maybe (SimpleFragment a))] + -> [Vector c (Maybe (SimpleFragment b))] testdata/Builtins.lc 292:18-292:21 - forall a b . (a -> b) -> List a -> List b + forall a b . (a -> b) -> [a] -> [b] testdata/Builtins.lc 292:18-292:37 - List (Vector _a (Maybe (SimpleFragment _e))) - -> List (Vector _a (Maybe (SimpleFragment _d))) + [Vector _a (Maybe (SimpleFragment _e))] + -> [Vector _a (Maybe (SimpleFragment _d))] testdata/Builtins.lc 292:23-292:34 forall a b (c :: Nat) . (a -> b) -> Fragment c a -> Fragment c b testdata/Builtins.lc 292:23-292:36 @@ -6208,9 +6207,9 @@ testdata/Builtins.lc 463:26-463:56 testdata/Builtins.lc 463:27-463:40 Type testdata/Builtins.lc 463:27-463:55 - List Type + [Type] testdata/Builtins.lc 463:42-463:55 - Type | List Type + Type | [Type] testdata/Builtins.lc 464:29-464:97 Type testdata/Builtins.lc 464:29-465:74 @@ -6218,21 +6217,21 @@ testdata/Builtins.lc 464:29-465:74 testdata/Builtins.lc 464:30-464:62 Type testdata/Builtins.lc 464:30-464:96 - List Type + [Type] testdata/Builtins.lc 464:31-464:45 Type testdata/Builtins.lc 464:31-464:61 - List Type + [Type] testdata/Builtins.lc 464:47-464:61 - Type | List Type + Type | [Type] testdata/Builtins.lc 464:64-464:96 - Type | List Type + Type | [Type] testdata/Builtins.lc 464:65-464:79 Type testdata/Builtins.lc 464:65-464:95 - List Type + [Type] testdata/Builtins.lc 464:81-464:95 - Type | List Type + Type | [Type] testdata/Builtins.lc 465:29-465:32 Nat -> Type -> Type testdata/Builtins.lc 465:29-465:34 @@ -6388,7 +6387,7 @@ testdata/Builtins.lc 478:42-478:56 testdata/Builtins.lc 478:55-478:56 Type testdata/Builtins.lc 480:1-480:19 - forall (a :: List Type) (b :: List Type) (c :: List Type) (d :: PrimitiveType) + forall (a :: [Type]) (b :: [Type]) (c :: [Type]) (d :: PrimitiveType) . (map Type Type Interpolated a ~ b, c ~ : (Vec 4 Float) a) => HList b -> RasterContext (HList c) d @@ -6396,13 +6395,13 @@ testdata/Builtins.lc 480:1-480:19 testdata/Builtins.lc 481:8-486:34 Type | Type | Type | Type testdata/Builtins.lc 481:10-481:13 - forall a b . (a -> b) -> List a -> List b + forall a b . (a -> b) -> [a] -> [b] testdata/Builtins.lc 481:10-481:26 - List Type -> List Type + [Type] -> [Type] testdata/Builtins.lc 481:10-481:28 - List Type + [Type] testdata/Builtins.lc 481:10-481:30 - List Type -> Type + [Type] -> Type testdata/Builtins.lc 481:10-481:44 Type testdata/Builtins.lc 481:14-481:26 @@ -6430,25 +6429,25 @@ testdata/Builtins.lc 482:14-482:19 testdata/Builtins.lc 482:14-482:25 Type testdata/Builtins.lc 482:14-482:26 - List Type -> List Type + [Type] -> [Type] testdata/Builtins.lc 482:14-482:28 - List Type + [Type] testdata/Builtins.lc 482:18-482:19 _b testdata/Builtins.lc 482:20-482:25 Type testdata/Builtins.lc 482:25-482:26 - forall a . a -> List a -> List a + forall a . a -> [a] -> [a] testdata/Builtins.lc 482:27-482:28 - List Type + [Type] testdata/Builtins.lc 483:8-483:13 - List Type -> Type + [Type] -> Type testdata/Builtins.lc 483:8-483:27 Type testdata/Builtins.lc 483:8-486:34 Type testdata/Builtins.lc 483:14-483:27 - List Type + [Type] testdata/Builtins.lc 484:8-484:21 Type -> PrimitiveType -> Type testdata/Builtins.lc 484:8-484:31 @@ -6458,11 +6457,11 @@ testdata/Builtins.lc 484:8-484:33 testdata/Builtins.lc 484:8-486:34 Type testdata/Builtins.lc 484:23-484:28 - List Type -> Type + [Type] -> Type testdata/Builtins.lc 484:23-484:30 Type testdata/Builtins.lc 484:29-484:30 - List Type + [Type] testdata/Builtins.lc 484:32-484:33 _e testdata/Builtins.lc 485:8-485:17 @@ -6474,11 +6473,11 @@ testdata/Builtins.lc 485:8-485:29 testdata/Builtins.lc 485:8-486:34 Type testdata/Builtins.lc 485:19-485:24 - List Type -> Type + [Type] -> Type testdata/Builtins.lc 485:19-485:26 Type testdata/Builtins.lc 485:25-485:26 - List Type + [Type] testdata/Builtins.lc 485:28-485:29 PrimitiveType testdata/Builtins.lc 486:8-486:22 @@ -6490,30 +6489,29 @@ testdata/Builtins.lc 486:8-486:34 testdata/Builtins.lc 486:23-486:24 _b testdata/Builtins.lc 486:26-486:31 - List Type -> Type + [Type] -> Type testdata/Builtins.lc 486:26-486:33 Type testdata/Builtins.lc 486:32-486:33 - List Type + [Type] testdata/Builtins.lc 488:1-488:20 - forall (a :: List Type) (b :: PrimitiveType) + forall (a :: [Type]) (b :: PrimitiveType) . RasterContext (HList (: (Vec 4 Float) a)) b -> HList (map Type Type Interpolated a) - -> List (Primitive (HList (: (Vec 4 Float) a)) b) - -> List (Vector 1 (Maybe (SimpleFragment (HList a)))) + -> [Primitive (HList (: (Vec 4 Float) a)) b] + -> [Vector 1 (Maybe (SimpleFragment (HList a)))] testdata/Builtins.lc 488:32-488:38 - forall a . List (List a) -> List a + forall a . [[a]] -> [a] testdata/Builtins.lc 488:32-488:74 - List (Vector 1 (Maybe (SimpleFragment (HList _b)))) + [Vector 1 (Maybe (SimpleFragment (HList _b)))] testdata/Builtins.lc 488:40-488:43 - forall a b . (a -> b) -> List a -> List b + forall a b . (a -> b) -> [a] -> [b] testdata/Builtins.lc 488:40-488:71 - List (Primitive (HList (: (Vec 4 Float) _b)) _a) - -> List (List (Fragment 1 (HList _b))) + [Primitive (HList (: (Vec 4 Float) _b)) _a] -> [[Fragment 1 (HList _b)]] testdata/Builtins.lc 488:40-488:73 - List (List (Fragment 1 (HList _b))) + [[Fragment 1 (HList _b)]] testdata/Builtins.lc 488:45-488:63 - forall (a :: List Type) (b :: List Type) (c :: List Type) (d :: PrimitiveType) + forall (a :: [Type]) (b :: [Type]) (c :: [Type]) (d :: PrimitiveType) . (map Type Type Interpolated a ~ b, c ~ : (Vec 4 Float) a) => HList b -> RasterContext (HList c) d @@ -6540,21 +6538,21 @@ testdata/Builtins.lc 492:12-492:15 testdata/Builtins.lc 492:12-492:23 Type testdata/Builtins.lc 492:12-495:50 - forall a . List a -> Type + forall a . [a] -> Type testdata/Builtins.lc 492:13-492:14 _b testdata/Builtins.lc 492:19-492:23 Type | Type testdata/Builtins.lc 493:1-493:8 - forall a . List a -> Type + forall a . [a] -> Type testdata/Builtins.lc 493:14-493:19 Type testdata/Builtins.lc 493:14-495:50 - List _a -> Type | Type + [_a] -> Type | Type testdata/Builtins.lc 494:15-494:20 Type testdata/Builtins.lc 494:15-495:50 - List _c -> Type | Type + [_c] -> Type | Type testdata/Builtins.lc 495:22-495:25 Type -> Type -> Type testdata/Builtins.lc 495:22-495:33 @@ -6572,38 +6570,38 @@ testdata/Builtins.lc 495:29-495:30 testdata/Builtins.lc 495:31-495:32 _c testdata/Builtins.lc 495:35-495:42 - forall a . List a -> Type + forall a . [a] -> Type testdata/Builtins.lc 495:35-495:49 Type testdata/Builtins.lc 495:44-495:45 _g testdata/Builtins.lc 495:44-495:46 - List _f -> List _f + [_f] -> [_f] testdata/Builtins.lc 495:44-495:48 - List _e + [_e] testdata/Builtins.lc 495:45-495:46 - forall a . a -> List a -> List a + forall a . a -> [a] -> [a] testdata/Builtins.lc 495:46-495:48 - List _e + [_e] testdata/Builtins.lc 497:1-497:16 - List Type -> Type + [Type] -> Type testdata/Builtins.lc 497:21-497:28 - forall a . List a -> Type + forall a . [a] -> Type testdata/Builtins.lc 497:21-497:45 Type testdata/Builtins.lc 497:30-497:33 - forall a b . (a -> b) -> List a -> List b + forall a b . (a -> b) -> [a] -> [b] testdata/Builtins.lc 497:30-497:42 - List Type -> List Nat + [Type] -> [Nat] testdata/Builtins.lc 497:30-497:44 - List Nat + [Nat] testdata/Builtins.lc 497:34-497:42 Type -> Nat testdata/Builtins.lc 497:43-497:44 _b testdata/Builtins.lc 509:6-509:17 - Nat -> List ImageKind -> Type | Nat -> List ImageKind -> Type | Nat - -> List ImageKind -> Type | Type | Type + Nat -> [ImageKind] -> Type | Nat -> [ImageKind] -> Type | Nat + -> [ImageKind] -> Type | Type | Type testdata/Builtins.lc 509:6-509:46 Type testdata/Builtins.lc 509:24-509:27 @@ -6621,31 +6619,30 @@ testdata/Builtins.lc 511:30-511:36 testdata/Builtins.lc 511:31-511:35 Type testdata/Builtins.lc 512:1-512:11 - List ImageKind -> List Type + [ImageKind] -> [Type] testdata/Builtins.lc 512:25-512:28 - forall a b . (a -> b) -> List a -> List b + forall a b . (a -> b) -> [a] -> [b] testdata/Builtins.lc 512:25-512:38 - List ImageKind -> List Type + [ImageKind] -> [Type] testdata/Builtins.lc 512:25-512:40 - List Type + [Type] testdata/Builtins.lc 512:25-513:31 - List Type -> ImageKind -> List Type | List Type | List Type + [Type] -> ImageKind -> [Type] | [Type] | [Type] testdata/Builtins.lc 512:29-512:38 ImageKind -> Type testdata/Builtins.lc 512:39-512:40 - List _c + [_c] testdata/Builtins.lc 513:16-513:19 - forall a b . (a -> b) -> List a -> List b | forall a b - . (a -> b) -> List a -> List b | forall a b . (a -> b) -> List a -> List b + forall a b . (a -> b) -> [a] -> [b] | forall a b + . (a -> b) -> [a] -> [b] | forall a b . (a -> b) -> [a] -> [b] testdata/Builtins.lc 513:16-513:29 - List ImageKind -> List Type | List ImageKind -> List Type | List ImageKind - -> List Type + [ImageKind] -> [Type] | [ImageKind] -> [Type] | [ImageKind] -> [Type] testdata/Builtins.lc 513:16-513:31 - List Type | List Type | List Type + [Type] | [Type] | [Type] testdata/Builtins.lc 513:20-513:29 ImageKind -> Type | ImageKind -> Type | ImageKind -> Type testdata/Builtins.lc 513:30-513:31 - List ImageKind | List ImageKind | List ImageKind + [ImageKind] | [ImageKind] | [ImageKind] testdata/Builtins.lc 515:40-515:49 Type | Type testdata/Builtins.lc 515:56-515:77 @@ -6653,7 +6650,7 @@ testdata/Builtins.lc 515:56-515:77 testdata/Builtins.lc 515:102-515:103 ImageKind testdata/Builtins.lc 517:1-517:11 - forall (a :: List ImageKind) (b :: Nat) (c :: List Type) + forall (a :: [ImageKind]) (b :: Nat) (c :: [Type]) . (a ~ map Type ImageKind FragmentOperationKind c) => HList c -> FragmentStream b (HList (imageType' a)) -> FrameBuffer b a -> FrameBuffer b a @@ -6678,23 +6675,23 @@ testdata/Builtins.lc 517:50-517:81 testdata/Builtins.lc 517:52-517:53 forall a . a -> a -> Type testdata/Builtins.lc 517:54-517:57 - forall a b . (a -> b) -> List a -> List b + forall a b . (a -> b) -> [a] -> [b] testdata/Builtins.lc 517:54-517:79 - List Type -> List ImageKind + [Type] -> [ImageKind] testdata/Builtins.lc 517:54-517:81 - List ImageKind + [ImageKind] testdata/Builtins.lc 517:58-517:79 Type -> ImageKind testdata/Builtins.lc 517:80-517:81 - List Type + [Type] testdata/Builtins.lc 517:86-517:91 - List Type -> Type + [Type] -> Type testdata/Builtins.lc 517:86-517:93 Type testdata/Builtins.lc 517:86-517:174 Type testdata/Builtins.lc 517:92-517:93 - List Type + [Type] testdata/Builtins.lc 517:97-517:111 Nat -> Type -> Type testdata/Builtins.lc 517:97-517:113 @@ -6706,19 +6703,19 @@ testdata/Builtins.lc 517:97-517:174 testdata/Builtins.lc 517:112-517:113 Nat testdata/Builtins.lc 517:115-517:120 - List Type -> Type + [Type] -> Type testdata/Builtins.lc 517:115-517:135 Type testdata/Builtins.lc 517:122-517:132 - List ImageKind -> List Type + [ImageKind] -> [Type] testdata/Builtins.lc 517:122-517:134 - List Type + [Type] testdata/Builtins.lc 517:133-517:134 - List ImageKind + [ImageKind] testdata/Builtins.lc 517:140-517:151 - Nat -> List ImageKind -> Type + Nat -> [ImageKind] -> Type testdata/Builtins.lc 517:140-517:153 - List ImageKind -> Type + [ImageKind] -> Type testdata/Builtins.lc 517:140-517:155 Type testdata/Builtins.lc 517:140-517:174 @@ -6726,17 +6723,17 @@ testdata/Builtins.lc 517:140-517:174 testdata/Builtins.lc 517:152-517:153 Nat testdata/Builtins.lc 517:154-517:155 - List ImageKind + [ImageKind] testdata/Builtins.lc 517:159-517:170 - Nat -> List ImageKind -> Type + Nat -> [ImageKind] -> Type testdata/Builtins.lc 517:159-517:172 - List ImageKind -> Type + [ImageKind] -> Type testdata/Builtins.lc 517:159-517:174 Type | Type testdata/Builtins.lc 517:171-517:172 Nat testdata/Builtins.lc 517:173-517:174 - List ImageKind + [ImageKind] testdata/Builtins.lc 519:1-519:15 forall a b . a -> b -> (a, b) testdata/Builtins.lc 519:24-519:32 @@ -6746,13 +6743,14 @@ testdata/Builtins.lc 519:25-519:28 testdata/Builtins.lc 519:30-519:31 _e | ((_b)) testdata/Builtins.lc 520:1-520:8 - forall (a :: Nat) (b :: List Type) + forall (a :: Nat) (b :: [Type]) . FrameBuffer a (map Type ImageKind FragmentOperationKind b) - -> (HList b, List - (Fragment a (HList (imageType' (map Type ImageKind FragmentOperationKind b))))) + -> (HList b, [Fragment + a + (HList (imageType' (map Type ImageKind FragmentOperationKind b)))]) -> FrameBuffer a (map Type ImageKind FragmentOperationKind b) testdata/Builtins.lc 520:25-520:35 - forall (a :: List ImageKind) (b :: Nat) (c :: List Type) + forall (a :: [ImageKind]) (b :: Nat) (c :: [Type]) . (a ~ map Type ImageKind FragmentOperationKind c) => HList c -> FragmentStream b (HList (imageType' a)) -> FrameBuffer b a -> FrameBuffer b a @@ -6784,7 +6782,7 @@ testdata/Builtins.lc 524:47-524:59 testdata/Builtins.lc 524:74-524:75 ImageKind testdata/Builtins.lc 530:1-530:12 - forall (a :: List Type) + forall (a :: [Type]) . sameLayerCounts a => HList a -> FrameBuffer (ImageLC (head Type a)) (map Type ImageKind GetImageKind a) @@ -6795,23 +6793,23 @@ testdata/Builtins.lc 530:31-530:35 testdata/Builtins.lc 530:40-530:125 Type testdata/Builtins.lc 530:41-530:56 - List Type -> Type + [Type] -> Type testdata/Builtins.lc 530:41-530:58 Type testdata/Builtins.lc 530:57-530:58 - List Type + [Type] testdata/Builtins.lc 530:63-530:68 - List Type -> Type + [Type] -> Type testdata/Builtins.lc 530:63-530:70 Type testdata/Builtins.lc 530:63-530:125 Type testdata/Builtins.lc 530:69-530:70 - List Type + [Type] testdata/Builtins.lc 530:74-530:85 - Nat -> List ImageKind -> Type + Nat -> [ImageKind] -> Type testdata/Builtins.lc 530:74-530:104 - List ImageKind -> Type + [ImageKind] -> Type testdata/Builtins.lc 530:74-530:125 Type | Type testdata/Builtins.lc 530:87-530:94 @@ -6819,40 +6817,40 @@ testdata/Builtins.lc 530:87-530:94 testdata/Builtins.lc 530:87-530:103 Nat testdata/Builtins.lc 530:96-530:100 - forall a . List a -> a + forall a . [a] -> a testdata/Builtins.lc 530:96-530:102 Type testdata/Builtins.lc 530:101-530:102 - List Type + [Type] testdata/Builtins.lc 530:106-530:109 - forall a b . (a -> b) -> List a -> List b + forall a b . (a -> b) -> [a] -> [b] testdata/Builtins.lc 530:106-530:122 - List Type -> List ImageKind + [Type] -> [ImageKind] testdata/Builtins.lc 530:106-530:124 - List ImageKind + [ImageKind] testdata/Builtins.lc 530:110-530:122 Type -> ImageKind testdata/Builtins.lc 530:123-530:124 - List Type + [Type] testdata/Builtins.lc 532:1-532:11 - forall (a :: List Type) + forall (a :: [Type]) . sameLayerCounts a => HList a -> FrameBuffer (ImageLC (head Type a)) (map Type ImageKind GetImageKind a) testdata/Builtins.lc 532:14-532:25 - forall (a :: List Type) + forall (a :: [Type]) . sameLayerCounts a => HList a -> FrameBuffer (ImageLC (head Type a)) (map Type ImageKind GetImageKind a) testdata/Builtins.lc 534:1-534:11 - forall (a :: Nat) (b :: List Type) c + forall (a :: Nat) (b :: [Type]) c . HList b -> (c -> HList (imageType' (map Type ImageKind FragmentOperationKind b))) - -> List (Vector a (Maybe (SimpleFragment c))) + -> [Vector a (Maybe (SimpleFragment c))] -> FrameBuffer a (map Type ImageKind FragmentOperationKind b) -> FrameBuffer a (map Type ImageKind FragmentOperationKind b) testdata/Builtins.lc 534:34-534:44 - forall (a :: List ImageKind) (b :: Nat) (c :: List Type) + forall (a :: [ImageKind]) (b :: Nat) (c :: [Type]) . (a ~ map Type ImageKind FragmentOperationKind c) => HList c -> FragmentStream b (HList (imageType' a)) -> FrameBuffer b a -> FrameBuffer b a @@ -6872,18 +6870,17 @@ testdata/Builtins.lc 534:45-534:48 testdata/Builtins.lc 534:50-534:62 forall a b (c :: Nat) . (a -> b) - -> List (Vector c (Maybe (SimpleFragment a))) - -> List (Vector c (Maybe (SimpleFragment b))) + -> [Vector c (Maybe (SimpleFragment a))] + -> [Vector c (Maybe (SimpleFragment b))] testdata/Builtins.lc 534:50-534:70 - List (Vector _a (Maybe (SimpleFragment _c))) - -> List (Vector _a (Maybe (SimpleFragment _b))) + [Vector _a (Maybe (SimpleFragment _c))] + -> [Vector _a (Maybe (SimpleFragment _b))] testdata/Builtins.lc 534:50-534:75 - List - (Vector - _c - (Maybe - (SimpleFragment - (HList (imageType' (map Type ImageKind FragmentOperationKind _b)))))) + [Vector + _c + (Maybe + (SimpleFragment + (HList (imageType' (map Type ImageKind FragmentOperationKind _b)))))] testdata/Builtins.lc 534:63-534:70 _k testdata/Builtins.lc 534:71-534:75 @@ -6891,11 +6888,11 @@ testdata/Builtins.lc 534:71-534:75 testdata/Builtins.lc 534:77-534:79 _e testdata/Builtins.lc 537:1-537:9 - forall (a :: ImageKind) . FrameBuffer 1 (: a 'Nil) -> Image 1 a + forall (a :: ImageKind) . FrameBuffer 1 (: a '[]) -> Image 1 a testdata/Builtins.lc 537:24-537:35 - Nat -> List ImageKind -> Type + Nat -> [ImageKind] -> Type testdata/Builtins.lc 537:24-537:37 - List ImageKind -> Type + [ImageKind] -> Type testdata/Builtins.lc 537:24-537:42 Type testdata/Builtins.lc 537:24-537:55 @@ -6903,7 +6900,7 @@ testdata/Builtins.lc 537:24-537:55 testdata/Builtins.lc 537:36-537:37 _b testdata/Builtins.lc 537:38-537:42 - List ImageKind + [ImageKind] testdata/Builtins.lc 537:40-537:41 _c testdata/Builtins.lc 537:46-537:51 @@ -6917,24 +6914,24 @@ testdata/Builtins.lc 537:52-537:53 testdata/Builtins.lc 537:54-537:55 ImageKind testdata/Builtins.lc 538:1-538:14 - FrameBuffer 1 (: 'Depth (: ('Color (Vec 4 Float)) 'Nil)) + FrameBuffer 1 (: 'Depth (: ('Color (Vec 4 Float)) '[])) -> Image 1 ('Color (Vec 4 Float)) testdata/Builtins.lc 538:24-538:35 - Nat -> List ImageKind -> Type + Nat -> [ImageKind] -> Type testdata/Builtins.lc 538:24-538:37 - List ImageKind -> Type + [ImageKind] -> Type testdata/Builtins.lc 538:24-538:70 Type testdata/Builtins.lc 538:36-538:37 _b testdata/Builtins.lc 538:38-538:70 - List ImageKind + [ImageKind] testdata/Builtins.lc 538:41-538:47 ImageKind testdata/Builtins.lc 538:49-538:55 Type -> ImageKind testdata/Builtins.lc 538:49-538:69 - ImageKind | List ImageKind + ImageKind | [ImageKind] testdata/Builtins.lc 538:57-538:60 Nat -> Type -> Type testdata/Builtins.lc 538:57-538:62 @@ -6972,12 +6969,12 @@ testdata/Builtins.lc 540:6-540:12 testdata/Builtins.lc 540:6-541:12 Type testdata/Builtins.lc 541:3-541:12 - forall (a :: Nat) (b :: List ImageKind) + forall (a :: Nat) (b :: [ImageKind]) . FrameBuffer a b -> Output | Output | Type | Type | Type | Type testdata/Builtins.lc 541:26-541:37 - Nat -> List ImageKind -> Type + Nat -> [ImageKind] -> Type testdata/Builtins.lc 541:26-541:39 - List ImageKind -> Type + [ImageKind] -> Type testdata/Builtins.lc 541:26-541:41 Type testdata/Builtins.lc 541:26-541:51 @@ -6989,9 +6986,9 @@ testdata/Builtins.lc 541:40-541:41 testdata/Builtins.lc 541:45-541:51 Type | Type testdata/Builtins.lc 543:1-543:12 - forall (a :: Nat) (b :: List ImageKind) . FrameBuffer a b -> Output + forall (a :: Nat) (b :: [ImageKind]) . FrameBuffer a b -> Output testdata/Builtins.lc 543:15-543:24 - forall (a :: Nat) (b :: List ImageKind) . FrameBuffer a b -> Output + forall (a :: Nat) (b :: [ImageKind]) . FrameBuffer a b -> Output testdata/Builtins.lc 549:6-549:13 Type | Type | Type | Type testdata/Builtins.lc 549:6-553:12 diff --git a/testdata/Internals.out b/testdata/Internals.out index 8d522708..d89f0fb7 100644 --- a/testdata/Internals.out +++ b/testdata/Internals.out @@ -192,15 +192,15 @@ negate :: forall v . Eq v => v -> v -> Bool infix 4 == data List (_ :: Type) :: Type where - [] :: List _a - (:) :: _a -> List _a -> List _a + [] :: forall a . [a] + (:) :: forall b . b -> [b] -> [b] infixr 5 : -data HList :: List Type -> Type where - HNil :: HList 'Nil +data HList :: [Type] -> Type where + HNil :: HList '[] HCons :: forall (a :: _) (b :: _) . a -> HList b -> HList (a : b) hlistNilCase :: forall (a :: _) -> a -> HList [] -> a hlistConsCase - :: forall a (b :: List Type) + :: forall a (b :: [Type]) . forall (c :: _) -> (a -> HList b -> c) -> HList (a : b) -> c main is not found ------------ trace @@ -288,31 +288,30 @@ negate :: forall a . Num a => a -> a 'Eq :: Type -> Type == :: forall a . Eq a => a -> a -> Bool 'List :: Type -> Type -[] :: forall a . List a -(:) :: forall a . a -> List a -> List a +[] :: forall a . [a] +(:) :: forall a . a -> [a] -> [a] 'ListCase :: forall a - . forall (b :: List a -> Type) - -> b 'Nil - -> (forall (c :: a) (d :: List a) -> b (: c d)) -> forall (e :: List a) -> b e + . forall (b :: [a] -> Type) + -> b '[] + -> (forall (c :: a) (d :: [a]) -> b (: c d)) -> forall (e :: [a]) -> b e match'List - :: forall (a :: Type -> Type) - -> (forall b -> a (List b)) -> forall c -> a c -> a c -'HList :: List Type -> Type + :: forall (a :: Type -> Type) -> (forall b -> a [b]) -> forall c -> a c -> a c +'HList :: [Type] -> Type HNil :: () -HCons :: forall a (b :: List Type) . a -> HList b -> HList (: a b) +HCons :: forall a (b :: [Type]) . a -> HList b -> HList (: a b) 'HListCase - :: forall (a :: forall (b :: List Type) -> HList b -> Type) - -> a 'Nil () - -> (forall c (d :: List Type) + :: forall (a :: forall (b :: [Type]) -> HList b -> Type) + -> a '[] () + -> (forall c (d :: [Type]) . forall (e :: c) (f :: HList d) -> a (: c d) ('HCons c d e f)) - -> forall (g :: List Type) . forall (h :: HList g) -> a g h + -> forall (g :: [Type]) . forall (h :: HList g) -> a g h match'HList :: forall (a :: Type -> Type) - -> (forall (b :: List Type) -> a (HList b)) -> forall c -> a c -> a c + -> (forall (b :: [Type]) -> a (HList b)) -> forall c -> a c -> a c hlistNilCase :: forall a -> a -> () -> a hlistConsCase - :: forall a (b :: List Type) + :: forall a (b :: [Type]) . forall c -> (a -> HList b -> c) -> HList (: a b) -> c ------------ tooltips testdata/Internals.lc 6:1-6:8 @@ -828,9 +827,9 @@ testdata/Internals.lc 122:6-122:35 testdata/Internals.lc 122:11-122:12 Type | Type testdata/Internals.lc 122:15-122:18 - forall a . List a | List _b + forall a . [a] | [_b] testdata/Internals.lc 122:22-122:23 - forall a . a -> List a -> List a | List _e | Type | Type | Type + forall a . a -> [a] -> [a] | [_e] | Type | Type | Type testdata/Internals.lc 122:25-122:26 Type testdata/Internals.lc 122:28-122:32 @@ -840,7 +839,7 @@ testdata/Internals.lc 122:28-122:34 testdata/Internals.lc 122:33-122:34 Type testdata/Internals.lc 126:6-126:11 - List Type -> Type | List Type -> Type | Type | List Type -> Type | Type | Type + [Type] -> Type | [Type] -> Type | Type | [Type] -> Type | Type | Type testdata/Internals.lc 126:6-128:45 Type | Type testdata/Internals.lc 126:15-126:21 @@ -854,13 +853,13 @@ testdata/Internals.lc 127:5-127:9 testdata/Internals.lc 127:5-127:22 Type testdata/Internals.lc 127:13-127:18 - List Type -> Type + [Type] -> Type testdata/Internals.lc 127:13-127:22 Type testdata/Internals.lc 127:19-127:22 - forall a . List a | forall a . List a + forall a . [a] | forall a . [a] testdata/Internals.lc 128:5-128:10 - forall a (b :: List Type) . a -> HList b -> HList (: a b) | HList (: _d _c) + forall a (b :: [Type]) . a -> HList b -> HList (: a b) | HList (: _d _c) testdata/Internals.lc 128:5-128:45 Type | Type | Type | Type | Type testdata/Internals.lc 128:14-128:15 @@ -868,7 +867,7 @@ testdata/Internals.lc 128:14-128:15 testdata/Internals.lc 128:14-128:45 Type | Type testdata/Internals.lc 128:19-128:24 - List Type -> Type + [Type] -> Type testdata/Internals.lc 128:19-128:27 Type testdata/Internals.lc 128:19-128:45 @@ -876,19 +875,19 @@ testdata/Internals.lc 128:19-128:45 testdata/Internals.lc 128:25-128:27 _c testdata/Internals.lc 128:31-128:36 - List Type -> Type + [Type] -> Type testdata/Internals.lc 128:31-128:45 Type | Type testdata/Internals.lc 128:39-128:40 Type | Type testdata/Internals.lc 128:39-128:41 - List Type -> List Type | List Type -> List Type + [Type] -> [Type] | [Type] -> [Type] testdata/Internals.lc 128:39-128:44 - List Type | List Type + [Type] | [Type] testdata/Internals.lc 128:40-128:41 - forall a . a -> List a -> List a | forall a . a -> List a -> List a + forall a . a -> [a] -> [a] | forall a . a -> [a] -> [a] testdata/Internals.lc 128:42-128:44 - List Type | List Type + [Type] | [Type] testdata/Internals.lc 130:1-130:13 forall a -> a -> () -> a testdata/Internals.lc 130:29-130:30 @@ -896,18 +895,17 @@ testdata/Internals.lc 130:29-130:30 testdata/Internals.lc 130:29-130:48 Type testdata/Internals.lc 130:34-130:39 - List Type -> Type + [Type] -> Type testdata/Internals.lc 130:34-130:43 Type testdata/Internals.lc 130:34-130:48 Type testdata/Internals.lc 130:40-130:43 - forall a . List a + forall a . [a] testdata/Internals.lc 130:47-130:48 Type | Type testdata/Internals.lc 131:1-131:14 - forall a (b :: List Type) - . forall c -> (a -> HList b -> c) -> HList (: a b) -> c + forall a (b :: [Type]) . forall c -> (a -> HList b -> c) -> HList (: a b) -> c testdata/Internals.lc 132:21-132:25 Type testdata/Internals.lc 132:33-132:37 @@ -925,17 +923,17 @@ testdata/Internals.lc 134:8-136:9 testdata/Internals.lc 134:9-134:10 Type testdata/Internals.lc 134:14-134:19 - List Type -> Type + [Type] -> Type testdata/Internals.lc 134:14-134:21 Type testdata/Internals.lc 134:14-134:26 Type testdata/Internals.lc 134:20-134:21 - List Type + [Type] testdata/Internals.lc 134:25-134:26 _d | Type testdata/Internals.lc 135:8-135:13 - List Type -> Type + [Type] -> Type testdata/Internals.lc 135:8-135:20 Type testdata/Internals.lc 135:8-136:9 @@ -943,12 +941,12 @@ testdata/Internals.lc 135:8-136:9 testdata/Internals.lc 135:15-135:16 Type testdata/Internals.lc 135:15-135:17 - List Type -> List Type + [Type] -> [Type] testdata/Internals.lc 135:15-135:19 - List Type + [Type] testdata/Internals.lc 135:16-135:17 - forall a . a -> List a -> List a + forall a . a -> [a] -> [a] testdata/Internals.lc 135:18-135:19 - List Type + [Type] testdata/Internals.lc 136:8-136:9 Type | Type \ No newline at end of file diff --git a/testdata/Material.out b/testdata/Material.out index 2a1525b4..41e812e0 100644 --- a/testdata/Material.out +++ b/testdata/Material.out @@ -93,7 +93,7 @@ data TCMod :: Type where data StageTexture :: Type where ST_Map :: String -> StageTexture ST_ClampMap :: String -> StageTexture - ST_AnimMap :: Float -> List String -> StageTexture + ST_AnimMap :: Float -> [String] -> StageTexture ST_Lightmap :: StageTexture ST_WhiteImage :: StageTexture data AlphaFunction :: Type where @@ -105,11 +105,11 @@ data DepthFunction :: Type where D_Lequal :: DepthFunction data StageAttrs :: Type where StageAttrs - :: Maybe (HList (Blending' : Blending' : 'Nil)) + :: Maybe (HList (Blending' : Blending' : '[])) -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs saBlend @@ -184,14 +184,13 @@ defaultStageAttrs :: StageAttrs data CommonAttrs :: Type where CommonAttrs - :: HList 'Nil - -> HList 'Nil + :: HList '[] + -> HList '[] -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs caSkyParms = \(a :: _) -> 'CommonAttrsCase \_ -> _ :: _ @@ -478,14 +477,14 @@ match'TCMod :: forall (a :: Type -> Type) -> a TCMod -> forall b -> a b -> a b 'StageTexture :: Type ST_Map :: String -> StageTexture ST_ClampMap :: String -> StageTexture -ST_AnimMap :: Float -> List String -> StageTexture +ST_AnimMap :: Float -> [String] -> StageTexture ST_Lightmap :: StageTexture ST_WhiteImage :: StageTexture 'StageTextureCase :: forall (a :: StageTexture -> Type) -> (forall (b :: String) -> a ('ST_Map b)) -> (forall (c :: String) -> a ('ST_ClampMap c)) - -> (forall (d :: Float) (e :: List String) -> a ('ST_AnimMap d e)) + -> (forall (d :: Float) (e :: [String]) -> a ('ST_AnimMap d e)) -> a 'ST_Lightmap -> a 'ST_WhiteImage -> forall (f :: StageTexture) -> a f match'StageTexture :: forall (a :: Type -> Type) -> a StageTexture -> forall b -> a b -> a b @@ -512,7 +511,7 @@ StageAttrs -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs 'StageAttrsCase @@ -521,7 +520,7 @@ StageAttrs (c :: RGBGen) (d :: AlphaGen) (e :: TCGen) - (f :: List TCMod) + (f :: [TCMod]) (g :: StageTexture) (h :: Bool) (i :: DepthFunction) (j :: Maybe AlphaFunction) (k :: Bool) (l :: String) @@ -533,7 +532,7 @@ saBlend :: StageAttrs -> Maybe (Blending', Blending') saRGBGen :: StageAttrs -> RGBGen saAlphaGen :: StageAttrs -> AlphaGen saTCGen :: StageAttrs -> TCGen -saTCMod :: StageAttrs -> List TCMod +saTCMod :: StageAttrs -> [TCMod] saTexture :: StageAttrs -> StageTexture saDepthWrite :: StageAttrs -> Bool saDepthFunc :: StageAttrs -> DepthFunction @@ -549,8 +548,7 @@ CommonAttrs -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs 'CommonAttrsCase :: forall (a :: CommonAttrs -> Type) -> (forall (b :: ()) @@ -560,7 +558,7 @@ CommonAttrs (f :: Bool) (g :: Bool) (h :: CullType) - (i :: List Deform) (j :: Bool) (k :: Bool) (l :: List StageAttrs) (m :: Bool) + (i :: [Deform]) (j :: Bool) (k :: Bool) (l :: [StageAttrs]) (m :: Bool) -> a ('CommonAttrs b c d e f g h i j k l m)) -> forall (n :: CommonAttrs) -> a n match'CommonAttrs @@ -572,10 +570,10 @@ caSort :: CommonAttrs -> Float caEntityMergable :: CommonAttrs -> Bool caFogOnly :: CommonAttrs -> Bool caCull :: CommonAttrs -> CullType -caDeformVertexes :: CommonAttrs -> List Deform +caDeformVertexes :: CommonAttrs -> [Deform] caNoMipMaps :: CommonAttrs -> Bool caPolygonOffset :: CommonAttrs -> Bool -caStages :: CommonAttrs -> List StageAttrs +caStages :: CommonAttrs -> [StageAttrs] caIsSky :: CommonAttrs -> Bool defaultCommonAttrs :: CommonAttrs ------------ tooltips @@ -962,7 +960,7 @@ testdata/Material.lc 113:7-113:18 testdata/Material.lc 113:21-113:27 Type testdata/Material.lc 114:7-114:17 - Float -> List String -> StageTexture | StageTexture | Type | Type | Type + Float -> [String] -> StageTexture | StageTexture | Type | Type | Type testdata/Material.lc 114:21-114:26 Type testdata/Material.lc 114:27-114:35 @@ -1002,7 +1000,7 @@ testdata/Material.lc 131:7-131:17 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction @@ -1021,9 +1019,9 @@ testdata/Material.lc 132:31-132:53 testdata/Material.lc 132:32-132:41 Type testdata/Material.lc 132:32-132:52 - List Type + [Type] testdata/Material.lc 132:43-132:52 - Type | List Type + Type | [Type] testdata/Material.lc 133:7-133:15 StageAttrs -> RGBGen testdata/Material.lc 133:24-133:30 @@ -1037,7 +1035,7 @@ testdata/Material.lc 135:7-135:14 testdata/Material.lc 135:24-135:29 Type testdata/Material.lc 136:7-136:14 - StageAttrs -> List TCMod + StageAttrs -> [TCMod] testdata/Material.lc 136:24-136:31 Type testdata/Material.lc 136:25-136:30 @@ -1079,29 +1077,29 @@ testdata/Material.lc 149:21-149:31 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/Material.lc 149:21-150:30 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/Material.lc 149:21-151:36 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/Material.lc 149:21-152:33 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/Material.lc 149:21-153:35 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/Material.lc 149:21-154:25 @@ -1128,7 +1126,7 @@ testdata/Material.lc 152:23-152:33 testdata/Material.lc 153:23-153:35 TCGen testdata/Material.lc 154:23-154:25 - forall a . List a + forall a . [a] testdata/Material.lc 155:23-155:36 StageTexture testdata/Material.lc 156:23-156:27 @@ -1155,10 +1153,10 @@ testdata/Material.lc 164:7-164:18 -> Bool -> Bool -> CullType - -> List Deform + -> [Deform] -> Bool -> Bool - -> List StageAttrs + -> [StageAttrs] -> Bool -> CommonAttrs | CommonAttrs | Type | Type | Type | Type | Type | Type | Type | Type | Type | Type | Type | Type | Type testdata/Material.lc 165:7-165:17 @@ -1190,7 +1188,7 @@ testdata/Material.lc 171:7-171:13 testdata/Material.lc 171:28-171:36 Type testdata/Material.lc 172:7-172:23 - CommonAttrs -> List Deform + CommonAttrs -> [Deform] testdata/Material.lc 172:28-172:36 Type testdata/Material.lc 172:29-172:35 @@ -1204,7 +1202,7 @@ testdata/Material.lc 174:7-174:22 testdata/Material.lc 174:28-174:32 Type testdata/Material.lc 175:7-175:15 - CommonAttrs -> List StageAttrs + CommonAttrs -> [StageAttrs] testdata/Material.lc 175:28-175:40 Type testdata/Material.lc 175:29-175:39 @@ -1224,49 +1222,42 @@ testdata/Material.lc 183:22-183:33 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/Material.lc 183:22-184:29 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/Material.lc 183:22-185:29 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/Material.lc 183:22-186:32 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/Material.lc 183:22-187:28 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/Material.lc 183:22-188:32 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/Material.lc 183:22-189:32 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/Material.lc 183:22-190:40 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/Material.lc 183:22-191:29 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/Material.lc 183:22-192:32 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/Material.lc 183:22-193:32 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/Material.lc 183:22-194:29 Bool -> CommonAttrs testdata/Material.lc 183:22-196:6 @@ -1286,12 +1277,12 @@ testdata/Material.lc 189:27-189:32 testdata/Material.lc 190:27-190:40 CullType testdata/Material.lc 191:27-191:29 - forall a . List a + forall a . [a] testdata/Material.lc 192:27-192:32 Bool testdata/Material.lc 193:27-193:32 Bool testdata/Material.lc 194:27-194:29 - forall a . List a + forall a . [a] testdata/Material.lc 195:27-195:32 Bool \ No newline at end of file diff --git a/testdata/Prelude.out b/testdata/Prelude.out index fdd8ce6b..6e3f4bf9 100644 --- a/testdata/Prelude.out +++ b/testdata/Prelude.out @@ -40,7 +40,7 @@ zip \(e :: _) (f :: _) -> _rhs (HCons c (HCons e HNil) : zip d f) b a) - :: forall (g :: _) (h :: _) . List g -> List h -> List (HList (g : h : 'Nil)) + :: forall (g :: _) (h :: _) . [g] -> [h] -> [HList (g : h : '[])] unzip = (\(a :: _) -> 'ListCase \_ -> _ :: _ @@ -77,8 +77,7 @@ unzip e b a) - :: forall (s :: _) (t :: _) - . List (HList (s : t : 'Nil)) -> HList (List s : List t : 'Nil) + :: forall (s :: _) (t :: _) . [HList (s : t : '[])] -> HList ([s] : [t] : '[]) filter = \(a :: _) (b :: _) -> 'ListCase \_ -> _ :: _ @@ -88,10 +87,10 @@ filter b tail = (\(a :: _) -> 'ListCase \_ -> _ :: _ (_rhs undefined) \_ (b :: _) -> _rhs b a) - :: forall (c :: _) . List c -> List c + :: forall (c :: _) . [c] -> [c] pairs = (\(a :: _) -> _rhs (zip a (tail a))) - :: forall (b :: _) . List b -> List (HList (b : b : 'Nil)) + :: forall (b :: _) . [b] -> [HList (b : b : '[])] foldl' = \(a :: _) (b :: _) (c :: _) -> 'ListCase \_ -> _ :: _ @@ -160,7 +159,7 @@ sortBy b iterate = (\(a :: _) (b :: _) -> _rhs (b : iterate a (a b))) - :: forall (c :: _) . (c -> c) -> c -> List c + :: forall (c :: _) . (c -> c) -> c -> [c] fst = \(a :: _) -> hlistConsCase (_ :: _) @@ -184,8 +183,8 @@ infixr 3 &&& data RecItem :: Type where RecItem :: String -> Type -> RecItem recItemType = \(a :: _) -> 'RecItemCase \_ -> _ :: _ \_ (b :: _) -> _rhs b a -data RecordC (_ :: List RecItem) :: Type where - RecordCons :: HList (map recItemType _a) -> RecordC _a +data RecordC (_ :: [RecItem]) :: Type where + RecordCons :: forall (a :: [RecItem]) . HList (map recItemType a) -> RecordC a isKeyC = \(a :: _) (b :: _) (c :: _) -> 'ListCase \_ -> _ :: _ @@ -220,7 +219,7 @@ project d e b) - :: forall (i :: _) (j :: List RecItem) + :: forall (i :: _) (j :: [RecItem]) . forall (k :: String) -> isKeyC k i j => RecordC j -> i rgb = \(a :: _) (b :: _) (c :: _) -> _rhs (V4 a b c 1.0) black = _rhs (rgb 0.0 0.0 0.0) @@ -454,7 +453,7 @@ fromTo (_rhs (a : fromTo (a + fromInt 1) b)) (_rhs []) (a > b)) - :: Float -> Float -> List Float + :: Float -> Float -> [Float] !! = (\(a :: _) (b :: _) -> 'ListCase \_ -> _ :: _ @@ -465,7 +464,7 @@ fromTo (_rhs c) (fromInt 0 == b) a) - :: forall (e :: _) . List e -> Int -> e + :: forall (e :: _) . [e] -> Int -> e main is not found ------------ trace const :: forall a b . a -> b -> a @@ -476,17 +475,17 @@ $ :: forall a b . (a -> b) -> a -> b uncurry :: forall a b c . (a -> c -> b) -> (a, c) -> b *** :: forall a b c d . (a -> c) -> (b -> d) -> (a, b) -> (c, d) pi :: Float -zip :: forall a b . List a -> List b -> List (a, b) -unzip :: forall a b . List (a, b) -> (List a, List b) -filter :: forall a . (a -> Bool) -> List a -> List a -tail :: forall a . List a -> List a -pairs :: forall a . List a -> List (a, a) -foldl' :: forall a b . (a -> b -> a) -> a -> List b -> a -foldr1 :: forall a . (a -> a -> a) -> List a -> a -split :: forall a . List a -> (List a, List a) -mergeBy :: forall a . (a -> a -> Ordering) -> List a -> List a -> List a -sortBy :: forall a . (a -> a -> Ordering) -> List a -> List a -iterate :: forall a . (a -> a) -> a -> List a +zip :: forall a b . [a] -> [b] -> [(a, b)] +unzip :: forall a b . [(a, b)] -> ([a], [b]) +filter :: forall a . (a -> Bool) -> [a] -> [a] +tail :: forall a . [a] -> [a] +pairs :: forall a . [a] -> [(a, a)] +foldl' :: forall a b . (a -> b -> a) -> a -> [b] -> a +foldr1 :: forall a . (a -> a -> a) -> [a] -> a +split :: forall a . [a] -> ([a], [a]) +mergeBy :: forall a . (a -> a -> Ordering) -> [a] -> [a] -> [a] +sortBy :: forall a . (a -> a -> Ordering) -> [a] -> [a] +iterate :: forall a . (a -> a) -> a -> [a] fst :: forall a b . (a, b) -> a snd :: forall a b . (a, b) -> b ||| :: Bool -> Bool -> Bool @@ -499,23 +498,22 @@ RecItem :: String -> Type -> RecItem match'RecItem :: forall (a :: Type -> Type) -> a RecItem -> forall b -> a b -> a b recItemType :: RecItem -> Type -'RecordC :: List RecItem -> Type +'RecordC :: [RecItem] -> Type RecordCons - :: forall (a :: List RecItem) - . HList (map RecItem Type recItemType a) -> RecordC a + :: forall (a :: [RecItem]) . HList (map RecItem Type recItemType a) -> RecordC a 'RecordCCase - :: forall (a :: List RecItem) + :: forall (a :: [RecItem]) . forall (b :: RecordC a -> Type) -> (forall (c :: HList (map RecItem Type recItemType a)) -> b ('RecordCons c)) -> forall (d :: RecordC a) -> b d match'RecordC :: forall (a :: Type -> Type) - -> (forall (b :: List RecItem) -> a (RecordC b)) -> forall c -> a c -> a c -isKeyC :: String -> Type -> List RecItem -> Type -fstTup :: forall a (b :: List Type) . HList (: a b) -> a -sndTup :: forall a (b :: List Type) . HList (: a b) -> HList b + -> (forall (b :: [RecItem]) -> a (RecordC b)) -> forall c -> a c -> a c +isKeyC :: String -> Type -> [RecItem] -> Type +fstTup :: forall a (b :: [Type]) . HList (: a b) -> a +sndTup :: forall a (b :: [Type]) . HList (: a b) -> HList b project - :: forall a (b :: List RecItem) + :: forall a (b :: [RecItem]) . forall (c :: String) -> isKeyC c a b => RecordC b -> a rgb :: Float -> Float -> Float -> VecS Float 4 black :: VecS Float 4 @@ -679,8 +677,8 @@ rotationEuler :: Float -> Float -> Float -> Mat 4 4 Float translateBefore4 :: Vec 3 Float -> Mat 4 4 Float lookat :: Vec 3 Float -> Vec 3 Float -> Vec 3 Float -> Mat 4 4 Float scale :: Float -> VecS Float 4 -> VecS Float 4 -fromTo :: Float -> Float -> List Float -!! :: forall a . List a -> Int -> a +fromTo :: Float -> Float -> [Float] +!! :: forall a . [a] -> Int -> a ------------ tooltips testdata/Prelude.lc 16:1-16:6 forall a b . a -> b -> a @@ -743,7 +741,7 @@ testdata/Prelude.lc 31:8-31:11 testdata/Prelude.lc 31:8-31:29 Type | Type testdata/Prelude.lc 31:8-34:39 - forall a b . List a -> List b -> List (a, b) + forall a b . [a] -> [b] -> [(a, b)] testdata/Prelude.lc 31:9-31:10 _d testdata/Prelude.lc 31:15-31:18 @@ -759,151 +757,151 @@ testdata/Prelude.lc 31:23-31:28 testdata/Prelude.lc 31:24-31:25 Type testdata/Prelude.lc 31:24-31:27 - List Type + [Type] testdata/Prelude.lc 31:26-31:27 - Type | List Type + Type | [Type] testdata/Prelude.lc 32:1-32:4 - forall a b . List a -> List b -> List (a, b) + forall a b . [a] -> [b] -> [(a, b)] testdata/Prelude.lc 32:22-32:24 - forall a . List a + forall a . [a] testdata/Prelude.lc 32:22-34:39 - List _a -> List (_a, _d) | List (_d, _c) + [_a] -> [(_a, _d)] | [(_d, _c)] testdata/Prelude.lc 33:22-33:24 - forall a . List a + forall a . [a] testdata/Prelude.lc 33:22-34:39 - List _a -> List (_e, _a) | List (_c, _f) + [_a] -> [(_e, _a)] | [(_c, _f)] testdata/Prelude.lc 34:23-34:28 (_h, _d) testdata/Prelude.lc 34:23-34:29 - List (_h, _d) -> List (_h, _d) + [(_h, _d)] -> [(_h, _d)] testdata/Prelude.lc 34:23-34:39 - List (_g, _c) + [(_g, _c)] testdata/Prelude.lc 34:24-34:25 _k testdata/Prelude.lc 34:26-34:27 _g | ((_d)) testdata/Prelude.lc 34:28-34:29 - forall a . a -> List a -> List a + forall a . a -> [a] -> [a] testdata/Prelude.lc 34:30-34:33 - forall a b . List a -> List b -> List (a, b) + forall a b . [a] -> [b] -> [(a, b)] testdata/Prelude.lc 34:30-34:36 - List _a -> List (_h, _a) + [_a] -> [(_h, _a)] testdata/Prelude.lc 34:30-34:39 - List (_g, _c) + [(_g, _c)] testdata/Prelude.lc 34:34-34:36 - List _i + [_i] testdata/Prelude.lc 34:37-34:39 - List _c + [_c] testdata/Prelude.lc 36:10-36:17 Type testdata/Prelude.lc 36:10-36:30 Type | Type testdata/Prelude.lc 36:10-39:27 - forall a b . List (a, b) -> (List a, List b) + forall a b . [(a, b)] -> ([a], [b]) testdata/Prelude.lc 36:11-36:16 Type testdata/Prelude.lc 36:12-36:13 _e testdata/Prelude.lc 36:12-36:15 - List Type + [Type] testdata/Prelude.lc 36:14-36:15 - _c | List Type + _c | [Type] testdata/Prelude.lc 36:21-36:30 Type | Type testdata/Prelude.lc 36:22-36:25 Type testdata/Prelude.lc 36:22-36:29 - List Type + [Type] testdata/Prelude.lc 36:23-36:24 Type testdata/Prelude.lc 36:26-36:29 - Type | List Type + Type | [Type] testdata/Prelude.lc 36:27-36:28 Type testdata/Prelude.lc 37:1-37:6 - forall a b . List (a, b) -> (List a, List b) + forall a b . [(a, b)] -> ([a], [b]) testdata/Prelude.lc 37:12-37:19 - (List _b, List _a) + ([_b], [_a]) testdata/Prelude.lc 37:12-39:27 - List (_b, _a) -> (List _b, List _a) | (List _c, List _b) + [(_b, _a)] -> ([_b], [_a]) | ([_c], [_b]) testdata/Prelude.lc 37:13-37:15 - forall a . List a + forall a . [a] testdata/Prelude.lc 37:16-37:18 - forall a . List a | ((List _a)) + forall a . [a] | (([_a])) testdata/Prelude.lc 38:20-38:31 - (List _n, List _i) + ([_n], [_i]) testdata/Prelude.lc 38:20-39:27 - (List _h, List _c) | (List _d, List _a) | (List _d, List _c) + ([_h], [_c]) | ([_d], [_a]) | ([_d], [_c]) testdata/Prelude.lc 38:21-38:22 _s testdata/Prelude.lc 38:21-38:23 - List _r -> List _r + [_r] -> [_r] testdata/Prelude.lc 38:21-38:25 - List _p + [_p] testdata/Prelude.lc 38:22-38:23 - forall a . a -> List a -> List a + forall a . a -> [a] -> [a] testdata/Prelude.lc 38:23-38:25 - List _f + [_f] testdata/Prelude.lc 38:26-38:27 _n testdata/Prelude.lc 38:26-38:28 - List _m -> List _m + [_m] -> [_m] testdata/Prelude.lc 38:26-38:30 - List _k | ((List _i)) + [_k] | (([_i])) testdata/Prelude.lc 38:27-38:28 - forall a . a -> List a -> List a + forall a . a -> [a] -> [a] testdata/Prelude.lc 38:28-38:30 - List _f + [_f] testdata/Prelude.lc 39:10-39:12 _k | _h | _d testdata/Prelude.lc 39:10-39:15 - (List _e, List _d) | (List _f, List _e) + ([_e], [_d]) | ([_f], [_e]) testdata/Prelude.lc 39:13-39:15 _f | _c | _c testdata/Prelude.lc 39:19-39:24 - forall a b . List (a, b) -> (List a, List b) + forall a b . [(a, b)] -> ([a], [b]) testdata/Prelude.lc 39:19-39:27 - (List _b, List _a) + ([_b], [_a]) testdata/Prelude.lc 39:25-39:27 - List _r + [_r] testdata/Prelude.lc 41:1-41:7 - forall a . (a -> Bool) -> List a -> List a + forall a . (a -> Bool) -> [a] -> [a] testdata/Prelude.lc 41:21-41:23 - forall a . List a + forall a . [a] testdata/Prelude.lc 41:21-44:49 - List _a -> List _a + [_a] -> [_a] testdata/Prelude.lc 42:22-44:49 - List _c + [_c] testdata/Prelude.lc 42:27-42:31 _g testdata/Prelude.lc 42:32-42:33 _f testdata/Prelude.lc 43:32-44:49 - Bool -> List _f + Bool -> [_f] testdata/Prelude.lc 43:33-43:34 _h testdata/Prelude.lc 43:33-43:36 - List _g -> List _g + [_g] -> [_g] testdata/Prelude.lc 43:33-43:51 - List _f + [_f] testdata/Prelude.lc 43:35-43:36 - forall a . a -> List a -> List a + forall a . a -> [a] -> [a] testdata/Prelude.lc 43:37-43:43 - _j -> List _f -> List _f + _j -> [_f] -> [_f] testdata/Prelude.lc 43:37-43:48 - List _f -> List _f + [_f] -> [_f] testdata/Prelude.lc 43:37-43:51 - List _f + [_f] testdata/Prelude.lc 43:44-43:48 _j testdata/Prelude.lc 43:49-43:51 - List _f + [_f] testdata/Prelude.lc 44:34-44:40 _m testdata/Prelude.lc 44:41-44:45 _n testdata/Prelude.lc 44:46-44:48 - List _k + [_k] testdata/Prelude.lc 49:9-49:12 Type testdata/Prelude.lc 49:9-49:19 @@ -915,9 +913,9 @@ testdata/Prelude.lc 49:16-49:19 testdata/Prelude.lc 49:17-49:18 Type testdata/Prelude.lc 50:1-50:5 - forall a . List a -> List a + forall a . [a] -> [a] testdata/Prelude.lc 50:16-50:18 - List _d | List _b + [_d] | [_b] testdata/Prelude.lc 52:10-52:13 Type testdata/Prelude.lc 52:10-52:25 @@ -931,31 +929,31 @@ testdata/Prelude.lc 52:18-52:24 testdata/Prelude.lc 52:19-52:20 Type testdata/Prelude.lc 52:19-52:23 - List Type + [Type] testdata/Prelude.lc 52:22-52:23 - Type | List Type + Type | [Type] testdata/Prelude.lc 53:1-53:6 - forall a . List a -> List (a, a) + forall a . [a] -> [(a, a)] testdata/Prelude.lc 53:11-53:14 - forall a b . List a -> List b -> List (a, b) + forall a b . [a] -> [b] -> [(a, b)] testdata/Prelude.lc 53:11-53:16 - List _a -> List (_c, _a) + [_a] -> [(_c, _a)] testdata/Prelude.lc 53:11-53:25 - List (_b, _b) + [(_b, _b)] testdata/Prelude.lc 53:15-53:16 - List _d + [_d] testdata/Prelude.lc 53:18-53:22 - forall a . List a -> List a + forall a . [a] -> [a] testdata/Prelude.lc 53:18-53:24 - List _b + [_b] testdata/Prelude.lc 53:23-53:24 - List _c + [_c] testdata/Prelude.lc 55:1-55:7 - forall a b . (a -> b -> a) -> a -> List b -> a + forall a b . (a -> b -> a) -> a -> [b] -> a testdata/Prelude.lc 55:17-55:18 _f testdata/Prelude.lc 55:17-56:41 - List _b -> _f + [_b] -> _f testdata/Prelude.lc 56:22-56:28 _k testdata/Prelude.lc 56:29-56:30 @@ -967,15 +965,15 @@ testdata/Prelude.lc 56:34-56:35 testdata/Prelude.lc 56:36-56:37 _k testdata/Prelude.lc 56:39-56:41 - List _h + [_h] testdata/Prelude.lc 58:1-58:7 - forall a . (a -> a -> a) -> List a -> a + forall a . (a -> a -> a) -> [a] -> a testdata/Prelude.lc 58:20-58:25 - forall a b . (b -> a -> a) -> a -> List b -> a + forall a b . (b -> a -> a) -> a -> [b] -> a testdata/Prelude.lc 58:20-58:27 - _b -> List _a -> _b + _b -> [_a] -> _b testdata/Prelude.lc 58:20-58:29 - List _a -> _e + [_a] -> _e testdata/Prelude.lc 58:20-58:32 _c testdata/Prelude.lc 58:26-58:27 @@ -983,27 +981,27 @@ testdata/Prelude.lc 58:26-58:27 testdata/Prelude.lc 58:28-58:29 _f testdata/Prelude.lc 58:30-58:32 - List _d + [_d] testdata/Prelude.lc 60:1-60:6 - forall a . List a -> (List a, List a) + forall a . [a] -> ([a], [a]) testdata/Prelude.lc 60:12-60:20 - (List _b, List _a) + ([_b], [_a]) testdata/Prelude.lc 60:12-61:55 - List _b -> (List _b, List _a) + [_b] -> ([_b], [_a]) testdata/Prelude.lc 60:13-60:15 - forall a . List a + forall a . [a] testdata/Prelude.lc 60:17-60:19 - forall a . List a | ((List _a)) + forall a . [a] | (([_a])) testdata/Prelude.lc 61:17-61:28 - (List _i, _c) + ([_i], _c) testdata/Prelude.lc 61:18-61:19 _m testdata/Prelude.lc 61:18-61:20 - List _l -> List _l + [_l] -> [_l] testdata/Prelude.lc 61:18-61:23 - List _j + [_j] testdata/Prelude.lc 61:19-61:20 - forall a . a -> List a -> List a + forall a . a -> [a] -> [a] testdata/Prelude.lc 61:21-61:23 _d testdata/Prelude.lc 61:25-61:27 @@ -1017,13 +1015,13 @@ testdata/Prelude.lc 61:41-61:43 testdata/Prelude.lc 61:47-61:52 _i testdata/Prelude.lc 61:53-61:55 - List _h + [_h] testdata/Prelude.lc 63:1-63:8 - forall a . (a -> a -> Ordering) -> List a -> List a -> List a + forall a . (a -> a -> Ordering) -> [a] -> [a] -> [a] testdata/Prelude.lc 63:27-65:32 - List _e + [_e] testdata/Prelude.lc 63:27-67:21 - List _c -> List _c | List _c + [_c] -> [_c] | [_c] testdata/Prelude.lc 63:32-63:33 _j testdata/Prelude.lc 63:34-63:35 @@ -1033,89 +1031,89 @@ testdata/Prelude.lc 63:36-63:37 testdata/Prelude.lc 64:11-64:12 _j testdata/Prelude.lc 64:11-64:13 - List _i -> List _i + [_i] -> [_i] testdata/Prelude.lc 64:11-64:33 - List _h + [_h] testdata/Prelude.lc 64:11-65:32 - List _g -> Ordering -> List _g + [_g] -> Ordering -> [_g] testdata/Prelude.lc 64:12-64:13 - forall a . a -> List a -> List a + forall a . a -> [a] -> [a] testdata/Prelude.lc 64:14-64:21 _p testdata/Prelude.lc 64:22-64:23 _q testdata/Prelude.lc 64:24-64:26 - List _l + [_l] testdata/Prelude.lc 64:28-64:29 _j testdata/Prelude.lc 64:28-64:30 - List _i -> List _i + [_i] -> [_i] testdata/Prelude.lc 64:28-64:32 - List _i + [_i] testdata/Prelude.lc 64:29-64:30 - forall a . a -> List a -> List a + forall a . a -> [a] -> [a] testdata/Prelude.lc 64:30-64:32 - List _i + [_i] testdata/Prelude.lc 65:10-65:11 _f | _h testdata/Prelude.lc 65:10-65:12 - List _e -> List _e | List _g -> List _g + [_e] -> [_e] | [_g] -> [_g] testdata/Prelude.lc 65:10-65:32 - List _g | List _g + [_g] | [_g] testdata/Prelude.lc 65:11-65:12 - forall a . a -> List a -> List a | forall a . a -> List a -> List a + forall a . a -> [a] -> [a] | forall a . a -> [a] -> [a] testdata/Prelude.lc 65:13-65:20 - _m -> List _g -> List _g -> List _g | _m -> List _g -> List _g -> List _g + _m -> [_g] -> [_g] -> [_g] | _m -> [_g] -> [_g] -> [_g] testdata/Prelude.lc 65:13-65:22 - List _g -> List _g -> List _g | List _g -> List _g -> List _g + [_g] -> [_g] -> [_g] | [_g] -> [_g] -> [_g] testdata/Prelude.lc 65:13-65:29 - List _g -> List _g | List _g -> List _g + [_g] -> [_g] | [_g] -> [_g] testdata/Prelude.lc 65:13-65:32 - List _g | List _g + [_g] | [_g] testdata/Prelude.lc 65:21-65:22 _m | _m testdata/Prelude.lc 65:24-65:25 _h | _h testdata/Prelude.lc 65:24-65:26 - List _g -> List _g | List _g -> List _g + [_g] -> [_g] | [_g] -> [_g] testdata/Prelude.lc 65:24-65:28 - List _g | List _g + [_g] | [_g] testdata/Prelude.lc 65:25-65:26 - forall a . a -> List a -> List a | forall a . a -> List a -> List a + forall a . a -> [a] -> [a] | forall a . a -> [a] -> [a] testdata/Prelude.lc 65:26-65:28 - List _g | List _g + [_g] | [_g] testdata/Prelude.lc 65:30-65:32 - List _g | List _g + [_g] | [_g] testdata/Prelude.lc 66:19-66:21 _d testdata/Prelude.lc 67:19-67:21 _i testdata/Prelude.lc 69:1-69:7 - forall a . (a -> a -> Ordering) -> List a -> List a + forall a . (a -> a -> Ordering) -> [a] -> [a] testdata/Prelude.lc 69:15-69:17 - forall a . List a + forall a . [a] testdata/Prelude.lc 69:15-71:71 - List _b -> List _b + [_b] -> [_b] testdata/Prelude.lc 70:16-70:19 - List _e + [_e] testdata/Prelude.lc 70:16-71:71 - List _b -> List _f | List _d + [_b] -> [_f] | [_d] testdata/Prelude.lc 70:17-70:18 _g testdata/Prelude.lc 71:15-71:22 forall a b c . (a -> c -> b) -> (a, c) -> b testdata/Prelude.lc 71:15-71:34 - (List _a, List _a) -> List _a + ([_a], [_a]) -> [_a] testdata/Prelude.lc 71:15-71:71 - List _h + [_h] testdata/Prelude.lc 71:24-71:31 - forall a . (a -> a -> Ordering) -> List a -> List a -> List a + forall a . (a -> a -> Ordering) -> [a] -> [a] -> [a] testdata/Prelude.lc 71:24-71:33 - List _a -> List _a -> List _a + [_a] -> [_a] -> [_a] testdata/Prelude.lc 71:32-71:33 _o testdata/Prelude.lc 71:36-71:70 - (List _h, List _h) + ([_h], [_h]) testdata/Prelude.lc 71:37-71:43 _p testdata/Prelude.lc 71:37-71:49 @@ -1133,15 +1131,15 @@ testdata/Prelude.lc 71:50-71:58 testdata/Prelude.lc 71:57-71:58 _i -> _i -> Ordering testdata/Prelude.lc 71:61-71:66 - forall a . List a -> (List a, List a) + forall a . [a] -> ([a], [a]) testdata/Prelude.lc 71:61-71:69 - (List _a, List _a) + ([_a], [_a]) testdata/Prelude.lc 71:67-71:69 _k testdata/Prelude.lc 73:12-73:32 Type testdata/Prelude.lc 73:12-74:35 - forall a . (a -> a) -> a -> List a + forall a . (a -> a) -> a -> [a] testdata/Prelude.lc 73:13-73:14 _b testdata/Prelude.lc 73:18-73:19 @@ -1155,21 +1153,21 @@ testdata/Prelude.lc 73:29-73:32 testdata/Prelude.lc 73:30-73:31 Type testdata/Prelude.lc 74:1-74:8 - forall a . (a -> a) -> a -> List a + forall a . (a -> a) -> a -> [a] testdata/Prelude.lc 74:16-74:17 _d testdata/Prelude.lc 74:16-74:19 - List _c -> List _c + [_c] -> [_c] testdata/Prelude.lc 74:16-74:35 - List _c + [_c] testdata/Prelude.lc 74:18-74:19 - forall a . a -> List a -> List a + forall a . a -> [a] -> [a] testdata/Prelude.lc 74:20-74:27 - forall a . (a -> a) -> a -> List a + forall a . (a -> a) -> a -> [a] testdata/Prelude.lc 74:20-74:29 - _c -> List _c + _c -> [_c] testdata/Prelude.lc 74:20-74:35 - List _c + [_c] testdata/Prelude.lc 74:28-74:29 _d -> _d testdata/Prelude.lc 74:31-74:32 @@ -1219,8 +1217,7 @@ testdata/Prelude.lc 124:1-124:12 testdata/Prelude.lc 124:29-124:30 Type testdata/Prelude.lc 126:6-126:13 - List RecItem -> Type | List RecItem -> Type | List RecItem -> Type | List - RecItem + [RecItem] -> Type | [RecItem] -> Type | [RecItem] -> Type | [RecItem] -> Type | Type testdata/Prelude.lc 126:6-126:17 Type | Type @@ -1229,36 +1226,36 @@ testdata/Prelude.lc 126:6-127:17 testdata/Prelude.lc 126:6-127:46 Type testdata/Prelude.lc 126:15-126:17 - List RecItem + [RecItem] testdata/Prelude.lc 126:21-126:30 Type | Type | Type testdata/Prelude.lc 126:22-126:29 Type | Type | Type testdata/Prelude.lc 127:7-127:17 - forall (a :: List RecItem) + forall (a :: [RecItem]) . HList (map RecItem Type recItemType a) -> RecordC a | RecordC _c | Type | Type testdata/Prelude.lc 127:19-127:24 - List Type -> Type + [Type] -> Type testdata/Prelude.lc 127:19-127:45 Type testdata/Prelude.lc 127:26-127:29 - forall a b . (a -> b) -> List a -> List b + forall a b . (a -> b) -> [a] -> [b] testdata/Prelude.lc 127:26-127:41 - List RecItem -> List Type + [RecItem] -> [Type] testdata/Prelude.lc 127:26-127:44 - List Type + [Type] testdata/Prelude.lc 127:30-127:41 RecItem -> Type testdata/Prelude.lc 127:42-127:44 - List RecItem + [RecItem] testdata/Prelude.lc 129:1-129:7 - String -> Type -> List RecItem -> Type + String -> Type -> [RecItem] -> Type testdata/Prelude.lc 129:17-129:23 String -> Type testdata/Prelude.lc 129:17-129:26 Type testdata/Prelude.lc 129:17-130:75 - List RecItem -> Type + [RecItem] -> Type testdata/Prelude.lc 129:24-129:26 String testdata/Prelude.lc 130:34-130:75 @@ -1292,12 +1289,11 @@ testdata/Prelude.lc 130:69-130:70 testdata/Prelude.lc 130:71-130:72 Type testdata/Prelude.lc 130:73-130:75 - List _i + [_i] testdata/Prelude.lc 132:1-132:7 - forall a (b :: List Type) . HList (: a b) -> a + forall a (b :: [Type]) . HList (: a b) -> a testdata/Prelude.lc 132:10-132:23 - forall a (b :: List Type) - . forall c -> (a -> HList b -> c) -> HList (: a b) -> c + forall a (b :: [Type]) . forall c -> (a -> HList b -> c) -> HList (: a b) -> c testdata/Prelude.lc 132:10-132:25 (_c -> HList _b -> _a) -> HList (: _c _b) -> _a testdata/Prelude.lc 132:10-132:37 @@ -1305,10 +1301,9 @@ testdata/Prelude.lc 132:10-132:37 testdata/Prelude.lc 132:35-132:36 _e testdata/Prelude.lc 133:1-133:7 - forall a (b :: List Type) . HList (: a b) -> HList b + forall a (b :: [Type]) . HList (: a b) -> HList b testdata/Prelude.lc 133:10-133:23 - forall a (b :: List Type) - . forall c -> (a -> HList b -> c) -> HList (: a b) -> c + forall a (b :: [Type]) . forall c -> (a -> HList b -> c) -> HList (: a b) -> c testdata/Prelude.lc 133:10-133:25 (_c -> HList _b -> _a) -> HList (: _c _b) -> _a testdata/Prelude.lc 133:10-133:37 @@ -1316,7 +1311,7 @@ testdata/Prelude.lc 133:10-133:37 testdata/Prelude.lc 133:35-133:36 HList _d testdata/Prelude.lc 136:12-138:181 - forall a (b :: List RecItem) + forall a (b :: [RecItem]) . forall (c :: String) -> isKeyC c a b => RecordC b -> a testdata/Prelude.lc 136:28-136:37 Type @@ -1329,11 +1324,11 @@ testdata/Prelude.lc 136:41-136:97 testdata/Prelude.lc 136:54-136:60 Type testdata/Prelude.lc 136:65-136:71 - String -> Type -> List RecItem -> Type + String -> Type -> [RecItem] -> Type testdata/Prelude.lc 136:65-136:73 - Type -> List RecItem -> Type + Type -> [RecItem] -> Type testdata/Prelude.lc 136:65-136:75 - List RecItem -> Type + [RecItem] -> Type testdata/Prelude.lc 136:65-136:78 Type testdata/Prelude.lc 136:65-136:97 @@ -1343,19 +1338,19 @@ testdata/Prelude.lc 136:72-136:73 testdata/Prelude.lc 136:74-136:75 _d testdata/Prelude.lc 136:76-136:78 - List RecItem + [RecItem] testdata/Prelude.lc 136:82-136:89 - List RecItem -> Type + [RecItem] -> Type testdata/Prelude.lc 136:82-136:92 Type testdata/Prelude.lc 136:82-136:97 Type testdata/Prelude.lc 136:90-136:92 - List RecItem + [RecItem] testdata/Prelude.lc 136:96-136:97 Type | Type testdata/Prelude.lc 137:1-137:8 - forall a (b :: List RecItem) + forall a (b :: [RecItem]) . forall (c :: String) -> isKeyC c a b => RecordC b -> a testdata/Prelude.lc 137:57-137:58 String @@ -1370,7 +1365,7 @@ testdata/Prelude.lc 137:59-137:61 testdata/Prelude.lc 137:62-137:64 String testdata/Prelude.lc 137:67-137:73 - forall a (b :: List Type) . HList (: a b) -> a + forall a (b :: [Type]) . HList (: a b) -> a testdata/Prelude.lc 137:67-137:129 _n testdata/Prelude.lc 137:67-138:181 @@ -1384,34 +1379,34 @@ testdata/Prelude.lc 137:75-137:125 testdata/Prelude.lc 137:75-137:128 HList (: _n (map RecItem Type recItemType _g)) testdata/Prelude.lc 137:93-137:98 - List Type -> Type + [Type] -> Type testdata/Prelude.lc 137:93-137:124 Type testdata/Prelude.lc 137:101-137:102 Type testdata/Prelude.lc 137:101-137:104 - List Type -> List Type + [Type] -> [Type] testdata/Prelude.lc 137:101-137:123 - List Type + [Type] testdata/Prelude.lc 137:103-137:104 - forall a . a -> List a -> List a + forall a . a -> [a] -> [a] testdata/Prelude.lc 137:105-137:108 - forall a b . (a -> b) -> List a -> List b + forall a b . (a -> b) -> [a] -> [b] testdata/Prelude.lc 137:105-137:120 - List RecItem -> List Type + [RecItem] -> [Type] testdata/Prelude.lc 137:105-137:123 - List Type + [Type] testdata/Prelude.lc 137:109-137:120 RecItem -> Type testdata/Prelude.lc 137:121-137:123 - List RecItem + [RecItem] testdata/Prelude.lc 137:126-137:128 HList (map RecItem Type recItemType _d) testdata/Prelude.lc 138:57-138:64 - forall a (b :: List RecItem) + forall a (b :: [RecItem]) . forall (c :: String) -> isKeyC c a b => RecordC b -> a testdata/Prelude.lc 138:57-138:67 - forall (a :: List RecItem) + forall (a :: [RecItem]) . forall (b :: String) -> isKeyC b _p a => RecordC a -> _p testdata/Prelude.lc 138:57-138:71 forall (a :: String) -> isKeyC a _o _h => RecordC _h -> _o @@ -1424,7 +1419,7 @@ testdata/Prelude.lc 138:57-138:181 testdata/Prelude.lc 138:66-138:67 Type testdata/Prelude.lc 138:69-138:71 - List _k + [_k] testdata/Prelude.lc 138:72-138:73 String testdata/Prelude.lc 138:76-138:85 @@ -1432,11 +1427,11 @@ testdata/Prelude.lc 138:76-138:85 testdata/Prelude.lc 138:76-138:102 isKeyC _m _o _h testdata/Prelude.lc 138:88-138:94 - String -> Type -> List RecItem -> Type + String -> Type -> [RecItem] -> Type testdata/Prelude.lc 138:88-138:96 - Type -> List RecItem -> Type + Type -> [RecItem] -> Type testdata/Prelude.lc 138:88-138:98 - List RecItem -> Type + [RecItem] -> Type testdata/Prelude.lc 138:88-138:101 Type testdata/Prelude.lc 138:95-138:96 @@ -1444,13 +1439,13 @@ testdata/Prelude.lc 138:95-138:96 testdata/Prelude.lc 138:97-138:98 Type testdata/Prelude.lc 138:99-138:101 - List RecItem + [RecItem] testdata/Prelude.lc 138:105-138:115 - forall (a :: List RecItem) . HList (map RecItem Type recItemType a) -> RecordC a + forall (a :: [RecItem]) . HList (map RecItem Type recItemType a) -> RecordC a testdata/Prelude.lc 138:105-138:180 RecordC _b testdata/Prelude.lc 138:117-138:123 - forall a (b :: List Type) . HList (: a b) -> HList b + forall a (b :: [Type]) . HList (: a b) -> HList b testdata/Prelude.lc 138:117-138:179 HList (map RecItem Type recItemType _h) testdata/Prelude.lc 138:125-138:137 @@ -1462,27 +1457,27 @@ testdata/Prelude.lc 138:125-138:175 testdata/Prelude.lc 138:125-138:178 HList (: _o (map RecItem Type recItemType _h)) testdata/Prelude.lc 138:143-138:148 - List Type -> Type + [Type] -> Type testdata/Prelude.lc 138:143-138:174 Type testdata/Prelude.lc 138:151-138:152 Type testdata/Prelude.lc 138:151-138:154 - List Type -> List Type + [Type] -> [Type] testdata/Prelude.lc 138:151-138:173 - List Type + [Type] testdata/Prelude.lc 138:153-138:154 - forall a . a -> List a -> List a + forall a . a -> [a] -> [a] testdata/Prelude.lc 138:155-138:158 - forall a b . (a -> b) -> List a -> List b + forall a b . (a -> b) -> [a] -> [b] testdata/Prelude.lc 138:155-138:170 - List RecItem -> List Type + [RecItem] -> [Type] testdata/Prelude.lc 138:155-138:173 - List Type + [Type] testdata/Prelude.lc 138:159-138:170 RecItem -> Type testdata/Prelude.lc 138:171-138:173 - List RecItem + [RecItem] testdata/Prelude.lc 138:176-138:178 HList (map RecItem Type recItemType _e) testdata/Prelude.lc 142:1-142:4 @@ -3438,7 +3433,7 @@ testdata/Prelude.lc 380:26-380:29 testdata/Prelude.lc 382:11-382:16 Type testdata/Prelude.lc 382:11-385:38 - Float -> Float -> List Float + Float -> Float -> [Float] testdata/Prelude.lc 382:20-382:25 Type testdata/Prelude.lc 382:20-382:36 @@ -3448,7 +3443,7 @@ testdata/Prelude.lc 382:29-382:36 testdata/Prelude.lc 382:30-382:35 Type testdata/Prelude.lc 383:1-383:7 - Float -> Float -> List Float + Float -> Float -> [Float] testdata/Prelude.lc 384:7-384:8 Float testdata/Prelude.lc 384:7-384:10 @@ -3456,30 +3451,30 @@ testdata/Prelude.lc 384:7-384:10 testdata/Prelude.lc 384:7-384:12 VecScalar 1 Bool testdata/Prelude.lc 384:7-385:38 - List Float + [Float] testdata/Prelude.lc 384:9-384:10 forall (a :: Nat) b . Num b => VecScalar a b -> VecScalar a b -> VecScalar a Bool testdata/Prelude.lc 384:11-384:12 Float testdata/Prelude.lc 384:15-384:17 - forall a . List a + forall a . [a] testdata/Prelude.lc 384:15-385:38 - Bool -> List Float + Bool -> [Float] testdata/Prelude.lc 385:19-385:20 Float testdata/Prelude.lc 385:19-385:21 - List Float -> List Float + [Float] -> [Float] testdata/Prelude.lc 385:19-385:38 - List Float + [Float] testdata/Prelude.lc 385:20-385:21 - forall a . a -> List a -> List a + forall a . a -> [a] -> [a] testdata/Prelude.lc 385:22-385:28 - Float -> Float -> List Float + Float -> Float -> [Float] testdata/Prelude.lc 385:22-385:36 - Float -> List Float + Float -> [Float] testdata/Prelude.lc 385:22-385:38 - List Float + [Float] testdata/Prelude.lc 385:30-385:31 Float testdata/Prelude.lc 385:30-385:33 @@ -3497,7 +3492,7 @@ testdata/Prelude.lc 387:9-387:12 testdata/Prelude.lc 387:9-387:24 Type testdata/Prelude.lc 387:9-389:30 - forall a . List a -> Int -> a + forall a . [a] -> Int -> a testdata/Prelude.lc 387:10-387:11 _b testdata/Prelude.lc 387:16-387:19 @@ -3507,19 +3502,19 @@ testdata/Prelude.lc 387:16-387:24 testdata/Prelude.lc 387:23-387:24 Type | Type testdata/Prelude.lc 388:10-388:12 - forall a . List a -> Int -> a + forall a . [a] -> Int -> a testdata/Prelude.lc 388:19-388:20 _d testdata/Prelude.lc 388:19-389:30 Bool -> _d | _c | _c testdata/Prelude.lc 389:19-389:21 - List _f + [_f] testdata/Prelude.lc 389:19-389:24 Int -> _e testdata/Prelude.lc 389:19-389:30 _d testdata/Prelude.lc 389:22-389:24 - forall a . List a -> Int -> a + forall a . [a] -> Int -> a testdata/Prelude.lc 389:26-389:27 Int testdata/Prelude.lc 389:26-389:28 diff --git a/testdata/SampleMaterial.out b/testdata/SampleMaterial.out index d76fc5b4..91701a48 100644 --- a/testdata/SampleMaterial.out +++ b/testdata/SampleMaterial.out @@ -2078,12 +2078,12 @@ sampleMaterial : []) main is not found ------------ trace -sampleMaterial :: List (String, CommonAttrs) +sampleMaterial :: [(String, CommonAttrs)] ------------ tooltips testdata/SampleMaterial.lc 3:1-3:15 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 4:3-2183:4 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 4:5-46:6 (String, CommonAttrs) testdata/SampleMaterial.lc 4:7-4:40 @@ -2095,49 +2095,42 @@ testdata/SampleMaterial.lc 5:7-5:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 5:7-6:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 5:7-7:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 5:7-8:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 5:7-9:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 5:7-10:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 5:7-11:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 5:7-12:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 5:7-13:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 5:7-14:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 5:7-15:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 5:7-43:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 5:7-45:10 @@ -2157,41 +2150,41 @@ testdata/SampleMaterial.lc 11:23-11:28 testdata/SampleMaterial.lc 12:20-12:33 CullType testdata/SampleMaterial.lc 13:30-13:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 14:25-14:30 Bool testdata/SampleMaterial.lc 15:29-15:34 Bool testdata/SampleMaterial.lc 17:13-43:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 17:15-17:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 17:15-18:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 17:15-19:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 17:15-20:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 17:15-21:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 17:15-22:31 @@ -2218,7 +2211,7 @@ testdata/SampleMaterial.lc 20:32-20:42 testdata/SampleMaterial.lc 21:29-21:36 TCGen testdata/SampleMaterial.lc 22:29-22:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 23:31-23:37 String -> StageTexture testdata/SampleMaterial.lc 23:31-23:71 @@ -2240,29 +2233,29 @@ testdata/SampleMaterial.lc 30:15-30:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 30:15-31:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 30:15-32:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 30:15-33:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 30:15-34:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 30:15-35:31 @@ -2279,7 +2272,7 @@ testdata/SampleMaterial.lc 30:15-39:40 testdata/SampleMaterial.lc 30:15-40:46 String -> StageAttrs testdata/SampleMaterial.lc 30:15-42:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 31:29-31:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 31:29-31:57 @@ -2297,7 +2290,7 @@ testdata/SampleMaterial.lc 33:32-33:42 testdata/SampleMaterial.lc 34:29-34:40 TCGen testdata/SampleMaterial.lc 35:29-35:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 36:31-36:42 StageTexture testdata/SampleMaterial.lc 37:34-37:38 @@ -2315,7 +2308,7 @@ testdata/SampleMaterial.lc 44:21-44:26 testdata/SampleMaterial.lc 47:5-89:6 (String, CommonAttrs) testdata/SampleMaterial.lc 47:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 47:7-47:39 String testdata/SampleMaterial.lc 48:7-48:18 @@ -2325,49 +2318,42 @@ testdata/SampleMaterial.lc 48:7-48:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 48:7-49:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 48:7-50:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 48:7-51:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 48:7-52:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 48:7-53:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 48:7-54:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 48:7-55:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 48:7-56:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 48:7-57:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 48:7-58:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 48:7-86:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 48:7-88:10 @@ -2387,41 +2373,41 @@ testdata/SampleMaterial.lc 54:23-54:28 testdata/SampleMaterial.lc 55:20-55:33 CullType testdata/SampleMaterial.lc 56:30-56:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 57:25-57:30 Bool testdata/SampleMaterial.lc 58:29-58:34 Bool testdata/SampleMaterial.lc 60:13-86:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 60:15-60:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 60:15-61:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 60:15-62:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 60:15-63:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 60:15-64:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 60:15-65:31 @@ -2448,7 +2434,7 @@ testdata/SampleMaterial.lc 63:32-63:42 testdata/SampleMaterial.lc 64:29-64:36 TCGen testdata/SampleMaterial.lc 65:29-65:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 66:31-66:37 String -> StageTexture testdata/SampleMaterial.lc 66:31-66:70 @@ -2470,29 +2456,29 @@ testdata/SampleMaterial.lc 73:15-73:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 73:15-74:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 73:15-75:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 73:15-76:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 73:15-77:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 73:15-78:31 @@ -2509,7 +2495,7 @@ testdata/SampleMaterial.lc 73:15-82:40 testdata/SampleMaterial.lc 73:15-83:46 String -> StageAttrs testdata/SampleMaterial.lc 73:15-85:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 74:29-74:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 74:29-74:57 @@ -2527,7 +2513,7 @@ testdata/SampleMaterial.lc 76:32-76:42 testdata/SampleMaterial.lc 77:29-77:40 TCGen testdata/SampleMaterial.lc 78:29-78:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 79:31-79:42 StageTexture testdata/SampleMaterial.lc 80:34-80:38 @@ -2545,7 +2531,7 @@ testdata/SampleMaterial.lc 87:21-87:26 testdata/SampleMaterial.lc 90:5-132:6 (String, CommonAttrs) testdata/SampleMaterial.lc 90:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 90:7-90:40 String testdata/SampleMaterial.lc 91:7-91:18 @@ -2555,49 +2541,42 @@ testdata/SampleMaterial.lc 91:7-91:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 91:7-92:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 91:7-93:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 91:7-94:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 91:7-95:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 91:7-96:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 91:7-97:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 91:7-98:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 91:7-99:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 91:7-100:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 91:7-101:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 91:7-129:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 91:7-131:10 @@ -2617,41 +2596,41 @@ testdata/SampleMaterial.lc 97:23-97:28 testdata/SampleMaterial.lc 98:20-98:33 CullType testdata/SampleMaterial.lc 99:30-99:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 100:25-100:30 Bool testdata/SampleMaterial.lc 101:29-101:34 Bool testdata/SampleMaterial.lc 103:13-129:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 103:15-103:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 103:15-104:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 103:15-105:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 103:15-106:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 103:15-107:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 103:15-108:31 @@ -2678,7 +2657,7 @@ testdata/SampleMaterial.lc 106:32-106:42 testdata/SampleMaterial.lc 107:29-107:36 TCGen testdata/SampleMaterial.lc 108:29-108:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 109:31-109:37 String -> StageTexture testdata/SampleMaterial.lc 109:31-109:71 @@ -2700,29 +2679,29 @@ testdata/SampleMaterial.lc 116:15-116:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 116:15-117:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 116:15-118:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 116:15-119:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 116:15-120:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 116:15-121:31 @@ -2739,7 +2718,7 @@ testdata/SampleMaterial.lc 116:15-125:40 testdata/SampleMaterial.lc 116:15-126:46 String -> StageAttrs testdata/SampleMaterial.lc 116:15-128:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 117:29-117:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 117:29-117:57 @@ -2757,7 +2736,7 @@ testdata/SampleMaterial.lc 119:32-119:42 testdata/SampleMaterial.lc 120:29-120:40 TCGen testdata/SampleMaterial.lc 121:29-121:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 122:31-122:42 StageTexture testdata/SampleMaterial.lc 123:34-123:38 @@ -2775,7 +2754,7 @@ testdata/SampleMaterial.lc 130:21-130:26 testdata/SampleMaterial.lc 133:5-175:6 (String, CommonAttrs) testdata/SampleMaterial.lc 133:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 133:7-133:42 String testdata/SampleMaterial.lc 134:7-134:18 @@ -2785,49 +2764,42 @@ testdata/SampleMaterial.lc 134:7-134:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 134:7-135:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 134:7-136:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 134:7-137:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 134:7-138:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 134:7-139:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 134:7-140:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 134:7-141:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 134:7-142:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 134:7-143:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 134:7-144:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 134:7-172:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 134:7-174:10 @@ -2847,41 +2819,41 @@ testdata/SampleMaterial.lc 140:23-140:28 testdata/SampleMaterial.lc 141:20-141:33 CullType testdata/SampleMaterial.lc 142:30-142:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 143:25-143:30 Bool testdata/SampleMaterial.lc 144:29-144:34 Bool testdata/SampleMaterial.lc 146:13-172:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 146:15-146:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 146:15-147:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 146:15-148:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 146:15-149:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 146:15-150:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 146:15-151:31 @@ -2908,7 +2880,7 @@ testdata/SampleMaterial.lc 149:32-149:42 testdata/SampleMaterial.lc 150:29-150:36 TCGen testdata/SampleMaterial.lc 151:29-151:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 152:31-152:37 String -> StageTexture testdata/SampleMaterial.lc 152:31-152:73 @@ -2930,29 +2902,29 @@ testdata/SampleMaterial.lc 159:15-159:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 159:15-160:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 159:15-161:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 159:15-162:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 159:15-163:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 159:15-164:31 @@ -2969,7 +2941,7 @@ testdata/SampleMaterial.lc 159:15-168:40 testdata/SampleMaterial.lc 159:15-169:46 String -> StageAttrs testdata/SampleMaterial.lc 159:15-171:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 160:29-160:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 160:29-160:57 @@ -2987,7 +2959,7 @@ testdata/SampleMaterial.lc 162:32-162:42 testdata/SampleMaterial.lc 163:29-163:40 TCGen testdata/SampleMaterial.lc 164:29-164:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 165:31-165:42 StageTexture testdata/SampleMaterial.lc 166:34-166:38 @@ -3005,7 +2977,7 @@ testdata/SampleMaterial.lc 173:21-173:26 testdata/SampleMaterial.lc 176:5-232:6 (String, CommonAttrs) testdata/SampleMaterial.lc 176:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 176:7-176:46 String testdata/SampleMaterial.lc 177:7-177:18 @@ -3015,49 +2987,42 @@ testdata/SampleMaterial.lc 177:7-177:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 177:7-178:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 177:7-179:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 177:7-180:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 177:7-181:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 177:7-182:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 177:7-183:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 177:7-184:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 177:7-185:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 177:7-186:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 177:7-187:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 177:7-229:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 177:7-231:10 @@ -3077,41 +3042,41 @@ testdata/SampleMaterial.lc 183:23-183:28 testdata/SampleMaterial.lc 184:20-184:33 CullType testdata/SampleMaterial.lc 185:30-185:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 186:25-186:30 Bool testdata/SampleMaterial.lc 187:29-187:34 Bool testdata/SampleMaterial.lc 189:13-229:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 189:15-189:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 189:15-190:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 189:15-191:42 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 189:15-192:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 189:15-193:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 189:15-195:88 @@ -3138,7 +3103,7 @@ testdata/SampleMaterial.lc 192:32-192:42 testdata/SampleMaterial.lc 193:29-193:36 TCGen testdata/SampleMaterial.lc 195:21-195:88 - List TCMod + [TCMod] testdata/SampleMaterial.lc 195:23-195:32 Float -> Float -> TCMod testdata/SampleMaterial.lc 195:23-195:36 @@ -3160,7 +3125,7 @@ testdata/SampleMaterial.lc 195:43-195:63 testdata/SampleMaterial.lc 195:43-195:67 TCMod testdata/SampleMaterial.lc 195:43-195:86 - List TCMod + [TCMod] testdata/SampleMaterial.lc 195:51-195:54 Float testdata/SampleMaterial.lc 195:55-195:59 @@ -3174,7 +3139,7 @@ testdata/SampleMaterial.lc 195:70-195:78 testdata/SampleMaterial.lc 195:70-195:82 Float -> TCMod testdata/SampleMaterial.lc 195:70-195:86 - TCMod | List TCMod + TCMod | [TCMod] testdata/SampleMaterial.lc 195:79-195:82 Float testdata/SampleMaterial.lc 195:83-195:86 @@ -3200,29 +3165,29 @@ testdata/SampleMaterial.lc 203:15-203:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 203:15-204:69 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 203:15-205:42 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 203:15-206:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 203:15-207:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 203:15-208:31 @@ -3241,7 +3206,7 @@ testdata/SampleMaterial.lc 203:15-213:46 testdata/SampleMaterial.lc 203:15-215:18 StageAttrs testdata/SampleMaterial.lc 203:15-228:18 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 204:29-204:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 204:29-204:69 @@ -3259,7 +3224,7 @@ testdata/SampleMaterial.lc 206:32-206:42 testdata/SampleMaterial.lc 207:29-207:36 TCGen testdata/SampleMaterial.lc 208:29-208:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 209:31-209:37 String -> StageTexture testdata/SampleMaterial.lc 209:31-209:81 @@ -3281,29 +3246,29 @@ testdata/SampleMaterial.lc 216:15-216:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 216:15-217:69 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 216:15-218:42 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 216:15-219:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 216:15-220:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 216:15-221:31 @@ -3320,7 +3285,7 @@ testdata/SampleMaterial.lc 216:15-225:40 testdata/SampleMaterial.lc 216:15-226:46 String -> StageAttrs testdata/SampleMaterial.lc 216:15-228:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 217:29-217:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 217:29-217:69 @@ -3338,7 +3303,7 @@ testdata/SampleMaterial.lc 219:32-219:42 testdata/SampleMaterial.lc 220:29-220:40 TCGen testdata/SampleMaterial.lc 221:29-221:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 222:31-222:42 StageTexture testdata/SampleMaterial.lc 223:34-223:39 @@ -3356,7 +3321,7 @@ testdata/SampleMaterial.lc 230:21-230:26 testdata/SampleMaterial.lc 233:5-275:6 (String, CommonAttrs) testdata/SampleMaterial.lc 233:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 233:7-233:40 String testdata/SampleMaterial.lc 234:7-234:18 @@ -3366,49 +3331,42 @@ testdata/SampleMaterial.lc 234:7-234:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 234:7-235:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 234:7-236:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 234:7-237:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 234:7-238:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 234:7-239:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 234:7-240:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 234:7-241:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 234:7-242:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 234:7-243:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 234:7-244:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 234:7-272:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 234:7-274:10 @@ -3428,41 +3386,41 @@ testdata/SampleMaterial.lc 240:23-240:28 testdata/SampleMaterial.lc 241:20-241:33 CullType testdata/SampleMaterial.lc 242:30-242:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 243:25-243:30 Bool testdata/SampleMaterial.lc 244:29-244:34 Bool testdata/SampleMaterial.lc 246:13-272:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 246:15-246:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 246:15-247:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 246:15-248:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 246:15-249:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 246:15-250:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 246:15-251:31 @@ -3489,7 +3447,7 @@ testdata/SampleMaterial.lc 249:32-249:42 testdata/SampleMaterial.lc 250:29-250:36 TCGen testdata/SampleMaterial.lc 251:29-251:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 252:31-252:37 String -> StageTexture testdata/SampleMaterial.lc 252:31-252:71 @@ -3511,29 +3469,29 @@ testdata/SampleMaterial.lc 259:15-259:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 259:15-260:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 259:15-261:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 259:15-262:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 259:15-263:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 259:15-264:31 @@ -3550,7 +3508,7 @@ testdata/SampleMaterial.lc 259:15-268:40 testdata/SampleMaterial.lc 259:15-269:46 String -> StageAttrs testdata/SampleMaterial.lc 259:15-271:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 260:29-260:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 260:29-260:57 @@ -3568,7 +3526,7 @@ testdata/SampleMaterial.lc 262:32-262:42 testdata/SampleMaterial.lc 263:29-263:40 TCGen testdata/SampleMaterial.lc 264:29-264:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 265:31-265:42 StageTexture testdata/SampleMaterial.lc 266:34-266:38 @@ -3586,7 +3544,7 @@ testdata/SampleMaterial.lc 273:21-273:26 testdata/SampleMaterial.lc 276:5-318:6 (String, CommonAttrs) testdata/SampleMaterial.lc 276:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 276:7-276:42 String testdata/SampleMaterial.lc 277:7-277:18 @@ -3596,49 +3554,42 @@ testdata/SampleMaterial.lc 277:7-277:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 277:7-278:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 277:7-279:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 277:7-280:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 277:7-281:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 277:7-282:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 277:7-283:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 277:7-284:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 277:7-285:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 277:7-286:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 277:7-287:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 277:7-315:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 277:7-317:10 @@ -3658,41 +3609,41 @@ testdata/SampleMaterial.lc 283:23-283:28 testdata/SampleMaterial.lc 284:20-284:33 CullType testdata/SampleMaterial.lc 285:30-285:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 286:25-286:30 Bool testdata/SampleMaterial.lc 287:29-287:34 Bool testdata/SampleMaterial.lc 289:13-315:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 289:15-289:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 289:15-290:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 289:15-291:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 289:15-292:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 289:15-293:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 289:15-294:31 @@ -3719,7 +3670,7 @@ testdata/SampleMaterial.lc 292:32-292:42 testdata/SampleMaterial.lc 293:29-293:36 TCGen testdata/SampleMaterial.lc 294:29-294:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 295:31-295:37 String -> StageTexture testdata/SampleMaterial.lc 295:31-295:73 @@ -3741,29 +3692,29 @@ testdata/SampleMaterial.lc 302:15-302:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 302:15-303:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 302:15-304:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 302:15-305:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 302:15-306:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 302:15-307:31 @@ -3780,7 +3731,7 @@ testdata/SampleMaterial.lc 302:15-311:40 testdata/SampleMaterial.lc 302:15-312:46 String -> StageAttrs testdata/SampleMaterial.lc 302:15-314:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 303:29-303:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 303:29-303:57 @@ -3798,7 +3749,7 @@ testdata/SampleMaterial.lc 305:32-305:42 testdata/SampleMaterial.lc 306:29-306:40 TCGen testdata/SampleMaterial.lc 307:29-307:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 308:31-308:42 StageTexture testdata/SampleMaterial.lc 309:34-309:38 @@ -3816,7 +3767,7 @@ testdata/SampleMaterial.lc 316:21-316:26 testdata/SampleMaterial.lc 319:5-361:6 (String, CommonAttrs) testdata/SampleMaterial.lc 319:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 319:7-319:43 String testdata/SampleMaterial.lc 320:7-320:18 @@ -3826,49 +3777,42 @@ testdata/SampleMaterial.lc 320:7-320:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 320:7-321:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 320:7-322:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 320:7-323:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 320:7-324:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 320:7-325:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 320:7-326:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 320:7-327:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 320:7-328:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 320:7-329:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 320:7-330:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 320:7-358:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 320:7-360:10 @@ -3888,41 +3832,41 @@ testdata/SampleMaterial.lc 326:23-326:28 testdata/SampleMaterial.lc 327:20-327:33 CullType testdata/SampleMaterial.lc 328:30-328:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 329:25-329:30 Bool testdata/SampleMaterial.lc 330:29-330:34 Bool testdata/SampleMaterial.lc 332:13-358:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 332:15-332:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 332:15-333:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 332:15-334:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 332:15-335:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 332:15-336:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 332:15-337:31 @@ -3949,7 +3893,7 @@ testdata/SampleMaterial.lc 335:32-335:42 testdata/SampleMaterial.lc 336:29-336:36 TCGen testdata/SampleMaterial.lc 337:29-337:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 338:31-338:37 String -> StageTexture testdata/SampleMaterial.lc 338:31-338:74 @@ -3971,29 +3915,29 @@ testdata/SampleMaterial.lc 345:15-345:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 345:15-346:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 345:15-347:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 345:15-348:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 345:15-349:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 345:15-350:31 @@ -4010,7 +3954,7 @@ testdata/SampleMaterial.lc 345:15-354:40 testdata/SampleMaterial.lc 345:15-355:46 String -> StageAttrs testdata/SampleMaterial.lc 345:15-357:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 346:29-346:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 346:29-346:57 @@ -4028,7 +3972,7 @@ testdata/SampleMaterial.lc 348:32-348:42 testdata/SampleMaterial.lc 349:29-349:40 TCGen testdata/SampleMaterial.lc 350:29-350:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 351:31-351:42 StageTexture testdata/SampleMaterial.lc 352:34-352:38 @@ -4046,7 +3990,7 @@ testdata/SampleMaterial.lc 359:21-359:26 testdata/SampleMaterial.lc 362:5-404:6 (String, CommonAttrs) testdata/SampleMaterial.lc 362:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 362:7-362:53 String testdata/SampleMaterial.lc 363:7-363:18 @@ -4056,49 +4000,42 @@ testdata/SampleMaterial.lc 363:7-363:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 363:7-364:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 363:7-365:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 363:7-366:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 363:7-367:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 363:7-368:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 363:7-369:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 363:7-370:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 363:7-371:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 363:7-372:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 363:7-373:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 363:7-401:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 363:7-403:10 @@ -4118,41 +4055,41 @@ testdata/SampleMaterial.lc 369:23-369:28 testdata/SampleMaterial.lc 370:20-370:33 CullType testdata/SampleMaterial.lc 371:30-371:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 372:25-372:30 Bool testdata/SampleMaterial.lc 373:29-373:34 Bool testdata/SampleMaterial.lc 375:13-401:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 375:15-375:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 375:15-376:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 375:15-377:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 375:15-378:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 375:15-379:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 375:15-380:31 @@ -4179,7 +4116,7 @@ testdata/SampleMaterial.lc 378:32-378:42 testdata/SampleMaterial.lc 379:29-379:36 TCGen testdata/SampleMaterial.lc 380:29-380:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 381:31-381:37 String -> StageTexture testdata/SampleMaterial.lc 381:31-381:84 @@ -4201,29 +4138,29 @@ testdata/SampleMaterial.lc 388:15-388:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 388:15-389:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 388:15-390:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 388:15-391:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 388:15-392:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 388:15-393:31 @@ -4240,7 +4177,7 @@ testdata/SampleMaterial.lc 388:15-397:40 testdata/SampleMaterial.lc 388:15-398:46 String -> StageAttrs testdata/SampleMaterial.lc 388:15-400:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 389:29-389:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 389:29-389:57 @@ -4258,7 +4195,7 @@ testdata/SampleMaterial.lc 391:32-391:42 testdata/SampleMaterial.lc 392:29-392:40 TCGen testdata/SampleMaterial.lc 393:29-393:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 394:31-394:42 StageTexture testdata/SampleMaterial.lc 395:34-395:38 @@ -4276,7 +4213,7 @@ testdata/SampleMaterial.lc 402:21-402:26 testdata/SampleMaterial.lc 405:5-447:6 (String, CommonAttrs) testdata/SampleMaterial.lc 405:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 405:7-405:53 String testdata/SampleMaterial.lc 406:7-406:18 @@ -4286,49 +4223,42 @@ testdata/SampleMaterial.lc 406:7-406:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 406:7-407:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 406:7-408:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 406:7-409:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 406:7-410:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 406:7-411:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 406:7-412:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 406:7-413:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 406:7-414:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 406:7-415:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 406:7-416:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 406:7-444:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 406:7-446:10 @@ -4348,41 +4278,41 @@ testdata/SampleMaterial.lc 412:23-412:28 testdata/SampleMaterial.lc 413:20-413:33 CullType testdata/SampleMaterial.lc 414:30-414:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 415:25-415:30 Bool testdata/SampleMaterial.lc 416:29-416:34 Bool testdata/SampleMaterial.lc 418:13-444:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 418:15-418:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 418:15-419:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 418:15-420:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 418:15-421:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 418:15-422:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 418:15-423:31 @@ -4409,7 +4339,7 @@ testdata/SampleMaterial.lc 421:32-421:42 testdata/SampleMaterial.lc 422:29-422:36 TCGen testdata/SampleMaterial.lc 423:29-423:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 424:31-424:37 String -> StageTexture testdata/SampleMaterial.lc 424:31-424:84 @@ -4431,29 +4361,29 @@ testdata/SampleMaterial.lc 431:15-431:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 431:15-432:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 431:15-433:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 431:15-434:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 431:15-435:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 431:15-436:31 @@ -4470,7 +4400,7 @@ testdata/SampleMaterial.lc 431:15-440:40 testdata/SampleMaterial.lc 431:15-441:46 String -> StageAttrs testdata/SampleMaterial.lc 431:15-443:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 432:29-432:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 432:29-432:57 @@ -4488,7 +4418,7 @@ testdata/SampleMaterial.lc 434:32-434:42 testdata/SampleMaterial.lc 435:29-435:40 TCGen testdata/SampleMaterial.lc 436:29-436:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 437:31-437:42 StageTexture testdata/SampleMaterial.lc 438:34-438:38 @@ -4506,7 +4436,7 @@ testdata/SampleMaterial.lc 445:21-445:26 testdata/SampleMaterial.lc 448:5-490:6 (String, CommonAttrs) testdata/SampleMaterial.lc 448:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 448:7-448:53 String testdata/SampleMaterial.lc 449:7-449:18 @@ -4516,49 +4446,42 @@ testdata/SampleMaterial.lc 449:7-449:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 449:7-450:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 449:7-451:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 449:7-452:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 449:7-453:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 449:7-454:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 449:7-455:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 449:7-456:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 449:7-457:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 449:7-458:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 449:7-459:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 449:7-487:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 449:7-489:10 @@ -4578,41 +4501,41 @@ testdata/SampleMaterial.lc 455:23-455:28 testdata/SampleMaterial.lc 456:20-456:33 CullType testdata/SampleMaterial.lc 457:30-457:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 458:25-458:30 Bool testdata/SampleMaterial.lc 459:29-459:34 Bool testdata/SampleMaterial.lc 461:13-487:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 461:15-461:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 461:15-462:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 461:15-463:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 461:15-464:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 461:15-465:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 461:15-466:31 @@ -4639,7 +4562,7 @@ testdata/SampleMaterial.lc 464:32-464:42 testdata/SampleMaterial.lc 465:29-465:36 TCGen testdata/SampleMaterial.lc 466:29-466:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 467:31-467:37 String -> StageTexture testdata/SampleMaterial.lc 467:31-467:84 @@ -4661,29 +4584,29 @@ testdata/SampleMaterial.lc 474:15-474:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 474:15-475:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 474:15-476:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 474:15-477:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 474:15-478:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 474:15-479:31 @@ -4700,7 +4623,7 @@ testdata/SampleMaterial.lc 474:15-483:40 testdata/SampleMaterial.lc 474:15-484:46 String -> StageAttrs testdata/SampleMaterial.lc 474:15-486:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 475:29-475:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 475:29-475:57 @@ -4718,7 +4641,7 @@ testdata/SampleMaterial.lc 477:32-477:42 testdata/SampleMaterial.lc 478:29-478:40 TCGen testdata/SampleMaterial.lc 479:29-479:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 480:31-480:42 StageTexture testdata/SampleMaterial.lc 481:34-481:38 @@ -4736,7 +4659,7 @@ testdata/SampleMaterial.lc 488:21-488:26 testdata/SampleMaterial.lc 491:5-533:6 (String, CommonAttrs) testdata/SampleMaterial.lc 491:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 491:7-491:53 String testdata/SampleMaterial.lc 492:7-492:18 @@ -4746,49 +4669,42 @@ testdata/SampleMaterial.lc 492:7-492:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 492:7-493:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 492:7-494:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 492:7-495:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 492:7-496:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 492:7-497:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 492:7-498:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 492:7-499:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 492:7-500:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 492:7-501:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 492:7-502:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 492:7-530:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 492:7-532:10 @@ -4808,41 +4724,41 @@ testdata/SampleMaterial.lc 498:23-498:28 testdata/SampleMaterial.lc 499:20-499:33 CullType testdata/SampleMaterial.lc 500:30-500:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 501:25-501:30 Bool testdata/SampleMaterial.lc 502:29-502:34 Bool testdata/SampleMaterial.lc 504:13-530:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 504:15-504:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 504:15-505:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 504:15-506:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 504:15-507:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 504:15-508:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 504:15-509:31 @@ -4869,7 +4785,7 @@ testdata/SampleMaterial.lc 507:32-507:42 testdata/SampleMaterial.lc 508:29-508:36 TCGen testdata/SampleMaterial.lc 509:29-509:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 510:31-510:37 String -> StageTexture testdata/SampleMaterial.lc 510:31-510:84 @@ -4891,29 +4807,29 @@ testdata/SampleMaterial.lc 517:15-517:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 517:15-518:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 517:15-519:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 517:15-520:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 517:15-521:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 517:15-522:31 @@ -4930,7 +4846,7 @@ testdata/SampleMaterial.lc 517:15-526:40 testdata/SampleMaterial.lc 517:15-527:46 String -> StageAttrs testdata/SampleMaterial.lc 517:15-529:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 518:29-518:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 518:29-518:57 @@ -4948,7 +4864,7 @@ testdata/SampleMaterial.lc 520:32-520:42 testdata/SampleMaterial.lc 521:29-521:40 TCGen testdata/SampleMaterial.lc 522:29-522:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 523:31-523:42 StageTexture testdata/SampleMaterial.lc 524:34-524:38 @@ -4966,7 +4882,7 @@ testdata/SampleMaterial.lc 531:21-531:26 testdata/SampleMaterial.lc 534:5-576:6 (String, CommonAttrs) testdata/SampleMaterial.lc 534:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 534:7-534:42 String testdata/SampleMaterial.lc 535:7-535:18 @@ -4976,49 +4892,42 @@ testdata/SampleMaterial.lc 535:7-535:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 535:7-536:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 535:7-537:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 535:7-538:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 535:7-539:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 535:7-540:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 535:7-541:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 535:7-542:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 535:7-543:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 535:7-544:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 535:7-545:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 535:7-573:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 535:7-575:10 @@ -5038,41 +4947,41 @@ testdata/SampleMaterial.lc 541:23-541:28 testdata/SampleMaterial.lc 542:20-542:33 CullType testdata/SampleMaterial.lc 543:30-543:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 544:25-544:30 Bool testdata/SampleMaterial.lc 545:29-545:34 Bool testdata/SampleMaterial.lc 547:13-573:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 547:15-547:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 547:15-548:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 547:15-549:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 547:15-550:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 547:15-551:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 547:15-552:31 @@ -5099,7 +5008,7 @@ testdata/SampleMaterial.lc 550:32-550:42 testdata/SampleMaterial.lc 551:29-551:36 TCGen testdata/SampleMaterial.lc 552:29-552:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 553:31-553:37 String -> StageTexture testdata/SampleMaterial.lc 553:31-553:73 @@ -5121,29 +5030,29 @@ testdata/SampleMaterial.lc 560:15-560:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 560:15-561:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 560:15-562:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 560:15-563:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 560:15-564:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 560:15-565:31 @@ -5160,7 +5069,7 @@ testdata/SampleMaterial.lc 560:15-569:40 testdata/SampleMaterial.lc 560:15-570:46 String -> StageAttrs testdata/SampleMaterial.lc 560:15-572:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 561:29-561:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 561:29-561:57 @@ -5178,7 +5087,7 @@ testdata/SampleMaterial.lc 563:32-563:42 testdata/SampleMaterial.lc 564:29-564:40 TCGen testdata/SampleMaterial.lc 565:29-565:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 566:31-566:42 StageTexture testdata/SampleMaterial.lc 567:34-567:38 @@ -5196,7 +5105,7 @@ testdata/SampleMaterial.lc 574:21-574:26 testdata/SampleMaterial.lc 577:5-619:6 (String, CommonAttrs) testdata/SampleMaterial.lc 577:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 577:7-577:42 String testdata/SampleMaterial.lc 578:7-578:18 @@ -5206,49 +5115,42 @@ testdata/SampleMaterial.lc 578:7-578:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 578:7-579:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 578:7-580:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 578:7-581:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 578:7-582:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 578:7-583:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 578:7-584:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 578:7-585:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 578:7-586:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 578:7-587:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 578:7-588:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 578:7-616:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 578:7-618:10 @@ -5268,41 +5170,41 @@ testdata/SampleMaterial.lc 584:23-584:28 testdata/SampleMaterial.lc 585:20-585:33 CullType testdata/SampleMaterial.lc 586:30-586:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 587:25-587:30 Bool testdata/SampleMaterial.lc 588:29-588:34 Bool testdata/SampleMaterial.lc 590:13-616:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 590:15-590:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 590:15-591:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 590:15-592:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 590:15-593:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 590:15-594:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 590:15-595:31 @@ -5329,7 +5231,7 @@ testdata/SampleMaterial.lc 593:32-593:42 testdata/SampleMaterial.lc 594:29-594:36 TCGen testdata/SampleMaterial.lc 595:29-595:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 596:31-596:37 String -> StageTexture testdata/SampleMaterial.lc 596:31-596:73 @@ -5351,29 +5253,29 @@ testdata/SampleMaterial.lc 603:15-603:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 603:15-604:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 603:15-605:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 603:15-606:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 603:15-607:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 603:15-608:31 @@ -5390,7 +5292,7 @@ testdata/SampleMaterial.lc 603:15-612:40 testdata/SampleMaterial.lc 603:15-613:46 String -> StageAttrs testdata/SampleMaterial.lc 603:15-615:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 604:29-604:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 604:29-604:57 @@ -5408,7 +5310,7 @@ testdata/SampleMaterial.lc 606:32-606:42 testdata/SampleMaterial.lc 607:29-607:40 TCGen testdata/SampleMaterial.lc 608:29-608:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 609:31-609:42 StageTexture testdata/SampleMaterial.lc 610:34-610:38 @@ -5426,7 +5328,7 @@ testdata/SampleMaterial.lc 617:21-617:26 testdata/SampleMaterial.lc 620:5-662:6 (String, CommonAttrs) testdata/SampleMaterial.lc 620:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 620:7-620:42 String testdata/SampleMaterial.lc 621:7-621:18 @@ -5436,49 +5338,42 @@ testdata/SampleMaterial.lc 621:7-621:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 621:7-622:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 621:7-623:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 621:7-624:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 621:7-625:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 621:7-626:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 621:7-627:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 621:7-628:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 621:7-629:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 621:7-630:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 621:7-631:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 621:7-659:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 621:7-661:10 @@ -5498,41 +5393,41 @@ testdata/SampleMaterial.lc 627:23-627:28 testdata/SampleMaterial.lc 628:20-628:33 CullType testdata/SampleMaterial.lc 629:30-629:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 630:25-630:30 Bool testdata/SampleMaterial.lc 631:29-631:34 Bool testdata/SampleMaterial.lc 633:13-659:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 633:15-633:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 633:15-634:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 633:15-635:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 633:15-636:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 633:15-637:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 633:15-638:31 @@ -5559,7 +5454,7 @@ testdata/SampleMaterial.lc 636:32-636:42 testdata/SampleMaterial.lc 637:29-637:36 TCGen testdata/SampleMaterial.lc 638:29-638:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 639:31-639:37 String -> StageTexture testdata/SampleMaterial.lc 639:31-639:73 @@ -5581,29 +5476,29 @@ testdata/SampleMaterial.lc 646:15-646:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 646:15-647:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 646:15-648:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 646:15-649:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 646:15-650:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 646:15-651:31 @@ -5620,7 +5515,7 @@ testdata/SampleMaterial.lc 646:15-655:40 testdata/SampleMaterial.lc 646:15-656:46 String -> StageAttrs testdata/SampleMaterial.lc 646:15-658:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 647:29-647:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 647:29-647:57 @@ -5638,7 +5533,7 @@ testdata/SampleMaterial.lc 649:32-649:42 testdata/SampleMaterial.lc 650:29-650:40 TCGen testdata/SampleMaterial.lc 651:29-651:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 652:31-652:42 StageTexture testdata/SampleMaterial.lc 653:34-653:38 @@ -5656,7 +5551,7 @@ testdata/SampleMaterial.lc 660:21-660:26 testdata/SampleMaterial.lc 663:5-705:6 (String, CommonAttrs) testdata/SampleMaterial.lc 663:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 663:7-663:42 String testdata/SampleMaterial.lc 664:7-664:18 @@ -5666,49 +5561,42 @@ testdata/SampleMaterial.lc 664:7-664:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 664:7-665:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 664:7-666:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 664:7-667:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 664:7-668:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 664:7-669:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 664:7-670:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 664:7-671:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 664:7-672:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 664:7-673:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 664:7-674:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 664:7-702:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 664:7-704:10 @@ -5728,41 +5616,41 @@ testdata/SampleMaterial.lc 670:23-670:28 testdata/SampleMaterial.lc 671:20-671:33 CullType testdata/SampleMaterial.lc 672:30-672:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 673:25-673:30 Bool testdata/SampleMaterial.lc 674:29-674:34 Bool testdata/SampleMaterial.lc 676:13-702:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 676:15-676:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 676:15-677:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 676:15-678:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 676:15-679:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 676:15-680:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 676:15-681:31 @@ -5789,7 +5677,7 @@ testdata/SampleMaterial.lc 679:32-679:42 testdata/SampleMaterial.lc 680:29-680:36 TCGen testdata/SampleMaterial.lc 681:29-681:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 682:31-682:37 String -> StageTexture testdata/SampleMaterial.lc 682:31-682:73 @@ -5811,29 +5699,29 @@ testdata/SampleMaterial.lc 689:15-689:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 689:15-690:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 689:15-691:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 689:15-692:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 689:15-693:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 689:15-694:31 @@ -5850,7 +5738,7 @@ testdata/SampleMaterial.lc 689:15-698:40 testdata/SampleMaterial.lc 689:15-699:46 String -> StageAttrs testdata/SampleMaterial.lc 689:15-701:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 690:29-690:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 690:29-690:57 @@ -5868,7 +5756,7 @@ testdata/SampleMaterial.lc 692:32-692:42 testdata/SampleMaterial.lc 693:29-693:40 TCGen testdata/SampleMaterial.lc 694:29-694:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 695:31-695:42 StageTexture testdata/SampleMaterial.lc 696:34-696:38 @@ -5886,7 +5774,7 @@ testdata/SampleMaterial.lc 703:21-703:26 testdata/SampleMaterial.lc 706:5-748:6 (String, CommonAttrs) testdata/SampleMaterial.lc 706:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 706:7-706:42 String testdata/SampleMaterial.lc 707:7-707:18 @@ -5896,49 +5784,42 @@ testdata/SampleMaterial.lc 707:7-707:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 707:7-708:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 707:7-709:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 707:7-710:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 707:7-711:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 707:7-712:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 707:7-713:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 707:7-714:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 707:7-715:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 707:7-716:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 707:7-717:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 707:7-745:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 707:7-747:10 @@ -5958,41 +5839,41 @@ testdata/SampleMaterial.lc 713:23-713:28 testdata/SampleMaterial.lc 714:20-714:33 CullType testdata/SampleMaterial.lc 715:30-715:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 716:25-716:30 Bool testdata/SampleMaterial.lc 717:29-717:34 Bool testdata/SampleMaterial.lc 719:13-745:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 719:15-719:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 719:15-720:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 719:15-721:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 719:15-722:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 719:15-723:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 719:15-724:31 @@ -6019,7 +5900,7 @@ testdata/SampleMaterial.lc 722:32-722:42 testdata/SampleMaterial.lc 723:29-723:36 TCGen testdata/SampleMaterial.lc 724:29-724:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 725:31-725:37 String -> StageTexture testdata/SampleMaterial.lc 725:31-725:73 @@ -6041,29 +5922,29 @@ testdata/SampleMaterial.lc 732:15-732:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 732:15-733:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 732:15-734:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 732:15-735:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 732:15-736:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 732:15-737:31 @@ -6080,7 +5961,7 @@ testdata/SampleMaterial.lc 732:15-741:40 testdata/SampleMaterial.lc 732:15-742:46 String -> StageAttrs testdata/SampleMaterial.lc 732:15-744:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 733:29-733:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 733:29-733:57 @@ -6098,7 +5979,7 @@ testdata/SampleMaterial.lc 735:32-735:42 testdata/SampleMaterial.lc 736:29-736:40 TCGen testdata/SampleMaterial.lc 737:29-737:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 738:31-738:42 StageTexture testdata/SampleMaterial.lc 739:34-739:38 @@ -6116,7 +5997,7 @@ testdata/SampleMaterial.lc 746:21-746:26 testdata/SampleMaterial.lc 749:5-791:6 (String, CommonAttrs) testdata/SampleMaterial.lc 749:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 749:7-749:42 String testdata/SampleMaterial.lc 750:7-750:18 @@ -6126,49 +6007,42 @@ testdata/SampleMaterial.lc 750:7-750:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 750:7-751:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 750:7-752:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 750:7-753:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 750:7-754:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 750:7-755:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 750:7-756:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 750:7-757:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 750:7-758:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 750:7-759:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 750:7-760:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 750:7-788:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 750:7-790:10 @@ -6188,41 +6062,41 @@ testdata/SampleMaterial.lc 756:23-756:28 testdata/SampleMaterial.lc 757:20-757:33 CullType testdata/SampleMaterial.lc 758:30-758:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 759:25-759:30 Bool testdata/SampleMaterial.lc 760:29-760:34 Bool testdata/SampleMaterial.lc 762:13-788:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 762:15-762:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 762:15-763:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 762:15-764:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 762:15-765:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 762:15-766:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 762:15-767:31 @@ -6249,7 +6123,7 @@ testdata/SampleMaterial.lc 765:32-765:42 testdata/SampleMaterial.lc 766:29-766:36 TCGen testdata/SampleMaterial.lc 767:29-767:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 768:31-768:37 String -> StageTexture testdata/SampleMaterial.lc 768:31-768:73 @@ -6271,29 +6145,29 @@ testdata/SampleMaterial.lc 775:15-775:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 775:15-776:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 775:15-777:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 775:15-778:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 775:15-779:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 775:15-780:31 @@ -6310,7 +6184,7 @@ testdata/SampleMaterial.lc 775:15-784:40 testdata/SampleMaterial.lc 775:15-785:46 String -> StageAttrs testdata/SampleMaterial.lc 775:15-787:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 776:29-776:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 776:29-776:57 @@ -6328,7 +6202,7 @@ testdata/SampleMaterial.lc 778:32-778:42 testdata/SampleMaterial.lc 779:29-779:40 TCGen testdata/SampleMaterial.lc 780:29-780:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 781:31-781:42 StageTexture testdata/SampleMaterial.lc 782:34-782:38 @@ -6346,7 +6220,7 @@ testdata/SampleMaterial.lc 789:21-789:26 testdata/SampleMaterial.lc 792:5-834:6 (String, CommonAttrs) testdata/SampleMaterial.lc 792:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 792:7-792:41 String testdata/SampleMaterial.lc 793:7-793:18 @@ -6356,49 +6230,42 @@ testdata/SampleMaterial.lc 793:7-793:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 793:7-794:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 793:7-795:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 793:7-796:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 793:7-797:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 793:7-798:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 793:7-799:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 793:7-800:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 793:7-801:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 793:7-802:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 793:7-803:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 793:7-831:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 793:7-833:10 @@ -6418,41 +6285,41 @@ testdata/SampleMaterial.lc 799:23-799:28 testdata/SampleMaterial.lc 800:20-800:33 CullType testdata/SampleMaterial.lc 801:30-801:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 802:25-802:30 Bool testdata/SampleMaterial.lc 803:29-803:34 Bool testdata/SampleMaterial.lc 805:13-831:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 805:15-805:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 805:15-806:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 805:15-807:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 805:15-808:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 805:15-809:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 805:15-810:31 @@ -6479,7 +6346,7 @@ testdata/SampleMaterial.lc 808:32-808:42 testdata/SampleMaterial.lc 809:29-809:36 TCGen testdata/SampleMaterial.lc 810:29-810:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 811:31-811:37 String -> StageTexture testdata/SampleMaterial.lc 811:31-811:72 @@ -6501,29 +6368,29 @@ testdata/SampleMaterial.lc 818:15-818:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 818:15-819:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 818:15-820:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 818:15-821:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 818:15-822:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 818:15-823:31 @@ -6540,7 +6407,7 @@ testdata/SampleMaterial.lc 818:15-827:40 testdata/SampleMaterial.lc 818:15-828:46 String -> StageAttrs testdata/SampleMaterial.lc 818:15-830:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 819:29-819:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 819:29-819:57 @@ -6558,7 +6425,7 @@ testdata/SampleMaterial.lc 821:32-821:42 testdata/SampleMaterial.lc 822:29-822:40 TCGen testdata/SampleMaterial.lc 823:29-823:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 824:31-824:42 StageTexture testdata/SampleMaterial.lc 825:34-825:38 @@ -6576,7 +6443,7 @@ testdata/SampleMaterial.lc 832:21-832:26 testdata/SampleMaterial.lc 835:5-891:6 (String, CommonAttrs) testdata/SampleMaterial.lc 835:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 835:7-835:41 String testdata/SampleMaterial.lc 836:7-836:18 @@ -6586,49 +6453,42 @@ testdata/SampleMaterial.lc 836:7-836:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 836:7-837:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 836:7-838:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 836:7-839:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 836:7-840:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 836:7-841:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 836:7-842:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 836:7-843:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 836:7-844:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 836:7-845:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 836:7-846:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 836:7-888:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 836:7-890:10 @@ -6648,41 +6508,41 @@ testdata/SampleMaterial.lc 842:23-842:28 testdata/SampleMaterial.lc 843:20-843:33 CullType testdata/SampleMaterial.lc 844:30-844:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 845:25-845:30 Bool testdata/SampleMaterial.lc 846:29-846:34 Bool testdata/SampleMaterial.lc 848:13-888:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 848:15-848:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 848:15-849:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 848:15-850:42 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 848:15-851:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 848:15-852:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 848:15-854:88 @@ -6709,7 +6569,7 @@ testdata/SampleMaterial.lc 851:32-851:42 testdata/SampleMaterial.lc 852:29-852:36 TCGen testdata/SampleMaterial.lc 854:21-854:88 - List TCMod + [TCMod] testdata/SampleMaterial.lc 854:23-854:32 Float -> Float -> TCMod testdata/SampleMaterial.lc 854:23-854:36 @@ -6731,7 +6591,7 @@ testdata/SampleMaterial.lc 854:43-854:63 testdata/SampleMaterial.lc 854:43-854:67 TCMod testdata/SampleMaterial.lc 854:43-854:86 - List TCMod + [TCMod] testdata/SampleMaterial.lc 854:51-854:54 Float testdata/SampleMaterial.lc 854:55-854:59 @@ -6745,7 +6605,7 @@ testdata/SampleMaterial.lc 854:70-854:78 testdata/SampleMaterial.lc 854:70-854:82 Float -> TCMod testdata/SampleMaterial.lc 854:70-854:86 - TCMod | List TCMod + TCMod | [TCMod] testdata/SampleMaterial.lc 854:79-854:82 Float testdata/SampleMaterial.lc 854:83-854:86 @@ -6771,29 +6631,29 @@ testdata/SampleMaterial.lc 862:15-862:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 862:15-863:69 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 862:15-864:42 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 862:15-865:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 862:15-866:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 862:15-867:31 @@ -6812,7 +6672,7 @@ testdata/SampleMaterial.lc 862:15-872:46 testdata/SampleMaterial.lc 862:15-874:18 StageAttrs testdata/SampleMaterial.lc 862:15-887:18 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 863:29-863:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 863:29-863:69 @@ -6830,7 +6690,7 @@ testdata/SampleMaterial.lc 865:32-865:42 testdata/SampleMaterial.lc 866:29-866:36 TCGen testdata/SampleMaterial.lc 867:29-867:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 868:31-868:37 String -> StageTexture testdata/SampleMaterial.lc 868:31-868:76 @@ -6852,29 +6712,29 @@ testdata/SampleMaterial.lc 875:15-875:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 875:15-876:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 875:15-877:42 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 875:15-878:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 875:15-879:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 875:15-880:31 @@ -6891,7 +6751,7 @@ testdata/SampleMaterial.lc 875:15-884:40 testdata/SampleMaterial.lc 875:15-885:46 String -> StageAttrs testdata/SampleMaterial.lc 875:15-887:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 876:29-876:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 876:29-876:57 @@ -6909,7 +6769,7 @@ testdata/SampleMaterial.lc 878:32-878:42 testdata/SampleMaterial.lc 879:29-879:40 TCGen testdata/SampleMaterial.lc 880:29-880:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 881:31-881:42 StageTexture testdata/SampleMaterial.lc 882:34-882:39 @@ -6927,7 +6787,7 @@ testdata/SampleMaterial.lc 889:21-889:26 testdata/SampleMaterial.lc 892:5-934:6 (String, CommonAttrs) testdata/SampleMaterial.lc 892:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 892:7-892:41 String testdata/SampleMaterial.lc 893:7-893:18 @@ -6937,49 +6797,42 @@ testdata/SampleMaterial.lc 893:7-893:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 893:7-894:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 893:7-895:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 893:7-896:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 893:7-897:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 893:7-898:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 893:7-899:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 893:7-900:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 893:7-901:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 893:7-902:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 893:7-903:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 893:7-931:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 893:7-933:10 @@ -6999,41 +6852,41 @@ testdata/SampleMaterial.lc 899:23-899:28 testdata/SampleMaterial.lc 900:20-900:33 CullType testdata/SampleMaterial.lc 901:30-901:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 902:25-902:30 Bool testdata/SampleMaterial.lc 903:29-903:34 Bool testdata/SampleMaterial.lc 905:13-931:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 905:15-905:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 905:15-906:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 905:15-907:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 905:15-908:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 905:15-909:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 905:15-910:31 @@ -7060,7 +6913,7 @@ testdata/SampleMaterial.lc 908:32-908:42 testdata/SampleMaterial.lc 909:29-909:36 TCGen testdata/SampleMaterial.lc 910:29-910:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 911:31-911:37 String -> StageTexture testdata/SampleMaterial.lc 911:31-911:72 @@ -7082,29 +6935,29 @@ testdata/SampleMaterial.lc 918:15-918:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 918:15-919:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 918:15-920:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 918:15-921:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 918:15-922:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 918:15-923:31 @@ -7121,7 +6974,7 @@ testdata/SampleMaterial.lc 918:15-927:40 testdata/SampleMaterial.lc 918:15-928:46 String -> StageAttrs testdata/SampleMaterial.lc 918:15-930:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 919:29-919:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 919:29-919:57 @@ -7139,7 +6992,7 @@ testdata/SampleMaterial.lc 921:32-921:42 testdata/SampleMaterial.lc 922:29-922:40 TCGen testdata/SampleMaterial.lc 923:29-923:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 924:31-924:42 StageTexture testdata/SampleMaterial.lc 925:34-925:38 @@ -7157,7 +7010,7 @@ testdata/SampleMaterial.lc 932:21-932:26 testdata/SampleMaterial.lc 935:5-978:6 (String, CommonAttrs) testdata/SampleMaterial.lc 935:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 935:7-935:54 String testdata/SampleMaterial.lc 936:7-936:18 @@ -7167,49 +7020,42 @@ testdata/SampleMaterial.lc 936:7-936:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 936:7-937:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 936:7-938:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 936:7-939:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 936:7-940:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 936:7-941:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 936:7-942:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 936:7-943:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 936:7-944:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 936:7-945:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 936:7-946:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 936:7-975:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 936:7-977:10 @@ -7229,41 +7075,41 @@ testdata/SampleMaterial.lc 942:23-942:28 testdata/SampleMaterial.lc 943:20-943:33 CullType testdata/SampleMaterial.lc 944:30-944:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 945:25-945:30 Bool testdata/SampleMaterial.lc 946:29-946:34 Bool testdata/SampleMaterial.lc 948:13-975:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 948:15-948:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 948:15-949:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 948:15-950:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 948:15-951:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 948:15-952:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 948:15-953:31 @@ -7290,7 +7136,7 @@ testdata/SampleMaterial.lc 951:32-951:42 testdata/SampleMaterial.lc 952:29-952:36 TCGen testdata/SampleMaterial.lc 953:29-953:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 955:21-955:27 String -> StageTexture testdata/SampleMaterial.lc 955:21-955:75 @@ -7312,29 +7158,29 @@ testdata/SampleMaterial.lc 962:15-962:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 962:15-963:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 962:15-964:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 962:15-965:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 962:15-966:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 962:15-967:31 @@ -7351,7 +7197,7 @@ testdata/SampleMaterial.lc 962:15-971:40 testdata/SampleMaterial.lc 962:15-972:46 String -> StageAttrs testdata/SampleMaterial.lc 962:15-974:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 963:29-963:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 963:29-963:57 @@ -7369,7 +7215,7 @@ testdata/SampleMaterial.lc 965:32-965:42 testdata/SampleMaterial.lc 966:29-966:40 TCGen testdata/SampleMaterial.lc 967:29-967:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 968:31-968:42 StageTexture testdata/SampleMaterial.lc 969:34-969:38 @@ -7387,7 +7233,7 @@ testdata/SampleMaterial.lc 976:21-976:26 testdata/SampleMaterial.lc 979:5-1021:6 (String, CommonAttrs) testdata/SampleMaterial.lc 979:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 979:7-979:45 String testdata/SampleMaterial.lc 980:7-980:18 @@ -7397,49 +7243,42 @@ testdata/SampleMaterial.lc 980:7-980:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 980:7-981:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 980:7-982:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 980:7-983:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 980:7-984:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 980:7-985:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 980:7-986:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 980:7-987:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 980:7-988:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 980:7-989:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 980:7-990:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 980:7-1018:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 980:7-1020:10 @@ -7459,41 +7298,41 @@ testdata/SampleMaterial.lc 986:23-986:28 testdata/SampleMaterial.lc 987:20-987:33 CullType testdata/SampleMaterial.lc 988:30-988:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 989:25-989:30 Bool testdata/SampleMaterial.lc 990:29-990:34 Bool testdata/SampleMaterial.lc 992:13-1018:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 992:15-992:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 992:15-993:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 992:15-994:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 992:15-995:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 992:15-996:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 992:15-997:31 @@ -7520,7 +7359,7 @@ testdata/SampleMaterial.lc 995:32-995:42 testdata/SampleMaterial.lc 996:29-996:36 TCGen testdata/SampleMaterial.lc 997:29-997:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 998:31-998:37 String -> StageTexture testdata/SampleMaterial.lc 998:31-998:76 @@ -7542,29 +7381,29 @@ testdata/SampleMaterial.lc 1005:15-1005:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1005:15-1006:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1005:15-1007:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1005:15-1008:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1005:15-1009:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1005:15-1010:31 @@ -7581,7 +7420,7 @@ testdata/SampleMaterial.lc 1005:15-1014:40 testdata/SampleMaterial.lc 1005:15-1015:46 String -> StageAttrs testdata/SampleMaterial.lc 1005:15-1017:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 1006:29-1006:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 1006:29-1006:57 @@ -7599,7 +7438,7 @@ testdata/SampleMaterial.lc 1008:32-1008:42 testdata/SampleMaterial.lc 1009:29-1009:40 TCGen testdata/SampleMaterial.lc 1010:29-1010:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1011:31-1011:42 StageTexture testdata/SampleMaterial.lc 1012:34-1012:38 @@ -7617,7 +7456,7 @@ testdata/SampleMaterial.lc 1019:21-1019:26 testdata/SampleMaterial.lc 1022:5-1064:6 (String, CommonAttrs) testdata/SampleMaterial.lc 1022:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 1022:7-1022:44 String testdata/SampleMaterial.lc 1023:7-1023:18 @@ -7627,49 +7466,42 @@ testdata/SampleMaterial.lc 1023:7-1023:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1023:7-1024:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1023:7-1025:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1023:7-1026:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1023:7-1027:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1023:7-1028:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1023:7-1029:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1023:7-1030:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1023:7-1031:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1023:7-1032:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1023:7-1033:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1023:7-1061:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 1023:7-1063:10 @@ -7689,41 +7521,41 @@ testdata/SampleMaterial.lc 1029:23-1029:28 testdata/SampleMaterial.lc 1030:20-1030:33 CullType testdata/SampleMaterial.lc 1031:30-1031:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1032:25-1032:30 Bool testdata/SampleMaterial.lc 1033:29-1033:34 Bool testdata/SampleMaterial.lc 1035:13-1061:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 1035:15-1035:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1035:15-1036:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1035:15-1037:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1035:15-1038:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1035:15-1039:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1035:15-1040:31 @@ -7750,7 +7582,7 @@ testdata/SampleMaterial.lc 1038:32-1038:42 testdata/SampleMaterial.lc 1039:29-1039:36 TCGen testdata/SampleMaterial.lc 1040:29-1040:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1041:31-1041:37 String -> StageTexture testdata/SampleMaterial.lc 1041:31-1041:75 @@ -7772,29 +7604,29 @@ testdata/SampleMaterial.lc 1048:15-1048:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1048:15-1049:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1048:15-1050:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1048:15-1051:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1048:15-1052:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1048:15-1053:31 @@ -7811,7 +7643,7 @@ testdata/SampleMaterial.lc 1048:15-1057:40 testdata/SampleMaterial.lc 1048:15-1058:46 String -> StageAttrs testdata/SampleMaterial.lc 1048:15-1060:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 1049:29-1049:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 1049:29-1049:57 @@ -7829,7 +7661,7 @@ testdata/SampleMaterial.lc 1051:32-1051:42 testdata/SampleMaterial.lc 1052:29-1052:40 TCGen testdata/SampleMaterial.lc 1053:29-1053:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1054:31-1054:42 StageTexture testdata/SampleMaterial.lc 1055:34-1055:38 @@ -7847,7 +7679,7 @@ testdata/SampleMaterial.lc 1062:21-1062:26 testdata/SampleMaterial.lc 1065:5-1107:6 (String, CommonAttrs) testdata/SampleMaterial.lc 1065:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 1065:7-1065:44 String testdata/SampleMaterial.lc 1066:7-1066:18 @@ -7857,49 +7689,42 @@ testdata/SampleMaterial.lc 1066:7-1066:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1066:7-1067:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1066:7-1068:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1066:7-1069:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1066:7-1070:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1066:7-1071:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1066:7-1072:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1066:7-1073:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1066:7-1074:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1066:7-1075:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1066:7-1076:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1066:7-1104:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 1066:7-1106:10 @@ -7919,41 +7744,41 @@ testdata/SampleMaterial.lc 1072:23-1072:28 testdata/SampleMaterial.lc 1073:20-1073:33 CullType testdata/SampleMaterial.lc 1074:30-1074:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1075:25-1075:30 Bool testdata/SampleMaterial.lc 1076:29-1076:34 Bool testdata/SampleMaterial.lc 1078:13-1104:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 1078:15-1078:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1078:15-1079:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1078:15-1080:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1078:15-1081:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1078:15-1082:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1078:15-1083:31 @@ -7980,7 +7805,7 @@ testdata/SampleMaterial.lc 1081:32-1081:42 testdata/SampleMaterial.lc 1082:29-1082:36 TCGen testdata/SampleMaterial.lc 1083:29-1083:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1084:31-1084:37 String -> StageTexture testdata/SampleMaterial.lc 1084:31-1084:75 @@ -8002,29 +7827,29 @@ testdata/SampleMaterial.lc 1091:15-1091:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1091:15-1092:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1091:15-1093:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1091:15-1094:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1091:15-1095:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1091:15-1096:31 @@ -8041,7 +7866,7 @@ testdata/SampleMaterial.lc 1091:15-1100:40 testdata/SampleMaterial.lc 1091:15-1101:46 String -> StageAttrs testdata/SampleMaterial.lc 1091:15-1103:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 1092:29-1092:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 1092:29-1092:57 @@ -8059,7 +7884,7 @@ testdata/SampleMaterial.lc 1094:32-1094:42 testdata/SampleMaterial.lc 1095:29-1095:40 TCGen testdata/SampleMaterial.lc 1096:29-1096:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1097:31-1097:42 StageTexture testdata/SampleMaterial.lc 1098:34-1098:38 @@ -8077,7 +7902,7 @@ testdata/SampleMaterial.lc 1105:21-1105:26 testdata/SampleMaterial.lc 1108:5-1150:6 (String, CommonAttrs) testdata/SampleMaterial.lc 1108:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 1108:7-1108:49 String testdata/SampleMaterial.lc 1109:7-1109:18 @@ -8087,49 +7912,42 @@ testdata/SampleMaterial.lc 1109:7-1109:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1109:7-1110:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1109:7-1111:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1109:7-1112:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1109:7-1113:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1109:7-1114:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1109:7-1115:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1109:7-1116:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1109:7-1117:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1109:7-1118:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1109:7-1119:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1109:7-1147:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 1109:7-1149:10 @@ -8149,41 +7967,41 @@ testdata/SampleMaterial.lc 1115:23-1115:28 testdata/SampleMaterial.lc 1116:20-1116:33 CullType testdata/SampleMaterial.lc 1117:30-1117:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1118:25-1118:30 Bool testdata/SampleMaterial.lc 1119:29-1119:34 Bool testdata/SampleMaterial.lc 1121:13-1147:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 1121:15-1121:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1121:15-1122:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1121:15-1123:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1121:15-1124:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1121:15-1125:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1121:15-1126:31 @@ -8210,7 +8028,7 @@ testdata/SampleMaterial.lc 1124:32-1124:42 testdata/SampleMaterial.lc 1125:29-1125:36 TCGen testdata/SampleMaterial.lc 1126:29-1126:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1127:31-1127:37 String -> StageTexture testdata/SampleMaterial.lc 1127:31-1127:80 @@ -8232,29 +8050,29 @@ testdata/SampleMaterial.lc 1134:15-1134:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1134:15-1135:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1134:15-1136:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1134:15-1137:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1134:15-1138:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1134:15-1139:31 @@ -8271,7 +8089,7 @@ testdata/SampleMaterial.lc 1134:15-1143:40 testdata/SampleMaterial.lc 1134:15-1144:46 String -> StageAttrs testdata/SampleMaterial.lc 1134:15-1146:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 1135:29-1135:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 1135:29-1135:57 @@ -8289,7 +8107,7 @@ testdata/SampleMaterial.lc 1137:32-1137:42 testdata/SampleMaterial.lc 1138:29-1138:40 TCGen testdata/SampleMaterial.lc 1139:29-1139:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1140:31-1140:42 StageTexture testdata/SampleMaterial.lc 1141:34-1141:38 @@ -8307,7 +8125,7 @@ testdata/SampleMaterial.lc 1148:21-1148:26 testdata/SampleMaterial.lc 1151:5-1193:6 (String, CommonAttrs) testdata/SampleMaterial.lc 1151:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 1151:7-1151:41 String testdata/SampleMaterial.lc 1152:7-1152:18 @@ -8317,49 +8135,42 @@ testdata/SampleMaterial.lc 1152:7-1152:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1152:7-1153:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1152:7-1154:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1152:7-1155:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1152:7-1156:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1152:7-1157:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1152:7-1158:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1152:7-1159:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1152:7-1160:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1152:7-1161:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1152:7-1162:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1152:7-1190:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 1152:7-1192:10 @@ -8379,41 +8190,41 @@ testdata/SampleMaterial.lc 1158:23-1158:28 testdata/SampleMaterial.lc 1159:20-1159:33 CullType testdata/SampleMaterial.lc 1160:30-1160:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1161:25-1161:30 Bool testdata/SampleMaterial.lc 1162:29-1162:34 Bool testdata/SampleMaterial.lc 1164:13-1190:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 1164:15-1164:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1164:15-1165:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1164:15-1166:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1164:15-1167:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1164:15-1168:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1164:15-1169:31 @@ -8440,7 +8251,7 @@ testdata/SampleMaterial.lc 1167:32-1167:42 testdata/SampleMaterial.lc 1168:29-1168:36 TCGen testdata/SampleMaterial.lc 1169:29-1169:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1170:31-1170:37 String -> StageTexture testdata/SampleMaterial.lc 1170:31-1170:72 @@ -8462,29 +8273,29 @@ testdata/SampleMaterial.lc 1177:15-1177:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1177:15-1178:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1177:15-1179:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1177:15-1180:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1177:15-1181:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1177:15-1182:31 @@ -8501,7 +8312,7 @@ testdata/SampleMaterial.lc 1177:15-1186:40 testdata/SampleMaterial.lc 1177:15-1187:46 String -> StageAttrs testdata/SampleMaterial.lc 1177:15-1189:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 1178:29-1178:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 1178:29-1178:57 @@ -8519,7 +8330,7 @@ testdata/SampleMaterial.lc 1180:32-1180:42 testdata/SampleMaterial.lc 1181:29-1181:40 TCGen testdata/SampleMaterial.lc 1182:29-1182:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1183:31-1183:42 StageTexture testdata/SampleMaterial.lc 1184:34-1184:38 @@ -8537,7 +8348,7 @@ testdata/SampleMaterial.lc 1191:21-1191:26 testdata/SampleMaterial.lc 1194:5-1236:6 (String, CommonAttrs) testdata/SampleMaterial.lc 1194:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 1194:7-1194:43 String testdata/SampleMaterial.lc 1195:7-1195:18 @@ -8547,49 +8358,42 @@ testdata/SampleMaterial.lc 1195:7-1195:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1195:7-1196:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1195:7-1197:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1195:7-1198:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1195:7-1199:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1195:7-1200:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1195:7-1201:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1195:7-1202:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1195:7-1203:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1195:7-1204:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1195:7-1205:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1195:7-1233:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 1195:7-1235:10 @@ -8609,41 +8413,41 @@ testdata/SampleMaterial.lc 1201:23-1201:28 testdata/SampleMaterial.lc 1202:20-1202:33 CullType testdata/SampleMaterial.lc 1203:30-1203:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1204:25-1204:30 Bool testdata/SampleMaterial.lc 1205:29-1205:34 Bool testdata/SampleMaterial.lc 1207:13-1233:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 1207:15-1207:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1207:15-1208:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1207:15-1209:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1207:15-1210:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1207:15-1211:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1207:15-1212:31 @@ -8670,7 +8474,7 @@ testdata/SampleMaterial.lc 1210:32-1210:42 testdata/SampleMaterial.lc 1211:29-1211:36 TCGen testdata/SampleMaterial.lc 1212:29-1212:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1213:31-1213:37 String -> StageTexture testdata/SampleMaterial.lc 1213:31-1213:74 @@ -8692,29 +8496,29 @@ testdata/SampleMaterial.lc 1220:15-1220:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1220:15-1221:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1220:15-1222:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1220:15-1223:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1220:15-1224:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1220:15-1225:31 @@ -8731,7 +8535,7 @@ testdata/SampleMaterial.lc 1220:15-1229:40 testdata/SampleMaterial.lc 1220:15-1230:46 String -> StageAttrs testdata/SampleMaterial.lc 1220:15-1232:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 1221:29-1221:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 1221:29-1221:57 @@ -8749,7 +8553,7 @@ testdata/SampleMaterial.lc 1223:32-1223:42 testdata/SampleMaterial.lc 1224:29-1224:40 TCGen testdata/SampleMaterial.lc 1225:29-1225:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1226:31-1226:42 StageTexture testdata/SampleMaterial.lc 1227:34-1227:38 @@ -8767,7 +8571,7 @@ testdata/SampleMaterial.lc 1234:21-1234:26 testdata/SampleMaterial.lc 1237:5-1279:6 (String, CommonAttrs) testdata/SampleMaterial.lc 1237:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 1237:7-1237:41 String testdata/SampleMaterial.lc 1238:7-1238:18 @@ -8777,49 +8581,42 @@ testdata/SampleMaterial.lc 1238:7-1238:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1238:7-1239:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1238:7-1240:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1238:7-1241:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1238:7-1242:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1238:7-1243:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1238:7-1244:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1238:7-1245:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1238:7-1246:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1238:7-1247:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1238:7-1248:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1238:7-1276:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 1238:7-1278:10 @@ -8839,41 +8636,41 @@ testdata/SampleMaterial.lc 1244:23-1244:28 testdata/SampleMaterial.lc 1245:20-1245:33 CullType testdata/SampleMaterial.lc 1246:30-1246:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1247:25-1247:30 Bool testdata/SampleMaterial.lc 1248:29-1248:34 Bool testdata/SampleMaterial.lc 1250:13-1276:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 1250:15-1250:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1250:15-1251:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1250:15-1252:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1250:15-1253:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1250:15-1254:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1250:15-1255:31 @@ -8900,7 +8697,7 @@ testdata/SampleMaterial.lc 1253:32-1253:42 testdata/SampleMaterial.lc 1254:29-1254:36 TCGen testdata/SampleMaterial.lc 1255:29-1255:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1256:31-1256:37 String -> StageTexture testdata/SampleMaterial.lc 1256:31-1256:72 @@ -8922,29 +8719,29 @@ testdata/SampleMaterial.lc 1263:15-1263:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1263:15-1264:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1263:15-1265:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1263:15-1266:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1263:15-1267:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1263:15-1268:31 @@ -8961,7 +8758,7 @@ testdata/SampleMaterial.lc 1263:15-1272:40 testdata/SampleMaterial.lc 1263:15-1273:46 String -> StageAttrs testdata/SampleMaterial.lc 1263:15-1275:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 1264:29-1264:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 1264:29-1264:57 @@ -8979,7 +8776,7 @@ testdata/SampleMaterial.lc 1266:32-1266:42 testdata/SampleMaterial.lc 1267:29-1267:40 TCGen testdata/SampleMaterial.lc 1268:29-1268:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1269:31-1269:42 StageTexture testdata/SampleMaterial.lc 1270:34-1270:38 @@ -8997,7 +8794,7 @@ testdata/SampleMaterial.lc 1277:21-1277:26 testdata/SampleMaterial.lc 1280:5-1322:6 (String, CommonAttrs) testdata/SampleMaterial.lc 1280:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 1280:7-1280:44 String testdata/SampleMaterial.lc 1281:7-1281:18 @@ -9007,49 +8804,42 @@ testdata/SampleMaterial.lc 1281:7-1281:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1281:7-1282:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1281:7-1283:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1281:7-1284:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1281:7-1285:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1281:7-1286:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1281:7-1287:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1281:7-1288:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1281:7-1289:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1281:7-1290:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1281:7-1291:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1281:7-1319:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 1281:7-1321:10 @@ -9069,41 +8859,41 @@ testdata/SampleMaterial.lc 1287:23-1287:28 testdata/SampleMaterial.lc 1288:20-1288:33 CullType testdata/SampleMaterial.lc 1289:30-1289:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1290:25-1290:30 Bool testdata/SampleMaterial.lc 1291:29-1291:34 Bool testdata/SampleMaterial.lc 1293:13-1319:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 1293:15-1293:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1293:15-1294:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1293:15-1295:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1293:15-1296:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1293:15-1297:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1293:15-1298:31 @@ -9130,7 +8920,7 @@ testdata/SampleMaterial.lc 1296:32-1296:42 testdata/SampleMaterial.lc 1297:29-1297:36 TCGen testdata/SampleMaterial.lc 1298:29-1298:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1299:31-1299:37 String -> StageTexture testdata/SampleMaterial.lc 1299:31-1299:75 @@ -9152,29 +8942,29 @@ testdata/SampleMaterial.lc 1306:15-1306:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1306:15-1307:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1306:15-1308:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1306:15-1309:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1306:15-1310:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1306:15-1311:31 @@ -9191,7 +8981,7 @@ testdata/SampleMaterial.lc 1306:15-1315:40 testdata/SampleMaterial.lc 1306:15-1316:46 String -> StageAttrs testdata/SampleMaterial.lc 1306:15-1318:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 1307:29-1307:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 1307:29-1307:57 @@ -9209,7 +8999,7 @@ testdata/SampleMaterial.lc 1309:32-1309:42 testdata/SampleMaterial.lc 1310:29-1310:40 TCGen testdata/SampleMaterial.lc 1311:29-1311:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1312:31-1312:42 StageTexture testdata/SampleMaterial.lc 1313:34-1313:38 @@ -9227,7 +9017,7 @@ testdata/SampleMaterial.lc 1320:21-1320:26 testdata/SampleMaterial.lc 1323:5-1365:6 (String, CommonAttrs) testdata/SampleMaterial.lc 1323:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 1323:7-1323:43 String testdata/SampleMaterial.lc 1324:7-1324:18 @@ -9237,49 +9027,42 @@ testdata/SampleMaterial.lc 1324:7-1324:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1324:7-1325:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1324:7-1326:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1324:7-1327:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1324:7-1328:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1324:7-1329:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1324:7-1330:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1324:7-1331:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1324:7-1332:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1324:7-1333:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1324:7-1334:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1324:7-1362:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 1324:7-1364:10 @@ -9299,41 +9082,41 @@ testdata/SampleMaterial.lc 1330:23-1330:28 testdata/SampleMaterial.lc 1331:20-1331:33 CullType testdata/SampleMaterial.lc 1332:30-1332:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1333:25-1333:30 Bool testdata/SampleMaterial.lc 1334:29-1334:34 Bool testdata/SampleMaterial.lc 1336:13-1362:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 1336:15-1336:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1336:15-1337:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1336:15-1338:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1336:15-1339:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1336:15-1340:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1336:15-1341:31 @@ -9360,7 +9143,7 @@ testdata/SampleMaterial.lc 1339:32-1339:42 testdata/SampleMaterial.lc 1340:29-1340:36 TCGen testdata/SampleMaterial.lc 1341:29-1341:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1342:31-1342:37 String -> StageTexture testdata/SampleMaterial.lc 1342:31-1342:74 @@ -9382,29 +9165,29 @@ testdata/SampleMaterial.lc 1349:15-1349:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1349:15-1350:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1349:15-1351:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1349:15-1352:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1349:15-1353:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1349:15-1354:31 @@ -9421,7 +9204,7 @@ testdata/SampleMaterial.lc 1349:15-1358:40 testdata/SampleMaterial.lc 1349:15-1359:46 String -> StageAttrs testdata/SampleMaterial.lc 1349:15-1361:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 1350:29-1350:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 1350:29-1350:57 @@ -9439,7 +9222,7 @@ testdata/SampleMaterial.lc 1352:32-1352:42 testdata/SampleMaterial.lc 1353:29-1353:40 TCGen testdata/SampleMaterial.lc 1354:29-1354:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1355:31-1355:42 StageTexture testdata/SampleMaterial.lc 1356:34-1356:38 @@ -9457,7 +9240,7 @@ testdata/SampleMaterial.lc 1363:21-1363:26 testdata/SampleMaterial.lc 1366:5-1408:6 (String, CommonAttrs) testdata/SampleMaterial.lc 1366:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 1366:7-1366:44 String testdata/SampleMaterial.lc 1367:7-1367:18 @@ -9467,49 +9250,42 @@ testdata/SampleMaterial.lc 1367:7-1367:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1367:7-1368:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1367:7-1369:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1367:7-1370:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1367:7-1371:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1367:7-1372:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1367:7-1373:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1367:7-1374:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1367:7-1375:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1367:7-1376:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1367:7-1377:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1367:7-1405:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 1367:7-1407:10 @@ -9529,41 +9305,41 @@ testdata/SampleMaterial.lc 1373:23-1373:28 testdata/SampleMaterial.lc 1374:20-1374:33 CullType testdata/SampleMaterial.lc 1375:30-1375:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1376:25-1376:30 Bool testdata/SampleMaterial.lc 1377:29-1377:34 Bool testdata/SampleMaterial.lc 1379:13-1405:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 1379:15-1379:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1379:15-1380:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1379:15-1381:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1379:15-1382:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1379:15-1383:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1379:15-1384:31 @@ -9590,7 +9366,7 @@ testdata/SampleMaterial.lc 1382:32-1382:42 testdata/SampleMaterial.lc 1383:29-1383:36 TCGen testdata/SampleMaterial.lc 1384:29-1384:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1385:31-1385:37 String -> StageTexture testdata/SampleMaterial.lc 1385:31-1385:75 @@ -9612,29 +9388,29 @@ testdata/SampleMaterial.lc 1392:15-1392:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1392:15-1393:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1392:15-1394:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1392:15-1395:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1392:15-1396:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1392:15-1397:31 @@ -9651,7 +9427,7 @@ testdata/SampleMaterial.lc 1392:15-1401:40 testdata/SampleMaterial.lc 1392:15-1402:46 String -> StageAttrs testdata/SampleMaterial.lc 1392:15-1404:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 1393:29-1393:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 1393:29-1393:57 @@ -9669,7 +9445,7 @@ testdata/SampleMaterial.lc 1395:32-1395:42 testdata/SampleMaterial.lc 1396:29-1396:40 TCGen testdata/SampleMaterial.lc 1397:29-1397:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1398:31-1398:42 StageTexture testdata/SampleMaterial.lc 1399:34-1399:38 @@ -9687,7 +9463,7 @@ testdata/SampleMaterial.lc 1406:21-1406:26 testdata/SampleMaterial.lc 1409:5-1451:6 (String, CommonAttrs) testdata/SampleMaterial.lc 1409:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 1409:7-1409:44 String testdata/SampleMaterial.lc 1410:7-1410:18 @@ -9697,49 +9473,42 @@ testdata/SampleMaterial.lc 1410:7-1410:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1410:7-1411:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1410:7-1412:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1410:7-1413:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1410:7-1414:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1410:7-1415:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1410:7-1416:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1410:7-1417:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1410:7-1418:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1410:7-1419:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1410:7-1420:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1410:7-1448:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 1410:7-1450:10 @@ -9759,41 +9528,41 @@ testdata/SampleMaterial.lc 1416:23-1416:28 testdata/SampleMaterial.lc 1417:20-1417:33 CullType testdata/SampleMaterial.lc 1418:30-1418:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1419:25-1419:30 Bool testdata/SampleMaterial.lc 1420:29-1420:34 Bool testdata/SampleMaterial.lc 1422:13-1448:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 1422:15-1422:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1422:15-1423:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1422:15-1424:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1422:15-1425:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1422:15-1426:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1422:15-1427:31 @@ -9820,7 +9589,7 @@ testdata/SampleMaterial.lc 1425:32-1425:42 testdata/SampleMaterial.lc 1426:29-1426:36 TCGen testdata/SampleMaterial.lc 1427:29-1427:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1428:31-1428:37 String -> StageTexture testdata/SampleMaterial.lc 1428:31-1428:75 @@ -9842,29 +9611,29 @@ testdata/SampleMaterial.lc 1435:15-1435:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1435:15-1436:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1435:15-1437:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1435:15-1438:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1435:15-1439:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1435:15-1440:31 @@ -9881,7 +9650,7 @@ testdata/SampleMaterial.lc 1435:15-1444:40 testdata/SampleMaterial.lc 1435:15-1445:46 String -> StageAttrs testdata/SampleMaterial.lc 1435:15-1447:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 1436:29-1436:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 1436:29-1436:57 @@ -9899,7 +9668,7 @@ testdata/SampleMaterial.lc 1438:32-1438:42 testdata/SampleMaterial.lc 1439:29-1439:40 TCGen testdata/SampleMaterial.lc 1440:29-1440:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1441:31-1441:42 StageTexture testdata/SampleMaterial.lc 1442:34-1442:38 @@ -9917,7 +9686,7 @@ testdata/SampleMaterial.lc 1449:21-1449:26 testdata/SampleMaterial.lc 1452:5-1494:6 (String, CommonAttrs) testdata/SampleMaterial.lc 1452:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 1452:7-1452:44 String testdata/SampleMaterial.lc 1453:7-1453:18 @@ -9927,49 +9696,42 @@ testdata/SampleMaterial.lc 1453:7-1453:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1453:7-1454:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1453:7-1455:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1453:7-1456:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1453:7-1457:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1453:7-1458:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1453:7-1459:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1453:7-1460:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1453:7-1461:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1453:7-1462:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1453:7-1463:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1453:7-1491:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 1453:7-1493:10 @@ -9989,41 +9751,41 @@ testdata/SampleMaterial.lc 1459:23-1459:28 testdata/SampleMaterial.lc 1460:20-1460:33 CullType testdata/SampleMaterial.lc 1461:30-1461:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1462:25-1462:30 Bool testdata/SampleMaterial.lc 1463:29-1463:34 Bool testdata/SampleMaterial.lc 1465:13-1491:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 1465:15-1465:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1465:15-1466:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1465:15-1467:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1465:15-1468:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1465:15-1469:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1465:15-1470:31 @@ -10050,7 +9812,7 @@ testdata/SampleMaterial.lc 1468:32-1468:42 testdata/SampleMaterial.lc 1469:29-1469:36 TCGen testdata/SampleMaterial.lc 1470:29-1470:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1471:31-1471:37 String -> StageTexture testdata/SampleMaterial.lc 1471:31-1471:75 @@ -10072,29 +9834,29 @@ testdata/SampleMaterial.lc 1478:15-1478:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1478:15-1479:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1478:15-1480:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1478:15-1481:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1478:15-1482:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1478:15-1483:31 @@ -10111,7 +9873,7 @@ testdata/SampleMaterial.lc 1478:15-1487:40 testdata/SampleMaterial.lc 1478:15-1488:46 String -> StageAttrs testdata/SampleMaterial.lc 1478:15-1490:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 1479:29-1479:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 1479:29-1479:57 @@ -10129,7 +9891,7 @@ testdata/SampleMaterial.lc 1481:32-1481:42 testdata/SampleMaterial.lc 1482:29-1482:40 TCGen testdata/SampleMaterial.lc 1483:29-1483:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1484:31-1484:42 StageTexture testdata/SampleMaterial.lc 1485:34-1485:38 @@ -10147,7 +9909,7 @@ testdata/SampleMaterial.lc 1492:21-1492:26 testdata/SampleMaterial.lc 1495:5-1537:6 (String, CommonAttrs) testdata/SampleMaterial.lc 1495:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 1495:7-1495:45 String testdata/SampleMaterial.lc 1496:7-1496:18 @@ -10157,49 +9919,42 @@ testdata/SampleMaterial.lc 1496:7-1496:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1496:7-1497:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1496:7-1498:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1496:7-1499:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1496:7-1500:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1496:7-1501:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1496:7-1502:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1496:7-1503:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1496:7-1504:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1496:7-1505:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1496:7-1506:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1496:7-1534:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 1496:7-1536:10 @@ -10219,41 +9974,41 @@ testdata/SampleMaterial.lc 1502:23-1502:28 testdata/SampleMaterial.lc 1503:20-1503:33 CullType testdata/SampleMaterial.lc 1504:30-1504:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1505:25-1505:30 Bool testdata/SampleMaterial.lc 1506:29-1506:34 Bool testdata/SampleMaterial.lc 1508:13-1534:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 1508:15-1508:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1508:15-1509:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1508:15-1510:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1508:15-1511:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1508:15-1512:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1508:15-1513:31 @@ -10280,7 +10035,7 @@ testdata/SampleMaterial.lc 1511:32-1511:42 testdata/SampleMaterial.lc 1512:29-1512:36 TCGen testdata/SampleMaterial.lc 1513:29-1513:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1514:31-1514:37 String -> StageTexture testdata/SampleMaterial.lc 1514:31-1514:76 @@ -10302,29 +10057,29 @@ testdata/SampleMaterial.lc 1521:15-1521:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1521:15-1522:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1521:15-1523:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1521:15-1524:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1521:15-1525:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1521:15-1526:31 @@ -10341,7 +10096,7 @@ testdata/SampleMaterial.lc 1521:15-1530:40 testdata/SampleMaterial.lc 1521:15-1531:46 String -> StageAttrs testdata/SampleMaterial.lc 1521:15-1533:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 1522:29-1522:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 1522:29-1522:57 @@ -10359,7 +10114,7 @@ testdata/SampleMaterial.lc 1524:32-1524:42 testdata/SampleMaterial.lc 1525:29-1525:40 TCGen testdata/SampleMaterial.lc 1526:29-1526:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1527:31-1527:42 StageTexture testdata/SampleMaterial.lc 1528:34-1528:38 @@ -10377,7 +10132,7 @@ testdata/SampleMaterial.lc 1535:21-1535:26 testdata/SampleMaterial.lc 1538:5-1580:6 (String, CommonAttrs) testdata/SampleMaterial.lc 1538:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 1538:7-1538:47 String testdata/SampleMaterial.lc 1539:7-1539:18 @@ -10387,49 +10142,42 @@ testdata/SampleMaterial.lc 1539:7-1539:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1539:7-1540:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1539:7-1541:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1539:7-1542:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1539:7-1543:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1539:7-1544:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1539:7-1545:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1539:7-1546:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1539:7-1547:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1539:7-1548:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1539:7-1549:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1539:7-1577:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 1539:7-1579:10 @@ -10449,41 +10197,41 @@ testdata/SampleMaterial.lc 1545:23-1545:28 testdata/SampleMaterial.lc 1546:20-1546:33 CullType testdata/SampleMaterial.lc 1547:30-1547:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1548:25-1548:30 Bool testdata/SampleMaterial.lc 1549:29-1549:34 Bool testdata/SampleMaterial.lc 1551:13-1577:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 1551:15-1551:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1551:15-1552:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1551:15-1553:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1551:15-1554:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1551:15-1555:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1551:15-1556:31 @@ -10510,7 +10258,7 @@ testdata/SampleMaterial.lc 1554:32-1554:42 testdata/SampleMaterial.lc 1555:29-1555:36 TCGen testdata/SampleMaterial.lc 1556:29-1556:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1557:31-1557:37 String -> StageTexture testdata/SampleMaterial.lc 1557:31-1557:78 @@ -10532,29 +10280,29 @@ testdata/SampleMaterial.lc 1564:15-1564:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1564:15-1565:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1564:15-1566:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1564:15-1567:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1564:15-1568:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1564:15-1569:31 @@ -10571,7 +10319,7 @@ testdata/SampleMaterial.lc 1564:15-1573:40 testdata/SampleMaterial.lc 1564:15-1574:46 String -> StageAttrs testdata/SampleMaterial.lc 1564:15-1576:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 1565:29-1565:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 1565:29-1565:57 @@ -10589,7 +10337,7 @@ testdata/SampleMaterial.lc 1567:32-1567:42 testdata/SampleMaterial.lc 1568:29-1568:40 TCGen testdata/SampleMaterial.lc 1569:29-1569:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1570:31-1570:42 StageTexture testdata/SampleMaterial.lc 1571:34-1571:38 @@ -10607,7 +10355,7 @@ testdata/SampleMaterial.lc 1578:21-1578:26 testdata/SampleMaterial.lc 1581:5-1623:6 (String, CommonAttrs) testdata/SampleMaterial.lc 1581:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 1581:7-1581:49 String testdata/SampleMaterial.lc 1582:7-1582:18 @@ -10617,49 +10365,42 @@ testdata/SampleMaterial.lc 1582:7-1582:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1582:7-1583:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1582:7-1584:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1582:7-1585:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1582:7-1586:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1582:7-1587:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1582:7-1588:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1582:7-1589:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1582:7-1590:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1582:7-1591:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1582:7-1592:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1582:7-1620:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 1582:7-1622:10 @@ -10679,41 +10420,41 @@ testdata/SampleMaterial.lc 1588:23-1588:28 testdata/SampleMaterial.lc 1589:20-1589:33 CullType testdata/SampleMaterial.lc 1590:30-1590:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1591:25-1591:30 Bool testdata/SampleMaterial.lc 1592:29-1592:34 Bool testdata/SampleMaterial.lc 1594:13-1620:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 1594:15-1594:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1594:15-1595:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1594:15-1596:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1594:15-1597:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1594:15-1598:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1594:15-1599:31 @@ -10740,7 +10481,7 @@ testdata/SampleMaterial.lc 1597:32-1597:42 testdata/SampleMaterial.lc 1598:29-1598:36 TCGen testdata/SampleMaterial.lc 1599:29-1599:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1600:31-1600:37 String -> StageTexture testdata/SampleMaterial.lc 1600:31-1600:80 @@ -10762,29 +10503,29 @@ testdata/SampleMaterial.lc 1607:15-1607:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1607:15-1608:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1607:15-1609:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1607:15-1610:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1607:15-1611:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1607:15-1612:31 @@ -10801,7 +10542,7 @@ testdata/SampleMaterial.lc 1607:15-1616:40 testdata/SampleMaterial.lc 1607:15-1617:46 String -> StageAttrs testdata/SampleMaterial.lc 1607:15-1619:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 1608:29-1608:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 1608:29-1608:57 @@ -10819,7 +10560,7 @@ testdata/SampleMaterial.lc 1610:32-1610:42 testdata/SampleMaterial.lc 1611:29-1611:40 TCGen testdata/SampleMaterial.lc 1612:29-1612:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1613:31-1613:42 StageTexture testdata/SampleMaterial.lc 1614:34-1614:38 @@ -10837,7 +10578,7 @@ testdata/SampleMaterial.lc 1621:21-1621:26 testdata/SampleMaterial.lc 1624:5-1666:6 (String, CommonAttrs) testdata/SampleMaterial.lc 1624:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 1624:7-1624:44 String testdata/SampleMaterial.lc 1625:7-1625:18 @@ -10847,49 +10588,42 @@ testdata/SampleMaterial.lc 1625:7-1625:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1625:7-1626:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1625:7-1627:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1625:7-1628:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1625:7-1629:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1625:7-1630:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1625:7-1631:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1625:7-1632:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1625:7-1633:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1625:7-1634:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1625:7-1635:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1625:7-1663:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 1625:7-1665:10 @@ -10909,41 +10643,41 @@ testdata/SampleMaterial.lc 1631:23-1631:28 testdata/SampleMaterial.lc 1632:20-1632:33 CullType testdata/SampleMaterial.lc 1633:30-1633:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1634:25-1634:30 Bool testdata/SampleMaterial.lc 1635:29-1635:34 Bool testdata/SampleMaterial.lc 1637:13-1663:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 1637:15-1637:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1637:15-1638:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1637:15-1639:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1637:15-1640:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1637:15-1641:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1637:15-1642:31 @@ -10970,7 +10704,7 @@ testdata/SampleMaterial.lc 1640:32-1640:42 testdata/SampleMaterial.lc 1641:29-1641:36 TCGen testdata/SampleMaterial.lc 1642:29-1642:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1643:31-1643:37 String -> StageTexture testdata/SampleMaterial.lc 1643:31-1643:75 @@ -10992,29 +10726,29 @@ testdata/SampleMaterial.lc 1650:15-1650:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1650:15-1651:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1650:15-1652:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1650:15-1653:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1650:15-1654:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1650:15-1655:31 @@ -11031,7 +10765,7 @@ testdata/SampleMaterial.lc 1650:15-1659:40 testdata/SampleMaterial.lc 1650:15-1660:46 String -> StageAttrs testdata/SampleMaterial.lc 1650:15-1662:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 1651:29-1651:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 1651:29-1651:57 @@ -11049,7 +10783,7 @@ testdata/SampleMaterial.lc 1653:32-1653:42 testdata/SampleMaterial.lc 1654:29-1654:40 TCGen testdata/SampleMaterial.lc 1655:29-1655:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1656:31-1656:42 StageTexture testdata/SampleMaterial.lc 1657:34-1657:38 @@ -11067,7 +10801,7 @@ testdata/SampleMaterial.lc 1664:21-1664:26 testdata/SampleMaterial.lc 1667:5-1709:6 (String, CommonAttrs) testdata/SampleMaterial.lc 1667:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 1667:7-1667:43 String testdata/SampleMaterial.lc 1668:7-1668:18 @@ -11077,49 +10811,42 @@ testdata/SampleMaterial.lc 1668:7-1668:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1668:7-1669:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1668:7-1670:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1668:7-1671:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1668:7-1672:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1668:7-1673:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1668:7-1674:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1668:7-1675:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1668:7-1676:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1668:7-1677:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1668:7-1678:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1668:7-1706:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 1668:7-1708:10 @@ -11139,41 +10866,41 @@ testdata/SampleMaterial.lc 1674:23-1674:28 testdata/SampleMaterial.lc 1675:20-1675:33 CullType testdata/SampleMaterial.lc 1676:30-1676:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1677:25-1677:30 Bool testdata/SampleMaterial.lc 1678:29-1678:34 Bool testdata/SampleMaterial.lc 1680:13-1706:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 1680:15-1680:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1680:15-1681:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1680:15-1682:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1680:15-1683:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1680:15-1684:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1680:15-1685:31 @@ -11200,7 +10927,7 @@ testdata/SampleMaterial.lc 1683:32-1683:42 testdata/SampleMaterial.lc 1684:29-1684:36 TCGen testdata/SampleMaterial.lc 1685:29-1685:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1686:31-1686:37 String -> StageTexture testdata/SampleMaterial.lc 1686:31-1686:74 @@ -11222,29 +10949,29 @@ testdata/SampleMaterial.lc 1693:15-1693:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1693:15-1694:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1693:15-1695:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1693:15-1696:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1693:15-1697:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1693:15-1698:31 @@ -11261,7 +10988,7 @@ testdata/SampleMaterial.lc 1693:15-1702:40 testdata/SampleMaterial.lc 1693:15-1703:46 String -> StageAttrs testdata/SampleMaterial.lc 1693:15-1705:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 1694:29-1694:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 1694:29-1694:57 @@ -11279,7 +11006,7 @@ testdata/SampleMaterial.lc 1696:32-1696:42 testdata/SampleMaterial.lc 1697:29-1697:40 TCGen testdata/SampleMaterial.lc 1698:29-1698:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1699:31-1699:42 StageTexture testdata/SampleMaterial.lc 1700:34-1700:38 @@ -11297,7 +11024,7 @@ testdata/SampleMaterial.lc 1707:21-1707:26 testdata/SampleMaterial.lc 1710:5-1752:6 (String, CommonAttrs) testdata/SampleMaterial.lc 1710:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 1710:7-1710:41 String testdata/SampleMaterial.lc 1711:7-1711:18 @@ -11307,49 +11034,42 @@ testdata/SampleMaterial.lc 1711:7-1711:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1711:7-1712:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1711:7-1713:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1711:7-1714:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1711:7-1715:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1711:7-1716:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1711:7-1717:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1711:7-1718:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1711:7-1719:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1711:7-1720:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1711:7-1721:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1711:7-1749:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 1711:7-1751:10 @@ -11369,41 +11089,41 @@ testdata/SampleMaterial.lc 1717:23-1717:28 testdata/SampleMaterial.lc 1718:20-1718:33 CullType testdata/SampleMaterial.lc 1719:30-1719:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1720:25-1720:30 Bool testdata/SampleMaterial.lc 1721:29-1721:34 Bool testdata/SampleMaterial.lc 1723:13-1749:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 1723:15-1723:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1723:15-1724:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1723:15-1725:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1723:15-1726:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1723:15-1727:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1723:15-1728:31 @@ -11430,7 +11150,7 @@ testdata/SampleMaterial.lc 1726:32-1726:42 testdata/SampleMaterial.lc 1727:29-1727:36 TCGen testdata/SampleMaterial.lc 1728:29-1728:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1729:31-1729:37 String -> StageTexture testdata/SampleMaterial.lc 1729:31-1729:72 @@ -11452,29 +11172,29 @@ testdata/SampleMaterial.lc 1736:15-1736:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1736:15-1737:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1736:15-1738:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1736:15-1739:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1736:15-1740:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1736:15-1741:31 @@ -11491,7 +11211,7 @@ testdata/SampleMaterial.lc 1736:15-1745:40 testdata/SampleMaterial.lc 1736:15-1746:46 String -> StageAttrs testdata/SampleMaterial.lc 1736:15-1748:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 1737:29-1737:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 1737:29-1737:57 @@ -11509,7 +11229,7 @@ testdata/SampleMaterial.lc 1739:32-1739:42 testdata/SampleMaterial.lc 1740:29-1740:40 TCGen testdata/SampleMaterial.lc 1741:29-1741:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1742:31-1742:42 StageTexture testdata/SampleMaterial.lc 1743:34-1743:38 @@ -11527,7 +11247,7 @@ testdata/SampleMaterial.lc 1750:21-1750:26 testdata/SampleMaterial.lc 1753:5-1795:6 (String, CommonAttrs) testdata/SampleMaterial.lc 1753:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 1753:7-1753:42 String testdata/SampleMaterial.lc 1754:7-1754:18 @@ -11537,49 +11257,42 @@ testdata/SampleMaterial.lc 1754:7-1754:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1754:7-1755:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1754:7-1756:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1754:7-1757:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1754:7-1758:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1754:7-1759:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1754:7-1760:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1754:7-1761:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1754:7-1762:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1754:7-1763:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1754:7-1764:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1754:7-1792:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 1754:7-1794:10 @@ -11599,41 +11312,41 @@ testdata/SampleMaterial.lc 1760:23-1760:28 testdata/SampleMaterial.lc 1761:20-1761:33 CullType testdata/SampleMaterial.lc 1762:30-1762:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1763:25-1763:30 Bool testdata/SampleMaterial.lc 1764:29-1764:34 Bool testdata/SampleMaterial.lc 1766:13-1792:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 1766:15-1766:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1766:15-1767:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1766:15-1768:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1766:15-1769:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1766:15-1770:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1766:15-1771:31 @@ -11660,7 +11373,7 @@ testdata/SampleMaterial.lc 1769:32-1769:42 testdata/SampleMaterial.lc 1770:29-1770:36 TCGen testdata/SampleMaterial.lc 1771:29-1771:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1772:31-1772:37 String -> StageTexture testdata/SampleMaterial.lc 1772:31-1772:73 @@ -11682,29 +11395,29 @@ testdata/SampleMaterial.lc 1779:15-1779:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1779:15-1780:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1779:15-1781:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1779:15-1782:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1779:15-1783:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1779:15-1784:31 @@ -11721,7 +11434,7 @@ testdata/SampleMaterial.lc 1779:15-1788:40 testdata/SampleMaterial.lc 1779:15-1789:46 String -> StageAttrs testdata/SampleMaterial.lc 1779:15-1791:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 1780:29-1780:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 1780:29-1780:57 @@ -11739,7 +11452,7 @@ testdata/SampleMaterial.lc 1782:32-1782:42 testdata/SampleMaterial.lc 1783:29-1783:40 TCGen testdata/SampleMaterial.lc 1784:29-1784:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1785:31-1785:42 StageTexture testdata/SampleMaterial.lc 1786:34-1786:38 @@ -11757,7 +11470,7 @@ testdata/SampleMaterial.lc 1793:21-1793:26 testdata/SampleMaterial.lc 1796:5-1838:6 (String, CommonAttrs) testdata/SampleMaterial.lc 1796:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 1796:7-1796:48 String testdata/SampleMaterial.lc 1797:7-1797:18 @@ -11767,49 +11480,42 @@ testdata/SampleMaterial.lc 1797:7-1797:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1797:7-1798:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1797:7-1799:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1797:7-1800:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1797:7-1801:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1797:7-1802:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1797:7-1803:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1797:7-1804:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1797:7-1805:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1797:7-1806:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1797:7-1807:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1797:7-1835:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 1797:7-1837:10 @@ -11829,41 +11535,41 @@ testdata/SampleMaterial.lc 1803:23-1803:28 testdata/SampleMaterial.lc 1804:20-1804:33 CullType testdata/SampleMaterial.lc 1805:30-1805:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1806:25-1806:30 Bool testdata/SampleMaterial.lc 1807:29-1807:34 Bool testdata/SampleMaterial.lc 1809:13-1835:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 1809:15-1809:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1809:15-1810:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1809:15-1811:42 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1809:15-1812:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1809:15-1813:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1809:15-1814:31 @@ -11890,7 +11596,7 @@ testdata/SampleMaterial.lc 1812:32-1812:42 testdata/SampleMaterial.lc 1813:29-1813:40 TCGen testdata/SampleMaterial.lc 1814:29-1814:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1815:31-1815:42 StageTexture testdata/SampleMaterial.lc 1816:34-1816:38 @@ -11908,29 +11614,29 @@ testdata/SampleMaterial.lc 1822:15-1822:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1822:15-1823:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1822:15-1824:42 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1822:15-1825:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1822:15-1826:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1822:15-1827:31 @@ -11947,7 +11653,7 @@ testdata/SampleMaterial.lc 1822:15-1831:40 testdata/SampleMaterial.lc 1822:15-1832:46 String -> StageAttrs testdata/SampleMaterial.lc 1822:15-1834:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 1823:29-1823:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 1823:29-1823:57 @@ -11965,7 +11671,7 @@ testdata/SampleMaterial.lc 1825:32-1825:42 testdata/SampleMaterial.lc 1826:29-1826:36 TCGen testdata/SampleMaterial.lc 1827:29-1827:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1828:31-1828:37 String -> StageTexture testdata/SampleMaterial.lc 1828:31-1828:77 @@ -11987,7 +11693,7 @@ testdata/SampleMaterial.lc 1836:21-1836:26 testdata/SampleMaterial.lc 1839:5-1881:6 (String, CommonAttrs) testdata/SampleMaterial.lc 1839:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 1839:7-1839:42 String testdata/SampleMaterial.lc 1840:7-1840:18 @@ -11997,49 +11703,42 @@ testdata/SampleMaterial.lc 1840:7-1840:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1840:7-1841:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1840:7-1842:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1840:7-1843:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1840:7-1844:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1840:7-1845:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1840:7-1846:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1840:7-1847:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1840:7-1848:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1840:7-1849:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1840:7-1850:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1840:7-1878:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 1840:7-1880:10 @@ -12059,41 +11758,41 @@ testdata/SampleMaterial.lc 1846:23-1846:28 testdata/SampleMaterial.lc 1847:20-1847:33 CullType testdata/SampleMaterial.lc 1848:30-1848:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1849:25-1849:30 Bool testdata/SampleMaterial.lc 1850:29-1850:34 Bool testdata/SampleMaterial.lc 1852:13-1878:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 1852:15-1852:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1852:15-1853:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1852:15-1854:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1852:15-1855:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1852:15-1856:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1852:15-1857:31 @@ -12120,7 +11819,7 @@ testdata/SampleMaterial.lc 1855:32-1855:42 testdata/SampleMaterial.lc 1856:29-1856:36 TCGen testdata/SampleMaterial.lc 1857:29-1857:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1858:31-1858:37 String -> StageTexture testdata/SampleMaterial.lc 1858:31-1858:73 @@ -12142,29 +11841,29 @@ testdata/SampleMaterial.lc 1865:15-1865:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1865:15-1866:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1865:15-1867:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1865:15-1868:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1865:15-1869:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1865:15-1870:31 @@ -12181,7 +11880,7 @@ testdata/SampleMaterial.lc 1865:15-1874:40 testdata/SampleMaterial.lc 1865:15-1875:46 String -> StageAttrs testdata/SampleMaterial.lc 1865:15-1877:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 1866:29-1866:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 1866:29-1866:57 @@ -12199,7 +11898,7 @@ testdata/SampleMaterial.lc 1868:32-1868:42 testdata/SampleMaterial.lc 1869:29-1869:40 TCGen testdata/SampleMaterial.lc 1870:29-1870:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1871:31-1871:42 StageTexture testdata/SampleMaterial.lc 1872:34-1872:38 @@ -12217,7 +11916,7 @@ testdata/SampleMaterial.lc 1879:21-1879:26 testdata/SampleMaterial.lc 1882:5-1924:6 (String, CommonAttrs) testdata/SampleMaterial.lc 1882:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 1882:7-1882:47 String testdata/SampleMaterial.lc 1883:7-1883:18 @@ -12227,49 +11926,42 @@ testdata/SampleMaterial.lc 1883:7-1883:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1883:7-1884:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1883:7-1885:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1883:7-1886:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1883:7-1887:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1883:7-1888:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1883:7-1889:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1883:7-1890:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1883:7-1891:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1883:7-1892:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1883:7-1893:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1883:7-1921:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 1883:7-1923:10 @@ -12289,41 +11981,41 @@ testdata/SampleMaterial.lc 1889:23-1889:28 testdata/SampleMaterial.lc 1890:20-1890:33 CullType testdata/SampleMaterial.lc 1891:30-1891:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1892:25-1892:30 Bool testdata/SampleMaterial.lc 1893:29-1893:34 Bool testdata/SampleMaterial.lc 1895:13-1921:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 1895:15-1895:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1895:15-1896:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1895:15-1897:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1895:15-1898:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1895:15-1899:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1895:15-1900:31 @@ -12350,7 +12042,7 @@ testdata/SampleMaterial.lc 1898:32-1898:42 testdata/SampleMaterial.lc 1899:29-1899:36 TCGen testdata/SampleMaterial.lc 1900:29-1900:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1901:31-1901:37 String -> StageTexture testdata/SampleMaterial.lc 1901:31-1901:78 @@ -12372,29 +12064,29 @@ testdata/SampleMaterial.lc 1908:15-1908:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1908:15-1909:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1908:15-1910:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1908:15-1911:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1908:15-1912:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1908:15-1913:31 @@ -12411,7 +12103,7 @@ testdata/SampleMaterial.lc 1908:15-1917:40 testdata/SampleMaterial.lc 1908:15-1918:46 String -> StageAttrs testdata/SampleMaterial.lc 1908:15-1920:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 1909:29-1909:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 1909:29-1909:57 @@ -12429,7 +12121,7 @@ testdata/SampleMaterial.lc 1911:32-1911:42 testdata/SampleMaterial.lc 1912:29-1912:40 TCGen testdata/SampleMaterial.lc 1913:29-1913:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1914:31-1914:42 StageTexture testdata/SampleMaterial.lc 1915:34-1915:38 @@ -12447,7 +12139,7 @@ testdata/SampleMaterial.lc 1922:21-1922:26 testdata/SampleMaterial.lc 1925:5-1967:6 (String, CommonAttrs) testdata/SampleMaterial.lc 1925:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 1925:7-1925:38 String testdata/SampleMaterial.lc 1926:7-1926:18 @@ -12457,49 +12149,42 @@ testdata/SampleMaterial.lc 1926:7-1926:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1926:7-1927:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1926:7-1928:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1926:7-1929:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1926:7-1930:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1926:7-1931:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1926:7-1932:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1926:7-1933:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1926:7-1934:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1926:7-1935:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1926:7-1936:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1926:7-1964:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 1926:7-1966:10 @@ -12519,41 +12204,41 @@ testdata/SampleMaterial.lc 1932:23-1932:28 testdata/SampleMaterial.lc 1933:20-1933:33 CullType testdata/SampleMaterial.lc 1934:30-1934:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1935:25-1935:30 Bool testdata/SampleMaterial.lc 1936:29-1936:34 Bool testdata/SampleMaterial.lc 1938:13-1964:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 1938:15-1938:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1938:15-1939:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1938:15-1940:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1938:15-1941:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1938:15-1942:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1938:15-1943:31 @@ -12580,7 +12265,7 @@ testdata/SampleMaterial.lc 1941:32-1941:42 testdata/SampleMaterial.lc 1942:29-1942:36 TCGen testdata/SampleMaterial.lc 1943:29-1943:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1944:31-1944:37 String -> StageTexture testdata/SampleMaterial.lc 1944:31-1944:69 @@ -12602,29 +12287,29 @@ testdata/SampleMaterial.lc 1951:15-1951:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1951:15-1952:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1951:15-1953:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1951:15-1954:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1951:15-1955:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1951:15-1956:31 @@ -12641,7 +12326,7 @@ testdata/SampleMaterial.lc 1951:15-1960:40 testdata/SampleMaterial.lc 1951:15-1961:46 String -> StageAttrs testdata/SampleMaterial.lc 1951:15-1963:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 1952:29-1952:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 1952:29-1952:57 @@ -12659,7 +12344,7 @@ testdata/SampleMaterial.lc 1954:32-1954:42 testdata/SampleMaterial.lc 1955:29-1955:40 TCGen testdata/SampleMaterial.lc 1956:29-1956:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1957:31-1957:42 StageTexture testdata/SampleMaterial.lc 1958:34-1958:38 @@ -12677,7 +12362,7 @@ testdata/SampleMaterial.lc 1965:21-1965:26 testdata/SampleMaterial.lc 1968:5-2010:6 (String, CommonAttrs) testdata/SampleMaterial.lc 1968:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 1968:7-1968:43 String testdata/SampleMaterial.lc 1969:7-1969:18 @@ -12687,49 +12372,42 @@ testdata/SampleMaterial.lc 1969:7-1969:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1969:7-1970:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1969:7-1971:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1969:7-1972:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1969:7-1973:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1969:7-1974:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1969:7-1975:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1969:7-1976:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1969:7-1977:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1969:7-1978:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1969:7-1979:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 1969:7-2007:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 1969:7-2009:10 @@ -12749,41 +12427,41 @@ testdata/SampleMaterial.lc 1975:23-1975:28 testdata/SampleMaterial.lc 1976:20-1976:33 CullType testdata/SampleMaterial.lc 1977:30-1977:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1978:25-1978:30 Bool testdata/SampleMaterial.lc 1979:29-1979:34 Bool testdata/SampleMaterial.lc 1981:13-2007:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 1981:15-1981:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1981:15-1982:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1981:15-1983:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1981:15-1984:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1981:15-1985:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1981:15-1986:31 @@ -12810,7 +12488,7 @@ testdata/SampleMaterial.lc 1984:32-1984:42 testdata/SampleMaterial.lc 1985:29-1985:36 TCGen testdata/SampleMaterial.lc 1986:29-1986:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 1987:31-1987:37 String -> StageTexture testdata/SampleMaterial.lc 1987:31-1987:74 @@ -12832,29 +12510,29 @@ testdata/SampleMaterial.lc 1994:15-1994:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1994:15-1995:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1994:15-1996:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1994:15-1997:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1994:15-1998:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 1994:15-1999:31 @@ -12871,7 +12549,7 @@ testdata/SampleMaterial.lc 1994:15-2003:40 testdata/SampleMaterial.lc 1994:15-2004:46 String -> StageAttrs testdata/SampleMaterial.lc 1994:15-2006:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 1995:29-1995:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 1995:29-1995:57 @@ -12889,7 +12567,7 @@ testdata/SampleMaterial.lc 1997:32-1997:42 testdata/SampleMaterial.lc 1998:29-1998:40 TCGen testdata/SampleMaterial.lc 1999:29-1999:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 2000:31-2000:42 StageTexture testdata/SampleMaterial.lc 2001:34-2001:38 @@ -12907,7 +12585,7 @@ testdata/SampleMaterial.lc 2008:21-2008:26 testdata/SampleMaterial.lc 2011:5-2053:6 (String, CommonAttrs) testdata/SampleMaterial.lc 2011:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 2011:7-2011:36 String testdata/SampleMaterial.lc 2012:7-2012:18 @@ -12917,49 +12595,42 @@ testdata/SampleMaterial.lc 2012:7-2012:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 2012:7-2013:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 2012:7-2014:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 2012:7-2015:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 2012:7-2016:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 2012:7-2017:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 2012:7-2018:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 2012:7-2019:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 2012:7-2020:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 2012:7-2021:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 2012:7-2022:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 2012:7-2050:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 2012:7-2052:10 @@ -12979,41 +12650,41 @@ testdata/SampleMaterial.lc 2018:23-2018:28 testdata/SampleMaterial.lc 2019:20-2019:33 CullType testdata/SampleMaterial.lc 2020:30-2020:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 2021:25-2021:30 Bool testdata/SampleMaterial.lc 2022:29-2022:34 Bool testdata/SampleMaterial.lc 2024:13-2050:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 2024:15-2024:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 2024:15-2025:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 2024:15-2026:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 2024:15-2027:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 2024:15-2028:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 2024:15-2029:31 @@ -13040,7 +12711,7 @@ testdata/SampleMaterial.lc 2027:32-2027:42 testdata/SampleMaterial.lc 2028:29-2028:36 TCGen testdata/SampleMaterial.lc 2029:29-2029:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 2030:31-2030:37 String -> StageTexture testdata/SampleMaterial.lc 2030:31-2030:67 @@ -13062,29 +12733,29 @@ testdata/SampleMaterial.lc 2037:15-2037:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 2037:15-2038:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 2037:15-2039:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 2037:15-2040:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 2037:15-2041:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 2037:15-2042:31 @@ -13101,7 +12772,7 @@ testdata/SampleMaterial.lc 2037:15-2046:40 testdata/SampleMaterial.lc 2037:15-2047:46 String -> StageAttrs testdata/SampleMaterial.lc 2037:15-2049:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 2038:29-2038:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 2038:29-2038:57 @@ -13119,7 +12790,7 @@ testdata/SampleMaterial.lc 2040:32-2040:42 testdata/SampleMaterial.lc 2041:29-2041:40 TCGen testdata/SampleMaterial.lc 2042:29-2042:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 2043:31-2043:42 StageTexture testdata/SampleMaterial.lc 2044:34-2044:38 @@ -13137,7 +12808,7 @@ testdata/SampleMaterial.lc 2051:21-2051:26 testdata/SampleMaterial.lc 2054:5-2096:6 (String, CommonAttrs) testdata/SampleMaterial.lc 2054:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 2054:7-2054:40 String testdata/SampleMaterial.lc 2055:7-2055:18 @@ -13147,49 +12818,42 @@ testdata/SampleMaterial.lc 2055:7-2055:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 2055:7-2056:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 2055:7-2057:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 2055:7-2058:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 2055:7-2059:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 2055:7-2060:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 2055:7-2061:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 2055:7-2062:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 2055:7-2063:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 2055:7-2064:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 2055:7-2065:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 2055:7-2093:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 2055:7-2095:10 @@ -13209,41 +12873,41 @@ testdata/SampleMaterial.lc 2061:23-2061:28 testdata/SampleMaterial.lc 2062:20-2062:33 CullType testdata/SampleMaterial.lc 2063:30-2063:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 2064:25-2064:30 Bool testdata/SampleMaterial.lc 2065:29-2065:34 Bool testdata/SampleMaterial.lc 2067:13-2093:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 2067:15-2067:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 2067:15-2068:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 2067:15-2069:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 2067:15-2070:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 2067:15-2071:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 2067:15-2072:31 @@ -13270,7 +12934,7 @@ testdata/SampleMaterial.lc 2070:32-2070:42 testdata/SampleMaterial.lc 2071:29-2071:36 TCGen testdata/SampleMaterial.lc 2072:29-2072:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 2073:31-2073:37 String -> StageTexture testdata/SampleMaterial.lc 2073:31-2073:71 @@ -13292,29 +12956,29 @@ testdata/SampleMaterial.lc 2080:15-2080:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 2080:15-2081:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 2080:15-2082:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 2080:15-2083:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 2080:15-2084:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 2080:15-2085:31 @@ -13331,7 +12995,7 @@ testdata/SampleMaterial.lc 2080:15-2089:40 testdata/SampleMaterial.lc 2080:15-2090:46 String -> StageAttrs testdata/SampleMaterial.lc 2080:15-2092:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 2081:29-2081:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 2081:29-2081:57 @@ -13349,7 +13013,7 @@ testdata/SampleMaterial.lc 2083:32-2083:42 testdata/SampleMaterial.lc 2084:29-2084:40 TCGen testdata/SampleMaterial.lc 2085:29-2085:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 2086:31-2086:42 StageTexture testdata/SampleMaterial.lc 2087:34-2087:38 @@ -13367,7 +13031,7 @@ testdata/SampleMaterial.lc 2094:21-2094:26 testdata/SampleMaterial.lc 2097:5-2139:6 (String, CommonAttrs) testdata/SampleMaterial.lc 2097:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/SampleMaterial.lc 2097:7-2097:50 String testdata/SampleMaterial.lc 2098:7-2098:18 @@ -13377,49 +13041,42 @@ testdata/SampleMaterial.lc 2098:7-2098:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 2098:7-2099:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 2098:7-2100:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 2098:7-2101:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 2098:7-2102:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 2098:7-2103:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 2098:7-2104:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 2098:7-2105:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 2098:7-2106:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 2098:7-2107:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 2098:7-2108:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 2098:7-2136:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 2098:7-2138:10 @@ -13439,41 +13096,41 @@ testdata/SampleMaterial.lc 2104:23-2104:28 testdata/SampleMaterial.lc 2105:20-2105:33 CullType testdata/SampleMaterial.lc 2106:30-2106:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 2107:25-2107:30 Bool testdata/SampleMaterial.lc 2108:29-2108:34 Bool testdata/SampleMaterial.lc 2110:13-2136:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 2110:15-2110:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 2110:15-2111:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 2110:15-2112:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 2110:15-2113:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 2110:15-2114:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 2110:15-2115:31 @@ -13500,7 +13157,7 @@ testdata/SampleMaterial.lc 2113:32-2113:42 testdata/SampleMaterial.lc 2114:29-2114:36 TCGen testdata/SampleMaterial.lc 2115:29-2115:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 2116:31-2116:37 String -> StageTexture testdata/SampleMaterial.lc 2116:31-2116:81 @@ -13522,29 +13179,29 @@ testdata/SampleMaterial.lc 2123:15-2123:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 2123:15-2124:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 2123:15-2125:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 2123:15-2126:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 2123:15-2127:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 2123:15-2128:31 @@ -13561,7 +13218,7 @@ testdata/SampleMaterial.lc 2123:15-2132:40 testdata/SampleMaterial.lc 2123:15-2133:46 String -> StageAttrs testdata/SampleMaterial.lc 2123:15-2135:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 2124:29-2124:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 2124:29-2124:57 @@ -13579,7 +13236,7 @@ testdata/SampleMaterial.lc 2126:32-2126:42 testdata/SampleMaterial.lc 2127:29-2127:40 TCGen testdata/SampleMaterial.lc 2128:29-2128:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 2129:31-2129:42 StageTexture testdata/SampleMaterial.lc 2130:34-2130:38 @@ -13595,7 +13252,7 @@ testdata/SampleMaterial.lc 2134:38-2134:54 testdata/SampleMaterial.lc 2137:21-2137:26 Bool testdata/SampleMaterial.lc 2140:5-2182:6 - (String, CommonAttrs) | List (String, CommonAttrs) + (String, CommonAttrs) | [(String, CommonAttrs)] testdata/SampleMaterial.lc 2140:7-2140:50 String testdata/SampleMaterial.lc 2141:7-2141:18 @@ -13605,49 +13262,42 @@ testdata/SampleMaterial.lc 2141:7-2141:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 2141:7-2142:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 2141:7-2143:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 2141:7-2144:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 2141:7-2145:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 2141:7-2146:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 2141:7-2147:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 2141:7-2148:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 2141:7-2149:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 2141:7-2150:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 2141:7-2151:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/SampleMaterial.lc 2141:7-2179:14 Bool -> CommonAttrs testdata/SampleMaterial.lc 2141:7-2181:10 @@ -13667,41 +13317,41 @@ testdata/SampleMaterial.lc 2147:23-2147:28 testdata/SampleMaterial.lc 2148:20-2148:33 CullType testdata/SampleMaterial.lc 2149:30-2149:32 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 2150:25-2150:30 Bool testdata/SampleMaterial.lc 2151:29-2151:34 Bool testdata/SampleMaterial.lc 2153:13-2179:14 - List StageAttrs + [StageAttrs] testdata/SampleMaterial.lc 2153:15-2153:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 2153:15-2154:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 2153:15-2155:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 2153:15-2156:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 2153:15-2157:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 2153:15-2158:31 @@ -13728,7 +13378,7 @@ testdata/SampleMaterial.lc 2156:32-2156:42 testdata/SampleMaterial.lc 2157:29-2157:36 TCGen testdata/SampleMaterial.lc 2158:29-2158:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 2159:31-2159:37 String -> StageTexture testdata/SampleMaterial.lc 2159:31-2159:81 @@ -13750,29 +13400,29 @@ testdata/SampleMaterial.lc 2166:15-2166:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 2166:15-2167:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 2166:15-2168:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 2166:15-2169:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 2166:15-2170:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/SampleMaterial.lc 2166:15-2171:31 @@ -13789,7 +13439,7 @@ testdata/SampleMaterial.lc 2166:15-2175:40 testdata/SampleMaterial.lc 2166:15-2176:46 String -> StageAttrs testdata/SampleMaterial.lc 2166:15-2178:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/SampleMaterial.lc 2167:29-2167:33 forall a . a -> Maybe a testdata/SampleMaterial.lc 2167:29-2167:57 @@ -13807,7 +13457,7 @@ testdata/SampleMaterial.lc 2169:32-2169:42 testdata/SampleMaterial.lc 2170:29-2170:40 TCGen testdata/SampleMaterial.lc 2171:29-2171:31 - forall a . List a + forall a . [a] testdata/SampleMaterial.lc 2172:31-2172:42 StageTexture testdata/SampleMaterial.lc 2173:34-2173:38 diff --git a/testdata/data.out b/testdata/data.out index 8e2003e2..615a5361 100644 --- a/testdata/data.out +++ b/testdata/data.out @@ -2,7 +2,7 @@ data Data0 :: Type where Data0 :: Data0 data Data1 (_ :: Type) (_ :: Type) (_ :: Type) :: Type where - Data1 :: _c -> _b -> _a -> Data1 _c _b _a + Data1 :: forall a b c . a -> b -> c -> Data1 a b c data Data2 :: Type where Data21 :: Int -> Data2 Data22 :: Int -> Int -> Data2 @@ -25,9 +25,9 @@ y (_rhs undefined) a data Data5 (_ :: Type) (_ :: Type) (_ :: Type) :: Type where - Data51 :: _c -> Data5 _c _b _a - Data52 :: _c -> _b -> _a -> Data5 _c _b _a - Data53 :: Int -> _c -> Float -> _b -> _a -> Data5 _c _b _a + Data51 :: forall a b c . a -> Data5 a b c + Data52 :: forall d e f . d -> e -> f -> Data5 d e f + Data53 :: forall g h i . Int -> g -> Float -> h -> i -> Data5 g h i a5 = \(a :: _) -> 'Data5Case \_ -> _ :: _ diff --git a/testdata/framebuffer02.reject.out b/testdata/framebuffer02.reject.out index b733b615..1899ff29 100644 --- a/testdata/framebuffer02.reject.out +++ b/testdata/framebuffer02.reject.out @@ -21,7 +21,7 @@ in testdata/framebuffer02.reject.lc:2:17: ) ------------ tooltips testdata/framebuffer02.reject.lc 2:17-2:28 - forall (a :: List Type) + forall (a :: [Type]) . sameLayerCounts a => HList a -> FrameBuffer (ImageLC (head Type a)) (map Type ImageKind GetImageKind a) @@ -36,7 +36,7 @@ testdata/framebuffer02.reject.lc 2:17-5:30 (Image 1 ('Color (VecScalar 4 Float))) (: (Image 2 ('Color (VecScalar 4 Float))) - (: (Image 1 ('Color (VecScalar 1 Float))) 'Nil)))) + (: (Image 1 ('Color (VecScalar 1 Float))) '[])))) testdata/framebuffer02.reject.lc 2:29-5:30 (Image 1 ('Color (VecScalar 4 Float)), Image 2 diff --git a/testdata/language-features/basic-list/list01.out b/testdata/language-features/basic-list/list01.out index 58abb9f1..5df5b1a0 100644 --- a/testdata/language-features/basic-list/list01.out +++ b/testdata/language-features/basic-list/list01.out @@ -4,47 +4,47 @@ value2 = _rhs (fromInt 1 : fromInt 2 : fromInt 3 : fromInt 4 : []) value3 = _rhs ('h' : 'e' : 'l' : 'l' : 'o' : []) main is not found ------------ trace -value1 :: forall a . List a -value2 :: forall a . Num a => List a -value3 :: List Char +value1 :: forall a . [a] +value2 :: forall a . Num a => [a] +value3 :: [Char] ------------ tooltips testdata/language-features/basic-list/list01.lc 1:1-1:7 - forall a . List a + forall a . [a] testdata/language-features/basic-list/list01.lc 1:10-1:12 - forall a . List a + forall a . [a] testdata/language-features/basic-list/list01.lc 2:1-2:7 - forall a . Num a => List a + forall a . Num a => [a] testdata/language-features/basic-list/list01.lc 2:10-2:19 - List _c + [_c] testdata/language-features/basic-list/list01.lc 2:11-2:12 _b testdata/language-features/basic-list/list01.lc 2:13-2:14 _b testdata/language-features/basic-list/list01.lc 2:13-2:18 - List _d + [_d] testdata/language-features/basic-list/list01.lc 2:15-2:16 _b testdata/language-features/basic-list/list01.lc 2:15-2:18 - List _e + [_e] testdata/language-features/basic-list/list01.lc 2:17-2:18 - _b | List _e + _b | [_e] testdata/language-features/basic-list/list01.lc 3:1-3:7 - List Char + [Char] testdata/language-features/basic-list/list01.lc 3:10-3:31 - List Char + [Char] testdata/language-features/basic-list/list01.lc 3:11-3:14 Char testdata/language-features/basic-list/list01.lc 3:15-3:18 Char testdata/language-features/basic-list/list01.lc 3:15-3:30 - List Char + [Char] testdata/language-features/basic-list/list01.lc 3:19-3:22 Char testdata/language-features/basic-list/list01.lc 3:19-3:30 - List Char + [Char] testdata/language-features/basic-list/list01.lc 3:23-3:26 Char testdata/language-features/basic-list/list01.lc 3:23-3:30 - List Char + [Char] testdata/language-features/basic-list/list01.lc 3:27-3:30 - Char | List Char \ No newline at end of file + Char | [Char] \ No newline at end of file diff --git a/testdata/language-features/basic-list/list02.out b/testdata/language-features/basic-list/list02.out index 66445671..dec74991 100644 --- a/testdata/language-features/basic-list/list02.out +++ b/testdata/language-features/basic-list/list02.out @@ -4,47 +4,47 @@ value2 = _rhs (fromInt 1 : fromInt 2 : fromInt 3 : fromInt 4 : []) value3 = _rhs ('h' : 'e' : 'l' : 'l' : 'o' : []) main is not found ------------ trace -value1 :: forall a . List a -value2 :: forall a . Num a => List a -value3 :: List Char +value1 :: forall a . [a] +value2 :: forall a . Num a => [a] +value3 :: [Char] ------------ tooltips testdata/language-features/basic-list/list02.lc 1:1-1:7 - forall a . List a + forall a . [a] testdata/language-features/basic-list/list02.lc 1:10-2:4 - forall a . List a + forall a . [a] testdata/language-features/basic-list/list02.lc 4:1-4:7 - forall a . Num a => List a + forall a . Num a => [a] testdata/language-features/basic-list/list02.lc 4:10-5:7 - List _c + [_c] testdata/language-features/basic-list/list02.lc 4:11-4:12 _b testdata/language-features/basic-list/list02.lc 4:13-4:14 _b testdata/language-features/basic-list/list02.lc 4:13-5:6 - List _d + [_d] testdata/language-features/basic-list/list02.lc 5:3-5:4 _b testdata/language-features/basic-list/list02.lc 5:3-5:6 - List _e + [_e] testdata/language-features/basic-list/list02.lc 5:5-5:6 - _b | List _e + _b | [_e] testdata/language-features/basic-list/list02.lc 7:1-7:7 - List Char + [Char] testdata/language-features/basic-list/list02.lc 8:3-13:4 - List Char + [Char] testdata/language-features/basic-list/list02.lc 8:5-8:8 Char testdata/language-features/basic-list/list02.lc 9:5-9:8 Char testdata/language-features/basic-list/list02.lc 9:5-12:8 - List Char + [Char] testdata/language-features/basic-list/list02.lc 10:5-10:8 Char testdata/language-features/basic-list/list02.lc 10:5-12:8 - List Char + [Char] testdata/language-features/basic-list/list02.lc 11:5-11:8 Char testdata/language-features/basic-list/list02.lc 11:5-12:8 - List Char + [Char] testdata/language-features/basic-list/list02.lc 12:5-12:8 - Char | List Char \ No newline at end of file + Char | [Char] \ No newline at end of file diff --git a/testdata/language-features/basic-list/list08.out b/testdata/language-features/basic-list/list08.out index 7c00caeb..aebab457 100644 --- a/testdata/language-features/basic-list/list08.out +++ b/testdata/language-features/basic-list/list08.out @@ -2,13 +2,13 @@ value = _rhs (fromInt 1 : 1.2 : []) main is not found ------------ trace -value :: List Float +value :: [Float] ------------ tooltips testdata/language-features/basic-list/list08.lc 1:1-1:6 - List Float + [Float] testdata/language-features/basic-list/list08.lc 1:9-1:16 - List Float + [Float] testdata/language-features/basic-list/list08.lc 1:10-1:11 _b testdata/language-features/basic-list/list08.lc 1:12-1:15 - Float | List Float \ No newline at end of file + Float | [Float] \ No newline at end of file diff --git a/testdata/language-features/basic-list/list09.out b/testdata/language-features/basic-list/list09.out index 1667abd0..11abf486 100644 --- a/testdata/language-features/basic-list/list09.out +++ b/testdata/language-features/basic-list/list09.out @@ -1,17 +1,17 @@ ------------ desugared source code -value = _rhs (fromInt 1 : 1.2 : [] :: List Float) +value = _rhs (fromInt 1 : 1.2 : [] :: [Float]) main is not found ------------ trace -value :: List Float +value :: [Float] ------------ tooltips testdata/language-features/basic-list/list09.lc 1:1-1:6 - List Float + [Float] testdata/language-features/basic-list/list09.lc 1:9-1:16 - List Float + [Float] testdata/language-features/basic-list/list09.lc 1:10-1:11 _b testdata/language-features/basic-list/list09.lc 1:12-1:15 - Float | List Float + Float | [Float] testdata/language-features/basic-list/list09.lc 1:20-1:27 Type testdata/language-features/basic-list/list09.lc 1:21-1:26 diff --git a/testdata/language-features/basic-list/list11.out b/testdata/language-features/basic-list/list11.out index 2c68182e..b70c324c 100644 --- a/testdata/language-features/basic-list/list11.out +++ b/testdata/language-features/basic-list/list11.out @@ -2,17 +2,17 @@ value = _rhs (fromInt 1 : []) main is not found ------------ trace -value :: forall a . Num a => List a +value :: forall a . Num a => [a] ------------ tooltips testdata/language-features/basic-list/list11.lc 1:1-1:6 - forall a . Num a => List a + forall a . Num a => [a] testdata/language-features/basic-list/list11.lc 1:9-1:10 _b testdata/language-features/basic-list/list11.lc 1:9-1:11 - List _b -> List _b + [_b] -> [_b] testdata/language-features/basic-list/list11.lc 1:9-1:13 - List _b + [_b] testdata/language-features/basic-list/list11.lc 1:10-1:11 - forall a . a -> List a -> List a + forall a . a -> [a] -> [a] testdata/language-features/basic-list/list11.lc 1:11-1:13 - forall a . List a \ No newline at end of file + forall a . [a] \ No newline at end of file diff --git a/testdata/language-features/basic-list/list12.out b/testdata/language-features/basic-list/list12.out index 6217fd5d..5a5f796d 100644 --- a/testdata/language-features/basic-list/list12.out +++ b/testdata/language-features/basic-list/list12.out @@ -2,49 +2,49 @@ value = _rhs (fromInt 1 : fromInt 2 : fromInt 3 : fromInt 4 : fromInt 5 : []) main is not found ------------ trace -value :: forall a . Num a => List a +value :: forall a . Num a => [a] ------------ tooltips testdata/language-features/basic-list/list12.lc 1:1-1:6 - forall a . Num a => List a + forall a . Num a => [a] testdata/language-features/basic-list/list12.lc 1:9-1:10 _b testdata/language-features/basic-list/list12.lc 1:9-1:11 - List _b -> List _b + [_b] -> [_b] testdata/language-features/basic-list/list12.lc 1:9-1:21 - List _c + [_c] testdata/language-features/basic-list/list12.lc 1:10-1:11 - forall a . a -> List a -> List a + forall a . a -> [a] -> [a] testdata/language-features/basic-list/list12.lc 1:11-1:12 _b testdata/language-features/basic-list/list12.lc 1:11-1:13 - List _b -> List _b + [_b] -> [_b] testdata/language-features/basic-list/list12.lc 1:11-1:21 - List _d + [_d] testdata/language-features/basic-list/list12.lc 1:12-1:13 - forall a . a -> List a -> List a + forall a . a -> [a] -> [a] testdata/language-features/basic-list/list12.lc 1:13-1:14 _b testdata/language-features/basic-list/list12.lc 1:13-1:15 - List _b -> List _b + [_b] -> [_b] testdata/language-features/basic-list/list12.lc 1:13-1:21 - List _e + [_e] testdata/language-features/basic-list/list12.lc 1:14-1:15 - forall a . a -> List a -> List a + forall a . a -> [a] -> [a] testdata/language-features/basic-list/list12.lc 1:15-1:16 _b testdata/language-features/basic-list/list12.lc 1:15-1:17 - List _b -> List _b + [_b] -> [_b] testdata/language-features/basic-list/list12.lc 1:15-1:21 - List _f + [_f] testdata/language-features/basic-list/list12.lc 1:16-1:17 - forall a . a -> List a -> List a + forall a . a -> [a] -> [a] testdata/language-features/basic-list/list12.lc 1:17-1:18 _b testdata/language-features/basic-list/list12.lc 1:17-1:19 - List _b -> List _b + [_b] -> [_b] testdata/language-features/basic-list/list12.lc 1:17-1:21 - List _f + [_f] testdata/language-features/basic-list/list12.lc 1:18-1:19 - forall a . a -> List a -> List a + forall a . a -> [a] -> [a] testdata/language-features/basic-list/list12.lc 1:19-1:21 - forall a . List a \ No newline at end of file + forall a . [a] \ No newline at end of file diff --git a/testdata/language-features/basic-list/list13.out b/testdata/language-features/basic-list/list13.out index c4567888..66403b86 100644 --- a/testdata/language-features/basic-list/list13.out +++ b/testdata/language-features/basic-list/list13.out @@ -2,49 +2,49 @@ value = _rhs ('h' : 'e' : 'l' : 'l' : 'o' : []) main is not found ------------ trace -value :: List Char +value :: [Char] ------------ tooltips testdata/language-features/basic-list/list13.lc 1:1-1:6 - List Char + [Char] testdata/language-features/basic-list/list13.lc 1:9-1:12 Char testdata/language-features/basic-list/list13.lc 1:9-1:13 - List Char -> List Char + [Char] -> [Char] testdata/language-features/basic-list/list13.lc 1:9-1:31 - List Char + [Char] testdata/language-features/basic-list/list13.lc 1:12-1:13 - forall a . a -> List a -> List a + forall a . a -> [a] -> [a] testdata/language-features/basic-list/list13.lc 1:13-1:16 Char testdata/language-features/basic-list/list13.lc 1:13-1:17 - List Char -> List Char + [Char] -> [Char] testdata/language-features/basic-list/list13.lc 1:13-1:31 - List Char + [Char] testdata/language-features/basic-list/list13.lc 1:16-1:17 - forall a . a -> List a -> List a + forall a . a -> [a] -> [a] testdata/language-features/basic-list/list13.lc 1:17-1:20 Char testdata/language-features/basic-list/list13.lc 1:17-1:21 - List Char -> List Char + [Char] -> [Char] testdata/language-features/basic-list/list13.lc 1:17-1:31 - List Char + [Char] testdata/language-features/basic-list/list13.lc 1:20-1:21 - forall a . a -> List a -> List a + forall a . a -> [a] -> [a] testdata/language-features/basic-list/list13.lc 1:21-1:24 Char testdata/language-features/basic-list/list13.lc 1:21-1:25 - List Char -> List Char + [Char] -> [Char] testdata/language-features/basic-list/list13.lc 1:21-1:31 - List Char + [Char] testdata/language-features/basic-list/list13.lc 1:24-1:25 - forall a . a -> List a -> List a + forall a . a -> [a] -> [a] testdata/language-features/basic-list/list13.lc 1:25-1:28 Char testdata/language-features/basic-list/list13.lc 1:25-1:29 - List Char -> List Char + [Char] -> [Char] testdata/language-features/basic-list/list13.lc 1:25-1:31 - List Char + [Char] testdata/language-features/basic-list/list13.lc 1:28-1:29 - forall a . a -> List a -> List a + forall a . a -> [a] -> [a] testdata/language-features/basic-list/list13.lc 1:29-1:31 - forall a . List a \ No newline at end of file + forall a . [a] \ No newline at end of file diff --git a/testdata/language-features/basic-list/list14.reject.out b/testdata/language-features/basic-list/list14.reject.out index 8d1a59e9..a8d86a22 100644 --- a/testdata/language-features/basic-list/list14.reject.out +++ b/testdata/language-features/basic-list/list14.reject.out @@ -1,5 +1,5 @@ type error: can not unify -'List 'Char +['Char] with () @@ -8,7 +8,7 @@ value = 'h':'i':() ^^ ------------ trace !type error: can not unify -'List 'Char +['Char] with () @@ -19,14 +19,14 @@ value = 'h':'i':() testdata/language-features/basic-list/list14.reject.lc 1:9-1:12 Char testdata/language-features/basic-list/list14.reject.lc 1:9-1:13 - List Char -> List Char + [Char] -> [Char] testdata/language-features/basic-list/list14.reject.lc 1:12-1:13 - forall a . a -> List a -> List a + forall a . a -> [a] -> [a] testdata/language-features/basic-list/list14.reject.lc 1:13-1:16 Char testdata/language-features/basic-list/list14.reject.lc 1:13-1:17 - List Char -> List Char + [Char] -> [Char] testdata/language-features/basic-list/list14.reject.lc 1:16-1:17 - forall a . a -> List a -> List a + forall a . a -> [a] -> [a] testdata/language-features/basic-list/list14.reject.lc 1:17-1:19 () \ No newline at end of file diff --git a/testdata/language-features/basic-list/list15.reject.out b/testdata/language-features/basic-list/list15.reject.out index 9caab32f..4260adbe 100644 --- a/testdata/language-features/basic-list/list15.reject.out +++ b/testdata/language-features/basic-list/list15.reject.out @@ -19,18 +19,18 @@ value = 'h':'i':():[] testdata/language-features/basic-list/list15.reject.lc 1:9-1:12 Char testdata/language-features/basic-list/list15.reject.lc 1:9-1:13 - List Char -> List Char + [Char] -> [Char] testdata/language-features/basic-list/list15.reject.lc 1:12-1:13 - forall a . a -> List a -> List a + forall a . a -> [a] -> [a] testdata/language-features/basic-list/list15.reject.lc 1:13-1:16 Char testdata/language-features/basic-list/list15.reject.lc 1:13-1:17 - List Char -> List Char + [Char] -> [Char] testdata/language-features/basic-list/list15.reject.lc 1:16-1:17 - forall a . a -> List a -> List a + forall a . a -> [a] -> [a] testdata/language-features/basic-list/list15.reject.lc 1:17-1:19 () testdata/language-features/basic-list/list15.reject.lc 1:17-1:20 - List () -> List () + [()] -> [()] testdata/language-features/basic-list/list15.reject.lc 1:19-1:20 - forall a . a -> List a -> List a \ No newline at end of file + forall a . a -> [a] -> [a] \ No newline at end of file diff --git a/testdata/language-features/basic-list/list16.reject.out b/testdata/language-features/basic-list/list16.reject.out index 4ffd3ea0..912f567c 100644 --- a/testdata/language-features/basic-list/list16.reject.out +++ b/testdata/language-features/basic-list/list16.reject.out @@ -1,5 +1,5 @@ type error: can not unify -'List 'Char +['Char] with 'Char @@ -8,7 +8,7 @@ value = 'h':'i' ^^^ ------------ trace !type error: can not unify -'List 'Char +['Char] with 'Char @@ -19,8 +19,8 @@ value = 'h':'i' testdata/language-features/basic-list/list16.reject.lc 1:9-1:12 Char testdata/language-features/basic-list/list16.reject.lc 1:9-1:13 - List Char -> List Char + [Char] -> [Char] testdata/language-features/basic-list/list16.reject.lc 1:12-1:13 - forall a . a -> List a -> List a + forall a . a -> [a] -> [a] testdata/language-features/basic-list/list16.reject.lc 1:13-1:16 Char \ No newline at end of file diff --git a/testdata/language-features/basic-list/listcomp01.out b/testdata/language-features/basic-list/listcomp01.out index be5d1871..a782100a 100644 --- a/testdata/language-features/basic-list/listcomp01.out +++ b/testdata/language-features/basic-list/listcomp01.out @@ -2,25 +2,25 @@ value = _rhs (concatMap \_ -> HNil : [] (HNil : HNil : HNil : HNil : [])) main is not found ------------ trace -value :: List () +value :: [()] ------------ tooltips testdata/language-features/basic-list/listcomp01.lc 1:1-1:6 - List () + [()] testdata/language-features/basic-list/listcomp01.lc 1:9-1:34 - List () + [()] testdata/language-features/basic-list/listcomp01.lc 1:10-1:12 - () | List () + () | [()] testdata/language-features/basic-list/listcomp01.lc 1:20-1:33 - List () + [()] testdata/language-features/basic-list/listcomp01.lc 1:21-1:23 () testdata/language-features/basic-list/listcomp01.lc 1:24-1:26 () testdata/language-features/basic-list/listcomp01.lc 1:24-1:32 - List () + [()] testdata/language-features/basic-list/listcomp01.lc 1:27-1:29 () testdata/language-features/basic-list/listcomp01.lc 1:27-1:32 - List () + [()] testdata/language-features/basic-list/listcomp01.lc 1:30-1:32 - () | List () \ No newline at end of file + () | [()] \ No newline at end of file diff --git a/testdata/language-features/basic-list/listcomp02.out b/testdata/language-features/basic-list/listcomp02.out index 825c5244..661abdad 100644 --- a/testdata/language-features/basic-list/listcomp02.out +++ b/testdata/language-features/basic-list/listcomp02.out @@ -3,30 +3,30 @@ l = _rhs (HNil : HNil : HNil : HNil : []) value = _rhs (concatMap \(a :: _) -> a : [] l) main is not found ------------ trace -l :: List () -value :: List () +l :: [()] +value :: [()] ------------ tooltips testdata/language-features/basic-list/listcomp02.lc 1:1-1:2 - List () + [()] testdata/language-features/basic-list/listcomp02.lc 1:5-1:18 - List () + [()] testdata/language-features/basic-list/listcomp02.lc 1:6-1:8 () testdata/language-features/basic-list/listcomp02.lc 1:9-1:11 () testdata/language-features/basic-list/listcomp02.lc 1:9-1:17 - List () + [()] testdata/language-features/basic-list/listcomp02.lc 1:12-1:14 () testdata/language-features/basic-list/listcomp02.lc 1:12-1:17 - List () + [()] testdata/language-features/basic-list/listcomp02.lc 1:15-1:17 - () | List () + () | [()] testdata/language-features/basic-list/listcomp02.lc 2:1-2:6 - List () + [()] testdata/language-features/basic-list/listcomp02.lc 2:9-2:21 - List () + [()] testdata/language-features/basic-list/listcomp02.lc 2:10-2:11 - _d | List _b + _d | [_b] testdata/language-features/basic-list/listcomp02.lc 2:19-2:20 - List () \ No newline at end of file + [()] \ No newline at end of file diff --git a/testdata/language-features/basic-list/listcomp03.out b/testdata/language-features/basic-list/listcomp03.out index 22d4ebf6..f6a524a8 100644 --- a/testdata/language-features/basic-list/listcomp03.out +++ b/testdata/language-features/basic-list/listcomp03.out @@ -6,29 +6,29 @@ value (HNil : HNil : HNil : HNil : [])) main is not found ------------ trace -value :: List () +value :: [()] ------------ tooltips testdata/language-features/basic-list/listcomp03.lc 1:1-1:6 - List () + [()] testdata/language-features/basic-list/listcomp03.lc 1:9-1:41 - List () + [()] testdata/language-features/basic-list/listcomp03.lc 1:10-1:12 - () | List () + () | [()] testdata/language-features/basic-list/listcomp03.lc 1:10-1:40 - List () -> List () | List () + [()] -> [()] | [()] testdata/language-features/basic-list/listcomp03.lc 1:20-1:33 - List () + [()] testdata/language-features/basic-list/listcomp03.lc 1:21-1:23 () testdata/language-features/basic-list/listcomp03.lc 1:24-1:26 () testdata/language-features/basic-list/listcomp03.lc 1:24-1:32 - List () + [()] testdata/language-features/basic-list/listcomp03.lc 1:27-1:29 () testdata/language-features/basic-list/listcomp03.lc 1:27-1:32 - List () + [()] testdata/language-features/basic-list/listcomp03.lc 1:30-1:32 - () | List () + () | [()] testdata/language-features/basic-list/listcomp03.lc 1:35-1:40 Bool \ No newline at end of file diff --git a/testdata/language-features/basic-list/listcomp04.out b/testdata/language-features/basic-list/listcomp04.out index c42d18fa..e1cdf511 100644 --- a/testdata/language-features/basic-list/listcomp04.out +++ b/testdata/language-features/basic-list/listcomp04.out @@ -3,34 +3,34 @@ l = _rhs (HNil : HNil : HNil : HNil : []) value = _rhs (concatMap \_ -> concatMap \_ -> HNil : [] l l) main is not found ------------ trace -l :: List () -value :: List () +l :: [()] +value :: [()] ------------ tooltips testdata/language-features/basic-list/listcomp04.lc 1:1-1:2 - List () + [()] testdata/language-features/basic-list/listcomp04.lc 1:5-1:18 - List () + [()] testdata/language-features/basic-list/listcomp04.lc 1:6-1:8 () testdata/language-features/basic-list/listcomp04.lc 1:9-1:11 () testdata/language-features/basic-list/listcomp04.lc 1:9-1:17 - List () + [()] testdata/language-features/basic-list/listcomp04.lc 1:12-1:14 () testdata/language-features/basic-list/listcomp04.lc 1:12-1:17 - List () + [()] testdata/language-features/basic-list/listcomp04.lc 1:15-1:17 - () | List () + () | [()] testdata/language-features/basic-list/listcomp04.lc 2:1-2:6 - List () + [()] testdata/language-features/basic-list/listcomp04.lc 2:9-2:30 - List () + [()] testdata/language-features/basic-list/listcomp04.lc 2:10-2:12 - () | List () + () | [()] testdata/language-features/basic-list/listcomp04.lc 2:10-2:29 - List () + [()] testdata/language-features/basic-list/listcomp04.lc 2:20-2:21 - List () + [()] testdata/language-features/basic-list/listcomp04.lc 2:28-2:29 - List () \ No newline at end of file + [()] \ No newline at end of file diff --git a/testdata/language-features/basic-list/listcomp05.out b/testdata/language-features/basic-list/listcomp05.out index 53238d6c..b5ac9f54 100644 --- a/testdata/language-features/basic-list/listcomp05.out +++ b/testdata/language-features/basic-list/listcomp05.out @@ -6,20 +6,20 @@ value (HNil : HNil : [])) main is not found ------------ trace -value :: List () +value :: [()] ------------ tooltips testdata/language-features/basic-list/listcomp05.lc 1:1-1:6 - List () + [()] testdata/language-features/basic-list/listcomp05.lc 1:9-1:39 - List () + [()] testdata/language-features/basic-list/listcomp05.lc 1:10-1:11 () testdata/language-features/basic-list/listcomp05.lc 1:19-1:26 - List () + [()] testdata/language-features/basic-list/listcomp05.lc 1:20-1:22 () testdata/language-features/basic-list/listcomp05.lc 1:23-1:25 - () | List () + () | [()] testdata/language-features/basic-list/listcomp05.lc 1:32-1:33 _b | () testdata/language-features/basic-list/listcomp05.lc 1:36-1:38 diff --git a/testdata/language-features/basic-list/listcomp06.out b/testdata/language-features/basic-list/listcomp06.out index 56ecc4c6..0002747e 100644 --- a/testdata/language-features/basic-list/listcomp06.out +++ b/testdata/language-features/basic-list/listcomp06.out @@ -17,23 +17,23 @@ value2 (HNil : HNil : [])) main is not found ------------ trace -value1 :: List () -value2 :: List () +value1 :: [()] +value2 :: [()] ------------ tooltips testdata/language-features/basic-list/listcomp06.lc 1:1-1:7 - List () + [()] testdata/language-features/basic-list/listcomp06.lc 1:10-1:46 - List () + [()] testdata/language-features/basic-list/listcomp06.lc 1:11-1:12 - () | List () + () | [()] testdata/language-features/basic-list/listcomp06.lc 1:11-1:45 - List () -> List () + [()] -> [()] testdata/language-features/basic-list/listcomp06.lc 1:20-1:27 - List () + [()] testdata/language-features/basic-list/listcomp06.lc 1:21-1:23 () testdata/language-features/basic-list/listcomp06.lc 1:24-1:26 - () | List () + () | [()] testdata/language-features/basic-list/listcomp06.lc 1:33-1:34 _b | () testdata/language-features/basic-list/listcomp06.lc 1:37-1:39 @@ -41,19 +41,19 @@ testdata/language-features/basic-list/listcomp06.lc 1:37-1:39 testdata/language-features/basic-list/listcomp06.lc 1:41-1:45 Bool testdata/language-features/basic-list/listcomp06.lc 3:1-3:7 - List () + [()] testdata/language-features/basic-list/listcomp06.lc 3:10-3:46 - List () + [()] testdata/language-features/basic-list/listcomp06.lc 3:11-3:12 () testdata/language-features/basic-list/listcomp06.lc 3:11-3:45 - List () + [()] testdata/language-features/basic-list/listcomp06.lc 3:20-3:27 - List () + [()] testdata/language-features/basic-list/listcomp06.lc 3:21-3:23 () testdata/language-features/basic-list/listcomp06.lc 3:24-3:26 - () | List () + () | [()] testdata/language-features/basic-list/listcomp06.lc 3:29-3:33 Bool testdata/language-features/basic-list/listcomp06.lc 3:39-3:40 diff --git a/testdata/language-features/basic-list/listcomp07.out b/testdata/language-features/basic-list/listcomp07.out index 9d3651c2..1dfa572d 100644 --- a/testdata/language-features/basic-list/listcomp07.out +++ b/testdata/language-features/basic-list/listcomp07.out @@ -25,22 +25,22 @@ value3 (HNil : HNil : [])) main is not found ------------ trace -value1 :: List () -value2 :: List () -value3 :: List () +value1 :: [()] +value2 :: [()] +value3 :: [()] ------------ tooltips testdata/language-features/basic-list/listcomp07.lc 1:1-1:7 - List () + [()] testdata/language-features/basic-list/listcomp07.lc 1:10-6:11 - List () + [()] testdata/language-features/basic-list/listcomp07.lc 1:12-1:13 () testdata/language-features/basic-list/listcomp07.lc 2:17-2:24 - List () + [()] testdata/language-features/basic-list/listcomp07.lc 2:18-2:20 () testdata/language-features/basic-list/listcomp07.lc 2:21-2:23 - () | List () + () | [()] testdata/language-features/basic-list/listcomp07.lc 3:16-3:17 _b | () testdata/language-features/basic-list/listcomp07.lc 3:20-3:22 @@ -52,17 +52,17 @@ testdata/language-features/basic-list/listcomp07.lc 5:16-5:17 testdata/language-features/basic-list/listcomp07.lc 5:20-5:21 () testdata/language-features/basic-list/listcomp07.lc 8:1-8:7 - List () + [()] testdata/language-features/basic-list/listcomp07.lc 8:10-12:11 - List () + [()] testdata/language-features/basic-list/listcomp07.lc 8:12-8:13 () testdata/language-features/basic-list/listcomp07.lc 8:21-8:28 - List () + [()] testdata/language-features/basic-list/listcomp07.lc 8:22-8:24 () testdata/language-features/basic-list/listcomp07.lc 8:25-8:27 - () | List () + () | [()] testdata/language-features/basic-list/listcomp07.lc 9:16-9:17 _b | () testdata/language-features/basic-list/listcomp07.lc 9:20-9:22 @@ -74,17 +74,17 @@ testdata/language-features/basic-list/listcomp07.lc 11:16-11:17 testdata/language-features/basic-list/listcomp07.lc 11:20-11:21 () testdata/language-features/basic-list/listcomp07.lc 14:1-14:7 - List () + [()] testdata/language-features/basic-list/listcomp07.lc 14:10-20:3 - List () + [()] testdata/language-features/basic-list/listcomp07.lc 14:12-14:13 () testdata/language-features/basic-list/listcomp07.lc 15:15-15:22 - List () + [()] testdata/language-features/basic-list/listcomp07.lc 15:16-15:18 () testdata/language-features/basic-list/listcomp07.lc 15:19-15:21 - () | List () + () | [()] testdata/language-features/basic-list/listcomp07.lc 17:2-17:3 _b | () testdata/language-features/basic-list/listcomp07.lc 17:6-17:8 diff --git a/testdata/language-features/basic-list/listcomp09.out b/testdata/language-features/basic-list/listcomp09.out index de34df2b..b9979154 100644 --- a/testdata/language-features/basic-list/listcomp09.out +++ b/testdata/language-features/basic-list/listcomp09.out @@ -3,15 +3,15 @@ value1 = _rhs (concatMap \_ -> (\(a :: _) -> hlistNilCase (_ :: _) "Hello" a) : [] []) main is not found ------------ trace -value1 :: Type => List (() -> String) +value1 :: Type => [() -> String] ------------ tooltips testdata/language-features/basic-list/listcomp09.lc 1:1-1:7 - Type => List (() -> String) + Type => [() -> String] testdata/language-features/basic-list/listcomp09.lc 1:10-1:36 - List (() -> String) + [() -> String] testdata/language-features/basic-list/listcomp09.lc 1:11-1:25 - List (() -> String) + [() -> String] testdata/language-features/basic-list/listcomp09.lc 1:18-1:25 String testdata/language-features/basic-list/listcomp09.lc 1:33-1:35 - forall a . List a \ No newline at end of file + forall a . [a] \ No newline at end of file diff --git a/testdata/language-features/basic-values/data01.out b/testdata/language-features/basic-values/data01.out index 7c8cf3d7..f1d99bf2 100644 --- a/testdata/language-features/basic-values/data01.out +++ b/testdata/language-features/basic-values/data01.out @@ -5,11 +5,11 @@ data A :: Type where D :: A data E :: Type where F :: E - G :: HList 'Nil -> E + G :: HList '[] -> E H :: E data D1 :: Type where C1 :: D1 - C2 :: HList 'Nil -> D1 + C2 :: HList '[] -> D1 C3 :: D1 main is not found ------------ trace diff --git a/testdata/language-features/basic-values/fixity02.out b/testdata/language-features/basic-values/fixity02.out index d38a6d55..f14d7e38 100644 --- a/testdata/language-features/basic-values/fixity02.out +++ b/testdata/language-features/basic-values/fixity02.out @@ -14,7 +14,7 @@ value4 = _rhs (HNil <@ 'c' <@ "hi" @> 1.2 :: Float) value5 = _rhs (HNil @> 'c' @> "hi" <@ 1.2 :: String) value6 = _rhs (HNil @> 'c' <@ "hi" <@ 1.2 :: Char) value7 = _rhs (HNil <@ 'c' @> "hi" <@ 1.2 :: String) -value8 = _rhs (HNil <@ 'c' <@ "hi" <@ 1.2 :: HList 'Nil) +value8 = _rhs (HNil <@ 'c' <@ "hi" <@ 1.2 :: HList '[]) funValue1 = _rhs (HNil `funR` 'c' `funR` "hi" `funR` 1.2 :: Float) funValue2 = _rhs (HNil `funR` 'c' `funL` "hi" `funR` 1.2 :: Float) funValue3 = _rhs (HNil `funL` 'c' `funR` "hi" `funR` 1.2 :: Float) @@ -22,7 +22,7 @@ funValue4 = _rhs (HNil `funL` 'c' `funL` "hi" `funR` 1.2 :: Float) funValue5 = _rhs (HNil `funR` 'c' `funR` "hi" `funL` 1.2 :: String) funValue6 = _rhs (HNil `funR` 'c' `funL` "hi" `funL` 1.2 :: Char) funValue7 = _rhs (HNil `funL` 'c' `funR` "hi" `funL` 1.2 :: String) -funValue8 = _rhs (HNil `funL` 'c' `funL` "hi" `funL` 1.2 :: HList 'Nil) +funValue8 = _rhs (HNil `funL` 'c' `funL` "hi" `funL` 1.2 :: HList '[]) main is not found ------------ trace funL :: forall a b . a -> b -> a diff --git a/testdata/language-features/basic-values/infix03.out b/testdata/language-features/basic-values/infix03.out index 6011a719..8c85e0c4 100644 --- a/testdata/language-features/basic-values/infix03.out +++ b/testdata/language-features/basic-values/infix03.out @@ -1,7 +1,7 @@ ------------ desugared source code data D :: Type where - D2 :: HList 'Nil -> HList 'Nil -> D - D3 :: HList 'Nil -> HList 'Nil -> HList 'Nil -> D + D2 :: HList '[] -> HList '[] -> D + D3 :: HList '[] -> HList '[] -> HList '[] -> D d2 = \(a :: _) (b :: _) -> _rhs (a `D2` b) d3 = \(a :: _) (b :: _) -> _rhs (a `D3` b) main is not found diff --git a/testdata/language-features/basic-values/typesig03.out b/testdata/language-features/basic-values/typesig03.out index acca5245..61adce6b 100644 --- a/testdata/language-features/basic-values/typesig03.out +++ b/testdata/language-features/basic-values/typesig03.out @@ -1,10 +1,10 @@ ------------ desugared source code fun1 = (\_ -> \_ -> \_ -> _rhs HNil) - :: forall (a :: _) (b :: _) (c :: _) . a -> b -> c -> HList 'Nil + :: forall (a :: _) (b :: _) (c :: _) . a -> b -> c -> HList '[] fun2 = (\_ -> \_ -> \_ -> _rhs HNil) - :: forall (a :: _) (b :: _) (c :: _) . a -> b -> c -> HList 'Nil + :: forall (a :: _) (b :: _) (c :: _) . a -> b -> c -> HList '[] main is not found ------------ trace fun1 :: forall a b c . a -> b -> c -> () diff --git a/testdata/language-features/basic-values/typesig04.out b/testdata/language-features/basic-values/typesig04.out index 9cae9eb3..d37e8d1b 100644 --- a/testdata/language-features/basic-values/typesig04.out +++ b/testdata/language-features/basic-values/typesig04.out @@ -1,10 +1,10 @@ ------------ desugared source code fun1 = (\_ -> \_ -> _rhs HNil) - :: forall (a :: _) (b :: _) (c :: _) . a -> (b -> c) -> HList 'Nil + :: forall (a :: _) (b :: _) (c :: _) . a -> (b -> c) -> HList '[] fun2 = (\_ -> \_ -> _rhs HNil) - :: forall (a :: _) (b :: _) (c :: _) . a -> (b -> c) -> HList 'Nil + :: forall (a :: _) (b :: _) (c :: _) . a -> (b -> c) -> HList '[] main is not found ------------ trace fun1 :: forall a b c . a -> (b -> c) -> () diff --git a/testdata/language-features/basic-values/typesig07.out b/testdata/language-features/basic-values/typesig07.out index 8d454af6..f45f79f2 100644 --- a/testdata/language-features/basic-values/typesig07.out +++ b/testdata/language-features/basic-values/typesig07.out @@ -2,9 +2,9 @@ value1 = _rhs (fromInt 1) :: Int value2 = _rhs (fromInt 2) :: Int value3 = _rhs (fromInt 3) :: Int -value4 = (\_ -> \_ -> _rhs HNil) :: HList 'Nil -> HList 'Nil -> HList 'Nil -@@@ = (\_ -> \_ -> _rhs HNil) :: HList 'Nil -> HList 'Nil -> HList 'Nil -value6 = (\_ -> \_ -> _rhs HNil) :: HList 'Nil -> HList 'Nil -> HList 'Nil +value4 = (\_ -> \_ -> _rhs HNil) :: HList '[] -> HList '[] -> HList '[] +@@@ = (\_ -> \_ -> _rhs HNil) :: HList '[] -> HList '[] -> HList '[] +value6 = (\_ -> \_ -> _rhs HNil) :: HList '[] -> HList '[] -> HList '[] main is not found ------------ trace value1 :: Int diff --git a/testdata/language-features/pattern/uncovered.out b/testdata/language-features/pattern/uncovered.out index 98526e80..9cf9ef79 100644 --- a/testdata/language-features/pattern/uncovered.out +++ b/testdata/language-features/pattern/uncovered.out @@ -76,8 +76,8 @@ h main is not found ------------ trace f :: forall a . Num a => Bool -> Bool -> Bool -> a -g :: List Bool -> Bool -h :: List (List Bool) -> Bool +g :: [Bool] -> Bool +h :: [[Bool]] -> Bool ------------ tooltips testdata/language-features/pattern/uncovered.lc 2:1-2:2 forall a . Num a => Bool -> Bool -> Bool -> a @@ -94,11 +94,11 @@ testdata/language-features/pattern/uncovered.lc 3:18-4:19 testdata/language-features/pattern/uncovered.lc 4:18-4:19 _b testdata/language-features/pattern/uncovered.lc 6:1-6:2 - List Bool -> Bool + [Bool] -> Bool testdata/language-features/pattern/uncovered.lc 6:25-6:30 Bool | Bool | Bool | Bool | Bool | Bool | Bool testdata/language-features/pattern/uncovered.lc 8:1-8:2 - List (List Bool) -> Bool + [[Bool]] -> Bool testdata/language-features/pattern/uncovered.lc 8:23-8:27 Bool | Bool | Bool | Bool | Bool | Bool | Bool | Bool | Bool ------------ warnings diff --git a/testdata/performance/Material.out b/testdata/performance/Material.out index e6d7df8b..604cf0fd 100644 --- a/testdata/performance/Material.out +++ b/testdata/performance/Material.out @@ -93,7 +93,7 @@ data TCMod :: Type where data StageTexture :: Type where ST_Map :: String -> StageTexture ST_ClampMap :: String -> StageTexture - ST_AnimMap :: Float -> List String -> StageTexture + ST_AnimMap :: Float -> [String] -> StageTexture ST_Lightmap :: StageTexture ST_WhiteImage :: StageTexture data AlphaFunction :: Type where @@ -105,11 +105,11 @@ data DepthFunction :: Type where D_Lequal :: DepthFunction data StageAttrs :: Type where StageAttrs - :: Maybe (HList (Blending' : Blending' : 'Nil)) + :: Maybe (HList (Blending' : Blending' : '[])) -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs saBlend @@ -184,14 +184,13 @@ defaultStageAttrs :: StageAttrs data CommonAttrs :: Type where CommonAttrs - :: HList 'Nil - -> HList 'Nil + :: HList '[] + -> HList '[] -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs caSkyParms = \(a :: _) -> 'CommonAttrsCase \_ -> _ :: _ @@ -478,14 +477,14 @@ match'TCMod :: forall (a :: Type -> Type) -> a TCMod -> forall b -> a b -> a b 'StageTexture :: Type ST_Map :: String -> StageTexture ST_ClampMap :: String -> StageTexture -ST_AnimMap :: Float -> List String -> StageTexture +ST_AnimMap :: Float -> [String] -> StageTexture ST_Lightmap :: StageTexture ST_WhiteImage :: StageTexture 'StageTextureCase :: forall (a :: StageTexture -> Type) -> (forall (b :: String) -> a ('ST_Map b)) -> (forall (c :: String) -> a ('ST_ClampMap c)) - -> (forall (d :: Float) (e :: List String) -> a ('ST_AnimMap d e)) + -> (forall (d :: Float) (e :: [String]) -> a ('ST_AnimMap d e)) -> a 'ST_Lightmap -> a 'ST_WhiteImage -> forall (f :: StageTexture) -> a f match'StageTexture :: forall (a :: Type -> Type) -> a StageTexture -> forall b -> a b -> a b @@ -512,7 +511,7 @@ StageAttrs -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs 'StageAttrsCase @@ -521,7 +520,7 @@ StageAttrs (c :: RGBGen) (d :: AlphaGen) (e :: TCGen) - (f :: List TCMod) + (f :: [TCMod]) (g :: StageTexture) (h :: Bool) (i :: DepthFunction) (j :: Maybe AlphaFunction) (k :: Bool) (l :: String) @@ -533,7 +532,7 @@ saBlend :: StageAttrs -> Maybe (Blending', Blending') saRGBGen :: StageAttrs -> RGBGen saAlphaGen :: StageAttrs -> AlphaGen saTCGen :: StageAttrs -> TCGen -saTCMod :: StageAttrs -> List TCMod +saTCMod :: StageAttrs -> [TCMod] saTexture :: StageAttrs -> StageTexture saDepthWrite :: StageAttrs -> Bool saDepthFunc :: StageAttrs -> DepthFunction @@ -549,8 +548,7 @@ CommonAttrs -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs 'CommonAttrsCase :: forall (a :: CommonAttrs -> Type) -> (forall (b :: ()) @@ -560,7 +558,7 @@ CommonAttrs (f :: Bool) (g :: Bool) (h :: CullType) - (i :: List Deform) (j :: Bool) (k :: Bool) (l :: List StageAttrs) (m :: Bool) + (i :: [Deform]) (j :: Bool) (k :: Bool) (l :: [StageAttrs]) (m :: Bool) -> a ('CommonAttrs b c d e f g h i j k l m)) -> forall (n :: CommonAttrs) -> a n match'CommonAttrs @@ -572,10 +570,10 @@ caSort :: CommonAttrs -> Float caEntityMergable :: CommonAttrs -> Bool caFogOnly :: CommonAttrs -> Bool caCull :: CommonAttrs -> CullType -caDeformVertexes :: CommonAttrs -> List Deform +caDeformVertexes :: CommonAttrs -> [Deform] caNoMipMaps :: CommonAttrs -> Bool caPolygonOffset :: CommonAttrs -> Bool -caStages :: CommonAttrs -> List StageAttrs +caStages :: CommonAttrs -> [StageAttrs] caIsSky :: CommonAttrs -> Bool defaultCommonAttrs :: CommonAttrs ------------ tooltips @@ -962,7 +960,7 @@ testdata/performance/Material.lc 113:7-113:18 testdata/performance/Material.lc 113:21-113:27 Type testdata/performance/Material.lc 114:7-114:17 - Float -> List String -> StageTexture | StageTexture | Type | Type | Type + Float -> [String] -> StageTexture | StageTexture | Type | Type | Type testdata/performance/Material.lc 114:21-114:26 Type testdata/performance/Material.lc 114:27-114:35 @@ -1002,7 +1000,7 @@ testdata/performance/Material.lc 131:7-131:17 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction @@ -1021,9 +1019,9 @@ testdata/performance/Material.lc 132:31-132:53 testdata/performance/Material.lc 132:32-132:41 Type testdata/performance/Material.lc 132:32-132:52 - List Type + [Type] testdata/performance/Material.lc 132:43-132:52 - Type | List Type + Type | [Type] testdata/performance/Material.lc 133:7-133:15 StageAttrs -> RGBGen testdata/performance/Material.lc 133:24-133:30 @@ -1037,7 +1035,7 @@ testdata/performance/Material.lc 135:7-135:14 testdata/performance/Material.lc 135:24-135:29 Type testdata/performance/Material.lc 136:7-136:14 - StageAttrs -> List TCMod + StageAttrs -> [TCMod] testdata/performance/Material.lc 136:24-136:31 Type testdata/performance/Material.lc 136:25-136:30 @@ -1079,29 +1077,29 @@ testdata/performance/Material.lc 149:21-149:31 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/Material.lc 149:21-150:30 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/Material.lc 149:21-151:36 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/Material.lc 149:21-152:33 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/Material.lc 149:21-153:35 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/Material.lc 149:21-154:25 @@ -1128,7 +1126,7 @@ testdata/performance/Material.lc 152:23-152:33 testdata/performance/Material.lc 153:23-153:35 TCGen testdata/performance/Material.lc 154:23-154:25 - forall a . List a + forall a . [a] testdata/performance/Material.lc 155:23-155:36 StageTexture testdata/performance/Material.lc 156:23-156:27 @@ -1155,10 +1153,10 @@ testdata/performance/Material.lc 164:7-164:18 -> Bool -> Bool -> CullType - -> List Deform + -> [Deform] -> Bool -> Bool - -> List StageAttrs + -> [StageAttrs] -> Bool -> CommonAttrs | CommonAttrs | Type | Type | Type | Type | Type | Type | Type | Type | Type | Type | Type | Type | Type testdata/performance/Material.lc 165:7-165:17 @@ -1190,7 +1188,7 @@ testdata/performance/Material.lc 171:7-171:13 testdata/performance/Material.lc 171:28-171:36 Type testdata/performance/Material.lc 172:7-172:23 - CommonAttrs -> List Deform + CommonAttrs -> [Deform] testdata/performance/Material.lc 172:28-172:36 Type testdata/performance/Material.lc 172:29-172:35 @@ -1204,7 +1202,7 @@ testdata/performance/Material.lc 174:7-174:22 testdata/performance/Material.lc 174:28-174:32 Type testdata/performance/Material.lc 175:7-175:15 - CommonAttrs -> List StageAttrs + CommonAttrs -> [StageAttrs] testdata/performance/Material.lc 175:28-175:40 Type testdata/performance/Material.lc 175:29-175:39 @@ -1224,49 +1222,42 @@ testdata/performance/Material.lc 183:22-183:33 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/Material.lc 183:22-184:29 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/Material.lc 183:22-185:29 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/Material.lc 183:22-186:32 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/Material.lc 183:22-187:28 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/Material.lc 183:22-188:32 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/Material.lc 183:22-189:32 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/Material.lc 183:22-190:40 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/Material.lc 183:22-191:29 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/Material.lc 183:22-192:32 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/Material.lc 183:22-193:32 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/Material.lc 183:22-194:29 Bool -> CommonAttrs testdata/performance/Material.lc 183:22-196:6 @@ -1286,12 +1277,12 @@ testdata/performance/Material.lc 189:27-189:32 testdata/performance/Material.lc 190:27-190:40 CullType testdata/performance/Material.lc 191:27-191:29 - forall a . List a + forall a . [a] testdata/performance/Material.lc 192:27-192:32 Bool testdata/performance/Material.lc 193:27-193:32 Bool testdata/performance/Material.lc 194:27-194:29 - forall a . List a + forall a . [a] testdata/performance/Material.lc 195:27-195:32 Bool \ No newline at end of file diff --git a/testdata/performance/SampleMaterial.out b/testdata/performance/SampleMaterial.out index 43d83545..95b4da4a 100644 --- a/testdata/performance/SampleMaterial.out +++ b/testdata/performance/SampleMaterial.out @@ -2078,12 +2078,12 @@ sampleMaterial : []) main is not found ------------ trace -sampleMaterial :: List (String, CommonAttrs) +sampleMaterial :: [(String, CommonAttrs)] ------------ tooltips testdata/performance/SampleMaterial.lc 3:1-3:15 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 4:3-2183:4 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 4:5-46:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 4:7-4:40 @@ -2095,49 +2095,42 @@ testdata/performance/SampleMaterial.lc 5:7-5:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 5:7-6:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 5:7-7:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 5:7-8:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 5:7-9:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 5:7-10:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 5:7-11:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 5:7-12:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 5:7-13:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 5:7-14:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 5:7-15:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 5:7-43:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 5:7-45:10 @@ -2157,41 +2150,41 @@ testdata/performance/SampleMaterial.lc 11:23-11:28 testdata/performance/SampleMaterial.lc 12:20-12:33 CullType testdata/performance/SampleMaterial.lc 13:30-13:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 14:25-14:30 Bool testdata/performance/SampleMaterial.lc 15:29-15:34 Bool testdata/performance/SampleMaterial.lc 17:13-43:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 17:15-17:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 17:15-18:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 17:15-19:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 17:15-20:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 17:15-21:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 17:15-22:31 @@ -2218,7 +2211,7 @@ testdata/performance/SampleMaterial.lc 20:32-20:42 testdata/performance/SampleMaterial.lc 21:29-21:36 TCGen testdata/performance/SampleMaterial.lc 22:29-22:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 23:31-23:37 String -> StageTexture testdata/performance/SampleMaterial.lc 23:31-23:71 @@ -2240,29 +2233,29 @@ testdata/performance/SampleMaterial.lc 30:15-30:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 30:15-31:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 30:15-32:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 30:15-33:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 30:15-34:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 30:15-35:31 @@ -2279,7 +2272,7 @@ testdata/performance/SampleMaterial.lc 30:15-39:40 testdata/performance/SampleMaterial.lc 30:15-40:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 30:15-42:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 31:29-31:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 31:29-31:57 @@ -2297,7 +2290,7 @@ testdata/performance/SampleMaterial.lc 33:32-33:42 testdata/performance/SampleMaterial.lc 34:29-34:40 TCGen testdata/performance/SampleMaterial.lc 35:29-35:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 36:31-36:42 StageTexture testdata/performance/SampleMaterial.lc 37:34-37:38 @@ -2315,7 +2308,7 @@ testdata/performance/SampleMaterial.lc 44:21-44:26 testdata/performance/SampleMaterial.lc 47:5-89:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 47:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 47:7-47:39 String testdata/performance/SampleMaterial.lc 48:7-48:18 @@ -2325,49 +2318,42 @@ testdata/performance/SampleMaterial.lc 48:7-48:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 48:7-49:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 48:7-50:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 48:7-51:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 48:7-52:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 48:7-53:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 48:7-54:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 48:7-55:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 48:7-56:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 48:7-57:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 48:7-58:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 48:7-86:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 48:7-88:10 @@ -2387,41 +2373,41 @@ testdata/performance/SampleMaterial.lc 54:23-54:28 testdata/performance/SampleMaterial.lc 55:20-55:33 CullType testdata/performance/SampleMaterial.lc 56:30-56:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 57:25-57:30 Bool testdata/performance/SampleMaterial.lc 58:29-58:34 Bool testdata/performance/SampleMaterial.lc 60:13-86:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 60:15-60:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 60:15-61:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 60:15-62:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 60:15-63:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 60:15-64:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 60:15-65:31 @@ -2448,7 +2434,7 @@ testdata/performance/SampleMaterial.lc 63:32-63:42 testdata/performance/SampleMaterial.lc 64:29-64:36 TCGen testdata/performance/SampleMaterial.lc 65:29-65:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 66:31-66:37 String -> StageTexture testdata/performance/SampleMaterial.lc 66:31-66:70 @@ -2470,29 +2456,29 @@ testdata/performance/SampleMaterial.lc 73:15-73:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 73:15-74:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 73:15-75:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 73:15-76:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 73:15-77:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 73:15-78:31 @@ -2509,7 +2495,7 @@ testdata/performance/SampleMaterial.lc 73:15-82:40 testdata/performance/SampleMaterial.lc 73:15-83:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 73:15-85:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 74:29-74:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 74:29-74:57 @@ -2527,7 +2513,7 @@ testdata/performance/SampleMaterial.lc 76:32-76:42 testdata/performance/SampleMaterial.lc 77:29-77:40 TCGen testdata/performance/SampleMaterial.lc 78:29-78:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 79:31-79:42 StageTexture testdata/performance/SampleMaterial.lc 80:34-80:38 @@ -2545,7 +2531,7 @@ testdata/performance/SampleMaterial.lc 87:21-87:26 testdata/performance/SampleMaterial.lc 90:5-132:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 90:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 90:7-90:40 String testdata/performance/SampleMaterial.lc 91:7-91:18 @@ -2555,49 +2541,42 @@ testdata/performance/SampleMaterial.lc 91:7-91:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 91:7-92:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 91:7-93:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 91:7-94:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 91:7-95:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 91:7-96:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 91:7-97:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 91:7-98:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 91:7-99:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 91:7-100:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 91:7-101:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 91:7-129:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 91:7-131:10 @@ -2617,41 +2596,41 @@ testdata/performance/SampleMaterial.lc 97:23-97:28 testdata/performance/SampleMaterial.lc 98:20-98:33 CullType testdata/performance/SampleMaterial.lc 99:30-99:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 100:25-100:30 Bool testdata/performance/SampleMaterial.lc 101:29-101:34 Bool testdata/performance/SampleMaterial.lc 103:13-129:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 103:15-103:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 103:15-104:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 103:15-105:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 103:15-106:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 103:15-107:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 103:15-108:31 @@ -2678,7 +2657,7 @@ testdata/performance/SampleMaterial.lc 106:32-106:42 testdata/performance/SampleMaterial.lc 107:29-107:36 TCGen testdata/performance/SampleMaterial.lc 108:29-108:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 109:31-109:37 String -> StageTexture testdata/performance/SampleMaterial.lc 109:31-109:71 @@ -2700,29 +2679,29 @@ testdata/performance/SampleMaterial.lc 116:15-116:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 116:15-117:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 116:15-118:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 116:15-119:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 116:15-120:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 116:15-121:31 @@ -2739,7 +2718,7 @@ testdata/performance/SampleMaterial.lc 116:15-125:40 testdata/performance/SampleMaterial.lc 116:15-126:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 116:15-128:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 117:29-117:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 117:29-117:57 @@ -2757,7 +2736,7 @@ testdata/performance/SampleMaterial.lc 119:32-119:42 testdata/performance/SampleMaterial.lc 120:29-120:40 TCGen testdata/performance/SampleMaterial.lc 121:29-121:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 122:31-122:42 StageTexture testdata/performance/SampleMaterial.lc 123:34-123:38 @@ -2775,7 +2754,7 @@ testdata/performance/SampleMaterial.lc 130:21-130:26 testdata/performance/SampleMaterial.lc 133:5-175:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 133:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 133:7-133:42 String testdata/performance/SampleMaterial.lc 134:7-134:18 @@ -2785,49 +2764,42 @@ testdata/performance/SampleMaterial.lc 134:7-134:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 134:7-135:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 134:7-136:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 134:7-137:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 134:7-138:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 134:7-139:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 134:7-140:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 134:7-141:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 134:7-142:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 134:7-143:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 134:7-144:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 134:7-172:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 134:7-174:10 @@ -2847,41 +2819,41 @@ testdata/performance/SampleMaterial.lc 140:23-140:28 testdata/performance/SampleMaterial.lc 141:20-141:33 CullType testdata/performance/SampleMaterial.lc 142:30-142:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 143:25-143:30 Bool testdata/performance/SampleMaterial.lc 144:29-144:34 Bool testdata/performance/SampleMaterial.lc 146:13-172:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 146:15-146:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 146:15-147:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 146:15-148:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 146:15-149:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 146:15-150:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 146:15-151:31 @@ -2908,7 +2880,7 @@ testdata/performance/SampleMaterial.lc 149:32-149:42 testdata/performance/SampleMaterial.lc 150:29-150:36 TCGen testdata/performance/SampleMaterial.lc 151:29-151:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 152:31-152:37 String -> StageTexture testdata/performance/SampleMaterial.lc 152:31-152:73 @@ -2930,29 +2902,29 @@ testdata/performance/SampleMaterial.lc 159:15-159:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 159:15-160:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 159:15-161:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 159:15-162:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 159:15-163:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 159:15-164:31 @@ -2969,7 +2941,7 @@ testdata/performance/SampleMaterial.lc 159:15-168:40 testdata/performance/SampleMaterial.lc 159:15-169:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 159:15-171:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 160:29-160:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 160:29-160:57 @@ -2987,7 +2959,7 @@ testdata/performance/SampleMaterial.lc 162:32-162:42 testdata/performance/SampleMaterial.lc 163:29-163:40 TCGen testdata/performance/SampleMaterial.lc 164:29-164:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 165:31-165:42 StageTexture testdata/performance/SampleMaterial.lc 166:34-166:38 @@ -3005,7 +2977,7 @@ testdata/performance/SampleMaterial.lc 173:21-173:26 testdata/performance/SampleMaterial.lc 176:5-232:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 176:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 176:7-176:46 String testdata/performance/SampleMaterial.lc 177:7-177:18 @@ -3015,49 +2987,42 @@ testdata/performance/SampleMaterial.lc 177:7-177:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 177:7-178:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 177:7-179:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 177:7-180:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 177:7-181:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 177:7-182:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 177:7-183:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 177:7-184:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 177:7-185:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 177:7-186:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 177:7-187:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 177:7-229:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 177:7-231:10 @@ -3077,41 +3042,41 @@ testdata/performance/SampleMaterial.lc 183:23-183:28 testdata/performance/SampleMaterial.lc 184:20-184:33 CullType testdata/performance/SampleMaterial.lc 185:30-185:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 186:25-186:30 Bool testdata/performance/SampleMaterial.lc 187:29-187:34 Bool testdata/performance/SampleMaterial.lc 189:13-229:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 189:15-189:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 189:15-190:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 189:15-191:42 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 189:15-192:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 189:15-193:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 189:15-195:88 @@ -3138,7 +3103,7 @@ testdata/performance/SampleMaterial.lc 192:32-192:42 testdata/performance/SampleMaterial.lc 193:29-193:36 TCGen testdata/performance/SampleMaterial.lc 195:21-195:88 - List TCMod + [TCMod] testdata/performance/SampleMaterial.lc 195:23-195:32 Float -> Float -> TCMod testdata/performance/SampleMaterial.lc 195:23-195:36 @@ -3160,7 +3125,7 @@ testdata/performance/SampleMaterial.lc 195:43-195:63 testdata/performance/SampleMaterial.lc 195:43-195:67 TCMod testdata/performance/SampleMaterial.lc 195:43-195:86 - List TCMod + [TCMod] testdata/performance/SampleMaterial.lc 195:51-195:54 Float testdata/performance/SampleMaterial.lc 195:55-195:59 @@ -3174,7 +3139,7 @@ testdata/performance/SampleMaterial.lc 195:70-195:78 testdata/performance/SampleMaterial.lc 195:70-195:82 Float -> TCMod testdata/performance/SampleMaterial.lc 195:70-195:86 - TCMod | List TCMod + TCMod | [TCMod] testdata/performance/SampleMaterial.lc 195:79-195:82 Float testdata/performance/SampleMaterial.lc 195:83-195:86 @@ -3200,29 +3165,29 @@ testdata/performance/SampleMaterial.lc 203:15-203:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 203:15-204:69 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 203:15-205:42 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 203:15-206:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 203:15-207:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 203:15-208:31 @@ -3241,7 +3206,7 @@ testdata/performance/SampleMaterial.lc 203:15-213:46 testdata/performance/SampleMaterial.lc 203:15-215:18 StageAttrs testdata/performance/SampleMaterial.lc 203:15-228:18 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 204:29-204:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 204:29-204:69 @@ -3259,7 +3224,7 @@ testdata/performance/SampleMaterial.lc 206:32-206:42 testdata/performance/SampleMaterial.lc 207:29-207:36 TCGen testdata/performance/SampleMaterial.lc 208:29-208:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 209:31-209:37 String -> StageTexture testdata/performance/SampleMaterial.lc 209:31-209:81 @@ -3281,29 +3246,29 @@ testdata/performance/SampleMaterial.lc 216:15-216:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 216:15-217:69 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 216:15-218:42 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 216:15-219:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 216:15-220:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 216:15-221:31 @@ -3320,7 +3285,7 @@ testdata/performance/SampleMaterial.lc 216:15-225:40 testdata/performance/SampleMaterial.lc 216:15-226:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 216:15-228:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 217:29-217:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 217:29-217:69 @@ -3338,7 +3303,7 @@ testdata/performance/SampleMaterial.lc 219:32-219:42 testdata/performance/SampleMaterial.lc 220:29-220:40 TCGen testdata/performance/SampleMaterial.lc 221:29-221:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 222:31-222:42 StageTexture testdata/performance/SampleMaterial.lc 223:34-223:39 @@ -3356,7 +3321,7 @@ testdata/performance/SampleMaterial.lc 230:21-230:26 testdata/performance/SampleMaterial.lc 233:5-275:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 233:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 233:7-233:40 String testdata/performance/SampleMaterial.lc 234:7-234:18 @@ -3366,49 +3331,42 @@ testdata/performance/SampleMaterial.lc 234:7-234:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 234:7-235:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 234:7-236:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 234:7-237:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 234:7-238:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 234:7-239:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 234:7-240:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 234:7-241:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 234:7-242:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 234:7-243:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 234:7-244:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 234:7-272:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 234:7-274:10 @@ -3428,41 +3386,41 @@ testdata/performance/SampleMaterial.lc 240:23-240:28 testdata/performance/SampleMaterial.lc 241:20-241:33 CullType testdata/performance/SampleMaterial.lc 242:30-242:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 243:25-243:30 Bool testdata/performance/SampleMaterial.lc 244:29-244:34 Bool testdata/performance/SampleMaterial.lc 246:13-272:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 246:15-246:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 246:15-247:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 246:15-248:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 246:15-249:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 246:15-250:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 246:15-251:31 @@ -3489,7 +3447,7 @@ testdata/performance/SampleMaterial.lc 249:32-249:42 testdata/performance/SampleMaterial.lc 250:29-250:36 TCGen testdata/performance/SampleMaterial.lc 251:29-251:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 252:31-252:37 String -> StageTexture testdata/performance/SampleMaterial.lc 252:31-252:71 @@ -3511,29 +3469,29 @@ testdata/performance/SampleMaterial.lc 259:15-259:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 259:15-260:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 259:15-261:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 259:15-262:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 259:15-263:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 259:15-264:31 @@ -3550,7 +3508,7 @@ testdata/performance/SampleMaterial.lc 259:15-268:40 testdata/performance/SampleMaterial.lc 259:15-269:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 259:15-271:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 260:29-260:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 260:29-260:57 @@ -3568,7 +3526,7 @@ testdata/performance/SampleMaterial.lc 262:32-262:42 testdata/performance/SampleMaterial.lc 263:29-263:40 TCGen testdata/performance/SampleMaterial.lc 264:29-264:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 265:31-265:42 StageTexture testdata/performance/SampleMaterial.lc 266:34-266:38 @@ -3586,7 +3544,7 @@ testdata/performance/SampleMaterial.lc 273:21-273:26 testdata/performance/SampleMaterial.lc 276:5-318:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 276:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 276:7-276:42 String testdata/performance/SampleMaterial.lc 277:7-277:18 @@ -3596,49 +3554,42 @@ testdata/performance/SampleMaterial.lc 277:7-277:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 277:7-278:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 277:7-279:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 277:7-280:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 277:7-281:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 277:7-282:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 277:7-283:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 277:7-284:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 277:7-285:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 277:7-286:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 277:7-287:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 277:7-315:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 277:7-317:10 @@ -3658,41 +3609,41 @@ testdata/performance/SampleMaterial.lc 283:23-283:28 testdata/performance/SampleMaterial.lc 284:20-284:33 CullType testdata/performance/SampleMaterial.lc 285:30-285:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 286:25-286:30 Bool testdata/performance/SampleMaterial.lc 287:29-287:34 Bool testdata/performance/SampleMaterial.lc 289:13-315:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 289:15-289:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 289:15-290:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 289:15-291:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 289:15-292:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 289:15-293:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 289:15-294:31 @@ -3719,7 +3670,7 @@ testdata/performance/SampleMaterial.lc 292:32-292:42 testdata/performance/SampleMaterial.lc 293:29-293:36 TCGen testdata/performance/SampleMaterial.lc 294:29-294:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 295:31-295:37 String -> StageTexture testdata/performance/SampleMaterial.lc 295:31-295:73 @@ -3741,29 +3692,29 @@ testdata/performance/SampleMaterial.lc 302:15-302:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 302:15-303:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 302:15-304:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 302:15-305:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 302:15-306:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 302:15-307:31 @@ -3780,7 +3731,7 @@ testdata/performance/SampleMaterial.lc 302:15-311:40 testdata/performance/SampleMaterial.lc 302:15-312:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 302:15-314:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 303:29-303:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 303:29-303:57 @@ -3798,7 +3749,7 @@ testdata/performance/SampleMaterial.lc 305:32-305:42 testdata/performance/SampleMaterial.lc 306:29-306:40 TCGen testdata/performance/SampleMaterial.lc 307:29-307:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 308:31-308:42 StageTexture testdata/performance/SampleMaterial.lc 309:34-309:38 @@ -3816,7 +3767,7 @@ testdata/performance/SampleMaterial.lc 316:21-316:26 testdata/performance/SampleMaterial.lc 319:5-361:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 319:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 319:7-319:43 String testdata/performance/SampleMaterial.lc 320:7-320:18 @@ -3826,49 +3777,42 @@ testdata/performance/SampleMaterial.lc 320:7-320:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 320:7-321:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 320:7-322:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 320:7-323:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 320:7-324:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 320:7-325:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 320:7-326:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 320:7-327:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 320:7-328:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 320:7-329:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 320:7-330:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 320:7-358:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 320:7-360:10 @@ -3888,41 +3832,41 @@ testdata/performance/SampleMaterial.lc 326:23-326:28 testdata/performance/SampleMaterial.lc 327:20-327:33 CullType testdata/performance/SampleMaterial.lc 328:30-328:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 329:25-329:30 Bool testdata/performance/SampleMaterial.lc 330:29-330:34 Bool testdata/performance/SampleMaterial.lc 332:13-358:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 332:15-332:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 332:15-333:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 332:15-334:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 332:15-335:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 332:15-336:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 332:15-337:31 @@ -3949,7 +3893,7 @@ testdata/performance/SampleMaterial.lc 335:32-335:42 testdata/performance/SampleMaterial.lc 336:29-336:36 TCGen testdata/performance/SampleMaterial.lc 337:29-337:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 338:31-338:37 String -> StageTexture testdata/performance/SampleMaterial.lc 338:31-338:74 @@ -3971,29 +3915,29 @@ testdata/performance/SampleMaterial.lc 345:15-345:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 345:15-346:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 345:15-347:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 345:15-348:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 345:15-349:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 345:15-350:31 @@ -4010,7 +3954,7 @@ testdata/performance/SampleMaterial.lc 345:15-354:40 testdata/performance/SampleMaterial.lc 345:15-355:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 345:15-357:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 346:29-346:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 346:29-346:57 @@ -4028,7 +3972,7 @@ testdata/performance/SampleMaterial.lc 348:32-348:42 testdata/performance/SampleMaterial.lc 349:29-349:40 TCGen testdata/performance/SampleMaterial.lc 350:29-350:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 351:31-351:42 StageTexture testdata/performance/SampleMaterial.lc 352:34-352:38 @@ -4046,7 +3990,7 @@ testdata/performance/SampleMaterial.lc 359:21-359:26 testdata/performance/SampleMaterial.lc 362:5-404:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 362:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 362:7-362:53 String testdata/performance/SampleMaterial.lc 363:7-363:18 @@ -4056,49 +4000,42 @@ testdata/performance/SampleMaterial.lc 363:7-363:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 363:7-364:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 363:7-365:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 363:7-366:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 363:7-367:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 363:7-368:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 363:7-369:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 363:7-370:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 363:7-371:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 363:7-372:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 363:7-373:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 363:7-401:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 363:7-403:10 @@ -4118,41 +4055,41 @@ testdata/performance/SampleMaterial.lc 369:23-369:28 testdata/performance/SampleMaterial.lc 370:20-370:33 CullType testdata/performance/SampleMaterial.lc 371:30-371:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 372:25-372:30 Bool testdata/performance/SampleMaterial.lc 373:29-373:34 Bool testdata/performance/SampleMaterial.lc 375:13-401:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 375:15-375:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 375:15-376:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 375:15-377:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 375:15-378:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 375:15-379:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 375:15-380:31 @@ -4179,7 +4116,7 @@ testdata/performance/SampleMaterial.lc 378:32-378:42 testdata/performance/SampleMaterial.lc 379:29-379:36 TCGen testdata/performance/SampleMaterial.lc 380:29-380:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 381:31-381:37 String -> StageTexture testdata/performance/SampleMaterial.lc 381:31-381:84 @@ -4201,29 +4138,29 @@ testdata/performance/SampleMaterial.lc 388:15-388:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 388:15-389:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 388:15-390:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 388:15-391:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 388:15-392:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 388:15-393:31 @@ -4240,7 +4177,7 @@ testdata/performance/SampleMaterial.lc 388:15-397:40 testdata/performance/SampleMaterial.lc 388:15-398:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 388:15-400:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 389:29-389:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 389:29-389:57 @@ -4258,7 +4195,7 @@ testdata/performance/SampleMaterial.lc 391:32-391:42 testdata/performance/SampleMaterial.lc 392:29-392:40 TCGen testdata/performance/SampleMaterial.lc 393:29-393:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 394:31-394:42 StageTexture testdata/performance/SampleMaterial.lc 395:34-395:38 @@ -4276,7 +4213,7 @@ testdata/performance/SampleMaterial.lc 402:21-402:26 testdata/performance/SampleMaterial.lc 405:5-447:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 405:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 405:7-405:53 String testdata/performance/SampleMaterial.lc 406:7-406:18 @@ -4286,49 +4223,42 @@ testdata/performance/SampleMaterial.lc 406:7-406:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 406:7-407:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 406:7-408:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 406:7-409:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 406:7-410:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 406:7-411:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 406:7-412:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 406:7-413:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 406:7-414:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 406:7-415:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 406:7-416:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 406:7-444:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 406:7-446:10 @@ -4348,41 +4278,41 @@ testdata/performance/SampleMaterial.lc 412:23-412:28 testdata/performance/SampleMaterial.lc 413:20-413:33 CullType testdata/performance/SampleMaterial.lc 414:30-414:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 415:25-415:30 Bool testdata/performance/SampleMaterial.lc 416:29-416:34 Bool testdata/performance/SampleMaterial.lc 418:13-444:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 418:15-418:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 418:15-419:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 418:15-420:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 418:15-421:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 418:15-422:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 418:15-423:31 @@ -4409,7 +4339,7 @@ testdata/performance/SampleMaterial.lc 421:32-421:42 testdata/performance/SampleMaterial.lc 422:29-422:36 TCGen testdata/performance/SampleMaterial.lc 423:29-423:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 424:31-424:37 String -> StageTexture testdata/performance/SampleMaterial.lc 424:31-424:84 @@ -4431,29 +4361,29 @@ testdata/performance/SampleMaterial.lc 431:15-431:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 431:15-432:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 431:15-433:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 431:15-434:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 431:15-435:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 431:15-436:31 @@ -4470,7 +4400,7 @@ testdata/performance/SampleMaterial.lc 431:15-440:40 testdata/performance/SampleMaterial.lc 431:15-441:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 431:15-443:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 432:29-432:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 432:29-432:57 @@ -4488,7 +4418,7 @@ testdata/performance/SampleMaterial.lc 434:32-434:42 testdata/performance/SampleMaterial.lc 435:29-435:40 TCGen testdata/performance/SampleMaterial.lc 436:29-436:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 437:31-437:42 StageTexture testdata/performance/SampleMaterial.lc 438:34-438:38 @@ -4506,7 +4436,7 @@ testdata/performance/SampleMaterial.lc 445:21-445:26 testdata/performance/SampleMaterial.lc 448:5-490:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 448:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 448:7-448:53 String testdata/performance/SampleMaterial.lc 449:7-449:18 @@ -4516,49 +4446,42 @@ testdata/performance/SampleMaterial.lc 449:7-449:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 449:7-450:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 449:7-451:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 449:7-452:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 449:7-453:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 449:7-454:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 449:7-455:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 449:7-456:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 449:7-457:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 449:7-458:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 449:7-459:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 449:7-487:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 449:7-489:10 @@ -4578,41 +4501,41 @@ testdata/performance/SampleMaterial.lc 455:23-455:28 testdata/performance/SampleMaterial.lc 456:20-456:33 CullType testdata/performance/SampleMaterial.lc 457:30-457:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 458:25-458:30 Bool testdata/performance/SampleMaterial.lc 459:29-459:34 Bool testdata/performance/SampleMaterial.lc 461:13-487:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 461:15-461:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 461:15-462:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 461:15-463:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 461:15-464:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 461:15-465:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 461:15-466:31 @@ -4639,7 +4562,7 @@ testdata/performance/SampleMaterial.lc 464:32-464:42 testdata/performance/SampleMaterial.lc 465:29-465:36 TCGen testdata/performance/SampleMaterial.lc 466:29-466:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 467:31-467:37 String -> StageTexture testdata/performance/SampleMaterial.lc 467:31-467:84 @@ -4661,29 +4584,29 @@ testdata/performance/SampleMaterial.lc 474:15-474:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 474:15-475:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 474:15-476:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 474:15-477:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 474:15-478:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 474:15-479:31 @@ -4700,7 +4623,7 @@ testdata/performance/SampleMaterial.lc 474:15-483:40 testdata/performance/SampleMaterial.lc 474:15-484:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 474:15-486:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 475:29-475:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 475:29-475:57 @@ -4718,7 +4641,7 @@ testdata/performance/SampleMaterial.lc 477:32-477:42 testdata/performance/SampleMaterial.lc 478:29-478:40 TCGen testdata/performance/SampleMaterial.lc 479:29-479:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 480:31-480:42 StageTexture testdata/performance/SampleMaterial.lc 481:34-481:38 @@ -4736,7 +4659,7 @@ testdata/performance/SampleMaterial.lc 488:21-488:26 testdata/performance/SampleMaterial.lc 491:5-533:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 491:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 491:7-491:53 String testdata/performance/SampleMaterial.lc 492:7-492:18 @@ -4746,49 +4669,42 @@ testdata/performance/SampleMaterial.lc 492:7-492:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 492:7-493:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 492:7-494:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 492:7-495:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 492:7-496:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 492:7-497:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 492:7-498:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 492:7-499:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 492:7-500:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 492:7-501:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 492:7-502:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 492:7-530:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 492:7-532:10 @@ -4808,41 +4724,41 @@ testdata/performance/SampleMaterial.lc 498:23-498:28 testdata/performance/SampleMaterial.lc 499:20-499:33 CullType testdata/performance/SampleMaterial.lc 500:30-500:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 501:25-501:30 Bool testdata/performance/SampleMaterial.lc 502:29-502:34 Bool testdata/performance/SampleMaterial.lc 504:13-530:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 504:15-504:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 504:15-505:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 504:15-506:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 504:15-507:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 504:15-508:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 504:15-509:31 @@ -4869,7 +4785,7 @@ testdata/performance/SampleMaterial.lc 507:32-507:42 testdata/performance/SampleMaterial.lc 508:29-508:36 TCGen testdata/performance/SampleMaterial.lc 509:29-509:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 510:31-510:37 String -> StageTexture testdata/performance/SampleMaterial.lc 510:31-510:84 @@ -4891,29 +4807,29 @@ testdata/performance/SampleMaterial.lc 517:15-517:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 517:15-518:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 517:15-519:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 517:15-520:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 517:15-521:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 517:15-522:31 @@ -4930,7 +4846,7 @@ testdata/performance/SampleMaterial.lc 517:15-526:40 testdata/performance/SampleMaterial.lc 517:15-527:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 517:15-529:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 518:29-518:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 518:29-518:57 @@ -4948,7 +4864,7 @@ testdata/performance/SampleMaterial.lc 520:32-520:42 testdata/performance/SampleMaterial.lc 521:29-521:40 TCGen testdata/performance/SampleMaterial.lc 522:29-522:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 523:31-523:42 StageTexture testdata/performance/SampleMaterial.lc 524:34-524:38 @@ -4966,7 +4882,7 @@ testdata/performance/SampleMaterial.lc 531:21-531:26 testdata/performance/SampleMaterial.lc 534:5-576:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 534:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 534:7-534:42 String testdata/performance/SampleMaterial.lc 535:7-535:18 @@ -4976,49 +4892,42 @@ testdata/performance/SampleMaterial.lc 535:7-535:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 535:7-536:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 535:7-537:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 535:7-538:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 535:7-539:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 535:7-540:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 535:7-541:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 535:7-542:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 535:7-543:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 535:7-544:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 535:7-545:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 535:7-573:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 535:7-575:10 @@ -5038,41 +4947,41 @@ testdata/performance/SampleMaterial.lc 541:23-541:28 testdata/performance/SampleMaterial.lc 542:20-542:33 CullType testdata/performance/SampleMaterial.lc 543:30-543:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 544:25-544:30 Bool testdata/performance/SampleMaterial.lc 545:29-545:34 Bool testdata/performance/SampleMaterial.lc 547:13-573:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 547:15-547:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 547:15-548:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 547:15-549:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 547:15-550:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 547:15-551:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 547:15-552:31 @@ -5099,7 +5008,7 @@ testdata/performance/SampleMaterial.lc 550:32-550:42 testdata/performance/SampleMaterial.lc 551:29-551:36 TCGen testdata/performance/SampleMaterial.lc 552:29-552:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 553:31-553:37 String -> StageTexture testdata/performance/SampleMaterial.lc 553:31-553:73 @@ -5121,29 +5030,29 @@ testdata/performance/SampleMaterial.lc 560:15-560:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 560:15-561:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 560:15-562:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 560:15-563:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 560:15-564:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 560:15-565:31 @@ -5160,7 +5069,7 @@ testdata/performance/SampleMaterial.lc 560:15-569:40 testdata/performance/SampleMaterial.lc 560:15-570:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 560:15-572:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 561:29-561:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 561:29-561:57 @@ -5178,7 +5087,7 @@ testdata/performance/SampleMaterial.lc 563:32-563:42 testdata/performance/SampleMaterial.lc 564:29-564:40 TCGen testdata/performance/SampleMaterial.lc 565:29-565:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 566:31-566:42 StageTexture testdata/performance/SampleMaterial.lc 567:34-567:38 @@ -5196,7 +5105,7 @@ testdata/performance/SampleMaterial.lc 574:21-574:26 testdata/performance/SampleMaterial.lc 577:5-619:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 577:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 577:7-577:42 String testdata/performance/SampleMaterial.lc 578:7-578:18 @@ -5206,49 +5115,42 @@ testdata/performance/SampleMaterial.lc 578:7-578:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 578:7-579:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 578:7-580:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 578:7-581:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 578:7-582:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 578:7-583:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 578:7-584:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 578:7-585:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 578:7-586:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 578:7-587:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 578:7-588:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 578:7-616:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 578:7-618:10 @@ -5268,41 +5170,41 @@ testdata/performance/SampleMaterial.lc 584:23-584:28 testdata/performance/SampleMaterial.lc 585:20-585:33 CullType testdata/performance/SampleMaterial.lc 586:30-586:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 587:25-587:30 Bool testdata/performance/SampleMaterial.lc 588:29-588:34 Bool testdata/performance/SampleMaterial.lc 590:13-616:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 590:15-590:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 590:15-591:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 590:15-592:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 590:15-593:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 590:15-594:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 590:15-595:31 @@ -5329,7 +5231,7 @@ testdata/performance/SampleMaterial.lc 593:32-593:42 testdata/performance/SampleMaterial.lc 594:29-594:36 TCGen testdata/performance/SampleMaterial.lc 595:29-595:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 596:31-596:37 String -> StageTexture testdata/performance/SampleMaterial.lc 596:31-596:73 @@ -5351,29 +5253,29 @@ testdata/performance/SampleMaterial.lc 603:15-603:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 603:15-604:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 603:15-605:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 603:15-606:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 603:15-607:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 603:15-608:31 @@ -5390,7 +5292,7 @@ testdata/performance/SampleMaterial.lc 603:15-612:40 testdata/performance/SampleMaterial.lc 603:15-613:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 603:15-615:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 604:29-604:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 604:29-604:57 @@ -5408,7 +5310,7 @@ testdata/performance/SampleMaterial.lc 606:32-606:42 testdata/performance/SampleMaterial.lc 607:29-607:40 TCGen testdata/performance/SampleMaterial.lc 608:29-608:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 609:31-609:42 StageTexture testdata/performance/SampleMaterial.lc 610:34-610:38 @@ -5426,7 +5328,7 @@ testdata/performance/SampleMaterial.lc 617:21-617:26 testdata/performance/SampleMaterial.lc 620:5-662:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 620:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 620:7-620:42 String testdata/performance/SampleMaterial.lc 621:7-621:18 @@ -5436,49 +5338,42 @@ testdata/performance/SampleMaterial.lc 621:7-621:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 621:7-622:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 621:7-623:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 621:7-624:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 621:7-625:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 621:7-626:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 621:7-627:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 621:7-628:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 621:7-629:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 621:7-630:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 621:7-631:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 621:7-659:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 621:7-661:10 @@ -5498,41 +5393,41 @@ testdata/performance/SampleMaterial.lc 627:23-627:28 testdata/performance/SampleMaterial.lc 628:20-628:33 CullType testdata/performance/SampleMaterial.lc 629:30-629:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 630:25-630:30 Bool testdata/performance/SampleMaterial.lc 631:29-631:34 Bool testdata/performance/SampleMaterial.lc 633:13-659:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 633:15-633:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 633:15-634:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 633:15-635:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 633:15-636:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 633:15-637:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 633:15-638:31 @@ -5559,7 +5454,7 @@ testdata/performance/SampleMaterial.lc 636:32-636:42 testdata/performance/SampleMaterial.lc 637:29-637:36 TCGen testdata/performance/SampleMaterial.lc 638:29-638:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 639:31-639:37 String -> StageTexture testdata/performance/SampleMaterial.lc 639:31-639:73 @@ -5581,29 +5476,29 @@ testdata/performance/SampleMaterial.lc 646:15-646:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 646:15-647:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 646:15-648:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 646:15-649:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 646:15-650:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 646:15-651:31 @@ -5620,7 +5515,7 @@ testdata/performance/SampleMaterial.lc 646:15-655:40 testdata/performance/SampleMaterial.lc 646:15-656:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 646:15-658:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 647:29-647:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 647:29-647:57 @@ -5638,7 +5533,7 @@ testdata/performance/SampleMaterial.lc 649:32-649:42 testdata/performance/SampleMaterial.lc 650:29-650:40 TCGen testdata/performance/SampleMaterial.lc 651:29-651:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 652:31-652:42 StageTexture testdata/performance/SampleMaterial.lc 653:34-653:38 @@ -5656,7 +5551,7 @@ testdata/performance/SampleMaterial.lc 660:21-660:26 testdata/performance/SampleMaterial.lc 663:5-705:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 663:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 663:7-663:42 String testdata/performance/SampleMaterial.lc 664:7-664:18 @@ -5666,49 +5561,42 @@ testdata/performance/SampleMaterial.lc 664:7-664:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 664:7-665:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 664:7-666:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 664:7-667:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 664:7-668:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 664:7-669:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 664:7-670:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 664:7-671:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 664:7-672:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 664:7-673:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 664:7-674:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 664:7-702:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 664:7-704:10 @@ -5728,41 +5616,41 @@ testdata/performance/SampleMaterial.lc 670:23-670:28 testdata/performance/SampleMaterial.lc 671:20-671:33 CullType testdata/performance/SampleMaterial.lc 672:30-672:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 673:25-673:30 Bool testdata/performance/SampleMaterial.lc 674:29-674:34 Bool testdata/performance/SampleMaterial.lc 676:13-702:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 676:15-676:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 676:15-677:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 676:15-678:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 676:15-679:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 676:15-680:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 676:15-681:31 @@ -5789,7 +5677,7 @@ testdata/performance/SampleMaterial.lc 679:32-679:42 testdata/performance/SampleMaterial.lc 680:29-680:36 TCGen testdata/performance/SampleMaterial.lc 681:29-681:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 682:31-682:37 String -> StageTexture testdata/performance/SampleMaterial.lc 682:31-682:73 @@ -5811,29 +5699,29 @@ testdata/performance/SampleMaterial.lc 689:15-689:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 689:15-690:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 689:15-691:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 689:15-692:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 689:15-693:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 689:15-694:31 @@ -5850,7 +5738,7 @@ testdata/performance/SampleMaterial.lc 689:15-698:40 testdata/performance/SampleMaterial.lc 689:15-699:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 689:15-701:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 690:29-690:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 690:29-690:57 @@ -5868,7 +5756,7 @@ testdata/performance/SampleMaterial.lc 692:32-692:42 testdata/performance/SampleMaterial.lc 693:29-693:40 TCGen testdata/performance/SampleMaterial.lc 694:29-694:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 695:31-695:42 StageTexture testdata/performance/SampleMaterial.lc 696:34-696:38 @@ -5886,7 +5774,7 @@ testdata/performance/SampleMaterial.lc 703:21-703:26 testdata/performance/SampleMaterial.lc 706:5-748:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 706:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 706:7-706:42 String testdata/performance/SampleMaterial.lc 707:7-707:18 @@ -5896,49 +5784,42 @@ testdata/performance/SampleMaterial.lc 707:7-707:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 707:7-708:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 707:7-709:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 707:7-710:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 707:7-711:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 707:7-712:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 707:7-713:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 707:7-714:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 707:7-715:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 707:7-716:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 707:7-717:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 707:7-745:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 707:7-747:10 @@ -5958,41 +5839,41 @@ testdata/performance/SampleMaterial.lc 713:23-713:28 testdata/performance/SampleMaterial.lc 714:20-714:33 CullType testdata/performance/SampleMaterial.lc 715:30-715:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 716:25-716:30 Bool testdata/performance/SampleMaterial.lc 717:29-717:34 Bool testdata/performance/SampleMaterial.lc 719:13-745:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 719:15-719:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 719:15-720:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 719:15-721:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 719:15-722:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 719:15-723:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 719:15-724:31 @@ -6019,7 +5900,7 @@ testdata/performance/SampleMaterial.lc 722:32-722:42 testdata/performance/SampleMaterial.lc 723:29-723:36 TCGen testdata/performance/SampleMaterial.lc 724:29-724:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 725:31-725:37 String -> StageTexture testdata/performance/SampleMaterial.lc 725:31-725:73 @@ -6041,29 +5922,29 @@ testdata/performance/SampleMaterial.lc 732:15-732:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 732:15-733:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 732:15-734:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 732:15-735:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 732:15-736:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 732:15-737:31 @@ -6080,7 +5961,7 @@ testdata/performance/SampleMaterial.lc 732:15-741:40 testdata/performance/SampleMaterial.lc 732:15-742:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 732:15-744:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 733:29-733:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 733:29-733:57 @@ -6098,7 +5979,7 @@ testdata/performance/SampleMaterial.lc 735:32-735:42 testdata/performance/SampleMaterial.lc 736:29-736:40 TCGen testdata/performance/SampleMaterial.lc 737:29-737:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 738:31-738:42 StageTexture testdata/performance/SampleMaterial.lc 739:34-739:38 @@ -6116,7 +5997,7 @@ testdata/performance/SampleMaterial.lc 746:21-746:26 testdata/performance/SampleMaterial.lc 749:5-791:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 749:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 749:7-749:42 String testdata/performance/SampleMaterial.lc 750:7-750:18 @@ -6126,49 +6007,42 @@ testdata/performance/SampleMaterial.lc 750:7-750:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 750:7-751:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 750:7-752:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 750:7-753:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 750:7-754:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 750:7-755:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 750:7-756:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 750:7-757:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 750:7-758:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 750:7-759:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 750:7-760:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 750:7-788:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 750:7-790:10 @@ -6188,41 +6062,41 @@ testdata/performance/SampleMaterial.lc 756:23-756:28 testdata/performance/SampleMaterial.lc 757:20-757:33 CullType testdata/performance/SampleMaterial.lc 758:30-758:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 759:25-759:30 Bool testdata/performance/SampleMaterial.lc 760:29-760:34 Bool testdata/performance/SampleMaterial.lc 762:13-788:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 762:15-762:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 762:15-763:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 762:15-764:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 762:15-765:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 762:15-766:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 762:15-767:31 @@ -6249,7 +6123,7 @@ testdata/performance/SampleMaterial.lc 765:32-765:42 testdata/performance/SampleMaterial.lc 766:29-766:36 TCGen testdata/performance/SampleMaterial.lc 767:29-767:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 768:31-768:37 String -> StageTexture testdata/performance/SampleMaterial.lc 768:31-768:73 @@ -6271,29 +6145,29 @@ testdata/performance/SampleMaterial.lc 775:15-775:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 775:15-776:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 775:15-777:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 775:15-778:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 775:15-779:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 775:15-780:31 @@ -6310,7 +6184,7 @@ testdata/performance/SampleMaterial.lc 775:15-784:40 testdata/performance/SampleMaterial.lc 775:15-785:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 775:15-787:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 776:29-776:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 776:29-776:57 @@ -6328,7 +6202,7 @@ testdata/performance/SampleMaterial.lc 778:32-778:42 testdata/performance/SampleMaterial.lc 779:29-779:40 TCGen testdata/performance/SampleMaterial.lc 780:29-780:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 781:31-781:42 StageTexture testdata/performance/SampleMaterial.lc 782:34-782:38 @@ -6346,7 +6220,7 @@ testdata/performance/SampleMaterial.lc 789:21-789:26 testdata/performance/SampleMaterial.lc 792:5-834:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 792:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 792:7-792:41 String testdata/performance/SampleMaterial.lc 793:7-793:18 @@ -6356,49 +6230,42 @@ testdata/performance/SampleMaterial.lc 793:7-793:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 793:7-794:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 793:7-795:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 793:7-796:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 793:7-797:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 793:7-798:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 793:7-799:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 793:7-800:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 793:7-801:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 793:7-802:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 793:7-803:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 793:7-831:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 793:7-833:10 @@ -6418,41 +6285,41 @@ testdata/performance/SampleMaterial.lc 799:23-799:28 testdata/performance/SampleMaterial.lc 800:20-800:33 CullType testdata/performance/SampleMaterial.lc 801:30-801:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 802:25-802:30 Bool testdata/performance/SampleMaterial.lc 803:29-803:34 Bool testdata/performance/SampleMaterial.lc 805:13-831:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 805:15-805:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 805:15-806:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 805:15-807:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 805:15-808:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 805:15-809:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 805:15-810:31 @@ -6479,7 +6346,7 @@ testdata/performance/SampleMaterial.lc 808:32-808:42 testdata/performance/SampleMaterial.lc 809:29-809:36 TCGen testdata/performance/SampleMaterial.lc 810:29-810:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 811:31-811:37 String -> StageTexture testdata/performance/SampleMaterial.lc 811:31-811:72 @@ -6501,29 +6368,29 @@ testdata/performance/SampleMaterial.lc 818:15-818:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 818:15-819:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 818:15-820:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 818:15-821:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 818:15-822:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 818:15-823:31 @@ -6540,7 +6407,7 @@ testdata/performance/SampleMaterial.lc 818:15-827:40 testdata/performance/SampleMaterial.lc 818:15-828:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 818:15-830:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 819:29-819:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 819:29-819:57 @@ -6558,7 +6425,7 @@ testdata/performance/SampleMaterial.lc 821:32-821:42 testdata/performance/SampleMaterial.lc 822:29-822:40 TCGen testdata/performance/SampleMaterial.lc 823:29-823:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 824:31-824:42 StageTexture testdata/performance/SampleMaterial.lc 825:34-825:38 @@ -6576,7 +6443,7 @@ testdata/performance/SampleMaterial.lc 832:21-832:26 testdata/performance/SampleMaterial.lc 835:5-891:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 835:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 835:7-835:41 String testdata/performance/SampleMaterial.lc 836:7-836:18 @@ -6586,49 +6453,42 @@ testdata/performance/SampleMaterial.lc 836:7-836:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 836:7-837:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 836:7-838:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 836:7-839:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 836:7-840:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 836:7-841:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 836:7-842:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 836:7-843:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 836:7-844:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 836:7-845:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 836:7-846:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 836:7-888:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 836:7-890:10 @@ -6648,41 +6508,41 @@ testdata/performance/SampleMaterial.lc 842:23-842:28 testdata/performance/SampleMaterial.lc 843:20-843:33 CullType testdata/performance/SampleMaterial.lc 844:30-844:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 845:25-845:30 Bool testdata/performance/SampleMaterial.lc 846:29-846:34 Bool testdata/performance/SampleMaterial.lc 848:13-888:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 848:15-848:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 848:15-849:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 848:15-850:42 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 848:15-851:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 848:15-852:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 848:15-854:88 @@ -6709,7 +6569,7 @@ testdata/performance/SampleMaterial.lc 851:32-851:42 testdata/performance/SampleMaterial.lc 852:29-852:36 TCGen testdata/performance/SampleMaterial.lc 854:21-854:88 - List TCMod + [TCMod] testdata/performance/SampleMaterial.lc 854:23-854:32 Float -> Float -> TCMod testdata/performance/SampleMaterial.lc 854:23-854:36 @@ -6731,7 +6591,7 @@ testdata/performance/SampleMaterial.lc 854:43-854:63 testdata/performance/SampleMaterial.lc 854:43-854:67 TCMod testdata/performance/SampleMaterial.lc 854:43-854:86 - List TCMod + [TCMod] testdata/performance/SampleMaterial.lc 854:51-854:54 Float testdata/performance/SampleMaterial.lc 854:55-854:59 @@ -6745,7 +6605,7 @@ testdata/performance/SampleMaterial.lc 854:70-854:78 testdata/performance/SampleMaterial.lc 854:70-854:82 Float -> TCMod testdata/performance/SampleMaterial.lc 854:70-854:86 - TCMod | List TCMod + TCMod | [TCMod] testdata/performance/SampleMaterial.lc 854:79-854:82 Float testdata/performance/SampleMaterial.lc 854:83-854:86 @@ -6771,29 +6631,29 @@ testdata/performance/SampleMaterial.lc 862:15-862:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 862:15-863:69 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 862:15-864:42 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 862:15-865:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 862:15-866:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 862:15-867:31 @@ -6812,7 +6672,7 @@ testdata/performance/SampleMaterial.lc 862:15-872:46 testdata/performance/SampleMaterial.lc 862:15-874:18 StageAttrs testdata/performance/SampleMaterial.lc 862:15-887:18 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 863:29-863:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 863:29-863:69 @@ -6830,7 +6690,7 @@ testdata/performance/SampleMaterial.lc 865:32-865:42 testdata/performance/SampleMaterial.lc 866:29-866:36 TCGen testdata/performance/SampleMaterial.lc 867:29-867:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 868:31-868:37 String -> StageTexture testdata/performance/SampleMaterial.lc 868:31-868:76 @@ -6852,29 +6712,29 @@ testdata/performance/SampleMaterial.lc 875:15-875:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 875:15-876:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 875:15-877:42 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 875:15-878:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 875:15-879:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 875:15-880:31 @@ -6891,7 +6751,7 @@ testdata/performance/SampleMaterial.lc 875:15-884:40 testdata/performance/SampleMaterial.lc 875:15-885:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 875:15-887:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 876:29-876:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 876:29-876:57 @@ -6909,7 +6769,7 @@ testdata/performance/SampleMaterial.lc 878:32-878:42 testdata/performance/SampleMaterial.lc 879:29-879:40 TCGen testdata/performance/SampleMaterial.lc 880:29-880:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 881:31-881:42 StageTexture testdata/performance/SampleMaterial.lc 882:34-882:39 @@ -6927,7 +6787,7 @@ testdata/performance/SampleMaterial.lc 889:21-889:26 testdata/performance/SampleMaterial.lc 892:5-934:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 892:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 892:7-892:41 String testdata/performance/SampleMaterial.lc 893:7-893:18 @@ -6937,49 +6797,42 @@ testdata/performance/SampleMaterial.lc 893:7-893:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 893:7-894:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 893:7-895:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 893:7-896:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 893:7-897:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 893:7-898:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 893:7-899:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 893:7-900:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 893:7-901:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 893:7-902:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 893:7-903:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 893:7-931:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 893:7-933:10 @@ -6999,41 +6852,41 @@ testdata/performance/SampleMaterial.lc 899:23-899:28 testdata/performance/SampleMaterial.lc 900:20-900:33 CullType testdata/performance/SampleMaterial.lc 901:30-901:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 902:25-902:30 Bool testdata/performance/SampleMaterial.lc 903:29-903:34 Bool testdata/performance/SampleMaterial.lc 905:13-931:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 905:15-905:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 905:15-906:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 905:15-907:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 905:15-908:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 905:15-909:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 905:15-910:31 @@ -7060,7 +6913,7 @@ testdata/performance/SampleMaterial.lc 908:32-908:42 testdata/performance/SampleMaterial.lc 909:29-909:36 TCGen testdata/performance/SampleMaterial.lc 910:29-910:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 911:31-911:37 String -> StageTexture testdata/performance/SampleMaterial.lc 911:31-911:72 @@ -7082,29 +6935,29 @@ testdata/performance/SampleMaterial.lc 918:15-918:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 918:15-919:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 918:15-920:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 918:15-921:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 918:15-922:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 918:15-923:31 @@ -7121,7 +6974,7 @@ testdata/performance/SampleMaterial.lc 918:15-927:40 testdata/performance/SampleMaterial.lc 918:15-928:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 918:15-930:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 919:29-919:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 919:29-919:57 @@ -7139,7 +6992,7 @@ testdata/performance/SampleMaterial.lc 921:32-921:42 testdata/performance/SampleMaterial.lc 922:29-922:40 TCGen testdata/performance/SampleMaterial.lc 923:29-923:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 924:31-924:42 StageTexture testdata/performance/SampleMaterial.lc 925:34-925:38 @@ -7157,7 +7010,7 @@ testdata/performance/SampleMaterial.lc 932:21-932:26 testdata/performance/SampleMaterial.lc 935:5-978:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 935:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 935:7-935:54 String testdata/performance/SampleMaterial.lc 936:7-936:18 @@ -7167,49 +7020,42 @@ testdata/performance/SampleMaterial.lc 936:7-936:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 936:7-937:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 936:7-938:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 936:7-939:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 936:7-940:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 936:7-941:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 936:7-942:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 936:7-943:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 936:7-944:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 936:7-945:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 936:7-946:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 936:7-975:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 936:7-977:10 @@ -7229,41 +7075,41 @@ testdata/performance/SampleMaterial.lc 942:23-942:28 testdata/performance/SampleMaterial.lc 943:20-943:33 CullType testdata/performance/SampleMaterial.lc 944:30-944:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 945:25-945:30 Bool testdata/performance/SampleMaterial.lc 946:29-946:34 Bool testdata/performance/SampleMaterial.lc 948:13-975:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 948:15-948:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 948:15-949:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 948:15-950:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 948:15-951:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 948:15-952:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 948:15-953:31 @@ -7290,7 +7136,7 @@ testdata/performance/SampleMaterial.lc 951:32-951:42 testdata/performance/SampleMaterial.lc 952:29-952:36 TCGen testdata/performance/SampleMaterial.lc 953:29-953:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 955:21-955:27 String -> StageTexture testdata/performance/SampleMaterial.lc 955:21-955:75 @@ -7312,29 +7158,29 @@ testdata/performance/SampleMaterial.lc 962:15-962:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 962:15-963:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 962:15-964:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 962:15-965:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 962:15-966:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 962:15-967:31 @@ -7351,7 +7197,7 @@ testdata/performance/SampleMaterial.lc 962:15-971:40 testdata/performance/SampleMaterial.lc 962:15-972:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 962:15-974:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 963:29-963:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 963:29-963:57 @@ -7369,7 +7215,7 @@ testdata/performance/SampleMaterial.lc 965:32-965:42 testdata/performance/SampleMaterial.lc 966:29-966:40 TCGen testdata/performance/SampleMaterial.lc 967:29-967:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 968:31-968:42 StageTexture testdata/performance/SampleMaterial.lc 969:34-969:38 @@ -7387,7 +7233,7 @@ testdata/performance/SampleMaterial.lc 976:21-976:26 testdata/performance/SampleMaterial.lc 979:5-1021:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 979:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 979:7-979:45 String testdata/performance/SampleMaterial.lc 980:7-980:18 @@ -7397,49 +7243,42 @@ testdata/performance/SampleMaterial.lc 980:7-980:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 980:7-981:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 980:7-982:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 980:7-983:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 980:7-984:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 980:7-985:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 980:7-986:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 980:7-987:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 980:7-988:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 980:7-989:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 980:7-990:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 980:7-1018:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 980:7-1020:10 @@ -7459,41 +7298,41 @@ testdata/performance/SampleMaterial.lc 986:23-986:28 testdata/performance/SampleMaterial.lc 987:20-987:33 CullType testdata/performance/SampleMaterial.lc 988:30-988:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 989:25-989:30 Bool testdata/performance/SampleMaterial.lc 990:29-990:34 Bool testdata/performance/SampleMaterial.lc 992:13-1018:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 992:15-992:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 992:15-993:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 992:15-994:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 992:15-995:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 992:15-996:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 992:15-997:31 @@ -7520,7 +7359,7 @@ testdata/performance/SampleMaterial.lc 995:32-995:42 testdata/performance/SampleMaterial.lc 996:29-996:36 TCGen testdata/performance/SampleMaterial.lc 997:29-997:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 998:31-998:37 String -> StageTexture testdata/performance/SampleMaterial.lc 998:31-998:76 @@ -7542,29 +7381,29 @@ testdata/performance/SampleMaterial.lc 1005:15-1005:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1005:15-1006:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1005:15-1007:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1005:15-1008:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1005:15-1009:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1005:15-1010:31 @@ -7581,7 +7420,7 @@ testdata/performance/SampleMaterial.lc 1005:15-1014:40 testdata/performance/SampleMaterial.lc 1005:15-1015:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 1005:15-1017:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 1006:29-1006:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 1006:29-1006:57 @@ -7599,7 +7438,7 @@ testdata/performance/SampleMaterial.lc 1008:32-1008:42 testdata/performance/SampleMaterial.lc 1009:29-1009:40 TCGen testdata/performance/SampleMaterial.lc 1010:29-1010:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1011:31-1011:42 StageTexture testdata/performance/SampleMaterial.lc 1012:34-1012:38 @@ -7617,7 +7456,7 @@ testdata/performance/SampleMaterial.lc 1019:21-1019:26 testdata/performance/SampleMaterial.lc 1022:5-1064:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 1022:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 1022:7-1022:44 String testdata/performance/SampleMaterial.lc 1023:7-1023:18 @@ -7627,49 +7466,42 @@ testdata/performance/SampleMaterial.lc 1023:7-1023:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1023:7-1024:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1023:7-1025:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1023:7-1026:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1023:7-1027:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1023:7-1028:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1023:7-1029:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1023:7-1030:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1023:7-1031:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1023:7-1032:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1023:7-1033:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1023:7-1061:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1023:7-1063:10 @@ -7689,41 +7521,41 @@ testdata/performance/SampleMaterial.lc 1029:23-1029:28 testdata/performance/SampleMaterial.lc 1030:20-1030:33 CullType testdata/performance/SampleMaterial.lc 1031:30-1031:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1032:25-1032:30 Bool testdata/performance/SampleMaterial.lc 1033:29-1033:34 Bool testdata/performance/SampleMaterial.lc 1035:13-1061:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 1035:15-1035:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1035:15-1036:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1035:15-1037:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1035:15-1038:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1035:15-1039:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1035:15-1040:31 @@ -7750,7 +7582,7 @@ testdata/performance/SampleMaterial.lc 1038:32-1038:42 testdata/performance/SampleMaterial.lc 1039:29-1039:36 TCGen testdata/performance/SampleMaterial.lc 1040:29-1040:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1041:31-1041:37 String -> StageTexture testdata/performance/SampleMaterial.lc 1041:31-1041:75 @@ -7772,29 +7604,29 @@ testdata/performance/SampleMaterial.lc 1048:15-1048:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1048:15-1049:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1048:15-1050:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1048:15-1051:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1048:15-1052:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1048:15-1053:31 @@ -7811,7 +7643,7 @@ testdata/performance/SampleMaterial.lc 1048:15-1057:40 testdata/performance/SampleMaterial.lc 1048:15-1058:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 1048:15-1060:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 1049:29-1049:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 1049:29-1049:57 @@ -7829,7 +7661,7 @@ testdata/performance/SampleMaterial.lc 1051:32-1051:42 testdata/performance/SampleMaterial.lc 1052:29-1052:40 TCGen testdata/performance/SampleMaterial.lc 1053:29-1053:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1054:31-1054:42 StageTexture testdata/performance/SampleMaterial.lc 1055:34-1055:38 @@ -7847,7 +7679,7 @@ testdata/performance/SampleMaterial.lc 1062:21-1062:26 testdata/performance/SampleMaterial.lc 1065:5-1107:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 1065:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 1065:7-1065:44 String testdata/performance/SampleMaterial.lc 1066:7-1066:18 @@ -7857,49 +7689,42 @@ testdata/performance/SampleMaterial.lc 1066:7-1066:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1066:7-1067:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1066:7-1068:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1066:7-1069:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1066:7-1070:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1066:7-1071:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1066:7-1072:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1066:7-1073:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1066:7-1074:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1066:7-1075:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1066:7-1076:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1066:7-1104:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1066:7-1106:10 @@ -7919,41 +7744,41 @@ testdata/performance/SampleMaterial.lc 1072:23-1072:28 testdata/performance/SampleMaterial.lc 1073:20-1073:33 CullType testdata/performance/SampleMaterial.lc 1074:30-1074:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1075:25-1075:30 Bool testdata/performance/SampleMaterial.lc 1076:29-1076:34 Bool testdata/performance/SampleMaterial.lc 1078:13-1104:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 1078:15-1078:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1078:15-1079:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1078:15-1080:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1078:15-1081:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1078:15-1082:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1078:15-1083:31 @@ -7980,7 +7805,7 @@ testdata/performance/SampleMaterial.lc 1081:32-1081:42 testdata/performance/SampleMaterial.lc 1082:29-1082:36 TCGen testdata/performance/SampleMaterial.lc 1083:29-1083:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1084:31-1084:37 String -> StageTexture testdata/performance/SampleMaterial.lc 1084:31-1084:75 @@ -8002,29 +7827,29 @@ testdata/performance/SampleMaterial.lc 1091:15-1091:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1091:15-1092:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1091:15-1093:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1091:15-1094:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1091:15-1095:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1091:15-1096:31 @@ -8041,7 +7866,7 @@ testdata/performance/SampleMaterial.lc 1091:15-1100:40 testdata/performance/SampleMaterial.lc 1091:15-1101:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 1091:15-1103:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 1092:29-1092:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 1092:29-1092:57 @@ -8059,7 +7884,7 @@ testdata/performance/SampleMaterial.lc 1094:32-1094:42 testdata/performance/SampleMaterial.lc 1095:29-1095:40 TCGen testdata/performance/SampleMaterial.lc 1096:29-1096:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1097:31-1097:42 StageTexture testdata/performance/SampleMaterial.lc 1098:34-1098:38 @@ -8077,7 +7902,7 @@ testdata/performance/SampleMaterial.lc 1105:21-1105:26 testdata/performance/SampleMaterial.lc 1108:5-1150:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 1108:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 1108:7-1108:49 String testdata/performance/SampleMaterial.lc 1109:7-1109:18 @@ -8087,49 +7912,42 @@ testdata/performance/SampleMaterial.lc 1109:7-1109:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1109:7-1110:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1109:7-1111:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1109:7-1112:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1109:7-1113:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1109:7-1114:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1109:7-1115:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1109:7-1116:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1109:7-1117:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1109:7-1118:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1109:7-1119:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1109:7-1147:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1109:7-1149:10 @@ -8149,41 +7967,41 @@ testdata/performance/SampleMaterial.lc 1115:23-1115:28 testdata/performance/SampleMaterial.lc 1116:20-1116:33 CullType testdata/performance/SampleMaterial.lc 1117:30-1117:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1118:25-1118:30 Bool testdata/performance/SampleMaterial.lc 1119:29-1119:34 Bool testdata/performance/SampleMaterial.lc 1121:13-1147:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 1121:15-1121:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1121:15-1122:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1121:15-1123:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1121:15-1124:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1121:15-1125:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1121:15-1126:31 @@ -8210,7 +8028,7 @@ testdata/performance/SampleMaterial.lc 1124:32-1124:42 testdata/performance/SampleMaterial.lc 1125:29-1125:36 TCGen testdata/performance/SampleMaterial.lc 1126:29-1126:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1127:31-1127:37 String -> StageTexture testdata/performance/SampleMaterial.lc 1127:31-1127:80 @@ -8232,29 +8050,29 @@ testdata/performance/SampleMaterial.lc 1134:15-1134:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1134:15-1135:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1134:15-1136:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1134:15-1137:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1134:15-1138:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1134:15-1139:31 @@ -8271,7 +8089,7 @@ testdata/performance/SampleMaterial.lc 1134:15-1143:40 testdata/performance/SampleMaterial.lc 1134:15-1144:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 1134:15-1146:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 1135:29-1135:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 1135:29-1135:57 @@ -8289,7 +8107,7 @@ testdata/performance/SampleMaterial.lc 1137:32-1137:42 testdata/performance/SampleMaterial.lc 1138:29-1138:40 TCGen testdata/performance/SampleMaterial.lc 1139:29-1139:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1140:31-1140:42 StageTexture testdata/performance/SampleMaterial.lc 1141:34-1141:38 @@ -8307,7 +8125,7 @@ testdata/performance/SampleMaterial.lc 1148:21-1148:26 testdata/performance/SampleMaterial.lc 1151:5-1193:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 1151:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 1151:7-1151:41 String testdata/performance/SampleMaterial.lc 1152:7-1152:18 @@ -8317,49 +8135,42 @@ testdata/performance/SampleMaterial.lc 1152:7-1152:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1152:7-1153:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1152:7-1154:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1152:7-1155:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1152:7-1156:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1152:7-1157:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1152:7-1158:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1152:7-1159:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1152:7-1160:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1152:7-1161:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1152:7-1162:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1152:7-1190:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1152:7-1192:10 @@ -8379,41 +8190,41 @@ testdata/performance/SampleMaterial.lc 1158:23-1158:28 testdata/performance/SampleMaterial.lc 1159:20-1159:33 CullType testdata/performance/SampleMaterial.lc 1160:30-1160:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1161:25-1161:30 Bool testdata/performance/SampleMaterial.lc 1162:29-1162:34 Bool testdata/performance/SampleMaterial.lc 1164:13-1190:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 1164:15-1164:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1164:15-1165:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1164:15-1166:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1164:15-1167:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1164:15-1168:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1164:15-1169:31 @@ -8440,7 +8251,7 @@ testdata/performance/SampleMaterial.lc 1167:32-1167:42 testdata/performance/SampleMaterial.lc 1168:29-1168:36 TCGen testdata/performance/SampleMaterial.lc 1169:29-1169:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1170:31-1170:37 String -> StageTexture testdata/performance/SampleMaterial.lc 1170:31-1170:72 @@ -8462,29 +8273,29 @@ testdata/performance/SampleMaterial.lc 1177:15-1177:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1177:15-1178:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1177:15-1179:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1177:15-1180:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1177:15-1181:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1177:15-1182:31 @@ -8501,7 +8312,7 @@ testdata/performance/SampleMaterial.lc 1177:15-1186:40 testdata/performance/SampleMaterial.lc 1177:15-1187:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 1177:15-1189:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 1178:29-1178:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 1178:29-1178:57 @@ -8519,7 +8330,7 @@ testdata/performance/SampleMaterial.lc 1180:32-1180:42 testdata/performance/SampleMaterial.lc 1181:29-1181:40 TCGen testdata/performance/SampleMaterial.lc 1182:29-1182:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1183:31-1183:42 StageTexture testdata/performance/SampleMaterial.lc 1184:34-1184:38 @@ -8537,7 +8348,7 @@ testdata/performance/SampleMaterial.lc 1191:21-1191:26 testdata/performance/SampleMaterial.lc 1194:5-1236:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 1194:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 1194:7-1194:43 String testdata/performance/SampleMaterial.lc 1195:7-1195:18 @@ -8547,49 +8358,42 @@ testdata/performance/SampleMaterial.lc 1195:7-1195:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1195:7-1196:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1195:7-1197:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1195:7-1198:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1195:7-1199:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1195:7-1200:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1195:7-1201:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1195:7-1202:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1195:7-1203:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1195:7-1204:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1195:7-1205:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1195:7-1233:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1195:7-1235:10 @@ -8609,41 +8413,41 @@ testdata/performance/SampleMaterial.lc 1201:23-1201:28 testdata/performance/SampleMaterial.lc 1202:20-1202:33 CullType testdata/performance/SampleMaterial.lc 1203:30-1203:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1204:25-1204:30 Bool testdata/performance/SampleMaterial.lc 1205:29-1205:34 Bool testdata/performance/SampleMaterial.lc 1207:13-1233:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 1207:15-1207:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1207:15-1208:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1207:15-1209:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1207:15-1210:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1207:15-1211:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1207:15-1212:31 @@ -8670,7 +8474,7 @@ testdata/performance/SampleMaterial.lc 1210:32-1210:42 testdata/performance/SampleMaterial.lc 1211:29-1211:36 TCGen testdata/performance/SampleMaterial.lc 1212:29-1212:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1213:31-1213:37 String -> StageTexture testdata/performance/SampleMaterial.lc 1213:31-1213:74 @@ -8692,29 +8496,29 @@ testdata/performance/SampleMaterial.lc 1220:15-1220:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1220:15-1221:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1220:15-1222:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1220:15-1223:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1220:15-1224:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1220:15-1225:31 @@ -8731,7 +8535,7 @@ testdata/performance/SampleMaterial.lc 1220:15-1229:40 testdata/performance/SampleMaterial.lc 1220:15-1230:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 1220:15-1232:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 1221:29-1221:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 1221:29-1221:57 @@ -8749,7 +8553,7 @@ testdata/performance/SampleMaterial.lc 1223:32-1223:42 testdata/performance/SampleMaterial.lc 1224:29-1224:40 TCGen testdata/performance/SampleMaterial.lc 1225:29-1225:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1226:31-1226:42 StageTexture testdata/performance/SampleMaterial.lc 1227:34-1227:38 @@ -8767,7 +8571,7 @@ testdata/performance/SampleMaterial.lc 1234:21-1234:26 testdata/performance/SampleMaterial.lc 1237:5-1279:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 1237:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 1237:7-1237:41 String testdata/performance/SampleMaterial.lc 1238:7-1238:18 @@ -8777,49 +8581,42 @@ testdata/performance/SampleMaterial.lc 1238:7-1238:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1238:7-1239:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1238:7-1240:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1238:7-1241:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1238:7-1242:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1238:7-1243:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1238:7-1244:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1238:7-1245:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1238:7-1246:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1238:7-1247:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1238:7-1248:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1238:7-1276:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1238:7-1278:10 @@ -8839,41 +8636,41 @@ testdata/performance/SampleMaterial.lc 1244:23-1244:28 testdata/performance/SampleMaterial.lc 1245:20-1245:33 CullType testdata/performance/SampleMaterial.lc 1246:30-1246:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1247:25-1247:30 Bool testdata/performance/SampleMaterial.lc 1248:29-1248:34 Bool testdata/performance/SampleMaterial.lc 1250:13-1276:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 1250:15-1250:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1250:15-1251:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1250:15-1252:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1250:15-1253:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1250:15-1254:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1250:15-1255:31 @@ -8900,7 +8697,7 @@ testdata/performance/SampleMaterial.lc 1253:32-1253:42 testdata/performance/SampleMaterial.lc 1254:29-1254:36 TCGen testdata/performance/SampleMaterial.lc 1255:29-1255:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1256:31-1256:37 String -> StageTexture testdata/performance/SampleMaterial.lc 1256:31-1256:72 @@ -8922,29 +8719,29 @@ testdata/performance/SampleMaterial.lc 1263:15-1263:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1263:15-1264:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1263:15-1265:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1263:15-1266:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1263:15-1267:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1263:15-1268:31 @@ -8961,7 +8758,7 @@ testdata/performance/SampleMaterial.lc 1263:15-1272:40 testdata/performance/SampleMaterial.lc 1263:15-1273:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 1263:15-1275:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 1264:29-1264:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 1264:29-1264:57 @@ -8979,7 +8776,7 @@ testdata/performance/SampleMaterial.lc 1266:32-1266:42 testdata/performance/SampleMaterial.lc 1267:29-1267:40 TCGen testdata/performance/SampleMaterial.lc 1268:29-1268:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1269:31-1269:42 StageTexture testdata/performance/SampleMaterial.lc 1270:34-1270:38 @@ -8997,7 +8794,7 @@ testdata/performance/SampleMaterial.lc 1277:21-1277:26 testdata/performance/SampleMaterial.lc 1280:5-1322:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 1280:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 1280:7-1280:44 String testdata/performance/SampleMaterial.lc 1281:7-1281:18 @@ -9007,49 +8804,42 @@ testdata/performance/SampleMaterial.lc 1281:7-1281:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1281:7-1282:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1281:7-1283:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1281:7-1284:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1281:7-1285:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1281:7-1286:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1281:7-1287:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1281:7-1288:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1281:7-1289:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1281:7-1290:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1281:7-1291:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1281:7-1319:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1281:7-1321:10 @@ -9069,41 +8859,41 @@ testdata/performance/SampleMaterial.lc 1287:23-1287:28 testdata/performance/SampleMaterial.lc 1288:20-1288:33 CullType testdata/performance/SampleMaterial.lc 1289:30-1289:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1290:25-1290:30 Bool testdata/performance/SampleMaterial.lc 1291:29-1291:34 Bool testdata/performance/SampleMaterial.lc 1293:13-1319:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 1293:15-1293:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1293:15-1294:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1293:15-1295:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1293:15-1296:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1293:15-1297:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1293:15-1298:31 @@ -9130,7 +8920,7 @@ testdata/performance/SampleMaterial.lc 1296:32-1296:42 testdata/performance/SampleMaterial.lc 1297:29-1297:36 TCGen testdata/performance/SampleMaterial.lc 1298:29-1298:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1299:31-1299:37 String -> StageTexture testdata/performance/SampleMaterial.lc 1299:31-1299:75 @@ -9152,29 +8942,29 @@ testdata/performance/SampleMaterial.lc 1306:15-1306:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1306:15-1307:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1306:15-1308:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1306:15-1309:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1306:15-1310:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1306:15-1311:31 @@ -9191,7 +8981,7 @@ testdata/performance/SampleMaterial.lc 1306:15-1315:40 testdata/performance/SampleMaterial.lc 1306:15-1316:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 1306:15-1318:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 1307:29-1307:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 1307:29-1307:57 @@ -9209,7 +8999,7 @@ testdata/performance/SampleMaterial.lc 1309:32-1309:42 testdata/performance/SampleMaterial.lc 1310:29-1310:40 TCGen testdata/performance/SampleMaterial.lc 1311:29-1311:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1312:31-1312:42 StageTexture testdata/performance/SampleMaterial.lc 1313:34-1313:38 @@ -9227,7 +9017,7 @@ testdata/performance/SampleMaterial.lc 1320:21-1320:26 testdata/performance/SampleMaterial.lc 1323:5-1365:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 1323:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 1323:7-1323:43 String testdata/performance/SampleMaterial.lc 1324:7-1324:18 @@ -9237,49 +9027,42 @@ testdata/performance/SampleMaterial.lc 1324:7-1324:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1324:7-1325:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1324:7-1326:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1324:7-1327:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1324:7-1328:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1324:7-1329:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1324:7-1330:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1324:7-1331:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1324:7-1332:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1324:7-1333:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1324:7-1334:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1324:7-1362:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1324:7-1364:10 @@ -9299,41 +9082,41 @@ testdata/performance/SampleMaterial.lc 1330:23-1330:28 testdata/performance/SampleMaterial.lc 1331:20-1331:33 CullType testdata/performance/SampleMaterial.lc 1332:30-1332:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1333:25-1333:30 Bool testdata/performance/SampleMaterial.lc 1334:29-1334:34 Bool testdata/performance/SampleMaterial.lc 1336:13-1362:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 1336:15-1336:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1336:15-1337:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1336:15-1338:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1336:15-1339:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1336:15-1340:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1336:15-1341:31 @@ -9360,7 +9143,7 @@ testdata/performance/SampleMaterial.lc 1339:32-1339:42 testdata/performance/SampleMaterial.lc 1340:29-1340:36 TCGen testdata/performance/SampleMaterial.lc 1341:29-1341:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1342:31-1342:37 String -> StageTexture testdata/performance/SampleMaterial.lc 1342:31-1342:74 @@ -9382,29 +9165,29 @@ testdata/performance/SampleMaterial.lc 1349:15-1349:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1349:15-1350:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1349:15-1351:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1349:15-1352:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1349:15-1353:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1349:15-1354:31 @@ -9421,7 +9204,7 @@ testdata/performance/SampleMaterial.lc 1349:15-1358:40 testdata/performance/SampleMaterial.lc 1349:15-1359:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 1349:15-1361:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 1350:29-1350:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 1350:29-1350:57 @@ -9439,7 +9222,7 @@ testdata/performance/SampleMaterial.lc 1352:32-1352:42 testdata/performance/SampleMaterial.lc 1353:29-1353:40 TCGen testdata/performance/SampleMaterial.lc 1354:29-1354:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1355:31-1355:42 StageTexture testdata/performance/SampleMaterial.lc 1356:34-1356:38 @@ -9457,7 +9240,7 @@ testdata/performance/SampleMaterial.lc 1363:21-1363:26 testdata/performance/SampleMaterial.lc 1366:5-1408:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 1366:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 1366:7-1366:44 String testdata/performance/SampleMaterial.lc 1367:7-1367:18 @@ -9467,49 +9250,42 @@ testdata/performance/SampleMaterial.lc 1367:7-1367:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1367:7-1368:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1367:7-1369:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1367:7-1370:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1367:7-1371:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1367:7-1372:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1367:7-1373:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1367:7-1374:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1367:7-1375:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1367:7-1376:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1367:7-1377:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1367:7-1405:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1367:7-1407:10 @@ -9529,41 +9305,41 @@ testdata/performance/SampleMaterial.lc 1373:23-1373:28 testdata/performance/SampleMaterial.lc 1374:20-1374:33 CullType testdata/performance/SampleMaterial.lc 1375:30-1375:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1376:25-1376:30 Bool testdata/performance/SampleMaterial.lc 1377:29-1377:34 Bool testdata/performance/SampleMaterial.lc 1379:13-1405:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 1379:15-1379:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1379:15-1380:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1379:15-1381:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1379:15-1382:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1379:15-1383:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1379:15-1384:31 @@ -9590,7 +9366,7 @@ testdata/performance/SampleMaterial.lc 1382:32-1382:42 testdata/performance/SampleMaterial.lc 1383:29-1383:36 TCGen testdata/performance/SampleMaterial.lc 1384:29-1384:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1385:31-1385:37 String -> StageTexture testdata/performance/SampleMaterial.lc 1385:31-1385:75 @@ -9612,29 +9388,29 @@ testdata/performance/SampleMaterial.lc 1392:15-1392:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1392:15-1393:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1392:15-1394:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1392:15-1395:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1392:15-1396:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1392:15-1397:31 @@ -9651,7 +9427,7 @@ testdata/performance/SampleMaterial.lc 1392:15-1401:40 testdata/performance/SampleMaterial.lc 1392:15-1402:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 1392:15-1404:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 1393:29-1393:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 1393:29-1393:57 @@ -9669,7 +9445,7 @@ testdata/performance/SampleMaterial.lc 1395:32-1395:42 testdata/performance/SampleMaterial.lc 1396:29-1396:40 TCGen testdata/performance/SampleMaterial.lc 1397:29-1397:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1398:31-1398:42 StageTexture testdata/performance/SampleMaterial.lc 1399:34-1399:38 @@ -9687,7 +9463,7 @@ testdata/performance/SampleMaterial.lc 1406:21-1406:26 testdata/performance/SampleMaterial.lc 1409:5-1451:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 1409:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 1409:7-1409:44 String testdata/performance/SampleMaterial.lc 1410:7-1410:18 @@ -9697,49 +9473,42 @@ testdata/performance/SampleMaterial.lc 1410:7-1410:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1410:7-1411:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1410:7-1412:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1410:7-1413:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1410:7-1414:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1410:7-1415:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1410:7-1416:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1410:7-1417:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1410:7-1418:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1410:7-1419:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1410:7-1420:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1410:7-1448:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1410:7-1450:10 @@ -9759,41 +9528,41 @@ testdata/performance/SampleMaterial.lc 1416:23-1416:28 testdata/performance/SampleMaterial.lc 1417:20-1417:33 CullType testdata/performance/SampleMaterial.lc 1418:30-1418:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1419:25-1419:30 Bool testdata/performance/SampleMaterial.lc 1420:29-1420:34 Bool testdata/performance/SampleMaterial.lc 1422:13-1448:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 1422:15-1422:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1422:15-1423:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1422:15-1424:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1422:15-1425:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1422:15-1426:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1422:15-1427:31 @@ -9820,7 +9589,7 @@ testdata/performance/SampleMaterial.lc 1425:32-1425:42 testdata/performance/SampleMaterial.lc 1426:29-1426:36 TCGen testdata/performance/SampleMaterial.lc 1427:29-1427:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1428:31-1428:37 String -> StageTexture testdata/performance/SampleMaterial.lc 1428:31-1428:75 @@ -9842,29 +9611,29 @@ testdata/performance/SampleMaterial.lc 1435:15-1435:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1435:15-1436:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1435:15-1437:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1435:15-1438:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1435:15-1439:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1435:15-1440:31 @@ -9881,7 +9650,7 @@ testdata/performance/SampleMaterial.lc 1435:15-1444:40 testdata/performance/SampleMaterial.lc 1435:15-1445:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 1435:15-1447:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 1436:29-1436:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 1436:29-1436:57 @@ -9899,7 +9668,7 @@ testdata/performance/SampleMaterial.lc 1438:32-1438:42 testdata/performance/SampleMaterial.lc 1439:29-1439:40 TCGen testdata/performance/SampleMaterial.lc 1440:29-1440:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1441:31-1441:42 StageTexture testdata/performance/SampleMaterial.lc 1442:34-1442:38 @@ -9917,7 +9686,7 @@ testdata/performance/SampleMaterial.lc 1449:21-1449:26 testdata/performance/SampleMaterial.lc 1452:5-1494:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 1452:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 1452:7-1452:44 String testdata/performance/SampleMaterial.lc 1453:7-1453:18 @@ -9927,49 +9696,42 @@ testdata/performance/SampleMaterial.lc 1453:7-1453:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1453:7-1454:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1453:7-1455:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1453:7-1456:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1453:7-1457:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1453:7-1458:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1453:7-1459:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1453:7-1460:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1453:7-1461:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1453:7-1462:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1453:7-1463:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1453:7-1491:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1453:7-1493:10 @@ -9989,41 +9751,41 @@ testdata/performance/SampleMaterial.lc 1459:23-1459:28 testdata/performance/SampleMaterial.lc 1460:20-1460:33 CullType testdata/performance/SampleMaterial.lc 1461:30-1461:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1462:25-1462:30 Bool testdata/performance/SampleMaterial.lc 1463:29-1463:34 Bool testdata/performance/SampleMaterial.lc 1465:13-1491:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 1465:15-1465:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1465:15-1466:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1465:15-1467:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1465:15-1468:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1465:15-1469:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1465:15-1470:31 @@ -10050,7 +9812,7 @@ testdata/performance/SampleMaterial.lc 1468:32-1468:42 testdata/performance/SampleMaterial.lc 1469:29-1469:36 TCGen testdata/performance/SampleMaterial.lc 1470:29-1470:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1471:31-1471:37 String -> StageTexture testdata/performance/SampleMaterial.lc 1471:31-1471:75 @@ -10072,29 +9834,29 @@ testdata/performance/SampleMaterial.lc 1478:15-1478:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1478:15-1479:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1478:15-1480:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1478:15-1481:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1478:15-1482:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1478:15-1483:31 @@ -10111,7 +9873,7 @@ testdata/performance/SampleMaterial.lc 1478:15-1487:40 testdata/performance/SampleMaterial.lc 1478:15-1488:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 1478:15-1490:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 1479:29-1479:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 1479:29-1479:57 @@ -10129,7 +9891,7 @@ testdata/performance/SampleMaterial.lc 1481:32-1481:42 testdata/performance/SampleMaterial.lc 1482:29-1482:40 TCGen testdata/performance/SampleMaterial.lc 1483:29-1483:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1484:31-1484:42 StageTexture testdata/performance/SampleMaterial.lc 1485:34-1485:38 @@ -10147,7 +9909,7 @@ testdata/performance/SampleMaterial.lc 1492:21-1492:26 testdata/performance/SampleMaterial.lc 1495:5-1537:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 1495:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 1495:7-1495:45 String testdata/performance/SampleMaterial.lc 1496:7-1496:18 @@ -10157,49 +9919,42 @@ testdata/performance/SampleMaterial.lc 1496:7-1496:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1496:7-1497:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1496:7-1498:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1496:7-1499:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1496:7-1500:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1496:7-1501:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1496:7-1502:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1496:7-1503:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1496:7-1504:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1496:7-1505:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1496:7-1506:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1496:7-1534:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1496:7-1536:10 @@ -10219,41 +9974,41 @@ testdata/performance/SampleMaterial.lc 1502:23-1502:28 testdata/performance/SampleMaterial.lc 1503:20-1503:33 CullType testdata/performance/SampleMaterial.lc 1504:30-1504:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1505:25-1505:30 Bool testdata/performance/SampleMaterial.lc 1506:29-1506:34 Bool testdata/performance/SampleMaterial.lc 1508:13-1534:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 1508:15-1508:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1508:15-1509:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1508:15-1510:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1508:15-1511:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1508:15-1512:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1508:15-1513:31 @@ -10280,7 +10035,7 @@ testdata/performance/SampleMaterial.lc 1511:32-1511:42 testdata/performance/SampleMaterial.lc 1512:29-1512:36 TCGen testdata/performance/SampleMaterial.lc 1513:29-1513:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1514:31-1514:37 String -> StageTexture testdata/performance/SampleMaterial.lc 1514:31-1514:76 @@ -10302,29 +10057,29 @@ testdata/performance/SampleMaterial.lc 1521:15-1521:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1521:15-1522:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1521:15-1523:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1521:15-1524:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1521:15-1525:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1521:15-1526:31 @@ -10341,7 +10096,7 @@ testdata/performance/SampleMaterial.lc 1521:15-1530:40 testdata/performance/SampleMaterial.lc 1521:15-1531:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 1521:15-1533:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 1522:29-1522:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 1522:29-1522:57 @@ -10359,7 +10114,7 @@ testdata/performance/SampleMaterial.lc 1524:32-1524:42 testdata/performance/SampleMaterial.lc 1525:29-1525:40 TCGen testdata/performance/SampleMaterial.lc 1526:29-1526:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1527:31-1527:42 StageTexture testdata/performance/SampleMaterial.lc 1528:34-1528:38 @@ -10377,7 +10132,7 @@ testdata/performance/SampleMaterial.lc 1535:21-1535:26 testdata/performance/SampleMaterial.lc 1538:5-1580:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 1538:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 1538:7-1538:47 String testdata/performance/SampleMaterial.lc 1539:7-1539:18 @@ -10387,49 +10142,42 @@ testdata/performance/SampleMaterial.lc 1539:7-1539:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1539:7-1540:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1539:7-1541:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1539:7-1542:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1539:7-1543:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1539:7-1544:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1539:7-1545:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1539:7-1546:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1539:7-1547:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1539:7-1548:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1539:7-1549:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1539:7-1577:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1539:7-1579:10 @@ -10449,41 +10197,41 @@ testdata/performance/SampleMaterial.lc 1545:23-1545:28 testdata/performance/SampleMaterial.lc 1546:20-1546:33 CullType testdata/performance/SampleMaterial.lc 1547:30-1547:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1548:25-1548:30 Bool testdata/performance/SampleMaterial.lc 1549:29-1549:34 Bool testdata/performance/SampleMaterial.lc 1551:13-1577:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 1551:15-1551:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1551:15-1552:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1551:15-1553:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1551:15-1554:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1551:15-1555:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1551:15-1556:31 @@ -10510,7 +10258,7 @@ testdata/performance/SampleMaterial.lc 1554:32-1554:42 testdata/performance/SampleMaterial.lc 1555:29-1555:36 TCGen testdata/performance/SampleMaterial.lc 1556:29-1556:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1557:31-1557:37 String -> StageTexture testdata/performance/SampleMaterial.lc 1557:31-1557:78 @@ -10532,29 +10280,29 @@ testdata/performance/SampleMaterial.lc 1564:15-1564:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1564:15-1565:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1564:15-1566:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1564:15-1567:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1564:15-1568:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1564:15-1569:31 @@ -10571,7 +10319,7 @@ testdata/performance/SampleMaterial.lc 1564:15-1573:40 testdata/performance/SampleMaterial.lc 1564:15-1574:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 1564:15-1576:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 1565:29-1565:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 1565:29-1565:57 @@ -10589,7 +10337,7 @@ testdata/performance/SampleMaterial.lc 1567:32-1567:42 testdata/performance/SampleMaterial.lc 1568:29-1568:40 TCGen testdata/performance/SampleMaterial.lc 1569:29-1569:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1570:31-1570:42 StageTexture testdata/performance/SampleMaterial.lc 1571:34-1571:38 @@ -10607,7 +10355,7 @@ testdata/performance/SampleMaterial.lc 1578:21-1578:26 testdata/performance/SampleMaterial.lc 1581:5-1623:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 1581:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 1581:7-1581:49 String testdata/performance/SampleMaterial.lc 1582:7-1582:18 @@ -10617,49 +10365,42 @@ testdata/performance/SampleMaterial.lc 1582:7-1582:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1582:7-1583:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1582:7-1584:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1582:7-1585:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1582:7-1586:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1582:7-1587:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1582:7-1588:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1582:7-1589:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1582:7-1590:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1582:7-1591:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1582:7-1592:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1582:7-1620:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1582:7-1622:10 @@ -10679,41 +10420,41 @@ testdata/performance/SampleMaterial.lc 1588:23-1588:28 testdata/performance/SampleMaterial.lc 1589:20-1589:33 CullType testdata/performance/SampleMaterial.lc 1590:30-1590:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1591:25-1591:30 Bool testdata/performance/SampleMaterial.lc 1592:29-1592:34 Bool testdata/performance/SampleMaterial.lc 1594:13-1620:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 1594:15-1594:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1594:15-1595:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1594:15-1596:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1594:15-1597:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1594:15-1598:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1594:15-1599:31 @@ -10740,7 +10481,7 @@ testdata/performance/SampleMaterial.lc 1597:32-1597:42 testdata/performance/SampleMaterial.lc 1598:29-1598:36 TCGen testdata/performance/SampleMaterial.lc 1599:29-1599:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1600:31-1600:37 String -> StageTexture testdata/performance/SampleMaterial.lc 1600:31-1600:80 @@ -10762,29 +10503,29 @@ testdata/performance/SampleMaterial.lc 1607:15-1607:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1607:15-1608:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1607:15-1609:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1607:15-1610:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1607:15-1611:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1607:15-1612:31 @@ -10801,7 +10542,7 @@ testdata/performance/SampleMaterial.lc 1607:15-1616:40 testdata/performance/SampleMaterial.lc 1607:15-1617:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 1607:15-1619:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 1608:29-1608:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 1608:29-1608:57 @@ -10819,7 +10560,7 @@ testdata/performance/SampleMaterial.lc 1610:32-1610:42 testdata/performance/SampleMaterial.lc 1611:29-1611:40 TCGen testdata/performance/SampleMaterial.lc 1612:29-1612:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1613:31-1613:42 StageTexture testdata/performance/SampleMaterial.lc 1614:34-1614:38 @@ -10837,7 +10578,7 @@ testdata/performance/SampleMaterial.lc 1621:21-1621:26 testdata/performance/SampleMaterial.lc 1624:5-1666:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 1624:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 1624:7-1624:44 String testdata/performance/SampleMaterial.lc 1625:7-1625:18 @@ -10847,49 +10588,42 @@ testdata/performance/SampleMaterial.lc 1625:7-1625:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1625:7-1626:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1625:7-1627:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1625:7-1628:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1625:7-1629:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1625:7-1630:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1625:7-1631:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1625:7-1632:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1625:7-1633:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1625:7-1634:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1625:7-1635:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1625:7-1663:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1625:7-1665:10 @@ -10909,41 +10643,41 @@ testdata/performance/SampleMaterial.lc 1631:23-1631:28 testdata/performance/SampleMaterial.lc 1632:20-1632:33 CullType testdata/performance/SampleMaterial.lc 1633:30-1633:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1634:25-1634:30 Bool testdata/performance/SampleMaterial.lc 1635:29-1635:34 Bool testdata/performance/SampleMaterial.lc 1637:13-1663:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 1637:15-1637:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1637:15-1638:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1637:15-1639:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1637:15-1640:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1637:15-1641:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1637:15-1642:31 @@ -10970,7 +10704,7 @@ testdata/performance/SampleMaterial.lc 1640:32-1640:42 testdata/performance/SampleMaterial.lc 1641:29-1641:36 TCGen testdata/performance/SampleMaterial.lc 1642:29-1642:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1643:31-1643:37 String -> StageTexture testdata/performance/SampleMaterial.lc 1643:31-1643:75 @@ -10992,29 +10726,29 @@ testdata/performance/SampleMaterial.lc 1650:15-1650:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1650:15-1651:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1650:15-1652:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1650:15-1653:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1650:15-1654:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1650:15-1655:31 @@ -11031,7 +10765,7 @@ testdata/performance/SampleMaterial.lc 1650:15-1659:40 testdata/performance/SampleMaterial.lc 1650:15-1660:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 1650:15-1662:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 1651:29-1651:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 1651:29-1651:57 @@ -11049,7 +10783,7 @@ testdata/performance/SampleMaterial.lc 1653:32-1653:42 testdata/performance/SampleMaterial.lc 1654:29-1654:40 TCGen testdata/performance/SampleMaterial.lc 1655:29-1655:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1656:31-1656:42 StageTexture testdata/performance/SampleMaterial.lc 1657:34-1657:38 @@ -11067,7 +10801,7 @@ testdata/performance/SampleMaterial.lc 1664:21-1664:26 testdata/performance/SampleMaterial.lc 1667:5-1709:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 1667:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 1667:7-1667:43 String testdata/performance/SampleMaterial.lc 1668:7-1668:18 @@ -11077,49 +10811,42 @@ testdata/performance/SampleMaterial.lc 1668:7-1668:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1668:7-1669:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1668:7-1670:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1668:7-1671:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1668:7-1672:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1668:7-1673:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1668:7-1674:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1668:7-1675:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1668:7-1676:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1668:7-1677:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1668:7-1678:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1668:7-1706:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1668:7-1708:10 @@ -11139,41 +10866,41 @@ testdata/performance/SampleMaterial.lc 1674:23-1674:28 testdata/performance/SampleMaterial.lc 1675:20-1675:33 CullType testdata/performance/SampleMaterial.lc 1676:30-1676:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1677:25-1677:30 Bool testdata/performance/SampleMaterial.lc 1678:29-1678:34 Bool testdata/performance/SampleMaterial.lc 1680:13-1706:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 1680:15-1680:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1680:15-1681:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1680:15-1682:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1680:15-1683:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1680:15-1684:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1680:15-1685:31 @@ -11200,7 +10927,7 @@ testdata/performance/SampleMaterial.lc 1683:32-1683:42 testdata/performance/SampleMaterial.lc 1684:29-1684:36 TCGen testdata/performance/SampleMaterial.lc 1685:29-1685:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1686:31-1686:37 String -> StageTexture testdata/performance/SampleMaterial.lc 1686:31-1686:74 @@ -11222,29 +10949,29 @@ testdata/performance/SampleMaterial.lc 1693:15-1693:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1693:15-1694:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1693:15-1695:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1693:15-1696:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1693:15-1697:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1693:15-1698:31 @@ -11261,7 +10988,7 @@ testdata/performance/SampleMaterial.lc 1693:15-1702:40 testdata/performance/SampleMaterial.lc 1693:15-1703:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 1693:15-1705:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 1694:29-1694:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 1694:29-1694:57 @@ -11279,7 +11006,7 @@ testdata/performance/SampleMaterial.lc 1696:32-1696:42 testdata/performance/SampleMaterial.lc 1697:29-1697:40 TCGen testdata/performance/SampleMaterial.lc 1698:29-1698:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1699:31-1699:42 StageTexture testdata/performance/SampleMaterial.lc 1700:34-1700:38 @@ -11297,7 +11024,7 @@ testdata/performance/SampleMaterial.lc 1707:21-1707:26 testdata/performance/SampleMaterial.lc 1710:5-1752:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 1710:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 1710:7-1710:41 String testdata/performance/SampleMaterial.lc 1711:7-1711:18 @@ -11307,49 +11034,42 @@ testdata/performance/SampleMaterial.lc 1711:7-1711:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1711:7-1712:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1711:7-1713:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1711:7-1714:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1711:7-1715:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1711:7-1716:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1711:7-1717:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1711:7-1718:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1711:7-1719:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1711:7-1720:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1711:7-1721:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1711:7-1749:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1711:7-1751:10 @@ -11369,41 +11089,41 @@ testdata/performance/SampleMaterial.lc 1717:23-1717:28 testdata/performance/SampleMaterial.lc 1718:20-1718:33 CullType testdata/performance/SampleMaterial.lc 1719:30-1719:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1720:25-1720:30 Bool testdata/performance/SampleMaterial.lc 1721:29-1721:34 Bool testdata/performance/SampleMaterial.lc 1723:13-1749:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 1723:15-1723:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1723:15-1724:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1723:15-1725:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1723:15-1726:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1723:15-1727:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1723:15-1728:31 @@ -11430,7 +11150,7 @@ testdata/performance/SampleMaterial.lc 1726:32-1726:42 testdata/performance/SampleMaterial.lc 1727:29-1727:36 TCGen testdata/performance/SampleMaterial.lc 1728:29-1728:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1729:31-1729:37 String -> StageTexture testdata/performance/SampleMaterial.lc 1729:31-1729:72 @@ -11452,29 +11172,29 @@ testdata/performance/SampleMaterial.lc 1736:15-1736:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1736:15-1737:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1736:15-1738:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1736:15-1739:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1736:15-1740:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1736:15-1741:31 @@ -11491,7 +11211,7 @@ testdata/performance/SampleMaterial.lc 1736:15-1745:40 testdata/performance/SampleMaterial.lc 1736:15-1746:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 1736:15-1748:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 1737:29-1737:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 1737:29-1737:57 @@ -11509,7 +11229,7 @@ testdata/performance/SampleMaterial.lc 1739:32-1739:42 testdata/performance/SampleMaterial.lc 1740:29-1740:40 TCGen testdata/performance/SampleMaterial.lc 1741:29-1741:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1742:31-1742:42 StageTexture testdata/performance/SampleMaterial.lc 1743:34-1743:38 @@ -11527,7 +11247,7 @@ testdata/performance/SampleMaterial.lc 1750:21-1750:26 testdata/performance/SampleMaterial.lc 1753:5-1795:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 1753:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 1753:7-1753:42 String testdata/performance/SampleMaterial.lc 1754:7-1754:18 @@ -11537,49 +11257,42 @@ testdata/performance/SampleMaterial.lc 1754:7-1754:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1754:7-1755:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1754:7-1756:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1754:7-1757:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1754:7-1758:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1754:7-1759:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1754:7-1760:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1754:7-1761:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1754:7-1762:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1754:7-1763:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1754:7-1764:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1754:7-1792:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1754:7-1794:10 @@ -11599,41 +11312,41 @@ testdata/performance/SampleMaterial.lc 1760:23-1760:28 testdata/performance/SampleMaterial.lc 1761:20-1761:33 CullType testdata/performance/SampleMaterial.lc 1762:30-1762:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1763:25-1763:30 Bool testdata/performance/SampleMaterial.lc 1764:29-1764:34 Bool testdata/performance/SampleMaterial.lc 1766:13-1792:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 1766:15-1766:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1766:15-1767:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1766:15-1768:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1766:15-1769:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1766:15-1770:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1766:15-1771:31 @@ -11660,7 +11373,7 @@ testdata/performance/SampleMaterial.lc 1769:32-1769:42 testdata/performance/SampleMaterial.lc 1770:29-1770:36 TCGen testdata/performance/SampleMaterial.lc 1771:29-1771:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1772:31-1772:37 String -> StageTexture testdata/performance/SampleMaterial.lc 1772:31-1772:73 @@ -11682,29 +11395,29 @@ testdata/performance/SampleMaterial.lc 1779:15-1779:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1779:15-1780:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1779:15-1781:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1779:15-1782:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1779:15-1783:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1779:15-1784:31 @@ -11721,7 +11434,7 @@ testdata/performance/SampleMaterial.lc 1779:15-1788:40 testdata/performance/SampleMaterial.lc 1779:15-1789:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 1779:15-1791:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 1780:29-1780:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 1780:29-1780:57 @@ -11739,7 +11452,7 @@ testdata/performance/SampleMaterial.lc 1782:32-1782:42 testdata/performance/SampleMaterial.lc 1783:29-1783:40 TCGen testdata/performance/SampleMaterial.lc 1784:29-1784:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1785:31-1785:42 StageTexture testdata/performance/SampleMaterial.lc 1786:34-1786:38 @@ -11757,7 +11470,7 @@ testdata/performance/SampleMaterial.lc 1793:21-1793:26 testdata/performance/SampleMaterial.lc 1796:5-1838:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 1796:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 1796:7-1796:48 String testdata/performance/SampleMaterial.lc 1797:7-1797:18 @@ -11767,49 +11480,42 @@ testdata/performance/SampleMaterial.lc 1797:7-1797:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1797:7-1798:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1797:7-1799:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1797:7-1800:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1797:7-1801:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1797:7-1802:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1797:7-1803:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1797:7-1804:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1797:7-1805:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1797:7-1806:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1797:7-1807:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1797:7-1835:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1797:7-1837:10 @@ -11829,41 +11535,41 @@ testdata/performance/SampleMaterial.lc 1803:23-1803:28 testdata/performance/SampleMaterial.lc 1804:20-1804:33 CullType testdata/performance/SampleMaterial.lc 1805:30-1805:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1806:25-1806:30 Bool testdata/performance/SampleMaterial.lc 1807:29-1807:34 Bool testdata/performance/SampleMaterial.lc 1809:13-1835:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 1809:15-1809:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1809:15-1810:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1809:15-1811:42 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1809:15-1812:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1809:15-1813:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1809:15-1814:31 @@ -11890,7 +11596,7 @@ testdata/performance/SampleMaterial.lc 1812:32-1812:42 testdata/performance/SampleMaterial.lc 1813:29-1813:40 TCGen testdata/performance/SampleMaterial.lc 1814:29-1814:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1815:31-1815:42 StageTexture testdata/performance/SampleMaterial.lc 1816:34-1816:38 @@ -11908,29 +11614,29 @@ testdata/performance/SampleMaterial.lc 1822:15-1822:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1822:15-1823:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1822:15-1824:42 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1822:15-1825:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1822:15-1826:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1822:15-1827:31 @@ -11947,7 +11653,7 @@ testdata/performance/SampleMaterial.lc 1822:15-1831:40 testdata/performance/SampleMaterial.lc 1822:15-1832:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 1822:15-1834:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 1823:29-1823:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 1823:29-1823:57 @@ -11965,7 +11671,7 @@ testdata/performance/SampleMaterial.lc 1825:32-1825:42 testdata/performance/SampleMaterial.lc 1826:29-1826:36 TCGen testdata/performance/SampleMaterial.lc 1827:29-1827:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1828:31-1828:37 String -> StageTexture testdata/performance/SampleMaterial.lc 1828:31-1828:77 @@ -11987,7 +11693,7 @@ testdata/performance/SampleMaterial.lc 1836:21-1836:26 testdata/performance/SampleMaterial.lc 1839:5-1881:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 1839:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 1839:7-1839:42 String testdata/performance/SampleMaterial.lc 1840:7-1840:18 @@ -11997,49 +11703,42 @@ testdata/performance/SampleMaterial.lc 1840:7-1840:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1840:7-1841:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1840:7-1842:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1840:7-1843:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1840:7-1844:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1840:7-1845:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1840:7-1846:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1840:7-1847:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1840:7-1848:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1840:7-1849:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1840:7-1850:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1840:7-1878:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1840:7-1880:10 @@ -12059,41 +11758,41 @@ testdata/performance/SampleMaterial.lc 1846:23-1846:28 testdata/performance/SampleMaterial.lc 1847:20-1847:33 CullType testdata/performance/SampleMaterial.lc 1848:30-1848:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1849:25-1849:30 Bool testdata/performance/SampleMaterial.lc 1850:29-1850:34 Bool testdata/performance/SampleMaterial.lc 1852:13-1878:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 1852:15-1852:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1852:15-1853:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1852:15-1854:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1852:15-1855:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1852:15-1856:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1852:15-1857:31 @@ -12120,7 +11819,7 @@ testdata/performance/SampleMaterial.lc 1855:32-1855:42 testdata/performance/SampleMaterial.lc 1856:29-1856:36 TCGen testdata/performance/SampleMaterial.lc 1857:29-1857:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1858:31-1858:37 String -> StageTexture testdata/performance/SampleMaterial.lc 1858:31-1858:73 @@ -12142,29 +11841,29 @@ testdata/performance/SampleMaterial.lc 1865:15-1865:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1865:15-1866:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1865:15-1867:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1865:15-1868:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1865:15-1869:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1865:15-1870:31 @@ -12181,7 +11880,7 @@ testdata/performance/SampleMaterial.lc 1865:15-1874:40 testdata/performance/SampleMaterial.lc 1865:15-1875:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 1865:15-1877:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 1866:29-1866:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 1866:29-1866:57 @@ -12199,7 +11898,7 @@ testdata/performance/SampleMaterial.lc 1868:32-1868:42 testdata/performance/SampleMaterial.lc 1869:29-1869:40 TCGen testdata/performance/SampleMaterial.lc 1870:29-1870:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1871:31-1871:42 StageTexture testdata/performance/SampleMaterial.lc 1872:34-1872:38 @@ -12217,7 +11916,7 @@ testdata/performance/SampleMaterial.lc 1879:21-1879:26 testdata/performance/SampleMaterial.lc 1882:5-1924:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 1882:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 1882:7-1882:47 String testdata/performance/SampleMaterial.lc 1883:7-1883:18 @@ -12227,49 +11926,42 @@ testdata/performance/SampleMaterial.lc 1883:7-1883:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1883:7-1884:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1883:7-1885:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1883:7-1886:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1883:7-1887:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1883:7-1888:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1883:7-1889:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1883:7-1890:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1883:7-1891:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1883:7-1892:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1883:7-1893:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1883:7-1921:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1883:7-1923:10 @@ -12289,41 +11981,41 @@ testdata/performance/SampleMaterial.lc 1889:23-1889:28 testdata/performance/SampleMaterial.lc 1890:20-1890:33 CullType testdata/performance/SampleMaterial.lc 1891:30-1891:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1892:25-1892:30 Bool testdata/performance/SampleMaterial.lc 1893:29-1893:34 Bool testdata/performance/SampleMaterial.lc 1895:13-1921:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 1895:15-1895:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1895:15-1896:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1895:15-1897:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1895:15-1898:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1895:15-1899:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1895:15-1900:31 @@ -12350,7 +12042,7 @@ testdata/performance/SampleMaterial.lc 1898:32-1898:42 testdata/performance/SampleMaterial.lc 1899:29-1899:36 TCGen testdata/performance/SampleMaterial.lc 1900:29-1900:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1901:31-1901:37 String -> StageTexture testdata/performance/SampleMaterial.lc 1901:31-1901:78 @@ -12372,29 +12064,29 @@ testdata/performance/SampleMaterial.lc 1908:15-1908:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1908:15-1909:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1908:15-1910:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1908:15-1911:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1908:15-1912:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1908:15-1913:31 @@ -12411,7 +12103,7 @@ testdata/performance/SampleMaterial.lc 1908:15-1917:40 testdata/performance/SampleMaterial.lc 1908:15-1918:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 1908:15-1920:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 1909:29-1909:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 1909:29-1909:57 @@ -12429,7 +12121,7 @@ testdata/performance/SampleMaterial.lc 1911:32-1911:42 testdata/performance/SampleMaterial.lc 1912:29-1912:40 TCGen testdata/performance/SampleMaterial.lc 1913:29-1913:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1914:31-1914:42 StageTexture testdata/performance/SampleMaterial.lc 1915:34-1915:38 @@ -12447,7 +12139,7 @@ testdata/performance/SampleMaterial.lc 1922:21-1922:26 testdata/performance/SampleMaterial.lc 1925:5-1967:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 1925:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 1925:7-1925:38 String testdata/performance/SampleMaterial.lc 1926:7-1926:18 @@ -12457,49 +12149,42 @@ testdata/performance/SampleMaterial.lc 1926:7-1926:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1926:7-1927:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1926:7-1928:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1926:7-1929:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1926:7-1930:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1926:7-1931:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1926:7-1932:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1926:7-1933:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1926:7-1934:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1926:7-1935:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1926:7-1936:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1926:7-1964:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1926:7-1966:10 @@ -12519,41 +12204,41 @@ testdata/performance/SampleMaterial.lc 1932:23-1932:28 testdata/performance/SampleMaterial.lc 1933:20-1933:33 CullType testdata/performance/SampleMaterial.lc 1934:30-1934:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1935:25-1935:30 Bool testdata/performance/SampleMaterial.lc 1936:29-1936:34 Bool testdata/performance/SampleMaterial.lc 1938:13-1964:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 1938:15-1938:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1938:15-1939:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1938:15-1940:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1938:15-1941:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1938:15-1942:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1938:15-1943:31 @@ -12580,7 +12265,7 @@ testdata/performance/SampleMaterial.lc 1941:32-1941:42 testdata/performance/SampleMaterial.lc 1942:29-1942:36 TCGen testdata/performance/SampleMaterial.lc 1943:29-1943:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1944:31-1944:37 String -> StageTexture testdata/performance/SampleMaterial.lc 1944:31-1944:69 @@ -12602,29 +12287,29 @@ testdata/performance/SampleMaterial.lc 1951:15-1951:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1951:15-1952:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1951:15-1953:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1951:15-1954:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1951:15-1955:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1951:15-1956:31 @@ -12641,7 +12326,7 @@ testdata/performance/SampleMaterial.lc 1951:15-1960:40 testdata/performance/SampleMaterial.lc 1951:15-1961:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 1951:15-1963:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 1952:29-1952:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 1952:29-1952:57 @@ -12659,7 +12344,7 @@ testdata/performance/SampleMaterial.lc 1954:32-1954:42 testdata/performance/SampleMaterial.lc 1955:29-1955:40 TCGen testdata/performance/SampleMaterial.lc 1956:29-1956:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1957:31-1957:42 StageTexture testdata/performance/SampleMaterial.lc 1958:34-1958:38 @@ -12677,7 +12362,7 @@ testdata/performance/SampleMaterial.lc 1965:21-1965:26 testdata/performance/SampleMaterial.lc 1968:5-2010:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 1968:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 1968:7-1968:43 String testdata/performance/SampleMaterial.lc 1969:7-1969:18 @@ -12687,49 +12372,42 @@ testdata/performance/SampleMaterial.lc 1969:7-1969:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1969:7-1970:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1969:7-1971:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1969:7-1972:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1969:7-1973:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1969:7-1974:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1969:7-1975:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1969:7-1976:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1969:7-1977:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1969:7-1978:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1969:7-1979:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1969:7-2007:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 1969:7-2009:10 @@ -12749,41 +12427,41 @@ testdata/performance/SampleMaterial.lc 1975:23-1975:28 testdata/performance/SampleMaterial.lc 1976:20-1976:33 CullType testdata/performance/SampleMaterial.lc 1977:30-1977:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1978:25-1978:30 Bool testdata/performance/SampleMaterial.lc 1979:29-1979:34 Bool testdata/performance/SampleMaterial.lc 1981:13-2007:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 1981:15-1981:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1981:15-1982:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1981:15-1983:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1981:15-1984:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1981:15-1985:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1981:15-1986:31 @@ -12810,7 +12488,7 @@ testdata/performance/SampleMaterial.lc 1984:32-1984:42 testdata/performance/SampleMaterial.lc 1985:29-1985:36 TCGen testdata/performance/SampleMaterial.lc 1986:29-1986:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 1987:31-1987:37 String -> StageTexture testdata/performance/SampleMaterial.lc 1987:31-1987:74 @@ -12832,29 +12510,29 @@ testdata/performance/SampleMaterial.lc 1994:15-1994:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1994:15-1995:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1994:15-1996:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1994:15-1997:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1994:15-1998:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 1994:15-1999:31 @@ -12871,7 +12549,7 @@ testdata/performance/SampleMaterial.lc 1994:15-2003:40 testdata/performance/SampleMaterial.lc 1994:15-2004:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 1994:15-2006:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 1995:29-1995:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 1995:29-1995:57 @@ -12889,7 +12567,7 @@ testdata/performance/SampleMaterial.lc 1997:32-1997:42 testdata/performance/SampleMaterial.lc 1998:29-1998:40 TCGen testdata/performance/SampleMaterial.lc 1999:29-1999:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 2000:31-2000:42 StageTexture testdata/performance/SampleMaterial.lc 2001:34-2001:38 @@ -12907,7 +12585,7 @@ testdata/performance/SampleMaterial.lc 2008:21-2008:26 testdata/performance/SampleMaterial.lc 2011:5-2053:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 2011:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 2011:7-2011:36 String testdata/performance/SampleMaterial.lc 2012:7-2012:18 @@ -12917,49 +12595,42 @@ testdata/performance/SampleMaterial.lc 2012:7-2012:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2012:7-2013:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2012:7-2014:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2012:7-2015:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2012:7-2016:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2012:7-2017:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2012:7-2018:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2012:7-2019:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2012:7-2020:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2012:7-2021:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2012:7-2022:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2012:7-2050:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2012:7-2052:10 @@ -12979,41 +12650,41 @@ testdata/performance/SampleMaterial.lc 2018:23-2018:28 testdata/performance/SampleMaterial.lc 2019:20-2019:33 CullType testdata/performance/SampleMaterial.lc 2020:30-2020:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 2021:25-2021:30 Bool testdata/performance/SampleMaterial.lc 2022:29-2022:34 Bool testdata/performance/SampleMaterial.lc 2024:13-2050:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 2024:15-2024:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 2024:15-2025:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 2024:15-2026:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 2024:15-2027:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 2024:15-2028:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 2024:15-2029:31 @@ -13040,7 +12711,7 @@ testdata/performance/SampleMaterial.lc 2027:32-2027:42 testdata/performance/SampleMaterial.lc 2028:29-2028:36 TCGen testdata/performance/SampleMaterial.lc 2029:29-2029:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 2030:31-2030:37 String -> StageTexture testdata/performance/SampleMaterial.lc 2030:31-2030:67 @@ -13062,29 +12733,29 @@ testdata/performance/SampleMaterial.lc 2037:15-2037:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 2037:15-2038:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 2037:15-2039:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 2037:15-2040:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 2037:15-2041:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 2037:15-2042:31 @@ -13101,7 +12772,7 @@ testdata/performance/SampleMaterial.lc 2037:15-2046:40 testdata/performance/SampleMaterial.lc 2037:15-2047:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 2037:15-2049:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 2038:29-2038:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 2038:29-2038:57 @@ -13119,7 +12790,7 @@ testdata/performance/SampleMaterial.lc 2040:32-2040:42 testdata/performance/SampleMaterial.lc 2041:29-2041:40 TCGen testdata/performance/SampleMaterial.lc 2042:29-2042:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 2043:31-2043:42 StageTexture testdata/performance/SampleMaterial.lc 2044:34-2044:38 @@ -13137,7 +12808,7 @@ testdata/performance/SampleMaterial.lc 2051:21-2051:26 testdata/performance/SampleMaterial.lc 2054:5-2096:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 2054:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 2054:7-2054:40 String testdata/performance/SampleMaterial.lc 2055:7-2055:18 @@ -13147,49 +12818,42 @@ testdata/performance/SampleMaterial.lc 2055:7-2055:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2055:7-2056:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2055:7-2057:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2055:7-2058:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2055:7-2059:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2055:7-2060:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2055:7-2061:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2055:7-2062:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2055:7-2063:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2055:7-2064:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2055:7-2065:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2055:7-2093:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2055:7-2095:10 @@ -13209,41 +12873,41 @@ testdata/performance/SampleMaterial.lc 2061:23-2061:28 testdata/performance/SampleMaterial.lc 2062:20-2062:33 CullType testdata/performance/SampleMaterial.lc 2063:30-2063:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 2064:25-2064:30 Bool testdata/performance/SampleMaterial.lc 2065:29-2065:34 Bool testdata/performance/SampleMaterial.lc 2067:13-2093:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 2067:15-2067:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 2067:15-2068:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 2067:15-2069:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 2067:15-2070:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 2067:15-2071:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 2067:15-2072:31 @@ -13270,7 +12934,7 @@ testdata/performance/SampleMaterial.lc 2070:32-2070:42 testdata/performance/SampleMaterial.lc 2071:29-2071:36 TCGen testdata/performance/SampleMaterial.lc 2072:29-2072:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 2073:31-2073:37 String -> StageTexture testdata/performance/SampleMaterial.lc 2073:31-2073:71 @@ -13292,29 +12956,29 @@ testdata/performance/SampleMaterial.lc 2080:15-2080:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 2080:15-2081:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 2080:15-2082:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 2080:15-2083:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 2080:15-2084:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 2080:15-2085:31 @@ -13331,7 +12995,7 @@ testdata/performance/SampleMaterial.lc 2080:15-2089:40 testdata/performance/SampleMaterial.lc 2080:15-2090:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 2080:15-2092:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 2081:29-2081:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 2081:29-2081:57 @@ -13349,7 +13013,7 @@ testdata/performance/SampleMaterial.lc 2083:32-2083:42 testdata/performance/SampleMaterial.lc 2084:29-2084:40 TCGen testdata/performance/SampleMaterial.lc 2085:29-2085:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 2086:31-2086:42 StageTexture testdata/performance/SampleMaterial.lc 2087:34-2087:38 @@ -13367,7 +13031,7 @@ testdata/performance/SampleMaterial.lc 2094:21-2094:26 testdata/performance/SampleMaterial.lc 2097:5-2139:6 (String, CommonAttrs) testdata/performance/SampleMaterial.lc 2097:5-2182:6 - List (String, CommonAttrs) + [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 2097:7-2097:50 String testdata/performance/SampleMaterial.lc 2098:7-2098:18 @@ -13377,49 +13041,42 @@ testdata/performance/SampleMaterial.lc 2098:7-2098:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2098:7-2099:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2098:7-2100:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2098:7-2101:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2098:7-2102:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2098:7-2103:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2098:7-2104:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2098:7-2105:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2098:7-2106:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2098:7-2107:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2098:7-2108:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2098:7-2136:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2098:7-2138:10 @@ -13439,41 +13096,41 @@ testdata/performance/SampleMaterial.lc 2104:23-2104:28 testdata/performance/SampleMaterial.lc 2105:20-2105:33 CullType testdata/performance/SampleMaterial.lc 2106:30-2106:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 2107:25-2107:30 Bool testdata/performance/SampleMaterial.lc 2108:29-2108:34 Bool testdata/performance/SampleMaterial.lc 2110:13-2136:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 2110:15-2110:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 2110:15-2111:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 2110:15-2112:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 2110:15-2113:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 2110:15-2114:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 2110:15-2115:31 @@ -13500,7 +13157,7 @@ testdata/performance/SampleMaterial.lc 2113:32-2113:42 testdata/performance/SampleMaterial.lc 2114:29-2114:36 TCGen testdata/performance/SampleMaterial.lc 2115:29-2115:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 2116:31-2116:37 String -> StageTexture testdata/performance/SampleMaterial.lc 2116:31-2116:81 @@ -13522,29 +13179,29 @@ testdata/performance/SampleMaterial.lc 2123:15-2123:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 2123:15-2124:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 2123:15-2125:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 2123:15-2126:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 2123:15-2127:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 2123:15-2128:31 @@ -13561,7 +13218,7 @@ testdata/performance/SampleMaterial.lc 2123:15-2132:40 testdata/performance/SampleMaterial.lc 2123:15-2133:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 2123:15-2135:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 2124:29-2124:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 2124:29-2124:57 @@ -13579,7 +13236,7 @@ testdata/performance/SampleMaterial.lc 2126:32-2126:42 testdata/performance/SampleMaterial.lc 2127:29-2127:40 TCGen testdata/performance/SampleMaterial.lc 2128:29-2128:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 2129:31-2129:42 StageTexture testdata/performance/SampleMaterial.lc 2130:34-2130:38 @@ -13595,7 +13252,7 @@ testdata/performance/SampleMaterial.lc 2134:38-2134:54 testdata/performance/SampleMaterial.lc 2137:21-2137:26 Bool testdata/performance/SampleMaterial.lc 2140:5-2182:6 - (String, CommonAttrs) | List (String, CommonAttrs) + (String, CommonAttrs) | [(String, CommonAttrs)] testdata/performance/SampleMaterial.lc 2140:7-2140:50 String testdata/performance/SampleMaterial.lc 2141:7-2141:18 @@ -13605,49 +13262,42 @@ testdata/performance/SampleMaterial.lc 2141:7-2141:18 -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2141:7-2142:26 () -> Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2141:7-2143:26 Bool -> Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2141:7-2144:27 Float -> Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2141:7-2145:21 Bool -> Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2141:7-2146:35 Bool - -> CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + -> CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2141:7-2147:28 - CullType - -> List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + CullType -> [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2141:7-2148:33 - List Deform -> Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + [Deform] -> Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2141:7-2149:32 - Bool -> Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2141:7-2150:30 - Bool -> List StageAttrs -> Bool -> CommonAttrs + Bool -> [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2141:7-2151:34 - List StageAttrs -> Bool -> CommonAttrs + [StageAttrs] -> Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2141:7-2179:14 Bool -> CommonAttrs testdata/performance/SampleMaterial.lc 2141:7-2181:10 @@ -13667,41 +13317,41 @@ testdata/performance/SampleMaterial.lc 2147:23-2147:28 testdata/performance/SampleMaterial.lc 2148:20-2148:33 CullType testdata/performance/SampleMaterial.lc 2149:30-2149:32 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 2150:25-2150:30 Bool testdata/performance/SampleMaterial.lc 2151:29-2151:34 Bool testdata/performance/SampleMaterial.lc 2153:13-2179:14 - List StageAttrs + [StageAttrs] testdata/performance/SampleMaterial.lc 2153:15-2153:25 Maybe (Blending', Blending') -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 2153:15-2154:36 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 2153:15-2155:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 2153:15-2156:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 2153:15-2157:36 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 2153:15-2158:31 @@ -13728,7 +13378,7 @@ testdata/performance/SampleMaterial.lc 2156:32-2156:42 testdata/performance/SampleMaterial.lc 2157:29-2157:36 TCGen testdata/performance/SampleMaterial.lc 2158:29-2158:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 2159:31-2159:37 String -> StageTexture testdata/performance/SampleMaterial.lc 2159:31-2159:81 @@ -13750,29 +13400,29 @@ testdata/performance/SampleMaterial.lc 2166:15-2166:25 -> RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 2166:15-2167:57 RGBGen -> AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 2166:15-2168:50 AlphaGen -> TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 2166:15-2169:42 TCGen - -> List TCMod + -> [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 2166:15-2170:40 - List TCMod + [TCMod] -> StageTexture -> Bool -> DepthFunction -> Maybe AlphaFunction -> Bool -> String -> StageAttrs testdata/performance/SampleMaterial.lc 2166:15-2171:31 @@ -13789,7 +13439,7 @@ testdata/performance/SampleMaterial.lc 2166:15-2175:40 testdata/performance/SampleMaterial.lc 2166:15-2176:46 String -> StageAttrs testdata/performance/SampleMaterial.lc 2166:15-2178:18 - StageAttrs | List StageAttrs + StageAttrs | [StageAttrs] testdata/performance/SampleMaterial.lc 2167:29-2167:33 forall a . a -> Maybe a testdata/performance/SampleMaterial.lc 2167:29-2167:57 @@ -13807,7 +13457,7 @@ testdata/performance/SampleMaterial.lc 2169:32-2169:42 testdata/performance/SampleMaterial.lc 2170:29-2170:40 TCGen testdata/performance/SampleMaterial.lc 2171:29-2171:31 - forall a . List a + forall a . [a] testdata/performance/SampleMaterial.lc 2172:31-2172:42 StageTexture testdata/performance/SampleMaterial.lc 2173:34-2173:38 diff --git a/testdata/record01.reject.out b/testdata/record01.reject.out index 3af31081..881ed1b1 100644 --- a/testdata/record01.reject.out +++ b/testdata/record01.reject.out @@ -159,7 +159,7 @@ testdata/record01.reject.lc 7:25-7:28 testdata/record01.reject.lc 7:29-7:32 Float testdata/record01.reject.lc 8:23-8:34 - forall (a :: List Type) + forall (a :: [Type]) . sameLayerCounts a => HList a -> FrameBuffer (ImageLC (head Type a)) (map Type ImageKind GetImageKind a) @@ -170,7 +170,7 @@ testdata/record01.reject.lc 8:23-8:75 Type ImageKind GetImageKind - (: (Image 1 'Depth) (: (Image 1 ('Color (VecScalar 4 Float))) 'Nil))) + (: (Image 1 'Depth) (: (Image 1 ('Color (VecScalar 4 Float))) '[]))) testdata/record01.reject.lc 8:35-8:75 (Image 1 'Depth, Image 1 ('Color (VecScalar 4 Float))) testdata/record01.reject.lc 8:36-8:47 @@ -308,7 +308,7 @@ testdata/record01.reject.lc 17:56-17:57 testdata/record01.reject.lc 17:59-17:60 VecS Float 4 | ((VecS Float 4)) testdata/record01.reject.lc 18:23-18:28 - forall (a :: PrimitiveType) (b :: List Type) + forall (a :: PrimitiveType) (b :: [Type]) . String -> HList b -> PrimitiveStream a (HList b) testdata/record01.reject.lc 18:23-18:37 HList _a -> PrimitiveStream _b (HList _a) @@ -331,38 +331,36 @@ testdata/record01.reject.lc 18:65-18:68 testdata/record01.reject.lc 18:65-18:70 Type -> Type testdata/record01.reject.lc 18:65-18:76 - Type | List Type + Type | [Type] testdata/record01.reject.lc 18:69-18:70 _b testdata/record01.reject.lc 18:71-18:76 Type testdata/record01.reject.lc 19:23-19:36 - forall a b (c :: PrimitiveType) - . (a -> b) -> List (Primitive a c) -> List (Primitive b c) + forall a b (c :: PrimitiveType) . (a -> b) -> [Primitive a c] -> [Primitive b c] testdata/record01.reject.lc 19:23-19:49 - List (Primitive ((VecS Float 4)) _a) - -> List (Primitive (VecS Float 4, VecS Float 4) _a) + [Primitive ((VecS Float 4)) _a] -> [Primitive (VecS Float 4, VecS Float 4) _a] testdata/record01.reject.lc 19:23-19:62 - List (Primitive (VecS Float 4, VecS Float 4) _a) + [Primitive (VecS Float 4, VecS Float 4) _a] testdata/record01.reject.lc 19:37-19:49 ((VecS Float 4)) -> (VecS Float 4, VecS Float 4) testdata/record01.reject.lc 19:50-19:62 forall (a :: PrimitiveType) . PrimitiveStream a ((Vec 4 Float)) testdata/record01.reject.lc 20:23-20:42 - forall (a :: List Type) (b :: PrimitiveType) + forall (a :: [Type]) (b :: PrimitiveType) . RasterContext (HList (: (Vec 4 Float) a)) b -> HList (map Type Type Interpolated a) - -> List (Primitive (HList (: (Vec 4 Float) a)) b) - -> List (Vector 1 (Maybe (SimpleFragment (HList a)))) + -> [Primitive (HList (: (Vec 4 Float) a)) b] + -> [Vector 1 (Maybe (SimpleFragment (HList a)))] testdata/record01.reject.lc 20:23-20:52 HList (map Type Type Interpolated _a) - -> List (Primitive (HList (: (Vec 4 Float) _a)) 'Triangle) - -> List (Vector 1 (Maybe (SimpleFragment (HList _a)))) + -> [Primitive (HList (: (Vec 4 Float) _a)) 'Triangle] + -> [Vector 1 (Maybe (SimpleFragment (HList _a)))] testdata/record01.reject.lc 20:23-20:63 - List (Primitive (HList (: (Vec 4 Float) _d)) 'Triangle) - -> List (Vector 1 (Maybe (SimpleFragment (HList _d)))) + [Primitive (HList (: (Vec 4 Float) _d)) 'Triangle] + -> [Vector 1 (Maybe (SimpleFragment (HList _d)))] testdata/record01.reject.lc 20:23-20:79 - List (Vector 1 (Maybe (SimpleFragment ((VecS Float 4))))) + [Vector 1 (Maybe (SimpleFragment ((VecS Float 4))))] testdata/record01.reject.lc 20:43-20:52 forall a . RasterContext a 'Triangle testdata/record01.reject.lc 20:53-20:63 @@ -370,7 +368,7 @@ testdata/record01.reject.lc 20:53-20:63 testdata/record01.reject.lc 20:55-20:61 forall a . Floating a => Interpolated a testdata/record01.reject.lc 20:64-20:79 - forall (a :: PrimitiveType) . List (Primitive (VecS Float 4, VecS Float 4) a) + forall (a :: PrimitiveType) . [Primitive (VecS Float 4, VecS Float 4) a] testdata/record01.reject.lc 21:33-21:55 ((VecS Float 4)) | ((VecS Float 4)) testdata/record01.reject.lc 21:35-21:37 @@ -420,17 +418,17 @@ testdata/record01.reject.lc 22:57-22:60 testdata/record01.reject.lc 22:61-22:64 Float testdata/record01.reject.lc 23:23-23:33 - forall (a :: Nat) (b :: List Type) c + forall (a :: Nat) (b :: [Type]) c . HList b -> (c -> HList (imageType' (map Type ImageKind FragmentOperationKind b))) - -> List (Vector a (Maybe (SimpleFragment c))) + -> [Vector a (Maybe (SimpleFragment c))] -> FrameBuffer a (map Type ImageKind FragmentOperationKind b) -> FrameBuffer a (map Type ImageKind FragmentOperationKind b) testdata/record01.reject.lc 23:23-23:45 (_a -> ((imageType (FragmentOperationKind (FragmentOperation ('Color (VecScalar 4 Float))))))) - -> List (Vector _b (Maybe (SimpleFragment _a))) + -> [Vector _b (Maybe (SimpleFragment _a))] -> FrameBuffer _b (map @@ -439,7 +437,7 @@ testdata/record01.reject.lc 23:23-23:45 FragmentOperationKind (: (FragmentOperation 'Depth) - (: (FragmentOperation ('Color (VecScalar 4 Float))) 'Nil))) + (: (FragmentOperation ('Color (VecScalar 4 Float))) '[]))) -> FrameBuffer _b (map @@ -448,9 +446,9 @@ testdata/record01.reject.lc 23:23-23:45 FragmentOperationKind (: (FragmentOperation 'Depth) - (: (FragmentOperation ('Color (VecScalar 4 Float))) 'Nil))) + (: (FragmentOperation ('Color (VecScalar 4 Float))) '[]))) testdata/record01.reject.lc 23:23-23:60 - List (Vector _a (Maybe (SimpleFragment ((VecS Float 4))))) + [Vector _a (Maybe (SimpleFragment ((VecS Float 4))))] -> FrameBuffer _a (map @@ -459,7 +457,7 @@ testdata/record01.reject.lc 23:23-23:60 FragmentOperationKind (: (FragmentOperation 'Depth) - (: (FragmentOperation ('Color (VecScalar 4 Float))) 'Nil))) + (: (FragmentOperation ('Color (VecScalar 4 Float))) '[]))) -> FrameBuffer _a (map @@ -468,7 +466,7 @@ testdata/record01.reject.lc 23:23-23:60 FragmentOperationKind (: (FragmentOperation 'Depth) - (: (FragmentOperation ('Color (VecScalar 4 Float))) 'Nil))) + (: (FragmentOperation ('Color (VecScalar 4 Float))) '[]))) testdata/record01.reject.lc 23:23-23:75 FrameBuffer 1 @@ -478,7 +476,7 @@ testdata/record01.reject.lc 23:23-23:75 FragmentOperationKind (: (FragmentOperation 'Depth) - (: (FragmentOperation ('Color (VecScalar 4 Float))) 'Nil))) + (: (FragmentOperation ('Color (VecScalar 4 Float))) '[]))) -> FrameBuffer 1 (map @@ -487,7 +485,7 @@ testdata/record01.reject.lc 23:23-23:75 FragmentOperationKind (: (FragmentOperation 'Depth) - (: (FragmentOperation ('Color (VecScalar 4 Float))) 'Nil))) + (: (FragmentOperation ('Color (VecScalar 4 Float))) '[]))) testdata/record01.reject.lc 23:23-23:83 FrameBuffer 1 @@ -497,13 +495,13 @@ testdata/record01.reject.lc 23:23-23:83 FragmentOperationKind (: (FragmentOperation 'Depth) - (: (FragmentOperation ('Color (VecScalar 4 Float))) 'Nil))) + (: (FragmentOperation ('Color (VecScalar 4 Float))) '[]))) testdata/record01.reject.lc 23:34-23:45 (FragmentOperation 'Depth, FragmentOperation ('Color (VecScalar 4 Float))) testdata/record01.reject.lc 23:46-23:60 ((VecS Float 4)) -> ((VecS Float 4)) testdata/record01.reject.lc 23:61-23:75 - List (Vector 1 (Maybe (SimpleFragment ((VecS Float 4))))) + [Vector 1 (Maybe (SimpleFragment ((VecS Float 4))))] testdata/record01.reject.lc 23:76-23:83 FrameBuffer 1 @@ -511,7 +509,7 @@ testdata/record01.reject.lc 23:76-23:83 Type ImageKind GetImageKind - (: (Image 1 'Depth) (: (Image 1 ('Color (VecScalar 4 Float))) 'Nil))) + (: (Image 1 'Depth) (: (Image 1 ('Color (VecScalar 4 Float))) '[]))) testdata/record01.reject.lc 24:12-24:58 RecordC (: @@ -527,14 +525,12 @@ testdata/record01.reject.lc 24:12-24:58 FragmentOperationKind (: (FragmentOperation 'Depth) - (: (FragmentOperation ('Color (VecScalar 4 Float))) 'Nil))))) - (: - ('RecItem "fieldC" ((BlendEquation, BlendEquation) -> Blending Float)) - 'Nil))) + (: (FragmentOperation ('Color (VecScalar 4 Float))) '[]))))) + (: ('RecItem "fieldC" ((BlendEquation, BlendEquation) -> Blending Float)) '[]))) testdata/record01.reject.lc 24:13-24:19 String | RecItem testdata/record01.reject.lc 24:13-24:47 - List RecItem + [RecItem] testdata/record01.reject.lc 24:21-24:24 Float testdata/record01.reject.lc 24:21-24:57 @@ -549,12 +545,12 @@ testdata/record01.reject.lc 24:21-24:57 FragmentOperationKind (: (FragmentOperation 'Depth) - (: (FragmentOperation ('Color (VecScalar 4 Float))) 'Nil))))), recItemType + (: (FragmentOperation ('Color (VecScalar 4 Float))) '[]))))), recItemType ('RecItem "fieldC" ((BlendEquation, BlendEquation) -> Blending Float))) testdata/record01.reject.lc 24:26-24:32 String | RecItem testdata/record01.reject.lc 24:26-24:47 - List RecItem + [RecItem] testdata/record01.reject.lc 24:34-24:39 FrameBuffer 1 @@ -564,7 +560,7 @@ testdata/record01.reject.lc 24:34-24:39 FragmentOperationKind (: (FragmentOperation 'Depth) - (: (FragmentOperation ('Color (VecScalar 4 Float))) 'Nil))) + (: (FragmentOperation ('Color (VecScalar 4 Float))) '[]))) testdata/record01.reject.lc 24:34-24:57 (FrameBuffer 1 @@ -574,10 +570,10 @@ testdata/record01.reject.lc 24:34-24:57 FragmentOperationKind (: (FragmentOperation 'Depth) - (: (FragmentOperation ('Color (VecScalar 4 Float))) 'Nil))), recItemType + (: (FragmentOperation ('Color (VecScalar 4 Float))) '[]))), recItemType ('RecItem "fieldC" ((BlendEquation, BlendEquation) -> Blending Float))) testdata/record01.reject.lc 24:41-24:47 - String | RecItem | List RecItem + String | RecItem | [RecItem] testdata/record01.reject.lc 24:49-24:57 (BlendEquation, BlendEquation) -> Blending Float | (((BlendEquation, BlendEquation) -> Blending Float)) @@ -596,16 +592,14 @@ testdata/record01.reject.lc 25:11-25:17 FragmentOperationKind (: (FragmentOperation 'Depth) - (: (FragmentOperation ('Color (VecScalar 4 Float))) 'Nil))))) - (: - ('RecItem "fieldC" ((BlendEquation, BlendEquation) -> Blending Float)) - 'Nil))) + (: (FragmentOperation ('Color (VecScalar 4 Float))) '[]))))) + (: ('RecItem "fieldC" ((BlendEquation, BlendEquation) -> Blending Float)) '[]))) testdata/record01.reject.lc 25:11-25:24 _b testdata/record01.reject.lc 25:18-25:24 String testdata/record01.reject.lc 26:5-26:14 - forall (a :: Nat) (b :: List ImageKind) . FrameBuffer a b -> Output + forall (a :: Nat) (b :: [ImageKind]) . FrameBuffer a b -> Output testdata/record01.reject.lc 26:15-26:21 RecordC (: @@ -621,10 +615,8 @@ testdata/record01.reject.lc 26:15-26:21 FragmentOperationKind (: (FragmentOperation 'Depth) - (: (FragmentOperation ('Color (VecScalar 4 Float))) 'Nil))))) - (: - ('RecItem "fieldC" ((BlendEquation, BlendEquation) -> Blending Float)) - 'Nil))) + (: (FragmentOperation ('Color (VecScalar 4 Float))) '[]))))) + (: ('RecItem "fieldC" ((BlendEquation, BlendEquation) -> Blending Float)) '[]))) testdata/record01.reject.lc 26:15-26:28 _b testdata/record01.reject.lc 26:22-26:28 diff --git a/testdata/traceTest.out b/testdata/traceTest.out index ef065db6..fe085529 100644 --- a/testdata/traceTest.out +++ b/testdata/traceTest.out @@ -2,7 +2,7 @@ id = \(a :: _) -> _rhs a data X (_ :: Type) (_ :: _a) :: Type where -x = _rhs undefined :: X \(a :: _) (b :: _) -> HList (a : b : 'Nil) +x = _rhs undefined :: X \(a :: _) (b :: _) -> HList (a : b : '[]) main is not found ------------ trace id :: forall a . a -> a @@ -32,9 +32,9 @@ testdata/traceTest.lc 10:17-10:24 testdata/traceTest.lc 10:19-10:20 _e testdata/traceTest.lc 10:19-10:23 - List Type + [Type] testdata/traceTest.lc 10:22-10:23 - _c | List Type + _c | [Type] testdata/traceTest.lc 11:1-11:2 X (Type -> Type -> Type) \(a :: Type) (b :: Type) -> (a, b) testdata/traceTest.lc 11:5-11:14 diff --git a/testdata/zip01.out b/testdata/zip01.out index cb886f64..1f7d4c25 100644 --- a/testdata/zip01.out +++ b/testdata/zip01.out @@ -9,17 +9,17 @@ zip2 \(e :: _) (f :: _) -> _rhs (HCons c (HCons e HNil) : zip2 d f) b a) - :: forall (g :: _) (h :: _) . List g -> List h -> List (HList (g : h : 'Nil)) + :: forall (g :: _) (h :: _) . [g] -> [h] -> [HList (g : h : '[])] main is not found ------------ trace -zip2 :: forall a b . List a -> List b -> List (a, b) +zip2 :: forall a b . [a] -> [b] -> [(a, b)] ------------ tooltips testdata/zip01.lc 1:9-1:12 Type testdata/zip01.lc 1:9-1:30 Type | Type testdata/zip01.lc 1:9-4:40 - forall a b . List a -> List b -> List (a, b) + forall a b . [a] -> [b] -> [(a, b)] testdata/zip01.lc 1:10-1:11 _d testdata/zip01.lc 1:16-1:19 @@ -35,38 +35,38 @@ testdata/zip01.lc 1:24-1:29 testdata/zip01.lc 1:25-1:26 Type testdata/zip01.lc 1:25-1:28 - List Type + [Type] testdata/zip01.lc 1:27-1:28 - Type | List Type + Type | [Type] testdata/zip01.lc 2:1-2:5 - forall a b . List a -> List b -> List (a, b) + forall a b . [a] -> [b] -> [(a, b)] testdata/zip01.lc 2:22-2:24 - forall a . List a + forall a . [a] testdata/zip01.lc 2:22-4:40 - List _a -> List (_a, _d) | List (_d, _c) + [_a] -> [(_a, _d)] | [(_d, _c)] testdata/zip01.lc 3:22-3:24 - forall a . List a + forall a . [a] testdata/zip01.lc 3:22-4:40 - List _a -> List (_e, _a) | List (_c, _f) + [_a] -> [(_e, _a)] | [(_c, _f)] testdata/zip01.lc 4:22-4:27 (_h, _d) testdata/zip01.lc 4:22-4:29 - List (_h, _d) -> List (_h, _d) + [(_h, _d)] -> [(_h, _d)] testdata/zip01.lc 4:22-4:40 - List (_g, _c) + [(_g, _c)] testdata/zip01.lc 4:23-4:24 _k testdata/zip01.lc 4:25-4:26 _g | ((_d)) testdata/zip01.lc 4:28-4:29 - forall a . a -> List a -> List a + forall a . a -> [a] -> [a] testdata/zip01.lc 4:30-4:34 - forall a b . List a -> List b -> List (a, b) + forall a b . [a] -> [b] -> [(a, b)] testdata/zip01.lc 4:30-4:37 - List _a -> List (_h, _a) + [_a] -> [(_h, _a)] testdata/zip01.lc 4:30-4:40 - List (_g, _c) + [(_g, _c)] testdata/zip01.lc 4:35-4:37 - List _i + [_i] testdata/zip01.lc 4:38-4:40 - List _c \ No newline at end of file + [_c] \ No newline at end of file -- cgit v1.2.3