{-# LANGUAGE RebindableSyntax, NegativeLiterals, NoImplicitPrelude #-} {-# OPTIONS_GHC -Wno-unused-matches -Wno-name-shadowing -Wno-missing-signatures #-} module Alien.Prelude ( add , mul , div , eq , lt , neg , s , c , b , t , f , i , cons , car , cdr , nil , isnil ) where import qualified Unsafe.Coerce as H (unsafeCoerce) import qualified Prelude as H ((+), (*), negate, quot, (==), (<), Integer, Bool(..)) -- | <> add = (H.+) :: H.Integer -> H.Integer -> H.Integer -- | <> mul = (H.*) :: H.Integer -> H.Integer -> H.Integer -- | <> div = H.quot :: H.Integer -> H.Integer -> H.Integer -- | <> eq = \x y -> case (x :: H.Integer) H.== y of H.True -> t; H.False -> f -- | <> lt = \x y -> case (x :: H.Integer) H.< y of H.True -> t; H.False -> f -- | <> neg = H.negate :: H.Integer -> H.Integer -- | <> s = H.unsafeCoerce (\f g x -> f x (g x)) -- | <> c = \f x y -> f y x -- | <> b = \f g x -> f (g x) -- | <> t = \t f -> t -- | <> f = \t f -> f -- | <> i = \x -> x -- | <> cons = H.unsafeCoerce (\x y p -> p x y) -- | <> car = \p -> p t -- | <> cdr = \p -> p f -- | <> nil = H.unsafeCoerce (\x -> t) -- | <> -- -- /Translation note: a conforming implementation is @isnil x = x (t (t f))@ or @isnil = c i (t (t f))@./ isnil = \x -> x (t (t f))