3

My goal is to be able to represent boolean expressions as strings, for example "True or False is True". In order to make it possible I first made some boolean predicates:

and' :: Bool -> Bool -> Bool
and' p q = p && q

or' :: Bool -> Bool -> Bool
or' p q = p || q

-- ... same for nor, nand, xor, imply and equivalent

equ' :: Bool -> Bool -> Bool
equ' p q = p == q

After that, I decided to make a function that maps functions to strings. I relied on the pattern matching feature of Haskell, but my trick didn't work.

-- representation function, a.k. "show" for functions
repr :: (Bool -> Bool -> Bool) -> [Char]
repr and'  = "and"
repr or'   = "or"
repr nand' = "nand"
repr nor'  = "nor"
repr xor'  = "xor'"
repr impl' = "implies"
repr equ'  = "equivalent to"
repr other = error "No representation for the given predicate"

GHC thinks that function name is a parameter name and considers only the first definition as a general case. For the remaining lines, GHC raises a warning that the "pattern match is redundant". This is an example of running repr function:

*LogicH99> repr equ'
"and"

Expected "equivalent to"

Is it possible to print a function in a fancy way in Haskell?

Andrey Kachow
  • 936
  • 7
  • 22
  • Maybe [here](https://stackoverflow.com/questions/15272231/function-to-output-function-name) is a solution. – Z-Y.L Jul 24 '21 at 06:59
  • 3
    That isn't how pattern matching works. A pattern either matches a specific constructor of a specific type (with more patterns for the fields of the constructor), or it's a variable in which case it matches everything, or it's a literal (in which case the type has to support both a class that understands the literal (`Num`, `IsString`, etc) and `Eq` for equality). To check against a specific term you have a name for you'd need to use a guard with an equality check, but functions can't be compared for equality so you can't use that either. – Ben Jul 24 '21 at 07:07
  • 1
    See [universe](https://hackage.haskell.org/package/universe). [Showing functions](https://hackage.haskell.org/package/universe-reverse-instances-1.1.1/docs/Data-Universe-Instances-Show.html) (well, actually, checking functions for equality, but let's rewrite history a tiny bit) is its raison d'être. – Daniel Wagner Jul 24 '21 at 15:38

5 Answers5

7

For functions in general, no there isn't. But for functions of type Bool -> Bool -> Bool, there's so few possibilities that it's practical to just exhaustively enumerate all inputs, by doing something like this:

repr f = case (f False False, f False True, f True False, f True True) of
    (False, False, False, True) -> "and"
    (False, True, True, True) -> "or"
    -- ...
    (True, False, False, True) -> "equivalent to"
    _ -> error "No representation for the given predicate"
3

You only need to test 4 inputs so you can define a pattern by exhaustively evaluating it on inputs as has been mentioned. You can then define a pattern synonym which only matches (&&):

{-# LANGUAGE PatternSynonyms, ViewPatterns #-}

isAnd :: (Bool -> Bool -> Bool) -> Bool
isAnd (·) = and
 [ True  · True  == True
 , True  · False == False
 , False · True  == False
 , False · False == False
 ]

-- case (&&) of 
--   IsAnd -> "and"
pattern IsAnd :: Bool -> Bool -> Bool
pattern IsAnd <- (isAnd -> True)
  where IsAnd = (&&)

describe :: (Bool -> Bool -> Bool) -> String
describe IsAnd = "and"
describe ..

This is fun but you should just create a datatype data Op = And | .. or index it by its signature

type Op :: Type -> Type
data Op sig where
 OpAnd   :: Op (Bool -> Bool -> Bool)
 OpNot   :: Op (Bool -> Bool)
 OpTrue  :: Op Bool
 OpFalse :: Op Bool
leftaroundabout
  • 117,950
  • 5
  • 174
  • 319
Iceland_jack
  • 6,848
  • 7
  • 37
  • 46
  • 1
    And of course, for the reader interested in the first approach, you can still use all the usual programming techniques Haskell gives you to generalize. For example, you don't need to duplicate `isAnd` for each additional operator, but can instead write `is :: (Bool -> Bool -> Bool) -> (Bool -> Bool -> Bool) -> Bool; is f g = and [{- check that f x y == g x y for all x and y -}]`. Then you get e.g. `pattern IsAnd <- (is (&&) -> True)` and `pattern IsOr <- (is (||) -> True)` with minimal code repetition. – Daniel Wagner Jul 26 '21 at 18:42
2

For your goal, there may be another way to change the boolean expression into a string. The following is an example:

toString :: Bool -> Bool -> Bool -> String -> String
toString p q r op = show p ++ op ++ show q ++ " is " ++ show r

and', or' :: Bool -> Bool -> (Bool, String)
and' p q = let r = p && q
            in (r, toString p q r " and ")
or' p q = let r = p || q
           in (r, toString p q r " or ")

So if you want to get the boolean result, you can get the first element of the result tuple, and if the string expression, get the second element.

λ> snd $ and' True False
"True and False is False"

λ> fst $ and' True False
False
Z-Y.L
  • 1,740
  • 1
  • 11
  • 15
2

In this situation, the conventional solution is to introduce a data type (an “initial” encoding) or a typeclass (a “final” encoding), then you can define the functions and pretty-printed forms as two different interpretations. For example, with a plain data type you can just pattern-match:

data Exp
  = Lit Bool
  | And Exp Exp
  | Or Exp Exp
  | Not Exp
  | Equ Exp Exp
  deriving (Read, Show)
  -- Roundtrip to a debugging representation string.
  -- (Plus whatever other standard classes you need.)

-- Evaluate an expression to a Boolean.
eval :: Exp -> Bool
eval (Lit b) = b
eval (And e1 e2) = eval e1 && eval e2
eval (Or e1 e2) = eval e1 || eval e2
eval (Not e) = not (eval e)
eval (Equ e1 e2) = eval e1 == eval e2

-- Render an expression to a pretty-printed string.
render :: Exp -> String
render (Lit b) = show b
render (And e1 e2) = concat ["(", render e1, " and ", render e2, ")"]
render (Or e1 e2) = concat ["(", render e1, " or ", render e2, ")"]
render (Not e) = concat ["not ", render e]
render (Equ e1 e2) = concat ["(", render e1, " equivalent to ", render e2, ")"]

With a GADT you can add some more specific static types:

{-# Language GADTs #-}

data Exp t where
  Lit :: Bool -> Exp Bool
  And, Or, Equ :: Exp (Bool -> Bool -> Bool)
  Not :: Exp (Bool -> Bool)
  (:$) :: Exp (a -> b) -> Exp a -> Exp b

eval :: Exp t -> t
eval (Lit b) = b
eval And = (&&)
eval Or = (||)
eval Equ = (==)
eval Not = not
eval (f :$ x) = eval f $ eval x

render :: Exp t -> String
render (Lit b) = show b
render And = "and"
render Or = "or"
render Equ = "equivalent to"
render Not = "not"
render (f :$ x :$ y) = concat [render x, " ", render f, " ", render y]
render (f :$ x) = concat [render f, " ", render x]

Or finally with a typeclass the result is similar:

-- The set of types that can be used as
-- /interpretations/ of expressions.
class Exp r where
  lit' :: Bool -> r
  and', or', equ' :: r -> r -> r
  not' :: r -> r

-- Expressions can be interpreted by evaluation.
instance Exp Bool where
  lit' = id
  and' = (&&)
  or' = (||)
  equ' = (==)
  not' = not

-- A pretty-printed string.
newtype Pretty = Pretty String

-- They can also be interpreted by pretty-printing.
instance Exp Pretty where
  lit' b = Pretty $ show b
  and' r1 r2 = Pretty $ concat ["(", r1, " and ", r2, ")"]
  or' r1 r2 = Pretty $ concat ["(", r1, " or ", r2, ")"]
  equ' r1 r2 = Pretty $ concat ["(", r1, " equivalent to ", r2, ")"]
  not' r = Pretty $ concat ["not ", r]

This adds flexibility and complexity that you probably don’t need here, but I mention it since this design pattern can be useful for larger problems. (See Tagless-final Style for more.)

Jon Purdy
  • 53,300
  • 8
  • 96
  • 166
  • Your GADT application rendering looks wrong. There are never parentheses, and you distinguish two cases I don't think you need to. – dfeuer Jul 25 '21 at 04:59
  • You can combine the GADT and tagless-final approaches: https://gist.github.com/treeowl/93cffbbafccf937ff38b2d5a83890f5e This version also isn't rendered right; oh well. – dfeuer Jul 25 '21 at 05:24
1

I want to add a counterpart to Joseph's answer. It performs the same computation (i.e. running the given function on all possible inputs in the worst case), but maybe in a more readable way. It uses the universe and containers packages.

import Data.Maybe
import Data.Universe.Instances.Reverse

import qualified Data.Map as M

repr :: (Bool -> Bool -> Bool) -> String
repr f = fromMaybe noName (M.lookup f names) where
    noName = "No short name for " ++ show f
    names = M.fromList
        [ ((&&), "and")
        , ((||), "or")
        , ((==), "equivalent to")
        ]

The nice thing about this is that you don't have to look at the list of outputs and reverse-engineer which function is being described, as one must do in Joseph's answer; instead there's a direct visual connection between the actual Haskell function (e.g. (&&)) and the name we want to give to it (e.g. "and"). Here's a quick example of using it in ghci:

> repr (&&)
"and"
> repr (/=)
"No short name for [(False,[(False,False),(True,True)]),(True,[(False,True),(True,False)])]"
> repr (\x -> if x then id else not)
"equivalent to"
Daniel Wagner
  • 145,880
  • 9
  • 220
  • 380