Module "Prelude" Nothing [(DataDecl (27,1) (Ident "Float" 0) [] []) ,(DataDecl (28,1) (Ident "Char" 0) [] []) ,(TypeDecl (29,1) (Ident "String" 0) [] (ListType (ConstructorType (QualIdent Nothing (Ident "Char" 0)) []))) ,(DataDecl (114,1) (Ident "Bool" 0) [] [(ConstrDecl (114,13) [] (Ident "False" 0) []),(ConstrDecl (114,21) [] (Ident "True" 0) [])]) ,(DataDecl (145,1) (Ident "Ordering" 0) [] [(ConstrDecl (145,17) [] (Ident "LT" 0) []),(ConstrDecl (145,22) [] (Ident "EQ" 0) []),(ConstrDecl (145,27) [] (Ident "GT" 0) [])]) ,(DataDecl (509,1) (Ident "Nat" 0) [] [(ConstrDecl (509,12) [] (Ident "IHi" 0) []),(ConstrDecl (509,18) [] (Ident "O" 0) [(ConstructorType (QualIdent Nothing (Ident "Nat" 0)) [])]),(ConstrDecl (509,26) [] (Ident "I" 0) [(ConstructorType (QualIdent Nothing (Ident "Nat" 0)) [])])]) ,(DataDecl (574,1) (Ident "Int" 0) [] [(ConstrDecl (574,12) [] (Ident "Neg" 0) [(ConstructorType (QualIdent Nothing (Ident "Nat" 0)) [])]),(ConstrDecl (574,22) [] (Ident "Zero" 0) []),(ConstrDecl (574,29) [] (Ident "Pos" 0) [(ConstructorType (QualIdent Nothing (Ident "Nat" 0)) [])])]) ,(DataDecl (694,1) (Ident "Success" 0) [] [(ConstrDecl (694,16) [] (Ident "Success" 0) [])]) ,(DataDecl (728,1) (Ident "Maybe" 0) [(Ident "a" 0)] [(ConstrDecl (728,16) [] (Ident "Nothing" 0) []),(ConstrDecl (728,26) [] (Ident "Just" 0) [(VariableType (Ident "a" 0))])]) ,(DataDecl (737,1) (Ident "Either" 0) [(Ident "a" 0),(Ident "b" 0)] [(ConstrDecl (737,19) [] (Ident "Left" 0) [(VariableType (Ident "a" 0))]),(ConstrDecl (737,28) [] (Ident "Right" 0) [(VariableType (Ident "b" 0))])]) ,(DataDecl (746,1) (Ident "IO" 0) [(Ident "_" 0)] []) ,(DataDecl (896,1) (Ident "SearchTree" 0) [(Ident "a" 0)] [(ConstrDecl (897,5) [] (Ident "Fail" 0) []),(ConstrDecl (898,5) [] (Ident "Value" 0) [(VariableType (Ident "a" 0))]),(ConstrDecl (899,5) [] (Ident "Choice" 0) [(ListType (ConstructorType (QualIdent Nothing (Ident "SearchTree" 0)) [(VariableType (Ident "a" 0))]))]),(ConstrDecl (900,5) [] (Ident "Suspend" 0) [])]) ,(InfixDecl (13,1) InfixL 9 [(Ident "!!" 0)]) ,(InfixDecl (14,1) InfixR 9 [(Ident "." 0)]) ,(InfixDecl (15,1) InfixL 7 [(Ident "*" 0),(Ident "*^" 0),(Ident "div" 0),(Ident "mod" 0)]) ,(InfixDecl (16,1) InfixL 6 [(Ident "+" 0),(Ident "+^" 0),(Ident "-" 0),(Ident "-^" 0)]) ,(InfixDecl (18,1) InfixR 5 [(Ident "++" 0)]) ,(InfixDecl (19,1) Infix 4 [(Ident "=:=" 0),(Ident "==" 0),(Ident "===" 0),(Ident "/=" 0),(Ident "<" 0),(Ident ">" 0),(Ident "<=" 0),(Ident ">=" 0),(Ident "=:<=" 0),(Ident "<^" 0),(Ident "<=^" 0),(Ident ">^" 0),(Ident ">=^" 0)]) ,(InfixDecl (20,1) Infix 4 [(Ident "elem" 0),(Ident "notElem" 0)]) ,(InfixDecl (21,1) InfixR 3 [(Ident "&&" 0)]) ,(InfixDecl (22,1) InfixR 2 [(Ident "||" 0)]) ,(InfixDecl (23,1) InfixL 1 [(Ident ">>" 0),(Ident ">>=" 0)]) ,(InfixDecl (24,1) InfixR 0 [(Ident "$" 0),(Ident "$!" 0),(Ident "$!!" 0),(Ident "$#" 0),(Ident "$##" 0),(Ident "seq" 0),(Ident "&" 0),(Ident "&>" 0),(Ident "?" 0)]) ,(TypeSig (34,1) [(Ident "." 0)] (ArrowType (ArrowType (VariableType (Ident "b" 0)) (VariableType (Ident "c" 0))) (ArrowType (ArrowType (VariableType (Ident "a" 0)) (VariableType (Ident "b" 0))) (ArrowType (VariableType (Ident "a" 0)) (VariableType (Ident "c" 0)))))) ,(FunctionDecl (35,1) (Ident "." 0) [(Equation (35,1) (OpLhs (VariablePattern (Ident "f" 2)) (Ident "." 0) (VariablePattern (Ident "g" 2))) (SimpleRhs (35,9) (Lambda [(VariablePattern (Ident "x" 4))] (Apply (Variable (QualIdent Nothing (Ident "f" 2))) (Paren (Apply (Variable (QualIdent Nothing (Ident "g" 2))) (Variable (QualIdent Nothing (Ident "x" 4))))))) []))]) ,(TypeSig (38,1) [(Ident "id" 0)] (ArrowType (VariableType (Ident "a" 0)) (VariableType (Ident "a" 0)))) ,(FunctionDecl (39,1) (Ident "id" 0) [(Equation (39,1) (FunLhs (Ident "id" 0) [(VariablePattern (Ident "x" 5))]) (SimpleRhs (39,19) (Variable (QualIdent Nothing (Ident "x" 5))) []))]) ,(TypeSig (42,1) [(Ident "const" 0)] (ArrowType (VariableType (Ident "a" 0)) (ArrowType (VariableType (Ident "_" 0)) (VariableType (Ident "a" 0))))) ,(FunctionDecl (43,1) (Ident "const" 0) [(Equation (43,1) (FunLhs (Ident "const" 0) [(VariablePattern (Ident "x" 7)),(VariablePattern (Ident "_" 8))]) (SimpleRhs (43,19) (Variable (QualIdent Nothing (Ident "x" 7))) []))]) ,(TypeSig (46,1) [(Ident "curry" 0)] (ArrowType (ArrowType (TupleType [(VariableType (Ident "a" 0)),(VariableType (Ident "b" 0))]) (VariableType (Ident "c" 0))) (ArrowType (VariableType (Ident "a" 0)) (ArrowType (VariableType (Ident "b" 0)) (VariableType (Ident "c" 0)))))) ,(FunctionDecl (47,1) (Ident "curry" 0) [(Equation (47,1) (FunLhs (Ident "curry" 0) [(VariablePattern (Ident "f" 10)),(VariablePattern (Ident "a" 10)),(VariablePattern (Ident "b" 10))]) (SimpleRhs (47,20) (Apply (Variable (QualIdent Nothing (Ident "f" 10))) (Tuple [(Variable (QualIdent Nothing (Ident "a" 10))),(Variable (QualIdent Nothing (Ident "b" 10)))])) []))]) ,(TypeSig (50,1) [(Ident "uncurry" 0)] (ArrowType (ArrowType (VariableType (Ident "a" 0)) (ArrowType (VariableType (Ident "b" 0)) (VariableType (Ident "c" 0)))) (ArrowType (TupleType [(VariableType (Ident "a" 0)),(VariableType (Ident "b" 0))]) (VariableType (Ident "c" 0))))) ,(FunctionDecl (51,1) (Ident "uncurry" 0) [(Equation (51,1) (FunLhs (Ident "uncurry" 0) [(VariablePattern (Ident "f" 12)),(TuplePattern [(VariablePattern (Ident "a" 12)),(VariablePattern (Ident "b" 12))])]) (SimpleRhs (51,19) (Apply (Apply (Variable (QualIdent Nothing (Ident "f" 12))) (Variable (QualIdent Nothing (Ident "a" 12)))) (Variable (QualIdent Nothing (Ident "b" 12)))) []))]) ,(TypeSig (54,1) [(Ident "flip" 0)] (ArrowType (ArrowType (VariableType (Ident "a" 0)) (ArrowType (VariableType (Ident "b" 0)) (VariableType (Ident "c" 0)))) (ArrowType (VariableType (Ident "b" 0)) (ArrowType (VariableType (Ident "a" 0)) (VariableType (Ident "c" 0)))))) ,(FunctionDecl (55,1) (Ident "flip" 0) [(Equation (55,1) (FunLhs (Ident "flip" 0) [(VariablePattern (Ident "f" 14)),(VariablePattern (Ident "x" 14)),(VariablePattern (Ident "y" 14))]) (SimpleRhs (55,19) (Apply (Apply (Variable (QualIdent Nothing (Ident "f" 14))) (Variable (QualIdent Nothing (Ident "y" 14)))) (Variable (QualIdent Nothing (Ident "x" 14)))) []))]) ,(TypeSig (58,1) [(Ident "until" 0)] (ArrowType (ArrowType (VariableType (Ident "a" 0)) (ConstructorType (QualIdent Nothing (Ident "Bool" 0)) [])) (ArrowType (ArrowType (VariableType (Ident "a" 0)) (VariableType (Ident "a" 0))) (ArrowType (VariableType (Ident "a" 0)) (VariableType (Ident "a" 0)))))) ,(FunctionDecl (59,1) (Ident "until" 0) [(Equation (59,1) (FunLhs (Ident "until" 0) [(VariablePattern (Ident "p" 16)),(VariablePattern (Ident "f" 16)),(VariablePattern (Ident "x" 16))]) (SimpleRhs (59,19) (IfThenElse (Apply (Variable (QualIdent Nothing (Ident "p" 16))) (Variable (QualIdent Nothing (Ident "x" 16)))) (Variable (QualIdent Nothing (Ident "x" 16))) (Apply (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "until" 0))) (Variable (QualIdent Nothing (Ident "p" 16)))) (Variable (QualIdent Nothing (Ident "f" 16)))) (Paren (Apply (Variable (QualIdent Nothing (Ident "f" 16))) (Variable (QualIdent Nothing (Ident "x" 16))))))) []))]) ,(TypeSig (62,1) [(Ident "$" 0)] (ArrowType (ArrowType (VariableType (Ident "a" 0)) (VariableType (Ident "b" 0))) (ArrowType (VariableType (Ident "a" 0)) (VariableType (Ident "b" 0))))) ,(FunctionDecl (63,1) (Ident "$" 0) [(Equation (63,1) (OpLhs (VariablePattern (Ident "f" 18)) (Ident "$" 0) (VariablePattern (Ident "x" 18))) (SimpleRhs (63,19) (Apply (Variable (QualIdent Nothing (Ident "f" 18))) (Variable (QualIdent Nothing (Ident "x" 18)))) []))]) ,(TypeSig (67,1) [(Ident "$!" 0)] (ArrowType (ArrowType (VariableType (Ident "a" 0)) (VariableType (Ident "b" 0))) (ArrowType (VariableType (Ident "a" 0)) (VariableType (Ident "b" 0))))) ,(FlatExternalDecl (68,1) [(Ident "$!" 0)]) ,(TypeSig (72,1) [(Ident "$!!" 0)] (ArrowType (ArrowType (VariableType (Ident "a" 0)) (VariableType (Ident "b" 0))) (ArrowType (VariableType (Ident "a" 0)) (VariableType (Ident "b" 0))))) ,(FlatExternalDecl (73,1) [(Ident "$!!" 0)]) ,(TypeSig (78,1) [(Ident "$#" 0)] (ArrowType (ArrowType (VariableType (Ident "a" 0)) (VariableType (Ident "b" 0))) (ArrowType (VariableType (Ident "a" 0)) (VariableType (Ident "b" 0))))) ,(FlatExternalDecl (79,1) [(Ident "$#" 0)]) ,(TypeSig (84,1) [(Ident "$##" 0)] (ArrowType (ArrowType (VariableType (Ident "a" 0)) (VariableType (Ident "b" 0))) (ArrowType (VariableType (Ident "a" 0)) (VariableType (Ident "b" 0))))) ,(FlatExternalDecl (85,1) [(Ident "$##" 0)]) ,(TypeSig (89,1) [(Ident "ensureSpine" 0)] (ArrowType (ListType (VariableType (Ident "a" 0))) (ListType (VariableType (Ident "a" 0))))) ,(FunctionDecl (90,1) (Ident "ensureSpine" 0) [(Equation (90,1) (FunLhs (Ident "ensureSpine" 0) []) (SimpleRhs (90,15) (LeftSection (Variable (QualIdent Nothing (Ident "ensureList" 21))) (InfixOp (QualIdent (Just "Prelude") (Ident "$#" 0)))) [(FunctionDecl (91,8) (Ident "ensureList" 21) [(Equation (91,8) (FunLhs (Ident "ensureList" 21) [(ListPattern [])]) (SimpleRhs (91,28) (List []) [])),(Equation (92,8) (FunLhs (Ident "ensureList" 21) [(ParenPattern (InfixPattern (VariablePattern (Ident "x" 24)) (QualIdent Nothing (Ident ":" 0)) (VariablePattern (Ident "xs" 24))))]) (SimpleRhs (92,28) (InfixApply (Variable (QualIdent Nothing (Ident "x" 24))) (InfixConstr (QualIdent Nothing (Ident ":" 0))) (Apply (Variable (QualIdent (Just "Prelude") (Ident "ensureSpine" 0))) (Variable (QualIdent Nothing (Ident "xs" 24))))) []))])]))]) ,(TypeSig (96,1) [(Ident "seq" 0)] (ArrowType (VariableType (Ident "_" 0)) (ArrowType (VariableType (Ident "a" 0)) (VariableType (Ident "a" 0))))) ,(FunctionDecl (97,1) (Ident "seq" 0) [(Equation (97,1) (FunLhs (Ident "seq" 0) [(VariablePattern (Ident "x" 26)),(VariablePattern (Ident "y" 26))]) (SimpleRhs (97,11) (InfixApply (Paren (Apply (Variable (QualIdent (Just "Prelude") (Ident "const" 0))) (Variable (QualIdent Nothing (Ident "y" 26))))) (InfixOp (QualIdent (Just "Prelude") (Ident "$!" 0))) (Variable (QualIdent Nothing (Ident "x" 26)))) []))]) ,(TypeSig (102,1) [(Ident "error" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "String" 0)) []) (VariableType (Ident "_" 0)))) ,(FunctionDecl (103,1) (Ident "error" 0) [(Equation (103,1) (FunLhs (Ident "error" 0) [(VariablePattern (Ident "s" 28))]) (SimpleRhs (103,11) (InfixApply (Variable (QualIdent (Just "Prelude") (Ident "prim_error" 0))) (InfixOp (QualIdent (Just "Prelude") (Ident "$##" 0))) (Variable (QualIdent Nothing (Ident "s" 28)))) []))]) ,(TypeSig (105,1) [(Ident "prim_error" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "String" 0)) []) (VariableType (Ident "_" 0)))) ,(FlatExternalDecl (106,1) [(Ident "prim_error" 0)]) ,(TypeSig (110,1) [(Ident "failed" 0)] (VariableType (Ident "_" 0))) ,(FlatExternalDecl (111,1) [(Ident "failed" 0)]) ,(TypeSig (117,1) [(Ident "&&" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Bool" 0)) []) (ArrowType (ConstructorType (QualIdent Nothing (Ident "Bool" 0)) []) (ConstructorType (QualIdent Nothing (Ident "Bool" 0)) [])))) ,(FunctionDecl (118,1) (Ident "&&" 0) [(Equation (118,1) (OpLhs (ConstructorPattern (QualIdent (Just "Prelude") (Ident "True" 0)) []) (Ident "&&" 0) (VariablePattern (Ident "x" 30))) (SimpleRhs (118,19) (Variable (QualIdent Nothing (Ident "x" 30))) [])),(Equation (119,1) (OpLhs (ConstructorPattern (QualIdent (Just "Prelude") (Ident "False" 0)) []) (Ident "&&" 0) (VariablePattern (Ident "_" 33))) (SimpleRhs (119,19) (Constructor (QualIdent (Just "Prelude") (Ident "False" 0))) []))]) ,(TypeSig (123,1) [(Ident "||" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Bool" 0)) []) (ArrowType (ConstructorType (QualIdent Nothing (Ident "Bool" 0)) []) (ConstructorType (QualIdent Nothing (Ident "Bool" 0)) [])))) ,(FunctionDecl (124,1) (Ident "||" 0) [(Equation (124,1) (OpLhs (ConstructorPattern (QualIdent (Just "Prelude") (Ident "True" 0)) []) (Ident "||" 0) (VariablePattern (Ident "_" 36))) (SimpleRhs (124,19) (Constructor (QualIdent (Just "Prelude") (Ident "True" 0))) [])),(Equation (125,1) (OpLhs (ConstructorPattern (QualIdent (Just "Prelude") (Ident "False" 0)) []) (Ident "||" 0) (VariablePattern (Ident "x" 38))) (SimpleRhs (125,19) (Variable (QualIdent Nothing (Ident "x" 38))) []))]) ,(TypeSig (129,1) [(Ident "not" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Bool" 0)) []) (ConstructorType (QualIdent Nothing (Ident "Bool" 0)) []))) ,(FunctionDecl (130,1) (Ident "not" 0) [(Equation (130,1) (FunLhs (Ident "not" 0) [(ConstructorPattern (QualIdent (Just "Prelude") (Ident "True" 0)) [])]) (SimpleRhs (130,19) (Constructor (QualIdent (Just "Prelude") (Ident "False" 0))) [])),(Equation (131,1) (FunLhs (Ident "not" 0) [(ConstructorPattern (QualIdent (Just "Prelude") (Ident "False" 0)) [])]) (SimpleRhs (131,19) (Constructor (QualIdent (Just "Prelude") (Ident "True" 0))) []))]) ,(TypeSig (134,1) [(Ident "otherwise" 0)] (ConstructorType (QualIdent Nothing (Ident "Bool" 0)) [])) ,(FunctionDecl (135,1) (Ident "otherwise" 0) [(Equation (135,1) (FunLhs (Ident "otherwise" 0) []) (SimpleRhs (135,19) (Constructor (QualIdent (Just "Prelude") (Ident "True" 0))) []))]) ,(TypeSig (139,1) [(Ident "if_then_else" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Bool" 0)) []) (ArrowType (VariableType (Ident "a" 0)) (ArrowType (VariableType (Ident "a" 0)) (VariableType (Ident "a" 0)))))) ,(FunctionDecl (140,1) (Ident "if_then_else" 0) [(Equation (140,1) (FunLhs (Ident "if_then_else" 0) [(VariablePattern (Ident "b" 46)),(VariablePattern (Ident "t" 46)),(VariablePattern (Ident "f" 46))]) (SimpleRhs (140,22) (Case (Variable (QualIdent Nothing (Ident "b" 46))) [(Alt (140,32) (ConstructorPattern (QualIdent (Just "Prelude") (Ident "True" 0)) []) (SimpleRhs (140,41) (Variable (QualIdent Nothing (Ident "t" 46))) [])),(Alt (141,32) (ConstructorPattern (QualIdent (Just "Prelude") (Ident "False" 0)) []) (SimpleRhs (141,41) (Variable (QualIdent Nothing (Ident "f" 46))) []))]) []))]) ,(FunctionDecl (147,1) (Ident "isLT" 0) [(Equation (147,1) (FunLhs (Ident "isLT" 0) [(ConstructorPattern (QualIdent (Just "Prelude") (Ident "LT" 0)) [])]) (SimpleRhs (147,11) (Constructor (QualIdent (Just "Prelude") (Ident "True" 0))) [])),(Equation (148,1) (FunLhs (Ident "isLT" 0) [(ConstructorPattern (QualIdent (Just "Prelude") (Ident "GT" 0)) [])]) (SimpleRhs (148,11) (Constructor (QualIdent (Just "Prelude") (Ident "False" 0))) [])),(Equation (149,1) (FunLhs (Ident "isLT" 0) [(ConstructorPattern (QualIdent (Just "Prelude") (Ident "EQ" 0)) [])]) (SimpleRhs (149,11) (Constructor (QualIdent (Just "Prelude") (Ident "False" 0))) []))]) ,(FunctionDecl (151,1) (Ident "isGT" 0) [(Equation (151,1) (FunLhs (Ident "isGT" 0) [(ConstructorPattern (QualIdent (Just "Prelude") (Ident "LT" 0)) [])]) (SimpleRhs (151,11) (Constructor (QualIdent (Just "Prelude") (Ident "False" 0))) [])),(Equation (152,1) (FunLhs (Ident "isGT" 0) [(ConstructorPattern (QualIdent (Just "Prelude") (Ident "GT" 0)) [])]) (SimpleRhs (152,11) (Constructor (QualIdent (Just "Prelude") (Ident "True" 0))) [])),(Equation (153,1) (FunLhs (Ident "isGT" 0) [(ConstructorPattern (QualIdent (Just "Prelude") (Ident "EQ" 0)) [])]) (SimpleRhs (153,11) (Constructor (QualIdent (Just "Prelude") (Ident "False" 0))) []))]) ,(FunctionDecl (155,1) (Ident "isEQ" 0) [(Equation (155,1) (FunLhs (Ident "isEQ" 0) [(ConstructorPattern (QualIdent (Just "Prelude") (Ident "LT" 0)) [])]) (SimpleRhs (155,11) (Constructor (QualIdent (Just "Prelude") (Ident "False" 0))) [])),(Equation (156,1) (FunLhs (Ident "isEQ" 0) [(ConstructorPattern (QualIdent (Just "Prelude") (Ident "GT" 0)) [])]) (SimpleRhs (156,11) (Constructor (QualIdent (Just "Prelude") (Ident "False" 0))) [])),(Equation (157,1) (FunLhs (Ident "isEQ" 0) [(ConstructorPattern (QualIdent (Just "Prelude") (Ident "EQ" 0)) [])]) (SimpleRhs (157,11) (Constructor (QualIdent (Just "Prelude") (Ident "True" 0))) []))]) ,(TypeSig (164,1) [(Ident "compare" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []) (ArrowType (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []) (ConstructorType (QualIdent Nothing (Ident "Ordering" 0)) [])))) ,(FunctionDecl (165,1) (Ident "compare" 0) [(Equation (165,1) (FunLhs (Ident "compare" 0) [(ConstructorPattern (QualIdent (Just "Prelude") (Ident "Zero" 0)) []),(ConstructorPattern (QualIdent (Just "Prelude") (Ident "Zero" 0)) [])]) (SimpleRhs (165,27) (Constructor (QualIdent (Just "Prelude") (Ident "EQ" 0))) [])),(Equation (166,1) (FunLhs (Ident "compare" 0) [(ConstructorPattern (QualIdent (Just "Prelude") (Ident "Zero" 0)) []),(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Pos" 0)) [(VariablePattern (Ident "_" 73))]))]) (SimpleRhs (166,27) (Constructor (QualIdent (Just "Prelude") (Ident "LT" 0))) [])),(Equation (167,1) (FunLhs (Ident "compare" 0) [(ConstructorPattern (QualIdent (Just "Prelude") (Ident "Zero" 0)) []),(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Neg" 0)) [(VariablePattern (Ident "_" 76))]))]) (SimpleRhs (167,27) (Constructor (QualIdent (Just "Prelude") (Ident "GT" 0))) [])),(Equation (168,1) (FunLhs (Ident "compare" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Pos" 0)) [(VariablePattern (Ident "_" 79))])),(ConstructorPattern (QualIdent (Just "Prelude") (Ident "Zero" 0)) [])]) (SimpleRhs (168,27) (Constructor (QualIdent (Just "Prelude") (Ident "GT" 0))) [])),(Equation (169,1) (FunLhs (Ident "compare" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Pos" 0)) [(VariablePattern (Ident "x" 81))])),(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Pos" 0)) [(VariablePattern (Ident "y" 81))]))]) (SimpleRhs (169,27) (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "cmpNat" 0))) (Variable (QualIdent Nothing (Ident "x" 81)))) (Variable (QualIdent Nothing (Ident "y" 81)))) [])),(Equation (170,1) (FunLhs (Ident "compare" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Pos" 0)) [(VariablePattern (Ident "_" 84))])),(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Neg" 0)) [(VariablePattern (Ident "_" 85))]))]) (SimpleRhs (170,27) (Constructor (QualIdent (Just "Prelude") (Ident "GT" 0))) [])),(Equation (171,1) (FunLhs (Ident "compare" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Neg" 0)) [(VariablePattern (Ident "_" 88))])),(ConstructorPattern (QualIdent (Just "Prelude") (Ident "Zero" 0)) [])]) (SimpleRhs (171,27) (Constructor (QualIdent (Just "Prelude") (Ident "LT" 0))) [])),(Equation (172,1) (FunLhs (Ident "compare" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Neg" 0)) [(VariablePattern (Ident "_" 91))])),(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Pos" 0)) [(VariablePattern (Ident "_" 92))]))]) (SimpleRhs (172,27) (Constructor (QualIdent (Just "Prelude") (Ident "LT" 0))) [])),(Equation (173,1) (FunLhs (Ident "compare" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Neg" 0)) [(VariablePattern (Ident "x" 94))])),(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Neg" 0)) [(VariablePattern (Ident "y" 94))]))]) (SimpleRhs (173,27) (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "cmpNat" 0))) (Variable (QualIdent Nothing (Ident "y" 94)))) (Variable (QualIdent Nothing (Ident "x" 94)))) []))]) ,(TypeSig (187,1) [(Ident "<" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []) (ArrowType (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []) (ConstructorType (QualIdent Nothing (Ident "Bool" 0)) [])))) ,(FunctionDecl (188,1) (Ident "<" 0) [(Equation (188,1) (OpLhs (VariablePattern (Ident "x" 96)) (Ident "<" 0) (VariablePattern (Ident "y" 96))) (SimpleRhs (188,9) (InfixApply (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "compare" 0))) (Variable (QualIdent Nothing (Ident "x" 96)))) (Variable (QualIdent Nothing (Ident "y" 96)))) (InfixOp (QualIdent (Just "Prelude") (Ident "==" 0))) (Constructor (QualIdent (Just "Prelude") (Ident "LT" 0)))) []))]) ,(TypeSig (191,1) [(Ident ">" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []) (ArrowType (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []) (ConstructorType (QualIdent Nothing (Ident "Bool" 0)) [])))) ,(FunctionDecl (192,1) (Ident ">" 0) [(Equation (192,1) (OpLhs (VariablePattern (Ident "x" 98)) (Ident ">" 0) (VariablePattern (Ident "y" 98))) (SimpleRhs (192,9) (InfixApply (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "compare" 0))) (Variable (QualIdent Nothing (Ident "x" 98)))) (Variable (QualIdent Nothing (Ident "y" 98)))) (InfixOp (QualIdent (Just "Prelude") (Ident "==" 0))) (Constructor (QualIdent (Just "Prelude") (Ident "GT" 0)))) []))]) ,(TypeSig (195,1) [(Ident "<=" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []) (ArrowType (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []) (ConstructorType (QualIdent Nothing (Ident "Bool" 0)) [])))) ,(FunctionDecl (196,1) (Ident "<=" 0) [(Equation (196,1) (OpLhs (VariablePattern (Ident "x" 100)) (Ident "<=" 0) (VariablePattern (Ident "y" 100))) (SimpleRhs (196,10) (InfixApply (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "compare" 0))) (Variable (QualIdent Nothing (Ident "x" 100)))) (Variable (QualIdent Nothing (Ident "y" 100)))) (InfixOp (QualIdent (Just "Prelude") (Ident "/=" 0))) (Constructor (QualIdent (Just "Prelude") (Ident "GT" 0)))) []))]) ,(TypeSig (199,1) [(Ident ">=" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []) (ArrowType (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []) (ConstructorType (QualIdent Nothing (Ident "Bool" 0)) [])))) ,(FunctionDecl (200,1) (Ident ">=" 0) [(Equation (200,1) (OpLhs (VariablePattern (Ident "x" 102)) (Ident ">=" 0) (VariablePattern (Ident "y" 102))) (SimpleRhs (200,10) (InfixApply (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "compare" 0))) (Variable (QualIdent Nothing (Ident "x" 102)))) (Variable (QualIdent Nothing (Ident "y" 102)))) (InfixOp (QualIdent (Just "Prelude") (Ident "/=" 0))) (Constructor (QualIdent (Just "Prelude") (Ident "LT" 0)))) []))]) ,(TypeSig (203,1) [(Ident "max" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []) (ArrowType (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []) (ConstructorType (QualIdent Nothing (Ident "Int" 0)) [])))) ,(FunctionDecl (204,1) (Ident "max" 0) [(Equation (204,1) (FunLhs (Ident "max" 0) [(VariablePattern (Ident "x" 104)),(VariablePattern (Ident "y" 104))]) (SimpleRhs (204,11) (Case (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "compare" 0))) (Variable (QualIdent Nothing (Ident "x" 104)))) (Variable (QualIdent Nothing (Ident "y" 104)))) [(Alt (205,3) (ConstructorPattern (QualIdent (Just "Prelude") (Ident "LT" 0)) []) (SimpleRhs (205,9) (Variable (QualIdent Nothing (Ident "y" 104))) [])),(Alt (206,3) (VariablePattern (Ident "_" 109)) (SimpleRhs (206,9) (Variable (QualIdent Nothing (Ident "x" 104))) []))]) []))]) ,(TypeSig (209,1) [(Ident "min" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []) (ArrowType (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []) (ConstructorType (QualIdent Nothing (Ident "Int" 0)) [])))) ,(FunctionDecl (210,1) (Ident "min" 0) [(Equation (210,1) (FunLhs (Ident "min" 0) [(VariablePattern (Ident "x" 111)),(VariablePattern (Ident "y" 111))]) (SimpleRhs (210,12) (Case (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "compare" 0))) (Variable (QualIdent Nothing (Ident "x" 111)))) (Variable (QualIdent Nothing (Ident "y" 111)))) [(Alt (211,3) (ConstructorPattern (QualIdent (Just "Prelude") (Ident "GT" 0)) []) (SimpleRhs (211,9) (Variable (QualIdent Nothing (Ident "y" 111))) [])),(Alt (212,3) (VariablePattern (Ident "_" 116)) (SimpleRhs (212,9) (Variable (QualIdent Nothing (Ident "x" 111))) []))]) []))]) ,(TypeSig (215,1) [(Ident "==" 0)] (ArrowType (VariableType (Ident "a" 0)) (ArrowType (VariableType (Ident "a" 0)) (ConstructorType (QualIdent Nothing (Ident "Bool" 0)) [])))) ,(FlatExternalDecl (216,1) [(Ident "==" 0)]) ,(TypeSig (219,1) [(Ident "/=" 0)] (ArrowType (VariableType (Ident "a" 0)) (ArrowType (VariableType (Ident "a" 0)) (ConstructorType (QualIdent Nothing (Ident "Bool" 0)) [])))) ,(FunctionDecl (220,1) (Ident "/=" 0) [(Equation (220,1) (OpLhs (VariablePattern (Ident "x" 118)) (Ident "/=" 0) (VariablePattern (Ident "y" 118))) (SimpleRhs (220,19) (Apply (Variable (QualIdent (Just "Prelude") (Ident "not" 0))) (Paren (InfixApply (Variable (QualIdent Nothing (Ident "x" 118))) (InfixOp (QualIdent (Just "Prelude") (Ident "==" 0))) (Variable (QualIdent Nothing (Ident "y" 118)))))) []))]) ,(TypeSig (228,1) [(Ident "fst" 0)] (ArrowType (TupleType [(VariableType (Ident "a" 0)),(VariableType (Ident "_" 0))]) (VariableType (Ident "a" 0)))) ,(FunctionDecl (229,1) (Ident "fst" 0) [(Equation (229,1) (FunLhs (Ident "fst" 0) [(TuplePattern [(VariablePattern (Ident "x" 120)),(VariablePattern (Ident "_" 121))])]) (SimpleRhs (229,19) (Variable (QualIdent Nothing (Ident "x" 120))) []))]) ,(TypeSig (232,1) [(Ident "snd" 0)] (ArrowType (TupleType [(VariableType (Ident "_" 0)),(VariableType (Ident "b" 0))]) (VariableType (Ident "b" 0)))) ,(FunctionDecl (233,1) (Ident "snd" 0) [(Equation (233,1) (FunLhs (Ident "snd" 0) [(TuplePattern [(VariablePattern (Ident "_" 124)),(VariablePattern (Ident "y" 123))])]) (SimpleRhs (233,19) (Variable (QualIdent Nothing (Ident "y" 123))) []))]) ,(TypeSig (244,1) [(Ident "head" 0)] (ArrowType (ListType (VariableType (Ident "a" 0))) (VariableType (Ident "a" 0)))) ,(FunctionDecl (245,1) (Ident "head" 0) [(Equation (245,1) (FunLhs (Ident "head" 0) [(ParenPattern (InfixPattern (VariablePattern (Ident "x" 126)) (QualIdent Nothing (Ident ":" 0)) (VariablePattern (Ident "_" 127))))]) (SimpleRhs (245,19) (Variable (QualIdent Nothing (Ident "x" 126))) []))]) ,(TypeSig (248,1) [(Ident "tail" 0)] (ArrowType (ListType (VariableType (Ident "a" 0))) (ListType (VariableType (Ident "a" 0))))) ,(FunctionDecl (249,1) (Ident "tail" 0) [(Equation (249,1) (FunLhs (Ident "tail" 0) [(ParenPattern (InfixPattern (VariablePattern (Ident "_" 130)) (QualIdent Nothing (Ident ":" 0)) (VariablePattern (Ident "xs" 129))))]) (SimpleRhs (249,19) (Variable (QualIdent Nothing (Ident "xs" 129))) []))]) ,(TypeSig (252,1) [(Ident "null" 0)] (ArrowType (ListType (VariableType (Ident "_" 0))) (ConstructorType (QualIdent Nothing (Ident "Bool" 0)) []))) ,(FunctionDecl (253,1) (Ident "null" 0) [(Equation (253,1) (FunLhs (Ident "null" 0) [(ListPattern [])]) (SimpleRhs (253,19) (Constructor (QualIdent (Just "Prelude") (Ident "True" 0))) [])),(Equation (254,1) (FunLhs (Ident "null" 0) [(ParenPattern (InfixPattern (VariablePattern (Ident "_" 135)) (QualIdent Nothing (Ident ":" 0)) (VariablePattern (Ident "_" 136))))]) (SimpleRhs (254,19) (Constructor (QualIdent (Just "Prelude") (Ident "False" 0))) []))]) ,(TypeSig (259,1) [(Ident "++" 0)] (ArrowType (ListType (VariableType (Ident "a" 0))) (ArrowType (ListType (VariableType (Ident "a" 0))) (ListType (VariableType (Ident "a" 0)))))) ,(FunctionDecl (260,1) (Ident "++" 0) [(Equation (260,1) (OpLhs (ListPattern []) (Ident "++" 0) (VariablePattern (Ident "ys" 138))) (SimpleRhs (260,19) (Variable (QualIdent Nothing (Ident "ys" 138))) [])),(Equation (261,1) (OpLhs (ParenPattern (InfixPattern (VariablePattern (Ident "x" 140)) (QualIdent Nothing (Ident ":" 0)) (VariablePattern (Ident "xs" 140)))) (Ident "++" 0) (VariablePattern (Ident "ys" 140))) (SimpleRhs (261,19) (InfixApply (Variable (QualIdent Nothing (Ident "x" 140))) (InfixConstr (QualIdent Nothing (Ident ":" 0))) (InfixApply (Variable (QualIdent Nothing (Ident "xs" 140))) (InfixOp (QualIdent (Just "Prelude") (Ident "++" 0))) (Variable (QualIdent Nothing (Ident "ys" 140))))) []))]) ,(TypeSig (264,1) [(Ident "length" 0)] (ArrowType (ListType (VariableType (Ident "_" 0))) (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []))) ,(FunctionDecl (265,1) (Ident "length" 0) [(Equation (265,1) (FunLhs (Ident "length" 0) [(ListPattern [])]) (SimpleRhs (265,19) (Literal (Int (Ident "_" 144) 0)) [])),(Equation (266,1) (FunLhs (Ident "length" 0) [(ParenPattern (InfixPattern (VariablePattern (Ident "_" 146)) (QualIdent Nothing (Ident ":" 0)) (VariablePattern (Ident "xs" 145))))]) (SimpleRhs (266,19) (InfixApply (Literal (Int (Ident "_" 148) 1)) (InfixOp (QualIdent (Just "Prelude") (Ident "+" 0))) (Apply (Variable (QualIdent (Just "Prelude") (Ident "length" 0))) (Variable (QualIdent Nothing (Ident "xs" 145))))) []))]) ,(TypeSig (269,1) [(Ident "!!" 0)] (ArrowType (ListType (VariableType (Ident "a" 0))) (ArrowType (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []) (VariableType (Ident "a" 0))))) ,(FunctionDecl (270,1) (Ident "!!" 0) [(Equation (270,1) (OpLhs (ParenPattern (InfixPattern (VariablePattern (Ident "x" 149)) (QualIdent Nothing (Ident ":" 0)) (VariablePattern (Ident "xs" 149)))) (Ident "!!" 0) (VariablePattern (Ident "n" 149))) (GuardedRhs [(CondExpr (270,13) (InfixApply (Variable (QualIdent Nothing (Ident "n" 149))) (InfixOp (QualIdent (Just "Prelude") (Ident "==" 0))) (Literal (Int (Ident "_" 151) 0))) (Variable (QualIdent Nothing (Ident "x" 149)))),(CondExpr (271,13) (InfixApply (Variable (QualIdent Nothing (Ident "n" 149))) (InfixOp (QualIdent (Just "Prelude") (Ident ">" 0))) (Literal (Int (Ident "_" 152) 0))) (InfixApply (Variable (QualIdent Nothing (Ident "xs" 149))) (InfixOp (QualIdent (Just "Prelude") (Ident "!!" 0))) (Paren (InfixApply (Variable (QualIdent Nothing (Ident "n" 149))) (InfixOp (QualIdent (Just "Prelude") (Ident "-" 0))) (Literal (Int (Ident "_" 153) 1))))))] []))]) ,(TypeSig (274,1) [(Ident "map" 0)] (ArrowType (ArrowType (VariableType (Ident "a" 0)) (VariableType (Ident "b" 0))) (ArrowType (ListType (VariableType (Ident "a" 0))) (ListType (VariableType (Ident "b" 0)))))) ,(FunctionDecl (275,1) (Ident "map" 0) [(Equation (275,1) (FunLhs (Ident "map" 0) [(VariablePattern (Ident "_" 155)),(ListPattern [])]) (SimpleRhs (275,19) (List []) [])),(Equation (276,1) (FunLhs (Ident "map" 0) [(VariablePattern (Ident "f" 157)),(ParenPattern (InfixPattern (VariablePattern (Ident "x" 157)) (QualIdent Nothing (Ident ":" 0)) (VariablePattern (Ident "xs" 157))))]) (SimpleRhs (276,19) (InfixApply (Apply (Variable (QualIdent Nothing (Ident "f" 157))) (Variable (QualIdent Nothing (Ident "x" 157)))) (InfixConstr (QualIdent Nothing (Ident ":" 0))) (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "map" 0))) (Variable (QualIdent Nothing (Ident "f" 157)))) (Variable (QualIdent Nothing (Ident "xs" 157))))) []))]) ,(TypeSig (281,1) [(Ident "foldl" 0)] (ArrowType (ArrowType (VariableType (Ident "a" 0)) (ArrowType (VariableType (Ident "b" 0)) (VariableType (Ident "a" 0)))) (ArrowType (VariableType (Ident "a" 0)) (ArrowType (ListType (VariableType (Ident "b" 0))) (VariableType (Ident "a" 0)))))) ,(FunctionDecl (282,1) (Ident "foldl" 0) [(Equation (282,1) (FunLhs (Ident "foldl" 0) [(VariablePattern (Ident "_" 160)),(VariablePattern (Ident "z" 159)),(ListPattern [])]) (SimpleRhs (282,20) (Variable (QualIdent Nothing (Ident "z" 159))) [])),(Equation (283,1) (FunLhs (Ident "foldl" 0) [(VariablePattern (Ident "f" 162)),(VariablePattern (Ident "z" 162)),(ParenPattern (InfixPattern (VariablePattern (Ident "x" 162)) (QualIdent Nothing (Ident ":" 0)) (VariablePattern (Ident "xs" 162))))]) (SimpleRhs (283,20) (Apply (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "foldl" 0))) (Variable (QualIdent Nothing (Ident "f" 162)))) (Paren (Apply (Apply (Variable (QualIdent Nothing (Ident "f" 162))) (Variable (QualIdent Nothing (Ident "z" 162)))) (Variable (QualIdent Nothing (Ident "x" 162)))))) (Variable (QualIdent Nothing (Ident "xs" 162)))) []))]) ,(TypeSig (286,1) [(Ident "foldl1" 0)] (ArrowType (ArrowType (VariableType (Ident "a" 0)) (ArrowType (VariableType (Ident "a" 0)) (VariableType (Ident "a" 0)))) (ArrowType (ListType (VariableType (Ident "a" 0))) (VariableType (Ident "a" 0))))) ,(FunctionDecl (287,1) (Ident "foldl1" 0) [(Equation (287,1) (FunLhs (Ident "foldl1" 0) [(VariablePattern (Ident "f" 164)),(ParenPattern (InfixPattern (VariablePattern (Ident "x" 164)) (QualIdent Nothing (Ident ":" 0)) (VariablePattern (Ident "xs" 164))))]) (SimpleRhs (287,20) (Apply (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "foldl" 0))) (Variable (QualIdent Nothing (Ident "f" 164)))) (Variable (QualIdent Nothing (Ident "x" 164)))) (Variable (QualIdent Nothing (Ident "xs" 164)))) []))]) ,(TypeSig (292,1) [(Ident "foldr" 0)] (ArrowType (ArrowType (VariableType (Ident "a" 0)) (ArrowType (VariableType (Ident "b" 0)) (VariableType (Ident "b" 0)))) (ArrowType (VariableType (Ident "b" 0)) (ArrowType (ListType (VariableType (Ident "a" 0))) (VariableType (Ident "b" 0)))))) ,(FunctionDecl (293,1) (Ident "foldr" 0) [(Equation (293,1) (FunLhs (Ident "foldr" 0) [(VariablePattern (Ident "_" 167)),(VariablePattern (Ident "z" 166)),(ListPattern [])]) (SimpleRhs (293,20) (Variable (QualIdent Nothing (Ident "z" 166))) [])),(Equation (294,1) (FunLhs (Ident "foldr" 0) [(VariablePattern (Ident "f" 169)),(VariablePattern (Ident "z" 169)),(ParenPattern (InfixPattern (VariablePattern (Ident "x" 169)) (QualIdent Nothing (Ident ":" 0)) (VariablePattern (Ident "xs" 169))))]) (SimpleRhs (294,20) (Apply (Apply (Variable (QualIdent Nothing (Ident "f" 169))) (Variable (QualIdent Nothing (Ident "x" 169)))) (Paren (Apply (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "foldr" 0))) (Variable (QualIdent Nothing (Ident "f" 169)))) (Variable (QualIdent Nothing (Ident "z" 169)))) (Variable (QualIdent Nothing (Ident "xs" 169)))))) []))]) ,(TypeSig (297,1) [(Ident "foldr1" 0)] (ArrowType (ArrowType (VariableType (Ident "a" 0)) (ArrowType (VariableType (Ident "a" 0)) (VariableType (Ident "a" 0)))) (ArrowType (ListType (VariableType (Ident "a" 0))) (VariableType (Ident "a" 0))))) ,(FunctionDecl (298,1) (Ident "foldr1" 0) [(Equation (298,1) (FunLhs (Ident "foldr1" 0) [(VariablePattern (Ident "_" 172)),(ListPattern [(VariablePattern (Ident "x" 171))])]) (SimpleRhs (298,23) (Variable (QualIdent Nothing (Ident "x" 171))) [])),(Equation (299,1) (FunLhs (Ident "foldr1" 0) [(VariablePattern (Ident "f" 174)),(ParenPattern (InfixPattern (VariablePattern (Ident "x1" 174)) (QualIdent Nothing (Ident ":" 0)) (InfixPattern (VariablePattern (Ident "x2" 174)) (QualIdent Nothing (Ident ":" 0)) (VariablePattern (Ident "xs" 174)))))]) (SimpleRhs (299,23) (Apply (Apply (Variable (QualIdent Nothing (Ident "f" 174))) (Variable (QualIdent Nothing (Ident "x1" 174)))) (Paren (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "foldr1" 0))) (Variable (QualIdent Nothing (Ident "f" 174)))) (Paren (InfixApply (Variable (QualIdent Nothing (Ident "x2" 174))) (InfixConstr (QualIdent Nothing (Ident ":" 0))) (Variable (QualIdent Nothing (Ident "xs" 174)))))))) []))]) ,(TypeSig (302,1) [(Ident "filter" 0)] (ArrowType (ArrowType (VariableType (Ident "a" 0)) (ConstructorType (QualIdent Nothing (Ident "Bool" 0)) [])) (ArrowType (ListType (VariableType (Ident "a" 0))) (ListType (VariableType (Ident "a" 0)))))) ,(FunctionDecl (303,1) (Ident "filter" 0) [(Equation (303,1) (FunLhs (Ident "filter" 0) [(VariablePattern (Ident "_" 177)),(ListPattern [])]) (SimpleRhs (303,21) (List []) [])),(Equation (304,1) (FunLhs (Ident "filter" 0) [(VariablePattern (Ident "p" 179)),(ParenPattern (InfixPattern (VariablePattern (Ident "x" 179)) (QualIdent Nothing (Ident ":" 0)) (VariablePattern (Ident "xs" 179))))]) (SimpleRhs (304,21) (IfThenElse (Apply (Variable (QualIdent Nothing (Ident "p" 179))) (Variable (QualIdent Nothing (Ident "x" 179)))) (InfixApply (Variable (QualIdent Nothing (Ident "x" 179))) (InfixConstr (QualIdent Nothing (Ident ":" 0))) (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "filter" 0))) (Variable (QualIdent Nothing (Ident "p" 179)))) (Variable (QualIdent Nothing (Ident "xs" 179))))) (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "filter" 0))) (Variable (QualIdent Nothing (Ident "p" 179)))) (Variable (QualIdent Nothing (Ident "xs" 179))))) []))]) ,(TypeSig (309,1) [(Ident "zip" 0)] (ArrowType (ListType (VariableType (Ident "a" 0))) (ArrowType (ListType (VariableType (Ident "b" 0))) (ListType (TupleType [(VariableType (Ident "a" 0)),(VariableType (Ident "b" 0))]))))) ,(FunctionDecl (310,1) (Ident "zip" 0) [(Equation (310,1) (FunLhs (Ident "zip" 0) [(ListPattern []),(VariablePattern (Ident "_" 182))]) (SimpleRhs (310,21) (List []) [])),(Equation (311,1) (FunLhs (Ident "zip" 0) [(ParenPattern (InfixPattern (VariablePattern (Ident "_" 185)) (QualIdent Nothing (Ident ":" 0)) (VariablePattern (Ident "_" 186)))),(ListPattern [])]) (SimpleRhs (311,21) (List []) [])),(Equation (312,1) (FunLhs (Ident "zip" 0) [(ParenPattern (InfixPattern (VariablePattern (Ident "x" 188)) (QualIdent Nothing (Ident ":" 0)) (VariablePattern (Ident "xs" 188)))),(ParenPattern (InfixPattern (VariablePattern (Ident "y" 188)) (QualIdent Nothing (Ident ":" 0)) (VariablePattern (Ident "ys" 188))))]) (SimpleRhs (312,21) (InfixApply (Tuple [(Variable (QualIdent Nothing (Ident "x" 188))),(Variable (QualIdent Nothing (Ident "y" 188)))]) (InfixConstr (QualIdent Nothing (Ident ":" 0))) (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "zip" 0))) (Variable (QualIdent Nothing (Ident "xs" 188)))) (Variable (QualIdent Nothing (Ident "ys" 188))))) []))]) ,(TypeSig (316,1) [(Ident "zip3" 0)] (ArrowType (ListType (VariableType (Ident "a" 0))) (ArrowType (ListType (VariableType (Ident "b" 0))) (ArrowType (ListType (VariableType (Ident "c" 0))) (ListType (TupleType [(VariableType (Ident "a" 0)),(VariableType (Ident "b" 0)),(VariableType (Ident "c" 0))])))))) ,(FunctionDecl (317,1) (Ident "zip3" 0) [(Equation (317,1) (FunLhs (Ident "zip3" 0) [(ListPattern []),(VariablePattern (Ident "_" 191)),(VariablePattern (Ident "_" 192))]) (SimpleRhs (317,29) (List []) [])),(Equation (318,1) (FunLhs (Ident "zip3" 0) [(ParenPattern (InfixPattern (VariablePattern (Ident "_" 195)) (QualIdent Nothing (Ident ":" 0)) (VariablePattern (Ident "_" 196)))),(ListPattern []),(VariablePattern (Ident "_" 197))]) (SimpleRhs (318,29) (List []) [])),(Equation (319,1) (FunLhs (Ident "zip3" 0) [(ParenPattern (InfixPattern (VariablePattern (Ident "_" 200)) (QualIdent Nothing (Ident ":" 0)) (VariablePattern (Ident "_" 201)))),(ParenPattern (InfixPattern (VariablePattern (Ident "_" 202)) (QualIdent Nothing (Ident ":" 0)) (VariablePattern (Ident "_" 203)))),(ListPattern [])]) (SimpleRhs (319,29) (List []) [])),(Equation (320,1) (FunLhs (Ident "zip3" 0) [(ParenPattern (InfixPattern (VariablePattern (Ident "x" 205)) (QualIdent Nothing (Ident ":" 0)) (VariablePattern (Ident "xs" 205)))),(ParenPattern (InfixPattern (VariablePattern (Ident "y" 205)) (QualIdent Nothing (Ident ":" 0)) (VariablePattern (Ident "ys" 205)))),(ParenPattern (InfixPattern (VariablePattern (Ident "z" 205)) (QualIdent Nothing (Ident ":" 0)) (VariablePattern (Ident "zs" 205))))]) (SimpleRhs (320,29) (InfixApply (Tuple [(Variable (QualIdent Nothing (Ident "x" 205))),(Variable (QualIdent Nothing (Ident "y" 205))),(Variable (QualIdent Nothing (Ident "z" 205)))]) (InfixConstr (QualIdent Nothing (Ident ":" 0))) (Apply (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "zip3" 0))) (Variable (QualIdent Nothing (Ident "xs" 205)))) (Variable (QualIdent Nothing (Ident "ys" 205)))) (Variable (QualIdent Nothing (Ident "zs" 205))))) []))]) ,(TypeSig (324,1) [(Ident "zipWith" 0)] (ArrowType (ArrowType (VariableType (Ident "a" 0)) (ArrowType (VariableType (Ident "b" 0)) (VariableType (Ident "c" 0)))) (ArrowType (ListType (VariableType (Ident "a" 0))) (ArrowType (ListType (VariableType (Ident "b" 0))) (ListType (VariableType (Ident "c" 0))))))) ,(FunctionDecl (325,1) (Ident "zipWith" 0) [(Equation (325,1) (FunLhs (Ident "zipWith" 0) [(VariablePattern (Ident "_" 208)),(ListPattern []),(VariablePattern (Ident "_" 209))]) (SimpleRhs (325,27) (List []) [])),(Equation (326,1) (FunLhs (Ident "zipWith" 0) [(VariablePattern (Ident "_" 212)),(ParenPattern (InfixPattern (VariablePattern (Ident "_" 213)) (QualIdent Nothing (Ident ":" 0)) (VariablePattern (Ident "_" 214)))),(ListPattern [])]) (SimpleRhs (326,27) (List []) [])),(Equation (327,1) (FunLhs (Ident "zipWith" 0) [(VariablePattern (Ident "f" 216)),(ParenPattern (InfixPattern (VariablePattern (Ident "x" 216)) (QualIdent Nothing (Ident ":" 0)) (VariablePattern (Ident "xs" 216)))),(ParenPattern (InfixPattern (VariablePattern (Ident "y" 216)) (QualIdent Nothing (Ident ":" 0)) (VariablePattern (Ident "ys" 216))))]) (SimpleRhs (327,27) (InfixApply (Apply (Apply (Variable (QualIdent Nothing (Ident "f" 216))) (Variable (QualIdent Nothing (Ident "x" 216)))) (Variable (QualIdent Nothing (Ident "y" 216)))) (InfixConstr (QualIdent Nothing (Ident ":" 0))) (Apply (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "zipWith" 0))) (Variable (QualIdent Nothing (Ident "f" 216)))) (Variable (QualIdent Nothing (Ident "xs" 216)))) (Variable (QualIdent Nothing (Ident "ys" 216))))) []))]) ,(TypeSig (331,1) [(Ident "zipWith3" 0)] (ArrowType (ArrowType (VariableType (Ident "a" 0)) (ArrowType (VariableType (Ident "b" 0)) (ArrowType (VariableType (Ident "c" 0)) (VariableType (Ident "d" 0))))) (ArrowType (ListType (VariableType (Ident "a" 0))) (ArrowType (ListType (VariableType (Ident "b" 0))) (ArrowType (ListType (VariableType (Ident "c" 0))) (ListType (VariableType (Ident "d" 0)))))))) ,(FunctionDecl (332,1) (Ident "zipWith3" 0) [(Equation (332,1) (FunLhs (Ident "zipWith3" 0) [(VariablePattern (Ident "_" 219)),(ListPattern []),(VariablePattern (Ident "_" 220)),(VariablePattern (Ident "_" 221))]) (SimpleRhs (332,35) (List []) [])),(Equation (333,1) (FunLhs (Ident "zipWith3" 0) [(VariablePattern (Ident "_" 224)),(ParenPattern (InfixPattern (VariablePattern (Ident "_" 225)) (QualIdent Nothing (Ident ":" 0)) (VariablePattern (Ident "_" 226)))),(ListPattern []),(VariablePattern (Ident "_" 227))]) (SimpleRhs (333,35) (List []) [])),(Equation (334,1) (FunLhs (Ident "zipWith3" 0) [(VariablePattern (Ident "_" 230)),(ParenPattern (InfixPattern (VariablePattern (Ident "_" 231)) (QualIdent Nothing (Ident ":" 0)) (VariablePattern (Ident "_" 232)))),(ParenPattern (InfixPattern (VariablePattern (Ident "_" 233)) (QualIdent Nothing (Ident ":" 0)) (VariablePattern (Ident "_" 234)))),(ListPattern [])]) (SimpleRhs (334,35) (List []) [])),(Equation (335,1) (FunLhs (Ident "zipWith3" 0) [(VariablePattern (Ident "f" 236)),(ParenPattern (InfixPattern (VariablePattern (Ident "x" 236)) (QualIdent Nothing (Ident ":" 0)) (VariablePattern (Ident "xs" 236)))),(ParenPattern (InfixPattern (VariablePattern (Ident "y" 236)) (QualIdent Nothing (Ident ":" 0)) (VariablePattern (Ident "ys" 236)))),(ParenPattern (InfixPattern (VariablePattern (Ident "z" 236)) (QualIdent Nothing (Ident ":" 0)) (VariablePattern (Ident "zs" 236))))]) (SimpleRhs (335,35) (InfixApply (Apply (Apply (Apply (Variable (QualIdent Nothing (Ident "f" 236))) (Variable (QualIdent Nothing (Ident "x" 236)))) (Variable (QualIdent Nothing (Ident "y" 236)))) (Variable (QualIdent Nothing (Ident "z" 236)))) (InfixConstr (QualIdent Nothing (Ident ":" 0))) (Apply (Apply (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "zipWith3" 0))) (Variable (QualIdent Nothing (Ident "f" 236)))) (Variable (QualIdent Nothing (Ident "xs" 236)))) (Variable (QualIdent Nothing (Ident "ys" 236)))) (Variable (QualIdent Nothing (Ident "zs" 236))))) []))]) ,(TypeSig (338,1) [(Ident "unzip" 0)] (ArrowType (ListType (TupleType [(VariableType (Ident "a" 0)),(VariableType (Ident "b" 0))])) (TupleType [(ListType (VariableType (Ident "a" 0))),(ListType (VariableType (Ident "b" 0)))]))) ,(FunctionDecl (339,1) (Ident "unzip" 0) [(Equation (339,1) (FunLhs (Ident "unzip" 0) [(ListPattern [])]) (SimpleRhs (339,23) (Tuple [(List []),(List [])]) [])),(Equation (340,1) (FunLhs (Ident "unzip" 0) [(ParenPattern (InfixPattern (TuplePattern [(VariablePattern (Ident "x" 240)),(VariablePattern (Ident "y" 240))]) (QualIdent Nothing (Ident ":" 0)) (VariablePattern (Ident "ps" 240))))]) (SimpleRhs (340,23) (Tuple [(InfixApply (Variable (QualIdent Nothing (Ident "x" 240))) (InfixConstr (QualIdent Nothing (Ident ":" 0))) (Variable (QualIdent Nothing (Ident "xs" 241)))),(InfixApply (Variable (QualIdent Nothing (Ident "y" 240))) (InfixConstr (QualIdent Nothing (Ident ":" 0))) (Variable (QualIdent Nothing (Ident "ys" 241))))]) [(PatternDecl (340,41) (TuplePattern [(VariablePattern (Ident "xs" 241)),(VariablePattern (Ident "ys" 241))]) (SimpleRhs (340,51) (Apply (Variable (QualIdent (Just "Prelude") (Ident "unzip" 0))) (Variable (QualIdent Nothing (Ident "ps" 240)))) []))]))]) ,(TypeSig (343,1) [(Ident "unzip3" 0)] (ArrowType (ListType (TupleType [(VariableType (Ident "a" 0)),(VariableType (Ident "b" 0)),(VariableType (Ident "c" 0))])) (TupleType [(ListType (VariableType (Ident "a" 0))),(ListType (VariableType (Ident "b" 0))),(ListType (VariableType (Ident "c" 0)))]))) ,(FunctionDecl (344,1) (Ident "unzip3" 0) [(Equation (344,1) (FunLhs (Ident "unzip3" 0) [(ListPattern [])]) (SimpleRhs (344,23) (Tuple [(List []),(List []),(List [])]) [])),(Equation (345,1) (FunLhs (Ident "unzip3" 0) [(ParenPattern (InfixPattern (TuplePattern [(VariablePattern (Ident "x" 245)),(VariablePattern (Ident "y" 245)),(VariablePattern (Ident "z" 245))]) (QualIdent Nothing (Ident ":" 0)) (VariablePattern (Ident "ts" 245))))]) (SimpleRhs (345,23) (Tuple [(InfixApply (Variable (QualIdent Nothing (Ident "x" 245))) (InfixConstr (QualIdent Nothing (Ident ":" 0))) (Variable (QualIdent Nothing (Ident "xs" 246)))),(InfixApply (Variable (QualIdent Nothing (Ident "y" 245))) (InfixConstr (QualIdent Nothing (Ident ":" 0))) (Variable (QualIdent Nothing (Ident "ys" 246)))),(InfixApply (Variable (QualIdent Nothing (Ident "z" 245))) (InfixConstr (QualIdent Nothing (Ident ":" 0))) (Variable (QualIdent Nothing (Ident "zs" 246))))]) [(PatternDecl (345,46) (TuplePattern [(VariablePattern (Ident "xs" 246)),(VariablePattern (Ident "ys" 246)),(VariablePattern (Ident "zs" 246))]) (SimpleRhs (345,59) (Apply (Variable (QualIdent (Just "Prelude") (Ident "unzip3" 0))) (Variable (QualIdent Nothing (Ident "ts" 245)))) []))]))]) ,(TypeSig (348,1) [(Ident "concat" 0)] (ArrowType (ListType (ListType (VariableType (Ident "a" 0)))) (ListType (VariableType (Ident "a" 0))))) ,(FunctionDecl (349,1) (Ident "concat" 0) [(Equation (349,1) (FunLhs (Ident "concat" 0) [(VariablePattern (Ident "l" 248))]) (SimpleRhs (349,21) (Apply (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "foldr" 0))) (Variable (QualIdent (Just "Prelude") (Ident "++" 0)))) (List [])) (Variable (QualIdent Nothing (Ident "l" 248)))) []))]) ,(TypeSig (352,1) [(Ident "concatMap" 0)] (ArrowType (ArrowType (VariableType (Ident "a" 0)) (ListType (VariableType (Ident "b" 0)))) (ArrowType (ListType (VariableType (Ident "a" 0))) (ListType (VariableType (Ident "b" 0)))))) ,(FunctionDecl (353,1) (Ident "concatMap" 0) [(Equation (353,1) (FunLhs (Ident "concatMap" 0) [(VariablePattern (Ident "f" 250))]) (SimpleRhs (353,21) (InfixApply (Variable (QualIdent (Just "Prelude") (Ident "concat" 0))) (InfixOp (QualIdent (Just "Prelude") (Ident "." 0))) (Apply (Variable (QualIdent (Just "Prelude") (Ident "map" 0))) (Variable (QualIdent Nothing (Ident "f" 250))))) []))]) ,(TypeSig (357,1) [(Ident "iterate" 0)] (ArrowType (ArrowType (VariableType (Ident "a" 0)) (VariableType (Ident "a" 0))) (ArrowType (VariableType (Ident "a" 0)) (ListType (VariableType (Ident "a" 0)))))) ,(FunctionDecl (358,1) (Ident "iterate" 0) [(Equation (358,1) (FunLhs (Ident "iterate" 0) [(VariablePattern (Ident "f" 252)),(VariablePattern (Ident "x" 252))]) (SimpleRhs (358,21) (InfixApply (Variable (QualIdent Nothing (Ident "x" 252))) (InfixConstr (QualIdent Nothing (Ident ":" 0))) (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "iterate" 0))) (Variable (QualIdent Nothing (Ident "f" 252)))) (Paren (Apply (Variable (QualIdent Nothing (Ident "f" 252))) (Variable (QualIdent Nothing (Ident "x" 252))))))) []))]) ,(TypeSig (362,1) [(Ident "repeat" 0)] (ArrowType (VariableType (Ident "a" 0)) (ListType (VariableType (Ident "a" 0))))) ,(FunctionDecl (363,1) (Ident "repeat" 0) [(Equation (363,1) (FunLhs (Ident "repeat" 0) [(VariablePattern (Ident "x" 254))]) (SimpleRhs (363,21) (InfixApply (Variable (QualIdent Nothing (Ident "x" 254))) (InfixConstr (QualIdent Nothing (Ident ":" 0))) (Apply (Variable (QualIdent (Just "Prelude") (Ident "repeat" 0))) (Variable (QualIdent Nothing (Ident "x" 254))))) []))]) ,(TypeSig (366,1) [(Ident "replicate" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []) (ArrowType (VariableType (Ident "a" 0)) (ListType (VariableType (Ident "a" 0)))))) ,(FunctionDecl (367,1) (Ident "replicate" 0) [(Equation (367,1) (FunLhs (Ident "replicate" 0) [(VariablePattern (Ident "n" 256)),(VariablePattern (Ident "x" 256))]) (SimpleRhs (367,21) (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "take" 0))) (Variable (QualIdent Nothing (Ident "n" 256)))) (Paren (Apply (Variable (QualIdent (Just "Prelude") (Ident "repeat" 0))) (Variable (QualIdent Nothing (Ident "x" 256)))))) []))]) ,(TypeSig (370,1) [(Ident "take" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []) (ArrowType (ListType (VariableType (Ident "a" 0))) (ListType (VariableType (Ident "a" 0)))))) ,(FunctionDecl (371,1) (Ident "take" 0) [(Equation (371,1) (FunLhs (Ident "take" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Neg" 0)) [(VariablePattern (Ident "_" 259))])),(VariablePattern (Ident "_" 260))]) (SimpleRhs (371,25) (List []) [])),(Equation (372,1) (FunLhs (Ident "take" 0) [(ConstructorPattern (QualIdent (Just "Prelude") (Ident "Zero" 0)) []),(VariablePattern (Ident "_" 263))]) (SimpleRhs (372,25) (List []) [])),(Equation (373,1) (FunLhs (Ident "take" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Pos" 0)) [(VariablePattern (Ident "_" 266))])),(ListPattern [])]) (SimpleRhs (373,25) (List []) [])),(Equation (374,1) (FunLhs (Ident "take" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Pos" 0)) [(VariablePattern (Ident "n" 268))])),(ParenPattern (InfixPattern (VariablePattern (Ident "x" 268)) (QualIdent Nothing (Ident ":" 0)) (VariablePattern (Ident "xs" 268))))]) (SimpleRhs (374,23) (InfixApply (Variable (QualIdent Nothing (Ident "x" 268))) (InfixConstr (QualIdent Nothing (Ident ":" 0))) (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "take" 0))) (Paren (InfixApply (Apply (Constructor (QualIdent (Just "Prelude") (Ident "Pos" 0))) (Variable (QualIdent Nothing (Ident "n" 268)))) (InfixOp (QualIdent (Just "Prelude") (Ident "-" 0))) (Literal (Int (Ident "_" 270) 1))))) (Variable (QualIdent Nothing (Ident "xs" 268))))) []))]) ,(TypeSig (377,1) [(Ident "drop" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []) (ArrowType (ListType (VariableType (Ident "a" 0))) (ListType (VariableType (Ident "a" 0)))))) ,(FunctionDecl (378,1) (Ident "drop" 0) [(Equation (378,1) (FunLhs (Ident "drop" 0) [(VariablePattern (Ident "n" 271)),(VariablePattern (Ident "l" 271))]) (SimpleRhs (378,21) (IfThenElse (InfixApply (Variable (QualIdent Nothing (Ident "n" 271))) (InfixOp (QualIdent (Just "Prelude") (Ident "<=" 0))) (Literal (Int (Ident "_" 280) 0))) (Variable (QualIdent Nothing (Ident "l" 271))) (Apply (Apply (Variable (QualIdent Nothing (Ident "dropp" 272))) (Variable (QualIdent Nothing (Ident "n" 271)))) (Variable (QualIdent Nothing (Ident "l" 271))))) [(FunctionDecl (379,10) (Ident "dropp" 272) [(Equation (379,10) (FunLhs (Ident "dropp" 272) [(VariablePattern (Ident "_" 274)),(ListPattern [])]) (SimpleRhs (379,27) (List []) [])),(Equation (380,10) (FunLhs (Ident "dropp" 272) [(VariablePattern (Ident "m" 276)),(ParenPattern (InfixPattern (VariablePattern (Ident "_" 277)) (QualIdent Nothing (Ident ":" 0)) (VariablePattern (Ident "xs" 276))))]) (SimpleRhs (380,27) (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "drop" 0))) (Paren (InfixApply (Variable (QualIdent Nothing (Ident "m" 276))) (InfixOp (QualIdent (Just "Prelude") (Ident "-" 0))) (Literal (Int (Ident "_" 279) 1))))) (Variable (QualIdent Nothing (Ident "xs" 276)))) []))])]))]) ,(TypeSig (383,1) [(Ident "splitAt" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []) (ArrowType (ListType (VariableType (Ident "a" 0))) (TupleType [(ListType (VariableType (Ident "a" 0))),(ListType (VariableType (Ident "a" 0)))])))) ,(FunctionDecl (384,1) (Ident "splitAt" 0) [(Equation (384,1) (FunLhs (Ident "splitAt" 0) [(VariablePattern (Ident "n" 281)),(VariablePattern (Ident "l" 281))]) (SimpleRhs (384,21) (IfThenElse (InfixApply (Variable (QualIdent Nothing (Ident "n" 281))) (InfixOp (QualIdent (Just "Prelude") (Ident "<=" 0))) (Literal (Int (Ident "_" 291) 0))) (Tuple [(List []),(Variable (QualIdent Nothing (Ident "l" 281)))]) (Apply (Apply (Variable (QualIdent Nothing (Ident "splitAtp" 282))) (Variable (QualIdent Nothing (Ident "n" 281)))) (Variable (QualIdent Nothing (Ident "l" 281))))) [(FunctionDecl (385,10) (Ident "splitAtp" 282) [(Equation (385,10) (FunLhs (Ident "splitAtp" 282) [(VariablePattern (Ident "_" 284)),(ListPattern [])]) (SimpleRhs (385,30) (Tuple [(List []),(List [])]) [])),(Equation (386,10) (FunLhs (Ident "splitAtp" 282) [(VariablePattern (Ident "m" 286)),(ParenPattern (InfixPattern (VariablePattern (Ident "x" 286)) (QualIdent Nothing (Ident ":" 0)) (VariablePattern (Ident "xs" 286))))]) (SimpleRhs (386,30) (Let [(PatternDecl (386,34) (TuplePattern [(VariablePattern (Ident "ys" 288)),(VariablePattern (Ident "zs" 288))]) (SimpleRhs (386,44) (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "splitAt" 0))) (Paren (InfixApply (Variable (QualIdent Nothing (Ident "m" 286))) (InfixOp (QualIdent (Just "Prelude") (Ident "-" 0))) (Literal (Int (Ident "_" 290) 1))))) (Variable (QualIdent Nothing (Ident "xs" 286)))) []))] (Tuple [(InfixApply (Variable (QualIdent Nothing (Ident "x" 286))) (InfixConstr (QualIdent Nothing (Ident ":" 0))) (Variable (QualIdent Nothing (Ident "ys" 288)))),(Variable (QualIdent Nothing (Ident "zs" 288)))])) []))])]))]) ,(TypeSig (389,1) [(Ident "takeWhile" 0)] (ArrowType (ArrowType (VariableType (Ident "a" 0)) (ConstructorType (QualIdent Nothing (Ident "Bool" 0)) [])) (ArrowType (ListType (VariableType (Ident "a" 0))) (ListType (VariableType (Ident "a" 0)))))) ,(FunctionDecl (390,1) (Ident "takeWhile" 0) [(Equation (390,1) (FunLhs (Ident "takeWhile" 0) [(VariablePattern (Ident "_" 293)),(ListPattern [])]) (SimpleRhs (390,22) (List []) [])),(Equation (391,1) (FunLhs (Ident "takeWhile" 0) [(VariablePattern (Ident "p" 295)),(ParenPattern (InfixPattern (VariablePattern (Ident "x" 295)) (QualIdent Nothing (Ident ":" 0)) (VariablePattern (Ident "xs" 295))))]) (SimpleRhs (391,22) (IfThenElse (Apply (Variable (QualIdent Nothing (Ident "p" 295))) (Variable (QualIdent Nothing (Ident "x" 295)))) (InfixApply (Variable (QualIdent Nothing (Ident "x" 295))) (InfixConstr (QualIdent Nothing (Ident ":" 0))) (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "takeWhile" 0))) (Variable (QualIdent Nothing (Ident "p" 295)))) (Variable (QualIdent Nothing (Ident "xs" 295))))) (List [])) []))]) ,(TypeSig (394,1) [(Ident "dropWhile" 0)] (ArrowType (ArrowType (VariableType (Ident "a" 0)) (ConstructorType (QualIdent Nothing (Ident "Bool" 0)) [])) (ArrowType (ListType (VariableType (Ident "a" 0))) (ListType (VariableType (Ident "a" 0)))))) ,(FunctionDecl (395,1) (Ident "dropWhile" 0) [(Equation (395,1) (FunLhs (Ident "dropWhile" 0) [(VariablePattern (Ident "_" 298)),(ListPattern [])]) (SimpleRhs (395,22) (List []) [])),(Equation (396,1) (FunLhs (Ident "dropWhile" 0) [(VariablePattern (Ident "p" 300)),(ParenPattern (InfixPattern (VariablePattern (Ident "x" 300)) (QualIdent Nothing (Ident ":" 0)) (VariablePattern (Ident "xs" 300))))]) (SimpleRhs (396,22) (IfThenElse (Apply (Variable (QualIdent Nothing (Ident "p" 300))) (Variable (QualIdent Nothing (Ident "x" 300)))) (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "dropWhile" 0))) (Variable (QualIdent Nothing (Ident "p" 300)))) (Variable (QualIdent Nothing (Ident "xs" 300)))) (InfixApply (Variable (QualIdent Nothing (Ident "x" 300))) (InfixConstr (QualIdent Nothing (Ident ":" 0))) (Variable (QualIdent Nothing (Ident "xs" 300))))) []))]) ,(TypeSig (399,1) [(Ident "span" 0)] (ArrowType (ArrowType (VariableType (Ident "a" 0)) (ConstructorType (QualIdent Nothing (Ident "Bool" 0)) [])) (ArrowType (ListType (VariableType (Ident "a" 0))) (TupleType [(ListType (VariableType (Ident "a" 0))),(ListType (VariableType (Ident "a" 0)))])))) ,(FunctionDecl (400,1) (Ident "span" 0) [(Equation (400,1) (FunLhs (Ident "span" 0) [(VariablePattern (Ident "_" 303)),(ListPattern [])]) (SimpleRhs (400,22) (Tuple [(List []),(List [])]) [])),(Equation (401,1) (FunLhs (Ident "span" 0) [(VariablePattern (Ident "p" 305)),(ParenPattern (InfixPattern (VariablePattern (Ident "x" 305)) (QualIdent Nothing (Ident ":" 0)) (VariablePattern (Ident "xs" 305))))]) (GuardedRhs [(CondExpr (402,8) (Apply (Variable (QualIdent Nothing (Ident "p" 305))) (Variable (QualIdent Nothing (Ident "x" 305)))) (Let [(PatternDecl (402,26) (TuplePattern [(VariablePattern (Ident "ys" 307)),(VariablePattern (Ident "zs" 307))]) (SimpleRhs (402,36) (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "span" 0))) (Variable (QualIdent Nothing (Ident "p" 305)))) (Variable (QualIdent Nothing (Ident "xs" 305)))) []))] (Tuple [(InfixApply (Variable (QualIdent Nothing (Ident "x" 305))) (InfixConstr (QualIdent Nothing (Ident ":" 0))) (Variable (QualIdent Nothing (Ident "ys" 307)))),(Variable (QualIdent Nothing (Ident "zs" 307)))]))),(CondExpr (403,8) (Variable (QualIdent (Just "Prelude") (Ident "otherwise" 0))) (Tuple [(List []),(InfixApply (Variable (QualIdent Nothing (Ident "x" 305))) (InfixConstr (QualIdent Nothing (Ident ":" 0))) (Variable (QualIdent Nothing (Ident "xs" 305))))]))] []))]) ,(TypeSig (407,1) [(Ident "break" 0)] (ArrowType (ArrowType (VariableType (Ident "a" 0)) (ConstructorType (QualIdent Nothing (Ident "Bool" 0)) [])) (ArrowType (ListType (VariableType (Ident "a" 0))) (TupleType [(ListType (VariableType (Ident "a" 0))),(ListType (VariableType (Ident "a" 0)))])))) ,(FunctionDecl (408,1) (Ident "break" 0) [(Equation (408,1) (FunLhs (Ident "break" 0) [(VariablePattern (Ident "p" 309))]) (SimpleRhs (408,22) (Apply (Variable (QualIdent (Just "Prelude") (Ident "span" 0))) (Paren (InfixApply (Variable (QualIdent (Just "Prelude") (Ident "not" 0))) (InfixOp (QualIdent (Just "Prelude") (Ident "." 0))) (Variable (QualIdent Nothing (Ident "p" 309)))))) []))]) ,(TypeSig (412,1) [(Ident "lines" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "String" 0)) []) (ListType (ConstructorType (QualIdent Nothing (Ident "String" 0)) [])))) ,(FunctionDecl (413,1) (Ident "lines" 0) [(Equation (413,1) (FunLhs (Ident "lines" 0) [(ListPattern [])]) (SimpleRhs (413,16) (List []) [])),(Equation (414,1) (FunLhs (Ident "lines" 0) [(ParenPattern (InfixPattern (VariablePattern (Ident "x" 313)) (QualIdent Nothing (Ident ":" 0)) (VariablePattern (Ident "xs" 313))))]) (SimpleRhs (414,16) (Let [(PatternDecl (414,20) (TuplePattern [(VariablePattern (Ident "l" 321)),(VariablePattern (Ident "xs_l" 321))]) (SimpleRhs (414,31) (Apply (Variable (QualIdent Nothing (Ident "splitline" 314))) (Paren (InfixApply (Variable (QualIdent Nothing (Ident "x" 313))) (InfixConstr (QualIdent Nothing (Ident ":" 0))) (Variable (QualIdent Nothing (Ident "xs" 313)))))) []))] (InfixApply (Variable (QualIdent Nothing (Ident "l" 321))) (InfixConstr (QualIdent Nothing (Ident ":" 0))) (Apply (Variable (QualIdent (Just "Prelude") (Ident "lines" 0))) (Variable (QualIdent Nothing (Ident "xs_l" 321)))))) [(FunctionDecl (415,8) (Ident "splitline" 314) [(Equation (415,8) (FunLhs (Ident "splitline" 314) [(ListPattern [])]) (SimpleRhs (415,27) (Tuple [(List []),(List [])]) [])),(Equation (416,8) (FunLhs (Ident "splitline" 314) [(ParenPattern (InfixPattern (VariablePattern (Ident "c" 317)) (QualIdent Nothing (Ident ":" 0)) (VariablePattern (Ident "cs" 317))))]) (SimpleRhs (416,27) (IfThenElse (InfixApply (Variable (QualIdent Nothing (Ident "c" 317))) (InfixOp (QualIdent (Just "Prelude") (Ident "==" 0))) (Literal (Char '\n'))) (Tuple [(List []),(Variable (QualIdent Nothing (Ident "cs" 317)))]) (Let [(PatternDecl (418,36) (TuplePattern [(VariablePattern (Ident "ds" 319)),(VariablePattern (Ident "es" 319))]) (SimpleRhs (418,46) (Apply (Variable (QualIdent Nothing (Ident "splitline" 314))) (Variable (QualIdent Nothing (Ident "cs" 317)))) []))] (Tuple [(InfixApply (Variable (QualIdent Nothing (Ident "c" 317))) (InfixConstr (QualIdent Nothing (Ident ":" 0))) (Variable (QualIdent Nothing (Ident "ds" 319)))),(Variable (QualIdent Nothing (Ident "es" 319)))]))) []))])]))]) ,(TypeSig (421,1) [(Ident "unlines" 0)] (ArrowType (ListType (ConstructorType (QualIdent Nothing (Ident "String" 0)) [])) (ConstructorType (QualIdent Nothing (Ident "String" 0)) []))) ,(FunctionDecl (422,1) (Ident "unlines" 0) [(Equation (422,1) (FunLhs (Ident "unlines" 0) [(VariablePattern (Ident "ls" 323))]) (SimpleRhs (422,14) (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "concatMap" 0))) (RightSection (InfixOp (QualIdent (Just "Prelude") (Ident "++" 0))) (Literal (String "\n")))) (Variable (QualIdent Nothing (Ident "ls" 323)))) []))]) ,(TypeSig (426,1) [(Ident "words" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "String" 0)) []) (ListType (ConstructorType (QualIdent Nothing (Ident "String" 0)) [])))) ,(FunctionDecl (427,1) (Ident "words" 0) [(Equation (427,1) (FunLhs (Ident "words" 0) [(VariablePattern (Ident "s" 325))]) (SimpleRhs (427,14) (Let [(PatternDecl (427,18) (VariablePattern (Ident "s1" 329)) (SimpleRhs (427,23) (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "dropWhile" 0))) (Variable (QualIdent Nothing (Ident "isSpace" 326)))) (Variable (QualIdent Nothing (Ident "s" 325)))) []))] (IfThenElse (InfixApply (Variable (QualIdent Nothing (Ident "s1" 329))) (InfixOp (QualIdent (Just "Prelude") (Ident "==" 0))) (Literal (String ""))) (List []) (Let [(PatternDecl (429,37) (TuplePattern [(VariablePattern (Ident "w" 331)),(VariablePattern (Ident "s2" 331))]) (SimpleRhs (429,46) (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "break" 0))) (Variable (QualIdent Nothing (Ident "isSpace" 326)))) (Variable (QualIdent Nothing (Ident "s1" 329)))) []))] (InfixApply (Variable (QualIdent Nothing (Ident "w" 331))) (InfixConstr (QualIdent Nothing (Ident ":" 0))) (Apply (Variable (QualIdent (Just "Prelude") (Ident "words" 0))) (Variable (QualIdent Nothing (Ident "s2" 331)))))))) [(FunctionDecl (432,4) (Ident "isSpace" 326) [(Equation (432,4) (FunLhs (Ident "isSpace" 326) [(VariablePattern (Ident "c" 327))]) (SimpleRhs (432,16) (InfixApply (InfixApply (Variable (QualIdent Nothing (Ident "c" 327))) (InfixOp (QualIdent (Just "Prelude") (Ident "==" 0))) (Literal (Char ' '))) (InfixOp (QualIdent (Just "Prelude") (Ident "||" 0))) (InfixApply (InfixApply (Variable (QualIdent Nothing (Ident "c" 327))) (InfixOp (QualIdent (Just "Prelude") (Ident "==" 0))) (Literal (Char '\t'))) (InfixOp (QualIdent (Just "Prelude") (Ident "||" 0))) (InfixApply (InfixApply (Variable (QualIdent Nothing (Ident "c" 327))) (InfixOp (QualIdent (Just "Prelude") (Ident "==" 0))) (Literal (Char '\n'))) (InfixOp (QualIdent (Just "Prelude") (Ident "||" 0))) (InfixApply (Variable (QualIdent Nothing (Ident "c" 327))) (InfixOp (QualIdent (Just "Prelude") (Ident "==" 0))) (Literal (Char '\r')))))) []))])]))]) ,(TypeSig (435,1) [(Ident "unwords" 0)] (ArrowType (ListType (ConstructorType (QualIdent Nothing (Ident "String" 0)) [])) (ConstructorType (QualIdent Nothing (Ident "String" 0)) []))) ,(FunctionDecl (436,1) (Ident "unwords" 0) [(Equation (436,1) (FunLhs (Ident "unwords" 0) [(VariablePattern (Ident "ws" 333))]) (SimpleRhs (436,14) (IfThenElse (InfixApply (Variable (QualIdent Nothing (Ident "ws" 333))) (InfixOp (QualIdent (Just "Prelude") (Ident "==" 0))) (List [])) (List []) (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "foldr1" 0))) (Paren (Lambda [(VariablePattern (Ident "w" 335)),(VariablePattern (Ident "s" 335))] (InfixApply (Variable (QualIdent Nothing (Ident "w" 335))) (InfixOp (QualIdent (Just "Prelude") (Ident "++" 0))) (InfixApply (Literal (Char ' ')) (InfixConstr (QualIdent Nothing (Ident ":" 0))) (Variable (QualIdent Nothing (Ident "s" 335)))))))) (Variable (QualIdent Nothing (Ident "ws" 333))))) []))]) ,(TypeSig (440,1) [(Ident "reverse" 0)] (ArrowType (ListType (VariableType (Ident "a" 0))) (ListType (VariableType (Ident "a" 0))))) ,(FunctionDecl (441,1) (Ident "reverse" 0) [(Equation (441,1) (FunLhs (Ident "reverse" 0) []) (SimpleRhs (441,14) (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "foldl" 0))) (Paren (Apply (Variable (QualIdent (Just "Prelude") (Ident "flip" 0))) (Constructor (QualIdent Nothing (Ident ":" 0)))))) (List [])) []))]) ,(TypeSig (444,1) [(Ident "and" 0)] (ArrowType (ListType (ConstructorType (QualIdent Nothing (Ident "Bool" 0)) [])) (ConstructorType (QualIdent Nothing (Ident "Bool" 0)) []))) ,(FunctionDecl (445,1) (Ident "and" 0) [(Equation (445,1) (FunLhs (Ident "and" 0) []) (SimpleRhs (445,14) (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "foldr" 0))) (Variable (QualIdent (Just "Prelude") (Ident "&&" 0)))) (Constructor (QualIdent (Just "Prelude") (Ident "True" 0)))) []))]) ,(TypeSig (448,1) [(Ident "or" 0)] (ArrowType (ListType (ConstructorType (QualIdent Nothing (Ident "Bool" 0)) [])) (ConstructorType (QualIdent Nothing (Ident "Bool" 0)) []))) ,(FunctionDecl (449,1) (Ident "or" 0) [(Equation (449,1) (FunLhs (Ident "or" 0) []) (SimpleRhs (449,14) (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "foldr" 0))) (Variable (QualIdent (Just "Prelude") (Ident "||" 0)))) (Constructor (QualIdent (Just "Prelude") (Ident "False" 0)))) []))]) ,(TypeSig (452,1) [(Ident "any" 0)] (ArrowType (ArrowType (VariableType (Ident "a" 0)) (ConstructorType (QualIdent Nothing (Ident "Bool" 0)) [])) (ArrowType (ListType (VariableType (Ident "a" 0))) (ConstructorType (QualIdent Nothing (Ident "Bool" 0)) [])))) ,(FunctionDecl (453,1) (Ident "any" 0) [(Equation (453,1) (FunLhs (Ident "any" 0) [(VariablePattern (Ident "p" 342))]) (SimpleRhs (453,14) (InfixApply (Variable (QualIdent (Just "Prelude") (Ident "or" 0))) (InfixOp (QualIdent (Just "Prelude") (Ident "." 0))) (Apply (Variable (QualIdent (Just "Prelude") (Ident "map" 0))) (Variable (QualIdent Nothing (Ident "p" 342))))) []))]) ,(TypeSig (456,1) [(Ident "all" 0)] (ArrowType (ArrowType (VariableType (Ident "a" 0)) (ConstructorType (QualIdent Nothing (Ident "Bool" 0)) [])) (ArrowType (ListType (VariableType (Ident "a" 0))) (ConstructorType (QualIdent Nothing (Ident "Bool" 0)) [])))) ,(FunctionDecl (457,1) (Ident "all" 0) [(Equation (457,1) (FunLhs (Ident "all" 0) [(VariablePattern (Ident "p" 344))]) (SimpleRhs (457,14) (InfixApply (Variable (QualIdent (Just "Prelude") (Ident "and" 0))) (InfixOp (QualIdent (Just "Prelude") (Ident "." 0))) (Apply (Variable (QualIdent (Just "Prelude") (Ident "map" 0))) (Variable (QualIdent Nothing (Ident "p" 344))))) []))]) ,(TypeSig (460,1) [(Ident "elem" 0)] (ArrowType (VariableType (Ident "a" 0)) (ArrowType (ListType (VariableType (Ident "a" 0))) (ConstructorType (QualIdent Nothing (Ident "Bool" 0)) [])))) ,(FunctionDecl (461,1) (Ident "elem" 0) [(Equation (461,1) (FunLhs (Ident "elem" 0) [(VariablePattern (Ident "x" 346))]) (SimpleRhs (461,14) (Apply (Variable (QualIdent (Just "Prelude") (Ident "any" 0))) (LeftSection (Variable (QualIdent Nothing (Ident "x" 346))) (InfixOp (QualIdent (Just "Prelude") (Ident "==" 0))))) []))]) ,(TypeSig (464,1) [(Ident "notElem" 0)] (ArrowType (VariableType (Ident "a" 0)) (ArrowType (ListType (VariableType (Ident "a" 0))) (ConstructorType (QualIdent Nothing (Ident "Bool" 0)) [])))) ,(FunctionDecl (465,1) (Ident "notElem" 0) [(Equation (465,1) (FunLhs (Ident "notElem" 0) [(VariablePattern (Ident "x" 348))]) (SimpleRhs (465,14) (Apply (Variable (QualIdent (Just "Prelude") (Ident "all" 0))) (LeftSection (Variable (QualIdent Nothing (Ident "x" 348))) (InfixOp (QualIdent (Just "Prelude") (Ident "/=" 0))))) []))]) ,(TypeSig (468,1) [(Ident "lookup" 0)] (ArrowType (VariableType (Ident "a" 0)) (ArrowType (ListType (TupleType [(VariableType (Ident "a" 0)),(VariableType (Ident "b" 0))])) (ConstructorType (QualIdent Nothing (Ident "Maybe" 0)) [(VariableType (Ident "b" 0))])))) ,(FunctionDecl (469,1) (Ident "lookup" 0) [(Equation (469,1) (FunLhs (Ident "lookup" 0) [(VariablePattern (Ident "_" 351)),(ListPattern [])]) (SimpleRhs (469,21) (Constructor (QualIdent (Just "Prelude") (Ident "Nothing" 0))) [])),(Equation (470,1) (FunLhs (Ident "lookup" 0) [(VariablePattern (Ident "k" 353)),(ParenPattern (InfixPattern (TuplePattern [(VariablePattern (Ident "x" 353)),(VariablePattern (Ident "y" 353))]) (QualIdent Nothing (Ident ":" 0)) (VariablePattern (Ident "xys" 353))))]) (GuardedRhs [(CondExpr (471,7) (InfixApply (Variable (QualIdent Nothing (Ident "k" 353))) (InfixOp (QualIdent (Just "Prelude") (Ident "==" 0))) (Variable (QualIdent Nothing (Ident "x" 353)))) (Apply (Constructor (QualIdent (Just "Prelude") (Ident "Just" 0))) (Variable (QualIdent Nothing (Ident "y" 353))))),(CondExpr (472,7) (Variable (QualIdent (Just "Prelude") (Ident "otherwise" 0))) (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "lookup" 0))) (Variable (QualIdent Nothing (Ident "k" 353)))) (Variable (QualIdent Nothing (Ident "xys" 353)))))] []))]) ,(TypeSig (475,1) [(Ident "enumFrom" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []) (ListType (ConstructorType (QualIdent Nothing (Ident "Int" 0)) [])))) ,(FunctionDecl (476,1) (Ident "enumFrom" 0) [(Equation (476,1) (FunLhs (Ident "enumFrom" 0) [(VariablePattern (Ident "n" 355))]) (SimpleRhs (476,26) (InfixApply (Variable (QualIdent Nothing (Ident "n" 355))) (InfixConstr (QualIdent Nothing (Ident ":" 0))) (Apply (Variable (QualIdent (Just "Prelude") (Ident "enumFrom" 0))) (Paren (InfixApply (Variable (QualIdent Nothing (Ident "n" 355))) (InfixOp (QualIdent (Just "Prelude") (Ident "+" 0))) (Literal (Int (Ident "_" 357) 1)))))) []))]) ,(TypeSig (479,1) [(Ident "enumFromThen" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []) (ArrowType (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []) (ListType (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []))))) ,(FunctionDecl (480,1) (Ident "enumFromThen" 0) [(Equation (480,1) (FunLhs (Ident "enumFromThen" 0) [(VariablePattern (Ident "n1" 358)),(VariablePattern (Ident "n2" 358))]) (SimpleRhs (480,26) (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "iterate" 0))) (LeftSection (Paren (InfixApply (Variable (QualIdent Nothing (Ident "n2" 358))) (InfixOp (QualIdent (Just "Prelude") (Ident "-" 0))) (Variable (QualIdent Nothing (Ident "n1" 358))))) (InfixOp (QualIdent (Just "Prelude") (Ident "+" 0))))) (Variable (QualIdent Nothing (Ident "n1" 358)))) []))]) ,(TypeSig (483,1) [(Ident "enumFromTo" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []) (ArrowType (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []) (ListType (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []))))) ,(FunctionDecl (484,1) (Ident "enumFromTo" 0) [(Equation (484,1) (FunLhs (Ident "enumFromTo" 0) [(VariablePattern (Ident "n" 360)),(VariablePattern (Ident "m" 360))]) (SimpleRhs (484,26) (IfThenElse (InfixApply (Variable (QualIdent Nothing (Ident "n" 360))) (InfixOp (QualIdent (Just "Prelude") (Ident ">" 0))) (Variable (QualIdent Nothing (Ident "m" 360)))) (List []) (InfixApply (Variable (QualIdent Nothing (Ident "n" 360))) (InfixConstr (QualIdent Nothing (Ident ":" 0))) (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "enumFromTo" 0))) (Paren (InfixApply (Variable (QualIdent Nothing (Ident "n" 360))) (InfixOp (QualIdent (Just "Prelude") (Ident "+" 0))) (Literal (Int (Ident "_" 362) 1))))) (Variable (QualIdent Nothing (Ident "m" 360)))))) []))]) ,(TypeSig (487,1) [(Ident "enumFromThenTo" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []) (ArrowType (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []) (ArrowType (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []) (ListType (ConstructorType (QualIdent Nothing (Ident "Int" 0)) [])))))) ,(FunctionDecl (488,1) (Ident "enumFromThenTo" 0) [(Equation (488,1) (FunLhs (Ident "enumFromThenTo" 0) [(VariablePattern (Ident "n1" 363)),(VariablePattern (Ident "n2" 363)),(VariablePattern (Ident "m" 363))]) (SimpleRhs (488,26) (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "takeWhile" 0))) (Variable (QualIdent Nothing (Ident "p" 364)))) (Paren (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "enumFromThen" 0))) (Variable (QualIdent Nothing (Ident "n1" 363)))) (Variable (QualIdent Nothing (Ident "n2" 363)))))) [(FunctionDecl (489,32) (Ident "p" 364) [(Equation (489,32) (FunLhs (Ident "p" 364) [(VariablePattern (Ident "x" 365))]) (GuardedRhs [(CondExpr (489,36) (InfixApply (Variable (QualIdent Nothing (Ident "n2" 363))) (InfixOp (QualIdent (Just "Prelude") (Ident ">=" 0))) (Variable (QualIdent Nothing (Ident "n1" 363)))) (Paren (InfixApply (Variable (QualIdent Nothing (Ident "x" 365))) (InfixOp (QualIdent (Just "Prelude") (Ident "<=" 0))) (Variable (QualIdent Nothing (Ident "m" 363)))))),(CondExpr (490,36) (Variable (QualIdent (Just "Prelude") (Ident "otherwise" 0))) (Paren (InfixApply (Variable (QualIdent Nothing (Ident "x" 365))) (InfixOp (QualIdent (Just "Prelude") (Ident ">=" 0))) (Variable (QualIdent Nothing (Ident "m" 363))))))] []))])]))]) ,(TypeSig (494,1) [(Ident "ord" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Char" 0)) []) (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []))) ,(FunctionDecl (495,1) (Ident "ord" 0) [(Equation (495,1) (FunLhs (Ident "ord" 0) [(VariablePattern (Ident "c" 367))]) (SimpleRhs (495,9) (InfixApply (Variable (QualIdent (Just "Prelude") (Ident "prim_ord" 0))) (InfixOp (QualIdent (Just "Prelude") (Ident "$##" 0))) (Variable (QualIdent Nothing (Ident "c" 367)))) []))]) ,(TypeSig (497,1) [(Ident "prim_ord" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Char" 0)) []) (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []))) ,(FlatExternalDecl (498,1) [(Ident "prim_ord" 0)]) ,(TypeSig (501,1) [(Ident "chr" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []) (ConstructorType (QualIdent Nothing (Ident "Char" 0)) []))) ,(FunctionDecl (502,1) (Ident "chr" 0) [(Equation (502,1) (FunLhs (Ident "chr" 0) [(VariablePattern (Ident "i" 369))]) (SimpleRhs (502,9) (InfixApply (Variable (QualIdent (Just "Prelude") (Ident "prim_chr" 0))) (InfixOp (QualIdent (Just "Prelude") (Ident "$##" 0))) (Variable (QualIdent Nothing (Ident "i" 369)))) []))]) ,(TypeSig (504,1) [(Ident "prim_chr" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []) (ConstructorType (QualIdent Nothing (Ident "Char" 0)) []))) ,(FlatExternalDecl (505,1) [(Ident "prim_chr" 0)]) ,(TypeSig (511,1) [(Ident "succ" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Nat" 0)) []) (ConstructorType (QualIdent Nothing (Ident "Nat" 0)) []))) ,(FunctionDecl (512,1) (Ident "succ" 0) [(Equation (512,1) (FunLhs (Ident "succ" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "O" 0)) [(VariablePattern (Ident "bs" 371))]))]) (SimpleRhs (512,15) (Apply (Constructor (QualIdent (Just "Prelude") (Ident "I" 0))) (Variable (QualIdent Nothing (Ident "bs" 371)))) [])),(Equation (513,1) (FunLhs (Ident "succ" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "I" 0)) [(VariablePattern (Ident "bs" 373))]))]) (SimpleRhs (513,15) (Apply (Constructor (QualIdent (Just "Prelude") (Ident "O" 0))) (Paren (Apply (Variable (QualIdent (Just "Prelude") (Ident "succ" 0))) (Variable (QualIdent Nothing (Ident "bs" 373)))))) [])),(Equation (514,1) (FunLhs (Ident "succ" 0) [(ConstructorPattern (QualIdent (Just "Prelude") (Ident "IHi" 0)) [])]) (SimpleRhs (514,12) (Apply (Constructor (QualIdent (Just "Prelude") (Ident "O" 0))) (Constructor (QualIdent (Just "Prelude") (Ident "IHi" 0)))) []))]) ,(TypeSig (516,1) [(Ident "+^" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Nat" 0)) []) (ArrowType (ConstructorType (QualIdent Nothing (Ident "Nat" 0)) []) (ConstructorType (QualIdent Nothing (Ident "Nat" 0)) [])))) ,(FunctionDecl (517,1) (Ident "+^" 0) [(Equation (517,1) (OpLhs (ConstructorPattern (QualIdent (Just "Prelude") (Ident "O" 0)) [(VariablePattern (Ident "x" 377))]) (Ident "+^" 0) (ConstructorPattern (QualIdent (Just "Prelude") (Ident "O" 0)) [(VariablePattern (Ident "y" 377))])) (SimpleRhs (517,14) (Apply (Constructor (QualIdent (Just "Prelude") (Ident "O" 0))) (Paren (InfixApply (Variable (QualIdent Nothing (Ident "x" 377))) (InfixOp (QualIdent (Just "Prelude") (Ident "+^" 0))) (Variable (QualIdent Nothing (Ident "y" 377)))))) [])),(Equation (518,1) (OpLhs (ConstructorPattern (QualIdent (Just "Prelude") (Ident "O" 0)) [(VariablePattern (Ident "x" 379))]) (Ident "+^" 0) (ConstructorPattern (QualIdent (Just "Prelude") (Ident "I" 0)) [(VariablePattern (Ident "y" 379))])) (SimpleRhs (518,14) (Apply (Constructor (QualIdent (Just "Prelude") (Ident "I" 0))) (Paren (InfixApply (Variable (QualIdent Nothing (Ident "x" 379))) (InfixOp (QualIdent (Just "Prelude") (Ident "+^" 0))) (Variable (QualIdent Nothing (Ident "y" 379)))))) [])),(Equation (519,1) (OpLhs (ConstructorPattern (QualIdent (Just "Prelude") (Ident "O" 0)) [(VariablePattern (Ident "x" 381))]) (Ident "+^" 0) (ConstructorPattern (QualIdent (Just "Prelude") (Ident "IHi" 0)) [])) (SimpleRhs (519,14) (Apply (Constructor (QualIdent (Just "Prelude") (Ident "I" 0))) (Variable (QualIdent Nothing (Ident "x" 381)))) [])),(Equation (520,1) (OpLhs (ConstructorPattern (QualIdent (Just "Prelude") (Ident "I" 0)) [(VariablePattern (Ident "x" 383))]) (Ident "+^" 0) (ConstructorPattern (QualIdent (Just "Prelude") (Ident "O" 0)) [(VariablePattern (Ident "y" 383))])) (SimpleRhs (520,14) (Apply (Constructor (QualIdent (Just "Prelude") (Ident "I" 0))) (Paren (InfixApply (Variable (QualIdent Nothing (Ident "x" 383))) (InfixOp (QualIdent (Just "Prelude") (Ident "+^" 0))) (Variable (QualIdent Nothing (Ident "y" 383)))))) [])),(Equation (521,1) (OpLhs (ConstructorPattern (QualIdent (Just "Prelude") (Ident "I" 0)) [(VariablePattern (Ident "x" 385))]) (Ident "+^" 0) (ConstructorPattern (QualIdent (Just "Prelude") (Ident "I" 0)) [(VariablePattern (Ident "y" 385))])) (SimpleRhs (521,14) (Apply (Constructor (QualIdent (Just "Prelude") (Ident "O" 0))) (Paren (InfixApply (Apply (Variable (QualIdent (Just "Prelude") (Ident "succ" 0))) (Variable (QualIdent Nothing (Ident "x" 385)))) (InfixOp (QualIdent (Just "Prelude") (Ident "+^" 0))) (Variable (QualIdent Nothing (Ident "y" 385)))))) [])),(Equation (522,1) (OpLhs (ConstructorPattern (QualIdent (Just "Prelude") (Ident "I" 0)) [(VariablePattern (Ident "x" 387))]) (Ident "+^" 0) (ConstructorPattern (QualIdent (Just "Prelude") (Ident "IHi" 0)) [])) (SimpleRhs (522,14) (Apply (Constructor (QualIdent (Just "Prelude") (Ident "O" 0))) (Paren (Apply (Variable (QualIdent (Just "Prelude") (Ident "succ" 0))) (Variable (QualIdent Nothing (Ident "x" 387)))))) [])),(Equation (523,1) (OpLhs (ConstructorPattern (QualIdent (Just "Prelude") (Ident "IHi" 0)) []) (Ident "+^" 0) (VariablePattern (Ident "y" 389))) (SimpleRhs (523,14) (Apply (Variable (QualIdent (Just "Prelude") (Ident "succ" 0))) (Variable (QualIdent Nothing (Ident "y" 389)))) []))]) ,(TypeSig (525,1) [(Ident "cmpNat" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Nat" 0)) []) (ArrowType (ConstructorType (QualIdent Nothing (Ident "Nat" 0)) []) (ConstructorType (QualIdent Nothing (Ident "Ordering" 0)) [])))) ,(FunctionDecl (526,1) (Ident "cmpNat" 0) [(Equation (526,1) (FunLhs (Ident "cmpNat" 0) [(ConstructorPattern (QualIdent (Just "Prelude") (Ident "IHi" 0)) []),(ConstructorPattern (QualIdent (Just "Prelude") (Ident "IHi" 0)) [])]) (SimpleRhs (526,20) (Constructor (QualIdent (Just "Prelude") (Ident "EQ" 0))) [])),(Equation (527,1) (FunLhs (Ident "cmpNat" 0) [(ConstructorPattern (QualIdent (Just "Prelude") (Ident "IHi" 0)) []),(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "O" 0)) [(VariablePattern (Ident "_" 394))]))]) (SimpleRhs (527,20) (Constructor (QualIdent (Just "Prelude") (Ident "LT" 0))) [])),(Equation (528,1) (FunLhs (Ident "cmpNat" 0) [(ConstructorPattern (QualIdent (Just "Prelude") (Ident "IHi" 0)) []),(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "I" 0)) [(VariablePattern (Ident "_" 397))]))]) (SimpleRhs (528,20) (Constructor (QualIdent (Just "Prelude") (Ident "LT" 0))) [])),(Equation (529,1) (FunLhs (Ident "cmpNat" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "O" 0)) [(VariablePattern (Ident "_" 400))])),(ConstructorPattern (QualIdent (Just "Prelude") (Ident "IHi" 0)) [])]) (SimpleRhs (529,20) (Constructor (QualIdent (Just "Prelude") (Ident "GT" 0))) [])),(Equation (530,1) (FunLhs (Ident "cmpNat" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "I" 0)) [(VariablePattern (Ident "_" 403))])),(ConstructorPattern (QualIdent (Just "Prelude") (Ident "IHi" 0)) [])]) (SimpleRhs (530,20) (Constructor (QualIdent (Just "Prelude") (Ident "GT" 0))) [])),(Equation (531,1) (FunLhs (Ident "cmpNat" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "O" 0)) [(VariablePattern (Ident "x" 405))])),(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "O" 0)) [(VariablePattern (Ident "y" 405))]))]) (SimpleRhs (531,22) (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "cmpNat" 0))) (Variable (QualIdent Nothing (Ident "x" 405)))) (Variable (QualIdent Nothing (Ident "y" 405)))) [])),(Equation (532,1) (FunLhs (Ident "cmpNat" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "I" 0)) [(VariablePattern (Ident "x" 407))])),(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "I" 0)) [(VariablePattern (Ident "y" 407))]))]) (SimpleRhs (532,22) (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "cmpNat" 0))) (Variable (QualIdent Nothing (Ident "x" 407)))) (Variable (QualIdent Nothing (Ident "y" 407)))) [])),(Equation (533,1) (FunLhs (Ident "cmpNat" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "O" 0)) [(VariablePattern (Ident "x" 409))])),(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "I" 0)) [(VariablePattern (Ident "y" 409))]))]) (SimpleRhs (533,22) (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "cmpNatLT" 0))) (Variable (QualIdent Nothing (Ident "x" 409)))) (Variable (QualIdent Nothing (Ident "y" 409)))) [])),(Equation (534,1) (FunLhs (Ident "cmpNat" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "I" 0)) [(VariablePattern (Ident "x" 411))])),(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "O" 0)) [(VariablePattern (Ident "y" 411))]))]) (SimpleRhs (534,22) (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "cmpNatGT" 0))) (Variable (QualIdent Nothing (Ident "x" 411)))) (Variable (QualIdent Nothing (Ident "y" 411)))) []))]) ,(TypeSig (536,1) [(Ident "cmpNatLT" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Nat" 0)) []) (ArrowType (ConstructorType (QualIdent Nothing (Ident "Nat" 0)) []) (ConstructorType (QualIdent Nothing (Ident "Ordering" 0)) [])))) ,(FunctionDecl (537,1) (Ident "cmpNatLT" 0) [(Equation (537,1) (FunLhs (Ident "cmpNatLT" 0) [(ConstructorPattern (QualIdent (Just "Prelude") (Ident "IHi" 0)) []),(VariablePattern (Ident "_" 414))]) (SimpleRhs (537,22) (Constructor (QualIdent (Just "Prelude") (Ident "LT" 0))) [])),(Equation (538,1) (FunLhs (Ident "cmpNatLT" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "O" 0)) [(VariablePattern (Ident "_" 417))])),(ConstructorPattern (QualIdent (Just "Prelude") (Ident "IHi" 0)) [])]) (SimpleRhs (538,22) (Constructor (QualIdent (Just "Prelude") (Ident "GT" 0))) [])),(Equation (539,1) (FunLhs (Ident "cmpNatLT" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "I" 0)) [(VariablePattern (Ident "_" 420))])),(ConstructorPattern (QualIdent (Just "Prelude") (Ident "IHi" 0)) [])]) (SimpleRhs (539,22) (Constructor (QualIdent (Just "Prelude") (Ident "GT" 0))) [])),(Equation (540,1) (FunLhs (Ident "cmpNatLT" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "O" 0)) [(VariablePattern (Ident "x" 422))])),(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "O" 0)) [(VariablePattern (Ident "y" 422))]))]) (SimpleRhs (540,24) (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "cmpNatLT" 0))) (Variable (QualIdent Nothing (Ident "x" 422)))) (Variable (QualIdent Nothing (Ident "y" 422)))) [])),(Equation (541,1) (FunLhs (Ident "cmpNatLT" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "I" 0)) [(VariablePattern (Ident "x" 424))])),(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "I" 0)) [(VariablePattern (Ident "y" 424))]))]) (SimpleRhs (541,24) (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "cmpNatLT" 0))) (Variable (QualIdent Nothing (Ident "x" 424)))) (Variable (QualIdent Nothing (Ident "y" 424)))) [])),(Equation (542,1) (FunLhs (Ident "cmpNatLT" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "O" 0)) [(VariablePattern (Ident "x" 426))])),(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "I" 0)) [(VariablePattern (Ident "y" 426))]))]) (SimpleRhs (542,24) (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "cmpNatLT" 0))) (Variable (QualIdent Nothing (Ident "x" 426)))) (Variable (QualIdent Nothing (Ident "y" 426)))) [])),(Equation (543,1) (FunLhs (Ident "cmpNatLT" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "I" 0)) [(VariablePattern (Ident "x" 428))])),(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "O" 0)) [(VariablePattern (Ident "y" 428))]))]) (SimpleRhs (543,24) (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "cmpNatGT" 0))) (Variable (QualIdent Nothing (Ident "x" 428)))) (Variable (QualIdent Nothing (Ident "y" 428)))) []))]) ,(TypeSig (545,1) [(Ident "cmpNatGT" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Nat" 0)) []) (ArrowType (ConstructorType (QualIdent Nothing (Ident "Nat" 0)) []) (ConstructorType (QualIdent Nothing (Ident "Ordering" 0)) [])))) ,(FunctionDecl (546,1) (Ident "cmpNatGT" 0) [(Equation (546,1) (FunLhs (Ident "cmpNatGT" 0) [(VariablePattern (Ident "_" 431)),(ConstructorPattern (QualIdent (Just "Prelude") (Ident "IHi" 0)) [])]) (SimpleRhs (546,22) (Constructor (QualIdent (Just "Prelude") (Ident "GT" 0))) [])),(Equation (547,1) (FunLhs (Ident "cmpNatGT" 0) [(ConstructorPattern (QualIdent (Just "Prelude") (Ident "IHi" 0)) []),(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "O" 0)) [(VariablePattern (Ident "_" 434))]))]) (SimpleRhs (547,22) (Constructor (QualIdent (Just "Prelude") (Ident "LT" 0))) [])),(Equation (548,1) (FunLhs (Ident "cmpNatGT" 0) [(ConstructorPattern (QualIdent (Just "Prelude") (Ident "IHi" 0)) []),(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "I" 0)) [(VariablePattern (Ident "_" 437))]))]) (SimpleRhs (548,22) (Constructor (QualIdent (Just "Prelude") (Ident "LT" 0))) [])),(Equation (549,1) (FunLhs (Ident "cmpNatGT" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "O" 0)) [(VariablePattern (Ident "x" 439))])),(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "O" 0)) [(VariablePattern (Ident "y" 439))]))]) (SimpleRhs (549,24) (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "cmpNatGT" 0))) (Variable (QualIdent Nothing (Ident "x" 439)))) (Variable (QualIdent Nothing (Ident "y" 439)))) [])),(Equation (550,1) (FunLhs (Ident "cmpNatGT" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "I" 0)) [(VariablePattern (Ident "x" 441))])),(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "I" 0)) [(VariablePattern (Ident "y" 441))]))]) (SimpleRhs (550,24) (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "cmpNatGT" 0))) (Variable (QualIdent Nothing (Ident "x" 441)))) (Variable (QualIdent Nothing (Ident "y" 441)))) [])),(Equation (551,1) (FunLhs (Ident "cmpNatGT" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "O" 0)) [(VariablePattern (Ident "x" 443))])),(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "I" 0)) [(VariablePattern (Ident "y" 443))]))]) (SimpleRhs (551,24) (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "cmpNatLT" 0))) (Variable (QualIdent Nothing (Ident "x" 443)))) (Variable (QualIdent Nothing (Ident "y" 443)))) [])),(Equation (552,1) (FunLhs (Ident "cmpNatGT" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "I" 0)) [(VariablePattern (Ident "x" 445))])),(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "O" 0)) [(VariablePattern (Ident "y" 445))]))]) (SimpleRhs (552,24) (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "cmpNatGT" 0))) (Variable (QualIdent Nothing (Ident "x" 445)))) (Variable (QualIdent Nothing (Ident "y" 445)))) []))]) ,(TypeSig (554,1) [(Ident "<^" 0),(Ident ">^" 0),(Ident "<=^" 0),(Ident ">=^" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Nat" 0)) []) (ArrowType (ConstructorType (QualIdent Nothing (Ident "Nat" 0)) []) (ConstructorType (QualIdent Nothing (Ident "Bool" 0)) [])))) ,(FunctionDecl (556,1) (Ident "<^" 0) [(Equation (556,1) (OpLhs (VariablePattern (Ident "x" 447)) (Ident "<^" 0) (VariablePattern (Ident "y" 447))) (SimpleRhs (556,11) (Apply (Variable (QualIdent (Just "Prelude") (Ident "isLT" 0))) (Paren (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "cmpNat" 0))) (Variable (QualIdent Nothing (Ident "x" 447)))) (Variable (QualIdent Nothing (Ident "y" 447)))))) []))]) ,(FunctionDecl (557,1) (Ident ">^" 0) [(Equation (557,1) (OpLhs (VariablePattern (Ident "x" 449)) (Ident ">^" 0) (VariablePattern (Ident "y" 449))) (SimpleRhs (557,11) (Apply (Variable (QualIdent (Just "Prelude") (Ident "isGT" 0))) (Paren (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "cmpNat" 0))) (Variable (QualIdent Nothing (Ident "x" 449)))) (Variable (QualIdent Nothing (Ident "y" 449)))))) []))]) ,(FunctionDecl (558,1) (Ident "<=^" 0) [(Equation (558,1) (OpLhs (VariablePattern (Ident "x" 451)) (Ident "<=^" 0) (VariablePattern (Ident "y" 451))) (SimpleRhs (558,11) (Apply (Variable (QualIdent (Just "Prelude") (Ident "not" 0))) (Paren (Apply (Variable (QualIdent (Just "Prelude") (Ident "isGT" 0))) (Paren (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "cmpNat" 0))) (Variable (QualIdent Nothing (Ident "x" 451)))) (Variable (QualIdent Nothing (Ident "y" 451)))))))) []))]) ,(FunctionDecl (559,1) (Ident ">=^" 0) [(Equation (559,1) (OpLhs (VariablePattern (Ident "x" 453)) (Ident ">=^" 0) (VariablePattern (Ident "y" 453))) (SimpleRhs (559,11) (Apply (Variable (QualIdent (Just "Prelude") (Ident "not" 0))) (Paren (Apply (Variable (QualIdent (Just "Prelude") (Ident "isLT" 0))) (Paren (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "cmpNat" 0))) (Variable (QualIdent Nothing (Ident "x" 453)))) (Variable (QualIdent Nothing (Ident "y" 453)))))))) []))]) ,(TypeSig (561,1) [(Ident "*^" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Nat" 0)) []) (ArrowType (ConstructorType (QualIdent Nothing (Ident "Nat" 0)) []) (ConstructorType (QualIdent Nothing (Ident "Nat" 0)) [])))) ,(FunctionDecl (562,1) (Ident "*^" 0) [(Equation (562,1) (OpLhs (ConstructorPattern (QualIdent (Just "Prelude") (Ident "IHi" 0)) []) (Ident "*^" 0) (VariablePattern (Ident "y" 455))) (SimpleRhs (562,12) (Variable (QualIdent Nothing (Ident "y" 455))) [])),(Equation (563,1) (OpLhs (ConstructorPattern (QualIdent (Just "Prelude") (Ident "I" 0)) [(VariablePattern (Ident "x" 457))]) (Ident "*^" 0) (VariablePattern (Ident "y" 457))) (SimpleRhs (563,12) (InfixApply (Apply (Constructor (QualIdent (Just "Prelude") (Ident "O" 0))) (Paren (InfixApply (Variable (QualIdent Nothing (Ident "y" 457))) (InfixOp (QualIdent (Just "Prelude") (Ident "*^" 0))) (Variable (QualIdent Nothing (Ident "x" 457)))))) (InfixOp (QualIdent (Just "Prelude") (Ident "+^" 0))) (Variable (QualIdent Nothing (Ident "y" 457)))) [])),(Equation (564,1) (OpLhs (ConstructorPattern (QualIdent (Just "Prelude") (Ident "O" 0)) [(VariablePattern (Ident "x" 459))]) (Ident "*^" 0) (VariablePattern (Ident "y" 459))) (SimpleRhs (564,12) (Apply (Constructor (QualIdent (Just "Prelude") (Ident "O" 0))) (Paren (InfixApply (Variable (QualIdent Nothing (Ident "x" 459))) (InfixOp (QualIdent (Just "Prelude") (Ident "*^" 0))) (Variable (QualIdent Nothing (Ident "y" 459)))))) []))]) ,(TypeSig (566,1) [(Ident "pred" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Nat" 0)) []) (ConstructorType (QualIdent Nothing (Ident "Nat" 0)) []))) ,(FunctionDecl (567,1) (Ident "pred" 0) [(Equation (567,1) (FunLhs (Ident "pred" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "O" 0)) [(ConstructorPattern (QualIdent (Just "Prelude") (Ident "IHi" 0)) [])]))]) (SimpleRhs (567,20) (Constructor (QualIdent (Just "Prelude") (Ident "IHi" 0))) [])),(Equation (568,1) (FunLhs (Ident "pred" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "O" 0)) [(AsPattern (Ident "x" 463) (ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "O" 0)) [(VariablePattern (Ident "_" 464))])))]))]) (SimpleRhs (568,20) (Apply (Constructor (QualIdent (Just "Prelude") (Ident "I" 0))) (Paren (Apply (Variable (QualIdent (Just "Prelude") (Ident "pred" 0))) (Variable (QualIdent Nothing (Ident "x" 463)))))) [])),(Equation (569,1) (FunLhs (Ident "pred" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "O" 0)) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "I" 0)) [(VariablePattern (Ident "x" 466))]))]))]) (SimpleRhs (569,20) (Apply (Constructor (QualIdent (Just "Prelude") (Ident "I" 0))) (Paren (Apply (Constructor (QualIdent (Just "Prelude") (Ident "O" 0))) (Variable (QualIdent Nothing (Ident "x" 466)))))) [])),(Equation (570,1) (FunLhs (Ident "pred" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "I" 0)) [(VariablePattern (Ident "x" 468))]))]) (SimpleRhs (570,20) (Apply (Constructor (QualIdent (Just "Prelude") (Ident "O" 0))) (Variable (QualIdent Nothing (Ident "x" 468)))) []))]) ,(TypeSig (578,1) [(Ident "inc" 0),(Ident "dec" 0),(Ident "mult2" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []) (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []))) ,(FunctionDecl (580,1) (Ident "inc" 0) [(Equation (580,1) (FunLhs (Ident "inc" 0) [(ConstructorPattern (QualIdent (Just "Prelude") (Ident "Zero" 0)) [])]) (SimpleRhs (580,12) (Apply (Constructor (QualIdent (Just "Prelude") (Ident "Pos" 0))) (Constructor (QualIdent (Just "Prelude") (Ident "IHi" 0)))) [])),(Equation (581,1) (FunLhs (Ident "inc" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Pos" 0)) [(VariablePattern (Ident "n" 472))]))]) (SimpleRhs (581,15) (Apply (Constructor (QualIdent (Just "Prelude") (Ident "Pos" 0))) (Paren (Apply (Variable (QualIdent (Just "Prelude") (Ident "succ" 0))) (Variable (QualIdent Nothing (Ident "n" 472)))))) [])),(Equation (582,1) (FunLhs (Ident "inc" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Neg" 0)) [(ConstructorPattern (QualIdent (Just "Prelude") (Ident "IHi" 0)) [])]))]) (SimpleRhs (582,17) (Constructor (QualIdent (Just "Prelude") (Ident "Zero" 0))) [])),(Equation (583,1) (FunLhs (Ident "inc" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Neg" 0)) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "O" 0)) [(VariablePattern (Ident "n" 476))]))]))]) (SimpleRhs (583,19) (Apply (Constructor (QualIdent (Just "Prelude") (Ident "Neg" 0))) (Paren (Apply (Variable (QualIdent (Just "Prelude") (Ident "pred" 0))) (Paren (Apply (Constructor (QualIdent (Just "Prelude") (Ident "O" 0))) (Variable (QualIdent Nothing (Ident "n" 476)))))))) [])),(Equation (584,1) (FunLhs (Ident "inc" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Neg" 0)) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "I" 0)) [(VariablePattern (Ident "n" 478))]))]))]) (SimpleRhs (584,19) (Apply (Constructor (QualIdent (Just "Prelude") (Ident "Neg" 0))) (Paren (Apply (Constructor (QualIdent (Just "Prelude") (Ident "O" 0))) (Variable (QualIdent Nothing (Ident "n" 478)))))) []))]) ,(FunctionDecl (586,1) (Ident "dec" 0) [(Equation (586,1) (FunLhs (Ident "dec" 0) [(ConstructorPattern (QualIdent (Just "Prelude") (Ident "Zero" 0)) [])]) (SimpleRhs (586,12) (Apply (Constructor (QualIdent (Just "Prelude") (Ident "Neg" 0))) (Constructor (QualIdent (Just "Prelude") (Ident "IHi" 0)))) [])),(Equation (587,1) (FunLhs (Ident "dec" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Neg" 0)) [(VariablePattern (Ident "n" 482))]))]) (SimpleRhs (587,15) (Apply (Constructor (QualIdent (Just "Prelude") (Ident "Neg" 0))) (Paren (Apply (Variable (QualIdent (Just "Prelude") (Ident "succ" 0))) (Variable (QualIdent Nothing (Ident "n" 482)))))) [])),(Equation (588,1) (FunLhs (Ident "dec" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Pos" 0)) [(ConstructorPattern (QualIdent (Just "Prelude") (Ident "IHi" 0)) [])]))]) (SimpleRhs (588,17) (Constructor (QualIdent (Just "Prelude") (Ident "Zero" 0))) [])),(Equation (589,1) (FunLhs (Ident "dec" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Pos" 0)) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "O" 0)) [(VariablePattern (Ident "n" 486))]))]))]) (SimpleRhs (589,19) (Apply (Constructor (QualIdent (Just "Prelude") (Ident "Pos" 0))) (Paren (Apply (Variable (QualIdent (Just "Prelude") (Ident "pred" 0))) (Paren (Apply (Constructor (QualIdent (Just "Prelude") (Ident "O" 0))) (Variable (QualIdent Nothing (Ident "n" 486)))))))) [])),(Equation (590,1) (FunLhs (Ident "dec" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Pos" 0)) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "I" 0)) [(VariablePattern (Ident "n" 488))]))]))]) (SimpleRhs (590,19) (Apply (Constructor (QualIdent (Just "Prelude") (Ident "Pos" 0))) (Paren (Apply (Constructor (QualIdent (Just "Prelude") (Ident "O" 0))) (Variable (QualIdent Nothing (Ident "n" 488)))))) []))]) ,(FunctionDecl (592,1) (Ident "mult2" 0) [(Equation (592,1) (FunLhs (Ident "mult2" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Pos" 0)) [(VariablePattern (Ident "n" 490))]))]) (SimpleRhs (592,17) (Apply (Constructor (QualIdent (Just "Prelude") (Ident "Pos" 0))) (Paren (Apply (Constructor (QualIdent (Just "Prelude") (Ident "O" 0))) (Variable (QualIdent Nothing (Ident "n" 490)))))) [])),(Equation (593,1) (FunLhs (Ident "mult2" 0) [(ConstructorPattern (QualIdent (Just "Prelude") (Ident "Zero" 0)) [])]) (SimpleRhs (593,17) (Constructor (QualIdent (Just "Prelude") (Ident "Zero" 0))) [])),(Equation (594,1) (FunLhs (Ident "mult2" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Neg" 0)) [(VariablePattern (Ident "n" 494))]))]) (SimpleRhs (594,17) (Apply (Constructor (QualIdent (Just "Prelude") (Ident "Neg" 0))) (Paren (Apply (Constructor (QualIdent (Just "Prelude") (Ident "O" 0))) (Variable (QualIdent Nothing (Ident "n" 494)))))) []))]) ,(TypeSig (596,1) [(Ident "-^" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Nat" 0)) []) (ArrowType (ConstructorType (QualIdent Nothing (Ident "Nat" 0)) []) (ConstructorType (QualIdent Nothing (Ident "Int" 0)) [])))) ,(FunctionDecl (597,1) (Ident "-^" 0) [(Equation (597,1) (OpLhs (ConstructorPattern (QualIdent (Just "Prelude") (Ident "IHi" 0)) []) (Ident "-^" 0) (VariablePattern (Ident "y" 496))) (SimpleRhs (597,14) (Apply (Variable (QualIdent (Just "Prelude") (Ident "inc" 0))) (Paren (Apply (Constructor (QualIdent (Just "Prelude") (Ident "Neg" 0))) (Variable (QualIdent Nothing (Ident "y" 496)))))) [])),(Equation (598,1) (OpLhs (ConstructorPattern (QualIdent (Just "Prelude") (Ident "O" 0)) [(VariablePattern (Ident "x" 498))]) (Ident "-^" 0) (ConstructorPattern (QualIdent (Just "Prelude") (Ident "IHi" 0)) [])) (SimpleRhs (598,14) (Apply (Constructor (QualIdent (Just "Prelude") (Ident "Pos" 0))) (Paren (Apply (Variable (QualIdent (Just "Prelude") (Ident "pred" 0))) (Paren (Apply (Constructor (QualIdent (Just "Prelude") (Ident "O" 0))) (Variable (QualIdent Nothing (Ident "x" 498)))))))) [])),(Equation (599,1) (OpLhs (ConstructorPattern (QualIdent (Just "Prelude") (Ident "O" 0)) [(VariablePattern (Ident "x" 500))]) (Ident "-^" 0) (ConstructorPattern (QualIdent (Just "Prelude") (Ident "O" 0)) [(VariablePattern (Ident "y" 500))])) (SimpleRhs (599,14) (Apply (Variable (QualIdent (Just "Prelude") (Ident "mult2" 0))) (Paren (InfixApply (Variable (QualIdent Nothing (Ident "x" 500))) (InfixOp (QualIdent (Just "Prelude") (Ident "-^" 0))) (Variable (QualIdent Nothing (Ident "y" 500)))))) [])),(Equation (600,1) (OpLhs (ConstructorPattern (QualIdent (Just "Prelude") (Ident "O" 0)) [(VariablePattern (Ident "x" 502))]) (Ident "-^" 0) (ConstructorPattern (QualIdent (Just "Prelude") (Ident "I" 0)) [(VariablePattern (Ident "y" 502))])) (SimpleRhs (600,14) (Apply (Variable (QualIdent (Just "Prelude") (Ident "dec" 0))) (Paren (Apply (Variable (QualIdent (Just "Prelude") (Ident "mult2" 0))) (Paren (InfixApply (Variable (QualIdent Nothing (Ident "x" 502))) (InfixOp (QualIdent (Just "Prelude") (Ident "-^" 0))) (Variable (QualIdent Nothing (Ident "y" 502)))))))) [])),(Equation (601,1) (OpLhs (ConstructorPattern (QualIdent (Just "Prelude") (Ident "I" 0)) [(VariablePattern (Ident "x" 504))]) (Ident "-^" 0) (ConstructorPattern (QualIdent (Just "Prelude") (Ident "IHi" 0)) [])) (SimpleRhs (601,14) (Apply (Constructor (QualIdent (Just "Prelude") (Ident "Pos" 0))) (Paren (Apply (Constructor (QualIdent (Just "Prelude") (Ident "O" 0))) (Variable (QualIdent Nothing (Ident "x" 504)))))) [])),(Equation (602,1) (OpLhs (ConstructorPattern (QualIdent (Just "Prelude") (Ident "I" 0)) [(VariablePattern (Ident "x" 506))]) (Ident "-^" 0) (ConstructorPattern (QualIdent (Just "Prelude") (Ident "O" 0)) [(VariablePattern (Ident "y" 506))])) (SimpleRhs (602,14) (Apply (Variable (QualIdent (Just "Prelude") (Ident "inc" 0))) (Paren (Apply (Variable (QualIdent (Just "Prelude") (Ident "mult2" 0))) (Paren (InfixApply (Variable (QualIdent Nothing (Ident "x" 506))) (InfixOp (QualIdent (Just "Prelude") (Ident "-^" 0))) (Variable (QualIdent Nothing (Ident "y" 506)))))))) [])),(Equation (603,1) (OpLhs (ConstructorPattern (QualIdent (Just "Prelude") (Ident "I" 0)) [(VariablePattern (Ident "x" 508))]) (Ident "-^" 0) (ConstructorPattern (QualIdent (Just "Prelude") (Ident "I" 0)) [(VariablePattern (Ident "y" 508))])) (SimpleRhs (603,14) (Apply (Variable (QualIdent (Just "Prelude") (Ident "mult2" 0))) (Paren (InfixApply (Variable (QualIdent Nothing (Ident "x" 508))) (InfixOp (QualIdent (Just "Prelude") (Ident "-^" 0))) (Variable (QualIdent Nothing (Ident "y" 508)))))) []))]) ,(TypeSig (605,1) [(Ident "div2" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Nat" 0)) []) (ConstructorType (QualIdent Nothing (Ident "Nat" 0)) []))) ,(FunctionDecl (606,1) (Ident "div2" 0) [(Equation (606,1) (FunLhs (Ident "div2" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "O" 0)) [(VariablePattern (Ident "x" 510))]))]) (SimpleRhs (606,14) (Variable (QualIdent Nothing (Ident "x" 510))) [])),(Equation (607,1) (FunLhs (Ident "div2" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "I" 0)) [(VariablePattern (Ident "x" 512))]))]) (SimpleRhs (607,14) (Variable (QualIdent Nothing (Ident "x" 512))) []))]) ,(TypeSig (609,1) [(Ident "mod2" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Nat" 0)) []) (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []))) ,(FunctionDecl (610,1) (Ident "mod2" 0) [(Equation (610,1) (FunLhs (Ident "mod2" 0) [(ConstructorPattern (QualIdent (Just "Prelude") (Ident "IHi" 0)) [])]) (SimpleRhs (610,14) (Apply (Constructor (QualIdent (Just "Prelude") (Ident "Pos" 0))) (Constructor (QualIdent (Just "Prelude") (Ident "IHi" 0)))) [])),(Equation (611,1) (FunLhs (Ident "mod2" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "O" 0)) [(VariablePattern (Ident "_" 517))]))]) (SimpleRhs (611,14) (Constructor (QualIdent (Just "Prelude") (Ident "Zero" 0))) [])),(Equation (612,1) (FunLhs (Ident "mod2" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "I" 0)) [(VariablePattern (Ident "_" 520))]))]) (SimpleRhs (612,14) (Apply (Constructor (QualIdent (Just "Prelude") (Ident "Pos" 0))) (Constructor (QualIdent (Just "Prelude") (Ident "IHi" 0)))) []))]) ,(TypeSig (614,1) [(Ident "divmodNat" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Nat" 0)) []) (ArrowType (ConstructorType (QualIdent Nothing (Ident "Nat" 0)) []) (TupleType [(ConstructorType (QualIdent Nothing (Ident "Int" 0)) []),(ConstructorType (QualIdent Nothing (Ident "Int" 0)) [])])))) ,(FunctionDecl (615,1) (Ident "divmodNat" 0) [(Equation (615,1) (FunLhs (Ident "divmodNat" 0) [(VariablePattern (Ident "x" 522)),(VariablePattern (Ident "y" 522))]) (GuardedRhs [(CondExpr (616,3) (InfixApply (Variable (QualIdent Nothing (Ident "y" 522))) (InfixOp (QualIdent (Just "Prelude") (Ident "==" 0))) (Constructor (QualIdent (Just "Prelude") (Ident "IHi" 0)))) (Tuple [(Apply (Constructor (QualIdent (Just "Prelude") (Ident "Pos" 0))) (Variable (QualIdent Nothing (Ident "x" 522)))),(Constructor (QualIdent (Just "Prelude") (Ident "Zero" 0)))])),(CondExpr (617,3) (Variable (QualIdent (Just "Prelude") (Ident "otherwise" 0))) (Case (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "cmpNat" 0))) (Variable (QualIdent Nothing (Ident "x" 522)))) (Variable (QualIdent Nothing (Ident "y" 522)))) [(Alt (618,5) (ConstructorPattern (QualIdent (Just "Prelude") (Ident "EQ" 0)) []) (SimpleRhs (618,11) (Tuple [(Apply (Constructor (QualIdent (Just "Prelude") (Ident "Pos" 0))) (Constructor (QualIdent (Just "Prelude") (Ident "IHi" 0)))),(Constructor (QualIdent (Just "Prelude") (Ident "Zero" 0)))]) [])),(Alt (619,5) (ConstructorPattern (QualIdent (Just "Prelude") (Ident "LT" 0)) []) (SimpleRhs (619,11) (Tuple [(Constructor (QualIdent (Just "Prelude") (Ident "Zero" 0))),(Apply (Constructor (QualIdent (Just "Prelude") (Ident "Pos" 0))) (Variable (QualIdent Nothing (Ident "x" 522))))]) [])),(Alt (620,5) (ConstructorPattern (QualIdent (Just "Prelude") (Ident "GT" 0)) []) (SimpleRhs (620,11) (Case (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "divmodNat" 0))) (Paren (Apply (Variable (QualIdent (Just "Prelude") (Ident "div2" 0))) (Variable (QualIdent Nothing (Ident "x" 522)))))) (Variable (QualIdent Nothing (Ident "y" 522)))) [(Alt (621,7) (TuplePattern [(ConstructorPattern (QualIdent (Just "Prelude") (Ident "Zero" 0)) []),(VariablePattern (Ident "_" 537))]) (SimpleRhs (621,24) (Tuple [(Apply (Constructor (QualIdent (Just "Prelude") (Ident "Pos" 0))) (Constructor (QualIdent (Just "Prelude") (Ident "IHi" 0)))),(InfixApply (Variable (QualIdent Nothing (Ident "x" 522))) (InfixOp (QualIdent (Just "Prelude") (Ident "-^" 0))) (Variable (QualIdent Nothing (Ident "y" 522))))]) [])),(Alt (622,7) (TuplePattern [(ConstructorPattern (QualIdent (Just "Prelude") (Ident "Pos" 0)) [(VariablePattern (Ident "d" 539))]),(ConstructorPattern (QualIdent (Just "Prelude") (Ident "Zero" 0)) [])]) (SimpleRhs (622,24) (Tuple [(Apply (Constructor (QualIdent (Just "Prelude") (Ident "Pos" 0))) (Paren (Apply (Constructor (QualIdent (Just "Prelude") (Ident "O" 0))) (Variable (QualIdent Nothing (Ident "d" 539)))))),(Apply (Variable (QualIdent (Just "Prelude") (Ident "mod2" 0))) (Variable (QualIdent Nothing (Ident "x" 522))))]) [])),(Alt (623,7) (TuplePattern [(ConstructorPattern (QualIdent (Just "Prelude") (Ident "Pos" 0)) [(VariablePattern (Ident "d" 541))]),(ConstructorPattern (QualIdent (Just "Prelude") (Ident "Pos" 0)) [(VariablePattern (Ident "m" 541))])]) (SimpleRhs (623,24) (Case (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "divmodNat" 0))) (Paren (Apply (Apply (Variable (QualIdent Nothing (Ident "shift" 523))) (Variable (QualIdent Nothing (Ident "x" 522)))) (Variable (QualIdent Nothing (Ident "m" 541)))))) (Variable (QualIdent Nothing (Ident "y" 522)))) [(Alt (624,9) (TuplePattern [(ConstructorPattern (QualIdent (Just "Prelude") (Ident "Zero" 0)) []),(VariablePattern (Ident "m'" 543))]) (SimpleRhs (624,24) (Tuple [(Apply (Constructor (QualIdent (Just "Prelude") (Ident "Pos" 0))) (Paren (Apply (Constructor (QualIdent (Just "Prelude") (Ident "O" 0))) (Variable (QualIdent Nothing (Ident "d" 541)))))),(Variable (QualIdent Nothing (Ident "m'" 543)))]) [])),(Alt (625,9) (TuplePattern [(ConstructorPattern (QualIdent (Just "Prelude") (Ident "Pos" 0)) [(VariablePattern (Ident "d'" 545))]),(VariablePattern (Ident "m'" 545))]) (SimpleRhs (625,24) (Tuple [(Apply (Constructor (QualIdent (Just "Prelude") (Ident "Pos" 0))) (Paren (InfixApply (Apply (Constructor (QualIdent (Just "Prelude") (Ident "O" 0))) (Variable (QualIdent Nothing (Ident "d" 541)))) (InfixOp (QualIdent (Just "Prelude") (Ident "+^" 0))) (Variable (QualIdent Nothing (Ident "d'" 545)))))),(Variable (QualIdent Nothing (Ident "m'" 545)))]) []))]) []))]) []))]))] [(FunctionDecl (627,5) (Ident "shift" 523) [(Equation (627,5) (FunLhs (Ident "shift" 523) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "O" 0)) [(VariablePattern (Ident "_" 525))])),(VariablePattern (Ident "n" 524))]) (SimpleRhs (627,21) (Apply (Constructor (QualIdent (Just "Prelude") (Ident "O" 0))) (Variable (QualIdent Nothing (Ident "n" 524)))) [])),(Equation (628,5) (FunLhs (Ident "shift" 523) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "I" 0)) [(VariablePattern (Ident "_" 528))])),(VariablePattern (Ident "n" 527))]) (SimpleRhs (628,21) (Apply (Constructor (QualIdent (Just "Prelude") (Ident "I" 0))) (Variable (QualIdent Nothing (Ident "n" 527)))) []))])]))]) ,(TypeSig (632,1) [(Ident "+" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []) (ArrowType (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []) (ConstructorType (QualIdent Nothing (Ident "Int" 0)) [])))) ,(FunctionDecl (633,1) (Ident "+" 0) [(Equation (633,1) (OpLhs (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Pos" 0)) [(VariablePattern (Ident "x" 547))]) (Ident "+" 0) (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Pos" 0)) [(VariablePattern (Ident "y" 547))])) (SimpleRhs (633,17) (Apply (Constructor (QualIdent (Just "Prelude") (Ident "Pos" 0))) (Paren (InfixApply (Variable (QualIdent Nothing (Ident "x" 547))) (InfixOp (QualIdent (Just "Prelude") (Ident "+^" 0))) (Variable (QualIdent Nothing (Ident "y" 547)))))) [])),(Equation (634,1) (OpLhs (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Neg" 0)) [(VariablePattern (Ident "x" 549))]) (Ident "+" 0) (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Neg" 0)) [(VariablePattern (Ident "y" 549))])) (SimpleRhs (634,17) (Apply (Constructor (QualIdent (Just "Prelude") (Ident "Neg" 0))) (Paren (InfixApply (Variable (QualIdent Nothing (Ident "x" 549))) (InfixOp (QualIdent (Just "Prelude") (Ident "+^" 0))) (Variable (QualIdent Nothing (Ident "y" 549)))))) [])),(Equation (635,1) (OpLhs (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Pos" 0)) [(VariablePattern (Ident "x" 551))]) (Ident "+" 0) (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Neg" 0)) [(VariablePattern (Ident "y" 551))])) (SimpleRhs (635,17) (InfixApply (Variable (QualIdent Nothing (Ident "x" 551))) (InfixOp (QualIdent (Just "Prelude") (Ident "-^" 0))) (Variable (QualIdent Nothing (Ident "y" 551)))) [])),(Equation (636,1) (OpLhs (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Neg" 0)) [(VariablePattern (Ident "x" 553))]) (Ident "+" 0) (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Pos" 0)) [(VariablePattern (Ident "y" 553))])) (SimpleRhs (636,17) (InfixApply (Variable (QualIdent Nothing (Ident "y" 553))) (InfixOp (QualIdent (Just "Prelude") (Ident "-^" 0))) (Variable (QualIdent Nothing (Ident "x" 553)))) [])),(Equation (637,1) (OpLhs (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Zero" 0)) []) (Ident "+" 0) (VariablePattern (Ident "x" 555))) (SimpleRhs (637,17) (Variable (QualIdent Nothing (Ident "x" 555))) [])),(Equation (638,1) (OpLhs (AsPattern (Ident "x" 557) (ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Pos" 0)) [(VariablePattern (Ident "_" 558))]))) (Ident "+" 0) (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Zero" 0)) [])) (SimpleRhs (638,20) (Variable (QualIdent Nothing (Ident "x" 557))) [])),(Equation (639,1) (OpLhs (AsPattern (Ident "x" 560) (ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Neg" 0)) [(VariablePattern (Ident "_" 561))]))) (Ident "+" 0) (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Zero" 0)) [])) (SimpleRhs (639,20) (Variable (QualIdent Nothing (Ident "x" 560))) []))]) ,(TypeSig (642,1) [(Ident "-" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []) (ArrowType (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []) (ConstructorType (QualIdent Nothing (Ident "Int" 0)) [])))) ,(FunctionDecl (643,1) (Ident "-" 0) [(Equation (643,1) (OpLhs (VariablePattern (Ident "x" 563)) (Ident "-" 0) (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Neg" 0)) [(VariablePattern (Ident "y" 563))])) (SimpleRhs (643,13) (InfixApply (Variable (QualIdent Nothing (Ident "x" 563))) (InfixOp (QualIdent (Just "Prelude") (Ident "+" 0))) (Apply (Constructor (QualIdent (Just "Prelude") (Ident "Pos" 0))) (Variable (QualIdent Nothing (Ident "y" 563))))) [])),(Equation (644,1) (OpLhs (VariablePattern (Ident "x" 565)) (Ident "-" 0) (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Pos" 0)) [(VariablePattern (Ident "y" 565))])) (SimpleRhs (644,13) (InfixApply (Variable (QualIdent Nothing (Ident "x" 565))) (InfixOp (QualIdent (Just "Prelude") (Ident "+" 0))) (Apply (Constructor (QualIdent (Just "Prelude") (Ident "Neg" 0))) (Variable (QualIdent Nothing (Ident "y" 565))))) [])),(Equation (645,1) (OpLhs (VariablePattern (Ident "x" 567)) (Ident "-" 0) (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Zero" 0)) [])) (SimpleRhs (645,13) (Variable (QualIdent Nothing (Ident "x" 567))) []))]) ,(TypeSig (648,1) [(Ident "*" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []) (ArrowType (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []) (ConstructorType (QualIdent Nothing (Ident "Int" 0)) [])))) ,(FunctionDecl (649,1) (Ident "*" 0) [(Equation (649,1) (OpLhs (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Pos" 0)) [(VariablePattern (Ident "x" 569))]) (Ident "*" 0) (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Pos" 0)) [(VariablePattern (Ident "y" 569))])) (SimpleRhs (649,17) (Apply (Constructor (QualIdent (Just "Prelude") (Ident "Pos" 0))) (Paren (InfixApply (Variable (QualIdent Nothing (Ident "x" 569))) (InfixOp (QualIdent (Just "Prelude") (Ident "*^" 0))) (Variable (QualIdent Nothing (Ident "y" 569)))))) [])),(Equation (650,1) (OpLhs (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Pos" 0)) [(VariablePattern (Ident "x" 571))]) (Ident "*" 0) (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Neg" 0)) [(VariablePattern (Ident "y" 571))])) (SimpleRhs (650,17) (Apply (Constructor (QualIdent (Just "Prelude") (Ident "Neg" 0))) (Paren (InfixApply (Variable (QualIdent Nothing (Ident "x" 571))) (InfixOp (QualIdent (Just "Prelude") (Ident "*^" 0))) (Variable (QualIdent Nothing (Ident "y" 571)))))) [])),(Equation (651,1) (OpLhs (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Neg" 0)) [(VariablePattern (Ident "x" 573))]) (Ident "*" 0) (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Neg" 0)) [(VariablePattern (Ident "y" 573))])) (SimpleRhs (651,17) (Apply (Constructor (QualIdent (Just "Prelude") (Ident "Pos" 0))) (Paren (InfixApply (Variable (QualIdent Nothing (Ident "x" 573))) (InfixOp (QualIdent (Just "Prelude") (Ident "*^" 0))) (Variable (QualIdent Nothing (Ident "y" 573)))))) [])),(Equation (652,1) (OpLhs (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Neg" 0)) [(VariablePattern (Ident "x" 575))]) (Ident "*" 0) (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Pos" 0)) [(VariablePattern (Ident "y" 575))])) (SimpleRhs (652,17) (Apply (Constructor (QualIdent (Just "Prelude") (Ident "Neg" 0))) (Paren (InfixApply (Variable (QualIdent Nothing (Ident "x" 575))) (InfixOp (QualIdent (Just "Prelude") (Ident "*^" 0))) (Variable (QualIdent Nothing (Ident "y" 575)))))) [])),(Equation (653,1) (OpLhs (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Zero" 0)) []) (Ident "*" 0) (VariablePattern (Ident "_" 578))) (SimpleRhs (653,17) (Constructor (QualIdent (Just "Prelude") (Ident "Zero" 0))) [])),(Equation (654,1) (OpLhs (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Pos" 0)) [(VariablePattern (Ident "_" 581))]) (Ident "*" 0) (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Zero" 0)) [])) (SimpleRhs (654,17) (Constructor (QualIdent (Just "Prelude") (Ident "Zero" 0))) [])),(Equation (655,1) (OpLhs (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Neg" 0)) [(VariablePattern (Ident "_" 584))]) (Ident "*" 0) (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Zero" 0)) [])) (SimpleRhs (655,17) (Constructor (QualIdent (Just "Prelude") (Ident "Zero" 0))) []))]) ,(TypeSig (666,1) [(Ident "divmod" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []) (ArrowType (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []) (TupleType [(ConstructorType (QualIdent Nothing (Ident "Int" 0)) []),(ConstructorType (QualIdent Nothing (Ident "Int" 0)) [])])))) ,(FunctionDecl (667,1) (Ident "divmod" 0) [(Equation (667,1) (FunLhs (Ident "divmod" 0) [(ConstructorPattern (QualIdent (Just "Prelude") (Ident "Zero" 0)) []),(VariablePattern (Ident "_" 587))]) (SimpleRhs (667,26) (Tuple [(Constructor (QualIdent (Just "Prelude") (Ident "Zero" 0))),(Constructor (QualIdent (Just "Prelude") (Ident "Zero" 0)))]) [])),(Equation (668,1) (FunLhs (Ident "divmod" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Pos" 0)) [(VariablePattern (Ident "_" 590))])),(ConstructorPattern (QualIdent (Just "Prelude") (Ident "Zero" 0)) [])]) (SimpleRhs (668,26) (Apply (Variable (QualIdent (Just "Prelude") (Ident "error" 0))) (Literal (String "division by 0"))) [])),(Equation (669,1) (FunLhs (Ident "divmod" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Pos" 0)) [(VariablePattern (Ident "x" 592))])),(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Pos" 0)) [(VariablePattern (Ident "y" 592))]))]) (SimpleRhs (669,26) (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "divmodNat" 0))) (Variable (QualIdent Nothing (Ident "x" 592)))) (Variable (QualIdent Nothing (Ident "y" 592)))) [])),(Equation (670,1) (FunLhs (Ident "divmod" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Pos" 0)) [(VariablePattern (Ident "x" 594))])),(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Neg" 0)) [(VariablePattern (Ident "y" 594))]))]) (SimpleRhs (670,26) (Let [(PatternDecl (670,30) (TuplePattern [(VariablePattern (Ident "d" 596)),(VariablePattern (Ident "m" 596))]) (SimpleRhs (670,38) (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "divmodNat" 0))) (Variable (QualIdent Nothing (Ident "x" 594)))) (Variable (QualIdent Nothing (Ident "y" 594)))) []))] (Tuple [(Apply (Variable (QualIdent (Just "Prelude") (Ident "negate" 0))) (Variable (QualIdent Nothing (Ident "d" 596)))),(Variable (QualIdent Nothing (Ident "m" 596)))])) [])),(Equation (671,1) (FunLhs (Ident "divmod" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Neg" 0)) [(VariablePattern (Ident "_" 599))])),(ConstructorPattern (QualIdent (Just "Prelude") (Ident "Zero" 0)) [])]) (SimpleRhs (671,26) (Apply (Variable (QualIdent (Just "Prelude") (Ident "error" 0))) (Literal (String "division by 0"))) [])),(Equation (672,1) (FunLhs (Ident "divmod" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Neg" 0)) [(VariablePattern (Ident "x" 601))])),(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Pos" 0)) [(VariablePattern (Ident "y" 601))]))]) (SimpleRhs (672,26) (Let [(PatternDecl (672,30) (TuplePattern [(VariablePattern (Ident "d" 603)),(VariablePattern (Ident "m" 603))]) (SimpleRhs (672,38) (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "divmodNat" 0))) (Variable (QualIdent Nothing (Ident "x" 601)))) (Variable (QualIdent Nothing (Ident "y" 601)))) []))] (Tuple [(Apply (Variable (QualIdent (Just "Prelude") (Ident "negate" 0))) (Variable (QualIdent Nothing (Ident "d" 603)))),(Apply (Variable (QualIdent (Just "Prelude") (Ident "negate" 0))) (Variable (QualIdent Nothing (Ident "m" 603))))])) [])),(Equation (673,1) (FunLhs (Ident "divmod" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Neg" 0)) [(VariablePattern (Ident "x" 605))])),(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Neg" 0)) [(VariablePattern (Ident "y" 605))]))]) (SimpleRhs (673,26) (Let [(PatternDecl (673,30) (TuplePattern [(VariablePattern (Ident "d" 607)),(VariablePattern (Ident "m" 607))]) (SimpleRhs (673,38) (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "divmodNat" 0))) (Variable (QualIdent Nothing (Ident "x" 605)))) (Variable (QualIdent Nothing (Ident "y" 605)))) []))] (Tuple [(Variable (QualIdent Nothing (Ident "d" 607))),(Apply (Variable (QualIdent (Just "Prelude") (Ident "negate" 0))) (Variable (QualIdent Nothing (Ident "m" 607))))])) []))]) ,(TypeSig (675,1) [(Ident "div" 0),(Ident "mod" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []) (ArrowType (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []) (ConstructorType (QualIdent Nothing (Ident "Int" 0)) [])))) ,(FunctionDecl (676,1) (Ident "div" 0) [(Equation (676,1) (OpLhs (VariablePattern (Ident "x" 609)) (Ident "div" 0) (VariablePattern (Ident "y" 609))) (SimpleRhs (676,13) (Apply (Variable (QualIdent (Just "Prelude") (Ident "fst" 0))) (Paren (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "divmod" 0))) (Variable (QualIdent Nothing (Ident "x" 609)))) (Variable (QualIdent Nothing (Ident "y" 609)))))) []))]) ,(FunctionDecl (678,1) (Ident "mod" 0) [(Equation (678,1) (OpLhs (VariablePattern (Ident "x" 611)) (Ident "mod" 0) (VariablePattern (Ident "y" 611))) (SimpleRhs (678,13) (Apply (Variable (QualIdent (Just "Prelude") (Ident "snd" 0))) (Paren (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "divmod" 0))) (Variable (QualIdent Nothing (Ident "x" 611)))) (Variable (QualIdent Nothing (Ident "y" 611)))))) []))]) ,(TypeSig (681,1) [(Ident "negate" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []) (ConstructorType (QualIdent Nothing (Ident "Int" 0)) []))) ,(FunctionDecl (682,1) (Ident "negate" 0) [(Equation (682,1) (FunLhs (Ident "negate" 0) [(ConstructorPattern (QualIdent (Just "Prelude") (Ident "Zero" 0)) [])]) (SimpleRhs (682,18) (Constructor (QualIdent (Just "Prelude") (Ident "Zero" 0))) [])),(Equation (683,1) (FunLhs (Ident "negate" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Pos" 0)) [(VariablePattern (Ident "x" 615))]))]) (SimpleRhs (683,18) (Apply (Constructor (QualIdent (Just "Prelude") (Ident "Neg" 0))) (Variable (QualIdent Nothing (Ident "x" 615)))) [])),(Equation (684,1) (FunLhs (Ident "negate" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Neg" 0)) [(VariablePattern (Ident "x" 617))]))]) (SimpleRhs (684,18) (Apply (Constructor (QualIdent (Just "Prelude") (Ident "Pos" 0))) (Variable (QualIdent Nothing (Ident "x" 617)))) []))]) ,(TypeSig (687,1) [(Ident "negateFloat" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Float" 0)) []) (ConstructorType (QualIdent Nothing (Ident "Float" 0)) []))) ,(FunctionDecl (688,1) (Ident "negateFloat" 0) [(Equation (688,1) (FunLhs (Ident "negateFloat" 0) [(VariablePattern (Ident "x" 619))]) (SimpleRhs (688,17) (InfixApply (Variable (QualIdent (Just "Prelude") (Ident "prim_negateFloat" 0))) (InfixOp (QualIdent (Just "Prelude") (Ident "$#" 0))) (Variable (QualIdent Nothing (Ident "x" 619)))) []))]) ,(TypeSig (690,1) [(Ident "prim_negateFloat" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Float" 0)) []) (ConstructorType (QualIdent Nothing (Ident "Float" 0)) []))) ,(FlatExternalDecl (691,1) [(Ident "prim_negateFloat" 0)]) ,(TypeSig (697,1) [(Ident "success" 0)] (ConstructorType (QualIdent Nothing (Ident "Success" 0)) [])) ,(FunctionDecl (698,1) (Ident "success" 0) [(Equation (698,1) (FunLhs (Ident "success" 0) []) (SimpleRhs (698,11) (Constructor (QualIdent (Just "Prelude") (Ident "Success" 0))) []))]) ,(TypeSig (704,1) [(Ident "=:=" 0)] (ArrowType (VariableType (Ident "a" 0)) (ArrowType (VariableType (Ident "a" 0)) (ConstructorType (QualIdent Nothing (Ident "Success" 0)) [])))) ,(FunctionDecl (705,1) (Ident "=:=" 0) [(Equation (705,1) (OpLhs (VariablePattern (Ident "x" 623)) (Ident "=:=" 0) (VariablePattern (Ident "y" 623))) (GuardedRhs [(CondExpr (705,9) (InfixApply (Variable (QualIdent Nothing (Ident "x" 623))) (InfixOp (QualIdent (Just "Prelude") (Ident "===" 0))) (Variable (QualIdent Nothing (Ident "y" 623)))) (Variable (QualIdent (Just "Prelude") (Ident "success" 0))))] []))]) ,(TypeSig (707,1) [(Ident "===" 0)] (ArrowType (VariableType (Ident "a" 0)) (ArrowType (VariableType (Ident "a" 0)) (ConstructorType (QualIdent Nothing (Ident "Bool" 0)) [])))) ,(FlatExternalDecl (708,1) [(Ident "===" 0)]) ,(TypeSig (714,1) [(Ident "&" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Success" 0)) []) (ArrowType (ConstructorType (QualIdent Nothing (Ident "Success" 0)) []) (ConstructorType (QualIdent Nothing (Ident "Success" 0)) [])))) ,(FlatExternalDecl (715,1) [(Ident "&" 0)]) ,(TypeSig (720,1) [(Ident "&>" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Success" 0)) []) (ArrowType (VariableType (Ident "a" 0)) (VariableType (Ident "a" 0))))) ,(FunctionDecl (721,1) (Ident "&>" 0) [(Equation (721,1) (OpLhs (VariablePattern (Ident "c" 625)) (Ident "&>" 0) (VariablePattern (Ident "x" 625))) (GuardedRhs [(CondExpr (721,8) (Variable (QualIdent Nothing (Ident "c" 625))) (Variable (QualIdent Nothing (Ident "x" 625))))] []))]) ,(TypeSig (730,1) [(Ident "maybe" 0)] (ArrowType (VariableType (Ident "b" 0)) (ArrowType (ArrowType (VariableType (Ident "a" 0)) (VariableType (Ident "b" 0))) (ArrowType (ConstructorType (QualIdent Nothing (Ident "Maybe" 0)) [(VariableType (Ident "a" 0))]) (VariableType (Ident "b" 0)))))) ,(FunctionDecl (731,1) (Ident "maybe" 0) [(Equation (731,1) (FunLhs (Ident "maybe" 0) [(VariablePattern (Ident "n" 627)),(VariablePattern (Ident "_" 628)),(ConstructorPattern (QualIdent (Just "Prelude") (Ident "Nothing" 0)) [])]) (SimpleRhs (731,22) (Variable (QualIdent Nothing (Ident "n" 627))) [])),(Equation (732,1) (FunLhs (Ident "maybe" 0) [(VariablePattern (Ident "_" 631)),(VariablePattern (Ident "f" 630)),(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Just" 0)) [(VariablePattern (Ident "x" 630))]))]) (SimpleRhs (732,22) (Apply (Variable (QualIdent Nothing (Ident "f" 630))) (Variable (QualIdent Nothing (Ident "x" 630)))) []))]) ,(TypeSig (739,1) [(Ident "either" 0)] (ArrowType (ArrowType (VariableType (Ident "a" 0)) (VariableType (Ident "c" 0))) (ArrowType (ArrowType (VariableType (Ident "b" 0)) (VariableType (Ident "c" 0))) (ArrowType (ConstructorType (QualIdent Nothing (Ident "Either" 0)) [(VariableType (Ident "a" 0)),(VariableType (Ident "b" 0))]) (VariableType (Ident "c" 0)))))) ,(FunctionDecl (740,1) (Ident "either" 0) [(Equation (740,1) (FunLhs (Ident "either" 0) [(VariablePattern (Ident "f" 633)),(VariablePattern (Ident "_" 634)),(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Left" 0)) [(VariablePattern (Ident "x" 633))]))]) (SimpleRhs (740,24) (Apply (Variable (QualIdent Nothing (Ident "f" 633))) (Variable (QualIdent Nothing (Ident "x" 633)))) [])),(Equation (741,1) (FunLhs (Ident "either" 0) [(VariablePattern (Ident "_" 637)),(VariablePattern (Ident "g" 636)),(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Right" 0)) [(VariablePattern (Ident "x" 636))]))]) (SimpleRhs (741,24) (Apply (Variable (QualIdent Nothing (Ident "g" 636))) (Variable (QualIdent Nothing (Ident "x" 636)))) []))]) ,(TypeSig (753,1) [(Ident ">>=" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "IO" 0)) [(VariableType (Ident "a" 0))]) (ArrowType (ArrowType (VariableType (Ident "a" 0)) (ConstructorType (QualIdent Nothing (Ident "IO" 0)) [(VariableType (Ident "b" 0))])) (ConstructorType (QualIdent Nothing (Ident "IO" 0)) [(VariableType (Ident "b" 0))])))) ,(FlatExternalDecl (754,1) [(Ident ">>=" 0)]) ,(TypeSig (757,1) [(Ident "return" 0)] (ArrowType (VariableType (Ident "a" 0)) (ConstructorType (QualIdent Nothing (Ident "IO" 0)) [(VariableType (Ident "a" 0))]))) ,(FlatExternalDecl (758,1) [(Ident "return" 0)]) ,(TypeSig (764,1) [(Ident ">>" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "IO" 0)) [(VariableType (Ident "_" 0))]) (ArrowType (ConstructorType (QualIdent Nothing (Ident "IO" 0)) [(VariableType (Ident "b" 0))]) (ConstructorType (QualIdent Nothing (Ident "IO" 0)) [(VariableType (Ident "b" 0))])))) ,(FunctionDecl (765,1) (Ident ">>" 0) [(Equation (765,1) (OpLhs (VariablePattern (Ident "a" 639)) (Ident ">>" 0) (VariablePattern (Ident "b" 639))) (SimpleRhs (765,21) (InfixApply (Variable (QualIdent Nothing (Ident "a" 639))) (InfixOp (QualIdent (Just "Prelude") (Ident ">>=" 0))) (Apply (Variable (QualIdent (Just "Prelude") (Ident "const" 0))) (Variable (QualIdent Nothing (Ident "b" 639))))) []))]) ,(TypeSig (768,1) [(Ident "done" 0)] (ConstructorType (QualIdent Nothing (Ident "IO" 0)) [(TupleType [])])) ,(FunctionDecl (769,1) (Ident "done" 0) [(Equation (769,1) (FunLhs (Ident "done" 0) []) (SimpleRhs (769,21) (Apply (Variable (QualIdent (Just "Prelude") (Ident "return" 0))) (Tuple [])) []))]) ,(TypeSig (772,1) [(Ident "putChar" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Char" 0)) []) (ConstructorType (QualIdent Nothing (Ident "IO" 0)) [(TupleType [])]))) ,(FunctionDecl (773,1) (Ident "putChar" 0) [(Equation (773,1) (FunLhs (Ident "putChar" 0) [(VariablePattern (Ident "c" 643))]) (SimpleRhs (773,13) (InfixApply (Variable (QualIdent (Just "Prelude") (Ident "prim_putChar" 0))) (InfixOp (QualIdent (Just "Prelude") (Ident "$##" 0))) (Variable (QualIdent Nothing (Ident "c" 643)))) []))]) ,(TypeSig (775,1) [(Ident "prim_putChar" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Char" 0)) []) (ConstructorType (QualIdent Nothing (Ident "IO" 0)) [(TupleType [])]))) ,(FlatExternalDecl (776,1) [(Ident "prim_putChar" 0)]) ,(TypeSig (779,1) [(Ident "getChar" 0)] (ConstructorType (QualIdent Nothing (Ident "IO" 0)) [(ConstructorType (QualIdent Nothing (Ident "Char" 0)) [])])) ,(FlatExternalDecl (780,1) [(Ident "getChar" 0)]) ,(TypeSig (783,1) [(Ident "readFile" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "String" 0)) []) (ConstructorType (QualIdent Nothing (Ident "IO" 0)) [(ConstructorType (QualIdent Nothing (Ident "String" 0)) [])]))) ,(FunctionDecl (784,1) (Ident "readFile" 0) [(Equation (784,1) (FunLhs (Ident "readFile" 0) [(VariablePattern (Ident "s" 645))]) (SimpleRhs (784,14) (InfixApply (Variable (QualIdent (Just "Prelude") (Ident "prim_readFile" 0))) (InfixOp (QualIdent (Just "Prelude") (Ident "$##" 0))) (Variable (QualIdent Nothing (Ident "s" 645)))) []))]) ,(TypeSig (786,1) [(Ident "prim_readFile" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "String" 0)) []) (ConstructorType (QualIdent Nothing (Ident "IO" 0)) [(ConstructorType (QualIdent Nothing (Ident "String" 0)) [])]))) ,(FlatExternalDecl (787,1) [(Ident "prim_readFile" 0)]) ,(TypeSig (792,1) [(Ident "writeFile" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "String" 0)) []) (ArrowType (ConstructorType (QualIdent Nothing (Ident "String" 0)) []) (ConstructorType (QualIdent Nothing (Ident "IO" 0)) [(TupleType [])])))) ,(FunctionDecl (793,1) (Ident "writeFile" 0) [(Equation (793,1) (FunLhs (Ident "writeFile" 0) [(VariablePattern (Ident "fn" 647)),(VariablePattern (Ident "s" 647))]) (SimpleRhs (793,18) (InfixApply (Paren (InfixApply (Variable (QualIdent (Just "Prelude") (Ident "prim_writeFile" 0))) (InfixOp (QualIdent (Just "Prelude") (Ident "$##" 0))) (Variable (QualIdent Nothing (Ident "fn" 647))))) (InfixOp (QualIdent (Just "Prelude") (Ident "$##" 0))) (Variable (QualIdent Nothing (Ident "s" 647)))) []))]) ,(TypeSig (795,1) [(Ident "prim_writeFile" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "String" 0)) []) (ArrowType (ConstructorType (QualIdent Nothing (Ident "String" 0)) []) (ConstructorType (QualIdent Nothing (Ident "IO" 0)) [(TupleType [])])))) ,(FlatExternalDecl (796,1) [(Ident "prim_writeFile" 0)]) ,(TypeSig (802,1) [(Ident "appendFile" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "String" 0)) []) (ArrowType (ConstructorType (QualIdent Nothing (Ident "String" 0)) []) (ConstructorType (QualIdent Nothing (Ident "IO" 0)) [(TupleType [])])))) ,(FunctionDecl (803,1) (Ident "appendFile" 0) [(Equation (803,1) (FunLhs (Ident "appendFile" 0) [(VariablePattern (Ident "fn" 649)),(VariablePattern (Ident "s" 649))]) (SimpleRhs (803,19) (InfixApply (Paren (InfixApply (Variable (QualIdent (Just "Prelude") (Ident "prim_appendFile" 0))) (InfixOp (QualIdent (Just "Prelude") (Ident "$##" 0))) (Variable (QualIdent Nothing (Ident "fn" 649))))) (InfixOp (QualIdent (Just "Prelude") (Ident "$##" 0))) (Variable (QualIdent Nothing (Ident "s" 649)))) []))]) ,(TypeSig (805,1) [(Ident "prim_appendFile" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "String" 0)) []) (ArrowType (ConstructorType (QualIdent Nothing (Ident "String" 0)) []) (ConstructorType (QualIdent Nothing (Ident "IO" 0)) [(TupleType [])])))) ,(FlatExternalDecl (806,1) [(Ident "prim_appendFile" 0)]) ,(TypeSig (812,1) [(Ident "catchFail" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "IO" 0)) [(VariableType (Ident "a" 0))]) (ArrowType (ConstructorType (QualIdent Nothing (Ident "IO" 0)) [(VariableType (Ident "a" 0))]) (ConstructorType (QualIdent Nothing (Ident "IO" 0)) [(VariableType (Ident "a" 0))])))) ,(FlatExternalDecl (813,1) [(Ident "catchFail" 0)]) ,(TypeSig (816,1) [(Ident "putStr" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "String" 0)) []) (ConstructorType (QualIdent Nothing (Ident "IO" 0)) [(TupleType [])]))) ,(FunctionDecl (817,1) (Ident "putStr" 0) [(Equation (817,1) (FunLhs (Ident "putStr" 0) [(ListPattern [])]) (SimpleRhs (817,21) (Variable (QualIdent (Just "Prelude") (Ident "done" 0))) [])),(Equation (818,1) (FunLhs (Ident "putStr" 0) [(ParenPattern (InfixPattern (VariablePattern (Ident "c" 653)) (QualIdent Nothing (Ident ":" 0)) (VariablePattern (Ident "cs" 653))))]) (SimpleRhs (818,21) (InfixApply (Apply (Variable (QualIdent (Just "Prelude") (Ident "putChar" 0))) (Variable (QualIdent Nothing (Ident "c" 653)))) (InfixOp (QualIdent (Just "Prelude") (Ident ">>" 0))) (Apply (Variable (QualIdent (Just "Prelude") (Ident "putStr" 0))) (Variable (QualIdent Nothing (Ident "cs" 653))))) []))]) ,(TypeSig (821,1) [(Ident "putStrLn" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "String" 0)) []) (ConstructorType (QualIdent Nothing (Ident "IO" 0)) [(TupleType [])]))) ,(FunctionDecl (822,1) (Ident "putStrLn" 0) [(Equation (822,1) (FunLhs (Ident "putStrLn" 0) [(VariablePattern (Ident "cs" 655))]) (SimpleRhs (822,21) (InfixApply (Apply (Variable (QualIdent (Just "Prelude") (Ident "putStr" 0))) (Variable (QualIdent Nothing (Ident "cs" 655)))) (InfixOp (QualIdent (Just "Prelude") (Ident ">>" 0))) (Apply (Variable (QualIdent (Just "Prelude") (Ident "putChar" 0))) (Literal (Char '\n')))) []))]) ,(TypeSig (825,1) [(Ident "getLine" 0)] (ConstructorType (QualIdent Nothing (Ident "IO" 0)) [(ConstructorType (QualIdent Nothing (Ident "String" 0)) [])])) ,(FunctionDecl (826,1) (Ident "getLine" 0) [(Equation (826,1) (FunLhs (Ident "getLine" 0) []) (SimpleRhs (826,21) (Do [(StmtBind (VariablePattern (Ident "c" 659)) (Variable (QualIdent (Just "Prelude") (Ident "getChar" 0))))] (IfThenElse (InfixApply (Variable (QualIdent Nothing (Ident "c" 659))) (InfixOp (QualIdent (Just "Prelude") (Ident "==" 0))) (Literal (Char '\n'))) (Apply (Variable (QualIdent (Just "Prelude") (Ident "return" 0))) (List [])) (Do [(StmtBind (VariablePattern (Ident "cs" 660)) (Variable (QualIdent (Just "Prelude") (Ident "getLine" 0))))] (Apply (Variable (QualIdent (Just "Prelude") (Ident "return" 0))) (Paren (InfixApply (Variable (QualIdent Nothing (Ident "c" 659))) (InfixConstr (QualIdent Nothing (Ident ":" 0))) (Variable (QualIdent Nothing (Ident "cs" 660))))))))) []))]) ,(TypeSig (832,1) [(Ident "show" 0)] (ArrowType (VariableType (Ident "_" 0)) (ConstructorType (QualIdent Nothing (Ident "String" 0)) []))) ,(FunctionDecl (833,1) (Ident "show" 0) [(Equation (833,1) (FunLhs (Ident "show" 0) [(VariablePattern (Ident "s" 661))]) (SimpleRhs (833,10) (InfixApply (Variable (QualIdent (Just "Prelude") (Ident "prim_show" 0))) (InfixOp (QualIdent (Just "Prelude") (Ident "$##" 0))) (Variable (QualIdent Nothing (Ident "s" 661)))) []))]) ,(TypeSig (835,1) [(Ident "prim_show" 0)] (ArrowType (VariableType (Ident "_" 0)) (ConstructorType (QualIdent Nothing (Ident "String" 0)) []))) ,(FlatExternalDecl (836,1) [(Ident "prim_show" 0)]) ,(TypeSig (839,1) [(Ident "print" 0)] (ArrowType (VariableType (Ident "_" 0)) (ConstructorType (QualIdent Nothing (Ident "IO" 0)) [(TupleType [])]))) ,(FunctionDecl (840,1) (Ident "print" 0) [(Equation (840,1) (FunLhs (Ident "print" 0) [(VariablePattern (Ident "t" 663))]) (SimpleRhs (840,11) (Apply (Variable (QualIdent (Just "Prelude") (Ident "putStrLn" 0))) (Paren (Apply (Variable (QualIdent (Just "Prelude") (Ident "show" 0))) (Variable (QualIdent Nothing (Ident "t" 663)))))) []))]) ,(TypeSig (844,1) [(Ident "doSolve" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Success" 0)) []) (ConstructorType (QualIdent Nothing (Ident "IO" 0)) [(TupleType [])]))) ,(FunctionDecl (845,1) (Ident "doSolve" 0) [(Equation (845,1) (FunLhs (Ident "doSolve" 0) [(VariablePattern (Ident "constraint" 665))]) (GuardedRhs [(CondExpr (845,20) (Variable (QualIdent Nothing (Ident "constraint" 665))) (Variable (QualIdent (Just "Prelude") (Ident "done" 0))))] []))]) ,(TypeSig (851,1) [(Ident "sequenceIO" 0)] (ArrowType (ListType (ConstructorType (QualIdent Nothing (Ident "IO" 0)) [(VariableType (Ident "a" 0))])) (ConstructorType (QualIdent Nothing (Ident "IO" 0)) [(ListType (VariableType (Ident "a" 0)))]))) ,(FunctionDecl (852,1) (Ident "sequenceIO" 0) [(Equation (852,1) (FunLhs (Ident "sequenceIO" 0) [(ListPattern [])]) (SimpleRhs (852,21) (Apply (Variable (QualIdent (Just "Prelude") (Ident "return" 0))) (List [])) [])),(Equation (853,1) (FunLhs (Ident "sequenceIO" 0) [(ParenPattern (InfixPattern (VariablePattern (Ident "c" 669)) (QualIdent Nothing (Ident ":" 0)) (VariablePattern (Ident "cs" 669))))]) (SimpleRhs (853,21) (Do [(StmtBind (VariablePattern (Ident "x" 671)) (Variable (QualIdent Nothing (Ident "c" 669)))),(StmtBind (VariablePattern (Ident "xs" 672)) (Apply (Variable (QualIdent (Just "Prelude") (Ident "sequenceIO" 0))) (Variable (QualIdent Nothing (Ident "cs" 669)))))] (Apply (Variable (QualIdent (Just "Prelude") (Ident "return" 0))) (Paren (InfixApply (Variable (QualIdent Nothing (Ident "x" 671))) (InfixConstr (QualIdent Nothing (Ident ":" 0))) (Variable (QualIdent Nothing (Ident "xs" 672))))))) []))]) ,(TypeSig (858,1) [(Ident "sequenceIO_" 0)] (ArrowType (ListType (ConstructorType (QualIdent Nothing (Ident "IO" 0)) [(VariableType (Ident "_" 0))])) (ConstructorType (QualIdent Nothing (Ident "IO" 0)) [(TupleType [])]))) ,(FunctionDecl (859,1) (Ident "sequenceIO_" 0) [(Equation (859,1) (FunLhs (Ident "sequenceIO_" 0) []) (SimpleRhs (859,23) (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "foldr" 0))) (Variable (QualIdent (Just "Prelude") (Ident ">>" 0)))) (Variable (QualIdent (Just "Prelude") (Ident "done" 0)))) []))]) ,(TypeSig (863,1) [(Ident "mapIO" 0)] (ArrowType (ArrowType (VariableType (Ident "a" 0)) (ConstructorType (QualIdent Nothing (Ident "IO" 0)) [(VariableType (Ident "b" 0))])) (ArrowType (ListType (VariableType (Ident "a" 0))) (ConstructorType (QualIdent Nothing (Ident "IO" 0)) [(ListType (VariableType (Ident "b" 0)))])))) ,(FunctionDecl (864,1) (Ident "mapIO" 0) [(Equation (864,1) (FunLhs (Ident "mapIO" 0) [(VariablePattern (Ident "f" 675))]) (SimpleRhs (864,22) (InfixApply (Variable (QualIdent (Just "Prelude") (Ident "sequenceIO" 0))) (InfixOp (QualIdent (Just "Prelude") (Ident "." 0))) (Apply (Variable (QualIdent (Just "Prelude") (Ident "map" 0))) (Variable (QualIdent Nothing (Ident "f" 675))))) []))]) ,(TypeSig (868,1) [(Ident "mapIO_" 0)] (ArrowType (ArrowType (VariableType (Ident "a" 0)) (ConstructorType (QualIdent Nothing (Ident "IO" 0)) [(VariableType (Ident "_" 0))])) (ArrowType (ListType (VariableType (Ident "a" 0))) (ConstructorType (QualIdent Nothing (Ident "IO" 0)) [(TupleType [])])))) ,(FunctionDecl (869,1) (Ident "mapIO_" 0) [(Equation (869,1) (FunLhs (Ident "mapIO_" 0) [(VariablePattern (Ident "f" 677))]) (SimpleRhs (869,22) (InfixApply (Variable (QualIdent (Just "Prelude") (Ident "sequenceIO_" 0))) (InfixOp (QualIdent (Just "Prelude") (Ident "." 0))) (Apply (Variable (QualIdent (Just "Prelude") (Ident "map" 0))) (Variable (QualIdent Nothing (Ident "f" 677))))) []))]) ,(TypeSig (880,1) [(Ident "?" 0)] (ArrowType (VariableType (Ident "a" 0)) (ArrowType (VariableType (Ident "a" 0)) (VariableType (Ident "a" 0))))) ,(FunctionDecl (881,1) (Ident "?" 0) [(Equation (881,1) (OpLhs (VariablePattern (Ident "x" 679)) (Ident "?" 0) (VariablePattern (Ident "_" 680))) (SimpleRhs (881,9) (Variable (QualIdent Nothing (Ident "x" 679))) [])),(Equation (882,1) (OpLhs (VariablePattern (Ident "_" 683)) (Ident "?" 0) (VariablePattern (Ident "y" 682))) (SimpleRhs (882,9) (Variable (QualIdent Nothing (Ident "y" 682))) []))]) ,(TypeSig (907,1) [(Ident "getSearchTree" 0)] (ArrowType (VariableType (Ident "a" 0)) (ConstructorType (QualIdent Nothing (Ident "IO" 0)) [(ConstructorType (QualIdent Nothing (Ident "SearchTree" 0)) [(VariableType (Ident "a" 0))])]))) ,(FlatExternalDecl (908,1) [(Ident "getSearchTree" 0)]) ,(TypeSig (943,1) [(Ident "allValuesD" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "SearchTree" 0)) [(VariableType (Ident "a" 0))]) (ListType (VariableType (Ident "a" 0))))) ,(FunctionDecl (944,1) (Ident "allValuesD" 0) [(Equation (944,1) (FunLhs (Ident "allValuesD" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Value" 0)) [(VariablePattern (Ident "x" 685))]))]) (SimpleRhs (944,24) (List [(Variable (QualIdent Nothing (Ident "x" 685)))]) [])),(Equation (945,1) (FunLhs (Ident "allValuesD" 0) [(ConstructorPattern (QualIdent (Just "Prelude") (Ident "Fail" 0)) [])]) (SimpleRhs (945,24) (List []) [])),(Equation (946,1) (FunLhs (Ident "allValuesD" 0) [(ConstructorPattern (QualIdent (Just "Prelude") (Ident "Suspend" 0)) [])]) (SimpleRhs (946,24) (List []) [])),(Equation (947,1) (FunLhs (Ident "allValuesD" 0) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Choice" 0)) [(VariablePattern (Ident "xs" 691))]))]) (SimpleRhs (947,28) (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "concatMap" 0))) (Variable (QualIdent (Just "Prelude") (Ident "allValuesD" 0)))) (Variable (QualIdent Nothing (Ident "xs" 691)))) []))]) ,(TypeSig (950,1) [(Ident "allValuesB" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "SearchTree" 0)) [(VariableType (Ident "a" 0))]) (ListType (VariableType (Ident "a" 0))))) ,(FunctionDecl (951,1) (Ident "allValuesB" 0) [(Equation (951,1) (FunLhs (Ident "allValuesB" 0) [(VariablePattern (Ident "st" 693))]) (SimpleRhs (951,17) (Apply (Variable (QualIdent Nothing (Ident "unfoldOrs" 694))) (List [(Variable (QualIdent Nothing (Ident "st" 693)))])) [(FunctionDecl (953,5) (Ident "partition" 694) [(Equation (953,5) (FunLhs (Ident "partition" 694) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Value" 0)) [(VariablePattern (Ident "x" 695))])),(VariablePattern (Ident "y" 695))]) (SimpleRhs (953,29) (Let [(PatternDecl (953,33) (TuplePattern [(VariablePattern (Ident "vs" 697)),(VariablePattern (Ident "ors" 697))]) (SimpleRhs (953,44) (Variable (QualIdent Nothing (Ident "y" 695))) []))] (Tuple [(InfixApply (Variable (QualIdent Nothing (Ident "x" 695))) (InfixConstr (QualIdent Nothing (Ident ":" 0))) (Variable (QualIdent Nothing (Ident "vs" 697)))),(Variable (QualIdent Nothing (Ident "ors" 697)))])) [])),(Equation (954,5) (FunLhs (Ident "partition" 694) [(ParenPattern (ConstructorPattern (QualIdent (Just "Prelude") (Ident "Choice" 0)) [(VariablePattern (Ident "xs" 699))])),(VariablePattern (Ident "y" 699))]) (SimpleRhs (954,33) (Let [(PatternDecl (954,37) (TuplePattern [(VariablePattern (Ident "vs" 701)),(VariablePattern (Ident "ors" 701))]) (SimpleRhs (954,48) (Variable (QualIdent Nothing (Ident "y" 699))) []))] (Tuple [(Variable (QualIdent Nothing (Ident "vs" 701))),(InfixApply (Variable (QualIdent Nothing (Ident "xs" 699))) (InfixOp (QualIdent (Just "Prelude") (Ident "++" 0))) (Variable (QualIdent Nothing (Ident "ors" 701))))])) [])),(Equation (955,5) (FunLhs (Ident "partition" 694) [(ConstructorPattern (QualIdent (Just "Prelude") (Ident "Fail" 0)) []),(VariablePattern (Ident "y" 703))]) (SimpleRhs (955,29) (Variable (QualIdent Nothing (Ident "y" 703))) [])),(Equation (956,5) (FunLhs (Ident "partition" 694) [(ConstructorPattern (QualIdent (Just "Prelude") (Ident "Suspend" 0)) []),(VariablePattern (Ident "y" 705))]) (SimpleRhs (956,29) (Variable (QualIdent Nothing (Ident "y" 705))) []))]),(FunctionDecl (958,5) (Ident "unfoldOrs" 694) [(Equation (958,5) (FunLhs (Ident "unfoldOrs" 694) [(ListPattern [])]) (SimpleRhs (958,20) (List []) [])),(Equation (959,5) (FunLhs (Ident "unfoldOrs" 694) [(ParenPattern (InfixPattern (VariablePattern (Ident "x" 709)) (QualIdent Nothing (Ident ":" 0)) (VariablePattern (Ident "xs" 709))))]) (SimpleRhs (959,24) (Let [(PatternDecl (959,28) (TuplePattern [(VariablePattern (Ident "vals" 711)),(VariablePattern (Ident "ors" 711))]) (SimpleRhs (959,41) (Apply (Apply (Apply (Variable (QualIdent (Just "Prelude") (Ident "foldr" 0))) (Variable (QualIdent Nothing (Ident "partition" 694)))) (Tuple [(List []),(List [])])) (Paren (InfixApply (Variable (QualIdent Nothing (Ident "x" 709))) (InfixConstr (QualIdent Nothing (Ident ":" 0))) (Variable (QualIdent Nothing (Ident "xs" 709)))))) []))] (InfixApply (Variable (QualIdent Nothing (Ident "vals" 711))) (InfixOp (QualIdent (Just "Prelude") (Ident "++" 0))) (Apply (Variable (QualIdent Nothing (Ident "unfoldOrs" 694))) (Variable (QualIdent Nothing (Ident "ors" 711)))))) []))])]))]) ,(TypeSig (966,1) [(Ident "inject" 0)] (ArrowType (ArrowType (VariableType (Ident "a" 0)) (ConstructorType (QualIdent Nothing (Ident "Success" 0)) [])) (ArrowType (ArrowType (VariableType (Ident "a" 0)) (ConstructorType (QualIdent Nothing (Ident "Success" 0)) [])) (ArrowType (VariableType (Ident "a" 0)) (ConstructorType (QualIdent Nothing (Ident "Success" 0)) []))))) ,(FunctionDecl (967,1) (Ident "inject" 0) [(Equation (967,1) (FunLhs (Ident "inject" 0) [(VariablePattern (Ident "g" 713)),(VariablePattern (Ident "p" 713))]) (SimpleRhs (967,14) (Lambda [(VariablePattern (Ident "x" 715))] (InfixApply (Apply (Variable (QualIdent Nothing (Ident "p" 713))) (Variable (QualIdent Nothing (Ident "x" 715)))) (InfixOp (QualIdent (Just "Prelude") (Ident "&" 0))) (Apply (Variable (QualIdent Nothing (Ident "g" 713))) (Variable (QualIdent Nothing (Ident "x" 715)))))) []))]) ,(TypeSig (971,1) [(Ident "PEVAL" 0)] (ArrowType (VariableType (Ident "a" 0)) (VariableType (Ident "a" 0)))) ,(FunctionDecl (972,1) (Ident "PEVAL" 0) [(Equation (972,1) (FunLhs (Ident "PEVAL" 0) [(VariablePattern (Ident "x" 716))]) (SimpleRhs (972,11) (Variable (QualIdent Nothing (Ident "x" 716))) []))]) ,(TypeSig (976,1) [(Ident "apply" 0)] (ArrowType (ArrowType (VariableType (Ident "a" 0)) (VariableType (Ident "b" 0))) (ArrowType (VariableType (Ident "a" 0)) (VariableType (Ident "b" 0))))) ,(FlatExternalDecl (977,1) [(Ident "apply" 0)]) ,(TypeSig (982,1) [(Ident "cond" 0)] (ArrowType (ConstructorType (QualIdent Nothing (Ident "Success" 0)) []) (ArrowType (VariableType (Ident "a" 0)) (VariableType (Ident "a" 0))))) ,(FlatExternalDecl (983,1) [(Ident "cond" 0)]) ,(TypeSig (985,1) [(Ident "unknown" 0)] (VariableType (Ident "a" 0))) ,(FunctionDecl (986,1) (Ident "unknown" 0) [(Equation (986,1) (FunLhs (Ident "unknown" 0) []) (SimpleRhs (986,11) (Let [(ExtraVariables (986,15) [(Ident "x" 720)])] (Variable (QualIdent Nothing (Ident "x" 720)))) []))]) ,(TypeSig (992,1) [(Ident "=:<=" 0)] (ArrowType (VariableType (Ident "a" 0)) (ArrowType (VariableType (Ident "a" 0)) (ConstructorType (QualIdent Nothing (Ident "Success" 0)) [])))) ,(FlatExternalDecl (993,1) [(Ident "=:<=" 0)]) ]