{-# LANGUAGE OverloadedStrings #-}
module Funcons.Operations.Booleans where
import Funcons.Operations.Internal
library :: (HasValues t, Eq t) => Library t
library = libFromList [
("is-equal", BinaryExpr is_equal)
]
tobool :: Bool -> Values t
tobool True = ADTVal "true" []
tobool False = ADTVal "false" []
frombool :: (Values t) -> Maybe Bool
frombool (ADTVal "true" []) = Just True
frombool (ADTVal "false" []) = Just False
frombool _ = Nothing
booleans_ :: HasValues t => OpExpr t
booleans_ = vNullaryOp "booleans" (Normal $ injectT $ ADT "booleans" [])
true_ :: HasValues t => Values t
true_ = tobool True
false_ :: HasValues t => Values t
false_ = tobool False
is_equal_ :: (HasValues t, Eq t) => [OpExpr t] -> OpExpr t
is_equal_ = binaryOp is_equal
is_equal :: (HasValues t, Eq t) => OpExpr t -> OpExpr t -> OpExpr t
is_equal = BinaryOp "is-equal" op
where op :: (Eq t, HasValues t) => t -> t -> Result t
op x y = Normal $ inject $ tobool (x == y)