module Stg.Prelude.Bool (
    and2,
    or2,
    not,
    bool,
    eq_Bool,
) where
import Prelude ()
import Stg.Language
import Stg.Parser.QuasiQuoter
eq_Bool, and2, or2, not, bool :: Program
eq_Bool = [program|
    eq_Bool = \x y -> case x of
        True -> case y of
            True    -> True;
            False   -> False;
            badBool -> Error_eq_Bool badBool;
        False -> case y of
            True    -> False;
            False   -> True;
            badBool -> Error_eq_Bool badBool;
        badBool -> Error_eq_Bool badBool
    |]
and2 = [program|
    and2 = \x y -> case x of
        True  -> y;
        False -> False;
        badBool  -> Error_and2 badBool
    |]
or2 = [program|
    or2 = \x y -> case x of
        True     -> True;
        False    -> y;
        badBool  -> Error_or2 badBool
    |]
not = [program|
    not = \x -> case x of
        True -> False;
        False -> True;
        badBool  -> Error_not badBool
    |]
bool = [program|
    bool = \f t p -> case p of
        True    -> t;
        False   -> f;
        badBool -> Error_bool badBool
    |]