{-# OPTIONS_GHC -cpp -XMagicHash #-} {- For Hugs, use the option -F"cpp -P -traditional" -} module LinearScan.Ssrnat where import Debug.Trace (trace, traceShow, traceShowId) import qualified Prelude import qualified Data.IntMap import qualified Data.IntSet import qualified Data.List import qualified Data.Ord import qualified Data.Functor.Identity import qualified Hask.Utils import qualified LinearScan.Eqtype as Eqtype import qualified LinearScan.Ssrbool as Ssrbool #ifdef __GLASGOW_HASKELL__ import qualified GHC.Base as GHC.Base import qualified GHC.Prim as GHC.Prim #else -- HUGS import qualified LinearScan.IOExts as IOExts #endif #ifdef __GLASGOW_HASKELL__ --unsafeCoerce :: a -> b unsafeCoerce = GHC.Base.unsafeCoerce# #else -- HUGS --unsafeCoerce :: a -> b unsafeCoerce = IOExts.unsafeCoerce #endif eqnP :: Eqtype.Equality__Coq_axiom Prelude.Int eqnP n m = Ssrbool.iffP ((Prelude.==) n m) (Ssrbool.idP ((Prelude.==) n m)) nat_eqMixin :: Eqtype.Equality__Coq_mixin_of Prelude.Int nat_eqMixin = Eqtype.Equality__Mixin (Prelude.==) eqnP nat_eqType :: Eqtype.Equality__Coq_type nat_eqType = unsafeCoerce nat_eqMixin nat_of_bool :: Prelude.Bool -> Prelude.Int nat_of_bool b = case b of { Prelude.True -> (Prelude.succ) 0; Prelude.False -> 0} odd :: Prelude.Int -> Prelude.Bool odd n = (\fO fS n -> if n Prelude.<= 0 then fO () else fS (n Prelude.- 1)) (\_ -> Prelude.False) (\n' -> Prelude.not (odd n')) n double_rec :: Prelude.Int -> Prelude.Int double_rec n = (\fO fS n -> if n Prelude.<= 0 then fO () else fS (n Prelude.- 1)) (\_ -> 0) (\n' -> (Prelude.succ) ((Prelude.succ) (double_rec n'))) n double :: Prelude.Int -> Prelude.Int double = double_rec