Prog "Integer" ["Prelude"] [] [Func ("Integer","pow") 2 Public (FuncType (TCons ("Prelude","Int") []) (FuncType (TCons ("Prelude","Int") []) (TCons ("Prelude","Int") []))) (Rule [1,2] (Case Rigid (Comb FuncCall ("Prelude",">=") [Var 2,Lit (Intc 0)]) [Branch (Pattern ("Prelude","True") []) (Comb FuncCall ("Integer","pow.powaux.3") [Lit (Intc 1),Var 1,Var 2]),Branch (Pattern ("Prelude","False") []) (Comb FuncCall ("Prelude","failed") [])])),Func ("Integer","pow.powaux.3") 3 Private (FuncType (TCons ("Prelude","Int") []) (FuncType (TCons ("Prelude","Int") []) (FuncType (TCons ("Prelude","Int") []) (TCons ("Prelude","Int") [])))) (Rule [1,2,3] (Case Rigid (Comb FuncCall ("Prelude","==") [Var 3,Lit (Intc 0)]) [Branch (Pattern ("Prelude","True") []) (Var 1),Branch (Pattern ("Prelude","False") []) (Comb FuncCall ("Integer","pow.powaux.3") [Comb FuncCall ("Prelude","*") [Var 1,Case Rigid (Comb FuncCall ("Prelude","==") [Comb FuncCall ("Prelude","mod") [Var 3,Lit (Intc 2)],Lit (Intc 1)]) [Branch (Pattern ("Prelude","True") []) (Var 2),Branch (Pattern ("Prelude","False") []) (Lit (Intc 1))]],Comb FuncCall ("Prelude","*") [Var 2,Var 2],Comb FuncCall ("Prelude","div") [Var 3,Lit (Intc 2)]])])),Func ("Integer","ilog") 1 Public (FuncType (TCons ("Prelude","Int") []) (TCons ("Prelude","Int") [])) (Rule [1] (Case Rigid (Comb FuncCall ("Prelude",">") [Var 1,Lit (Intc 0)]) [Branch (Pattern ("Prelude","True") []) (Case Rigid (Comb FuncCall ("Prelude","<") [Var 1,Lit (Intc 10)]) [Branch (Pattern ("Prelude","True") []) (Lit (Intc 0)),Branch (Pattern ("Prelude","False") []) (Comb FuncCall ("Prelude","+") [Lit (Intc 1),Comb FuncCall ("Integer","ilog") [Comb FuncCall ("Prelude","div") [Var 1,Lit (Intc 10)]]])]),Branch (Pattern ("Prelude","False") []) (Comb FuncCall ("Prelude","failed") [])])),Func ("Integer","isqrt") 1 Public (FuncType (TCons ("Prelude","Int") []) (TCons ("Prelude","Int") [])) (Rule [1] (Case Rigid (Comb FuncCall ("Prelude",">=") [Var 1,Lit (Intc 0)]) [Branch (Pattern ("Prelude","True") []) (Case Rigid (Comb FuncCall ("Prelude","==") [Var 1,Lit (Intc 0)]) [Branch (Pattern ("Prelude","True") []) (Lit (Intc 0)),Branch (Pattern ("Prelude","False") []) (Case Rigid (Comb FuncCall ("Prelude","<") [Var 1,Lit (Intc 4)]) [Branch (Pattern ("Prelude","True") []) (Lit (Intc 1)),Branch (Pattern ("Prelude","False") []) (Comb FuncCall ("Integer","isqrt.aux.21") [Var 1,Lit (Intc 2),Var 1])])]),Branch (Pattern ("Prelude","False") []) (Comb FuncCall ("Prelude","failed") [])])),Func ("Integer","isqrt.aux.21") 3 Private (FuncType (TCons ("Prelude","Int") []) (FuncType (TCons ("Prelude","Int") []) (FuncType (TCons ("Prelude","Int") []) (TCons ("Prelude","Int") [])))) (Rule [1,2,3] (Case Rigid (Comb FuncCall ("Prelude","==") [Var 3,Comb FuncCall ("Prelude","+") [Var 2,Lit (Intc 1)]]) [Branch (Pattern ("Prelude","True") []) (Var 2),Branch (Pattern ("Prelude","False") []) (Let [(4,Comb FuncCall ("Prelude","div") [Comb FuncCall ("Prelude","+") [Var 3,Var 2],Lit (Intc 2)])] (Case Rigid (Comb FuncCall ("Prelude",">") [Comb FuncCall ("Prelude","*") [Var 4,Var 4],Var 1]) [Branch (Pattern ("Prelude","True") []) (Comb FuncCall ("Integer","isqrt.aux.21") [Var 1,Var 2,Var 4]),Branch (Pattern ("Prelude","False") []) (Comb FuncCall ("Integer","isqrt.aux.21") [Var 1,Var 4,Var 3])]))])),Func ("Integer","factorial") 1 Public (FuncType (TCons ("Prelude","Int") []) (TCons ("Prelude","Int") [])) (Rule [1] (Case Rigid (Comb FuncCall ("Prelude",">=") [Var 1,Lit (Intc 0)]) [Branch (Pattern ("Prelude","True") []) (Case Rigid (Comb FuncCall ("Prelude","==") [Var 1,Lit (Intc 0)]) [Branch (Pattern ("Prelude","True") []) (Lit (Intc 1)),Branch (Pattern ("Prelude","False") []) (Comb FuncCall ("Prelude","*") [Var 1,Comb FuncCall ("Integer","factorial") [Comb FuncCall ("Prelude","-") [Var 1,Lit (Intc 1)]]])]),Branch (Pattern ("Prelude","False") []) (Comb FuncCall ("Prelude","failed") [])])),Func ("Integer","binomial") 2 Public (FuncType (TCons ("Prelude","Int") []) (FuncType (TCons ("Prelude","Int") []) (TCons ("Prelude","Int") []))) (Rule [1,2] (Case Rigid (Comb FuncCall ("Prelude","&&") [Comb FuncCall ("Prelude",">") [Var 2,Lit (Intc 0)],Comb FuncCall ("Prelude",">=") [Var 1,Var 2]]) [Branch (Pattern ("Prelude","True") []) (Comb FuncCall ("Prelude","div") [Comb FuncCall ("Integer","binomial.aux.41") [Var 2,Var 1],Comb FuncCall ("Integer","factorial") [Var 2]]),Branch (Pattern ("Prelude","False") []) (Comb FuncCall ("Prelude","failed") [])])),Func ("Integer","binomial.aux.41") 2 Private (FuncType (TCons ("Prelude","Int") []) (FuncType (TCons ("Prelude","Int") []) (TCons ("Prelude","Int") []))) (Rule [1,2] (Case Rigid (Comb FuncCall ("Prelude","==") [Var 1,Lit (Intc 0)]) [Branch (Pattern ("Prelude","True") []) (Lit (Intc 1)),Branch (Pattern ("Prelude","False") []) (Comb FuncCall ("Prelude","*") [Var 2,Comb FuncCall ("Integer","binomial.aux.41") [Comb FuncCall ("Prelude","-") [Var 1,Lit (Intc 1)],Comb FuncCall ("Prelude","-") [Var 2,Lit (Intc 1)]]])])),Func ("Integer","abs") 1 Public (FuncType (TCons ("Prelude","Int") []) (TCons ("Prelude","Int") [])) (Rule [1] (Case Rigid (Comb FuncCall ("Prelude","<") [Var 1,Lit (Intc 0)]) [Branch (Pattern ("Prelude","True") []) (Comb FuncCall ("Prelude","negate") [Var 1]),Branch (Pattern ("Prelude","False") []) (Var 1)])),Func ("Integer","max") 2 Public (FuncType (TCons ("Prelude","Int") []) (FuncType (TCons ("Prelude","Int") []) (TCons ("Prelude","Int") []))) (Rule [1,2] (Case Rigid (Comb FuncCall ("Prelude","<") [Var 1,Var 2]) [Branch (Pattern ("Prelude","True") []) (Var 2),Branch (Pattern ("Prelude","False") []) (Var 1)])),Func ("Integer","min") 2 Public (FuncType (TCons ("Prelude","Int") []) (FuncType (TCons ("Prelude","Int") []) (TCons ("Prelude","Int") []))) (Rule [1,2] (Case Rigid (Comb FuncCall ("Prelude","<") [Var 1,Var 2]) [Branch (Pattern ("Prelude","True") []) (Var 1),Branch (Pattern ("Prelude","False") []) (Var 2)])),Func ("Integer","max3") 3 Public (FuncType (TCons ("Prelude","Int") []) (FuncType (TCons ("Prelude","Int") []) (FuncType (TCons ("Prelude","Int") []) (TCons ("Prelude","Int") [])))) (Rule [1,2,3] (Comb FuncCall ("Integer","max") [Var 1,Comb FuncCall ("Integer","max") [Var 2,Var 3]])),Func ("Integer","min3") 3 Public (FuncType (TCons ("Prelude","Int") []) (FuncType (TCons ("Prelude","Int") []) (FuncType (TCons ("Prelude","Int") []) (TCons ("Prelude","Int") [])))) (Rule [1,2,3] (Comb FuncCall ("Integer","min") [Var 1,Comb FuncCall ("Integer","min") [Var 2,Var 3]])),Func ("Integer","maxlist") 1 Public (FuncType (TCons ("Prelude","[]") [TCons ("Prelude","Int") []]) (TCons ("Prelude","Int") [])) (Rule [1] (Case Flex (Var 1) [Branch (Pattern ("Prelude",":") [2,3]) (Case Flex (Var 3) [Branch (Pattern ("Prelude","[]") []) (Var 2),Branch (Pattern ("Prelude",":") [4,5]) (Comb FuncCall ("Integer","max") [Var 2,Comb FuncCall ("Integer","maxlist") [Comb ConsCall ("Prelude",":") [Var 4,Var 5]]])])])),Func ("Integer","minlist") 1 Public (FuncType (TCons ("Prelude","[]") [TCons ("Prelude","Int") []]) (TCons ("Prelude","Int") [])) (Rule [1] (Case Flex (Var 1) [Branch (Pattern ("Prelude",":") [2,3]) (Case Flex (Var 3) [Branch (Pattern ("Prelude","[]") []) (Var 2),Branch (Pattern ("Prelude",":") [4,5]) (Comb FuncCall ("Integer","min") [Var 2,Comb FuncCall ("Integer","minlist") [Comb ConsCall ("Prelude",":") [Var 4,Var 5]]])])])),Func ("Integer","bitTrunc") 2 Public (FuncType (TCons ("Prelude","Int") []) (FuncType (TCons ("Prelude","Int") []) (TCons ("Prelude","Int") []))) (Rule [1,2] (Comb FuncCall ("Integer","bitAnd") [Comb FuncCall ("Prelude","-") [Comb FuncCall ("Integer","pow") [Lit (Intc 2),Var 1],Lit (Intc 1)],Var 2])),Func ("Integer","bitAnd") 2 Public (FuncType (TCons ("Prelude","Int") []) (FuncType (TCons ("Prelude","Int") []) (TCons ("Prelude","Int") []))) (Rule [1,2] (Case Rigid (Comb FuncCall ("Prelude","==") [Var 2,Lit (Intc 0)]) [Branch (Pattern ("Prelude","True") []) (Lit (Intc 0)),Branch (Pattern ("Prelude","False") []) (Let [(3,Comb FuncCall ("Prelude","*") [Lit (Intc 2),Comb FuncCall ("Integer","bitAnd") [Comb FuncCall ("Prelude","div") [Var 1,Lit (Intc 2)],Comb FuncCall ("Prelude","div") [Var 2,Lit (Intc 2)]]])] (Let [(4,Case Rigid (Comb FuncCall ("Prelude","==") [Comb FuncCall ("Prelude","mod") [Var 2,Lit (Intc 2)],Lit (Intc 0)]) [Branch (Pattern ("Prelude","True") []) (Lit (Intc 0)),Branch (Pattern ("Prelude","False") []) (Comb FuncCall ("Prelude","mod") [Var 1,Lit (Intc 2)])])] (Comb FuncCall ("Prelude","+") [Var 3,Var 4])))])),Func ("Integer","bitOr") 2 Public (FuncType (TCons ("Prelude","Int") []) (FuncType (TCons ("Prelude","Int") []) (TCons ("Prelude","Int") []))) (Rule [1,2] (Case Rigid (Comb FuncCall ("Prelude","==") [Var 2,Lit (Intc 0)]) [Branch (Pattern ("Prelude","True") []) (Var 1),Branch (Pattern ("Prelude","False") []) (Let [(3,Comb FuncCall ("Prelude","*") [Lit (Intc 2),Comb FuncCall ("Integer","bitOr") [Comb FuncCall ("Prelude","div") [Var 1,Lit (Intc 2)],Comb FuncCall ("Prelude","div") [Var 2,Lit (Intc 2)]]])] (Let [(4,Case Rigid (Comb FuncCall ("Prelude","==") [Comb FuncCall ("Prelude","mod") [Var 2,Lit (Intc 2)],Lit (Intc 1)]) [Branch (Pattern ("Prelude","True") []) (Lit (Intc 1)),Branch (Pattern ("Prelude","False") []) (Comb FuncCall ("Prelude","mod") [Var 1,Lit (Intc 2)])])] (Comb FuncCall ("Prelude","+") [Var 3,Var 4])))])),Func ("Integer","bitNot") 1 Public (FuncType (TCons ("Prelude","Int") []) (TCons ("Prelude","Int") [])) (Rule [1] (Comb FuncCall ("Integer","bitNot.aux.100") [Lit (Intc 32),Var 1])),Func ("Integer","bitNot.aux.100") 2 Private (FuncType (TCons ("Prelude","Int") []) (FuncType (TCons ("Prelude","Int") []) (TCons ("Prelude","Int") []))) (Rule [1,2] (Case Rigid (Comb FuncCall ("Prelude","==") [Var 1,Lit (Intc 0)]) [Branch (Pattern ("Prelude","True") []) (Lit (Intc 0)),Branch (Pattern ("Prelude","False") []) (Let [(3,Comb FuncCall ("Prelude","*") [Lit (Intc 2),Comb FuncCall ("Integer","bitNot.aux.100") [Comb FuncCall ("Prelude","-") [Var 1,Lit (Intc 1)],Comb FuncCall ("Prelude","div") [Var 2,Lit (Intc 2)]]])] (Let [(4,Comb FuncCall ("Prelude","-") [Lit (Intc 1),Comb FuncCall ("Prelude","mod") [Var 2,Lit (Intc 2)]])] (Comb FuncCall ("Prelude","+") [Var 3,Var 4])))])),Func ("Integer","bitXor") 2 Public (FuncType (TCons ("Prelude","Int") []) (FuncType (TCons ("Prelude","Int") []) (TCons ("Prelude","Int") []))) (Rule [1,2] (Case Rigid (Comb FuncCall ("Prelude","==") [Var 2,Lit (Intc 0)]) [Branch (Pattern ("Prelude","True") []) (Var 1),Branch (Pattern ("Prelude","False") []) (Let [(3,Comb FuncCall ("Prelude","*") [Lit (Intc 2),Comb FuncCall ("Integer","bitXor") [Comb FuncCall ("Prelude","div") [Var 1,Lit (Intc 2)],Comb FuncCall ("Prelude","div") [Var 2,Lit (Intc 2)]]])] (Let [(4,Case Rigid (Comb FuncCall ("Prelude","==") [Comb FuncCall ("Prelude","mod") [Var 2,Lit (Intc 2)],Comb FuncCall ("Prelude","mod") [Var 1,Lit (Intc 2)]]) [Branch (Pattern ("Prelude","True") []) (Lit (Intc 0)),Branch (Pattern ("Prelude","False") []) (Lit (Intc 1))])] (Comb FuncCall ("Prelude","+") [Var 3,Var 4])))])),Func ("Integer","even") 1 Public (FuncType (TCons ("Prelude","Int") []) (TCons ("Prelude","Bool") [])) (Rule [1] (Comb FuncCall ("Prelude","==") [Comb FuncCall ("Prelude","mod") [Var 1,Lit (Intc 2)],Lit (Intc 0)])),Func ("Integer","odd") 1 Public (FuncType (TCons ("Prelude","Int") []) (TCons ("Prelude","Bool") [])) (Rule [1] (Comb FuncCall ("Prelude","/=") [Comb FuncCall ("Prelude","mod") [Var 1,Lit (Intc 2)],Lit (Intc 0)]))] []