module Hint.Util where

import Data.Char

type Expr = String

-- @safeBndFor expr@ generates a name @e@ such that it does not
-- occur free in @expr@ and, thus, it is safe to write something
-- like @e = expr@ (otherwise, it will get accidentally bound).
-- This ought to do the trick: observe that @safeBndFor expr@
-- contains more digits than @expr@ and, thus, cannot occur inside
-- @expr@.
safeBndFor :: Expr -> String
safeBndFor :: Expr -> Expr
safeBndFor Expr
expr = Expr
"e_1" Expr -> Expr -> Expr
forall a. [a] -> [a] -> [a]
++ (Char -> Bool) -> Expr -> Expr
forall a. (a -> Bool) -> [a] -> [a]
filter Char -> Bool
isDigit Expr
expr

partition :: (a -> Bool) -> [a] -> ([a], [a])
partition :: forall a. (a -> Bool) -> [a] -> ([a], [a])
partition a -> Bool
prop = (a -> ([a], [a]) -> ([a], [a])) -> ([a], [a]) -> [a] -> ([a], [a])
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr ((a -> Bool) -> a -> ([a], [a]) -> ([a], [a])
forall {a}. (a -> Bool) -> a -> ([a], [a]) -> ([a], [a])
select a -> Bool
prop) ([],[])
    where select :: (a -> Bool) -> a -> ([a], [a]) -> ([a], [a])
select a -> Bool
p a
x ~([a]
ts,[a]
fs) | a -> Bool
p a
x       = (a
xa -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
ts,[a]
fs)
                              | Bool
otherwise = ([a]
ts, a
xa -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
fs)

partitionEither :: [Either a b] -> ([a],[b])
partitionEither :: forall a b. [Either a b] -> ([a], [b])
partitionEither [] = ([],[])
partitionEither (Left  a
a:[Either a b]
xs) = let ([a]
ls,[b]
rs) = [Either a b] -> ([a], [b])
forall a b. [Either a b] -> ([a], [b])
partitionEither [Either a b]
xs in (a
aa -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
ls,[b]
rs)
partitionEither (Right b
b:[Either a b]
xs) = let ([a]
ls,[b]
rs) = [Either a b] -> ([a], [b])
forall a b. [Either a b] -> ([a], [b])
partitionEither [Either a b]
xs in ([a]
ls,b
bb -> [b] -> [b]
forall a. a -> [a] -> [a]
:[b]
rs)

quote :: String -> String
quote :: Expr -> Expr
quote Expr
s = [Expr] -> Expr
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [Expr
"'", Expr
s, Expr
"'"]